javelin-frames-0.1.0.2: Type-safe data frames based on higher-kinded types.
Copyright(c) Laurent P. René de Cotret
LicenseMIT
Maintainerlaurent.decotret@outlook.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageGHC2021

Data.Frame

Description

This is an experimental interface to dataframes.

This module defines the type machinery and some functions to process data frames. Data frames are structures where every row corresponds to an object, but data is stored in contiguous arrays known as columns.

A user guide is provided in the Data.Frame.Tutorial module.

Synopsis

Defining dataframe types

type family Column (f :: Type -> Type) x where ... Source #

Type family which allows for higher-kinded record types in two forms:

  • Single record type using Identity, where Column Identity a ~ a ;
  • Record type whose elements are some other functor (usually Vector).

Types are created like regular record types, but each element must have the type Column f a instead of a. For example:

>>> :{
     data Student f
         = MkStudent { studentName      :: Column f String
                     , studentAge       :: Column f Int
                     , studentMathGrade :: Column f Char
                     }
         deriving (Generic, Frameable)
:}

Equations

Column Identity x = x 
Column f x = f x 

class Frameable (t :: (Type -> Type) -> Type) Source #

Typeclass that endows any record type t with the ability to be packaged as a dataframe.

Under no circumstances should you write instances for Frameable; instead, simply derive an instance of Generic for t. For example:

>>> :set -XDeriveAnyClass
>>> :{
    data Store f
         = MkStore { storeName    :: Column f String
                   , storeId      :: Column f Int
                   , storeAddress :: Column f String
                   }
         deriving (Generic, Frameable)
:}

type Row (dt :: (Type -> Type) -> Type) = dt Identity Source #

Type synonym for a record type with scalar elements

type Frame (dt :: (Type -> Type) -> Type) = dt Vector Source #

Type synonym for a record type whose elements are arrays (columns)

Construction and deconstruction

fromRows :: (Frameable t, Foldable f) => f (Row t) -> Frame t Source #

Build a dataframe from a container of rows.

For the inverse operation, see toRows.

toRows :: Frameable t => Frame t -> Vector (Row t) Source #

Deconstruct a dataframe into its rows.

For the inverse operation, see fromRows.

fields :: Frameable t => Row t -> [(String, String)] Source #

Return the field names associated with a row or frame. This is useful to display frames via display.

Operations on rows

null :: Frameable t => Frame t -> Bool Source #

Returns True if a dataframe has no rows.

length :: Frameable t => Frame t -> Int Source #

Access the length of a dataframe, i.e. the number of rows.

mapRows :: (Frameable t1, Frameable t2) => (Row t1 -> Row t2) -> Frame t1 -> Frame t2 Source #

Map a function over each row individually.

For mapping with a monadic action, see mapRowsM.

mapRowsM :: (Frameable t1, Frameable t2, Monad m) => (Row t1 -> m (Row t2)) -> Frame t1 -> m (Frame t2) Source #

Map each element of a dataframe to a monadic action, evaluate these actions from left to right, and collect the result in a new dataframe.

For mapping without a monadic action, see mapRows.

filterRows :: Frameable t => (Row t -> Bool) -> Frame t -> Frame t Source #

Filter rows from a Frame t, only keeping the rows where the predicate is True.

foldlRows Source #

Arguments

:: Frameable t 
=> (b -> Row t -> b)

Reduction function that takes in individual rows

-> b

Initial value for the accumulator

-> Frame t

Data frame

-> b 

Left-associative fold of a structure, with strict application of the operator.

Sorting rows in frames

sortRowsBy :: Frameable t => (Row t -> Row t -> Ordering) -> Frame t -> Frame t Source #

Sort the rows of a frame using a custom comparison function.

Use the function on from Data.Function to easily create comparison functions. See the example below.

If you wish to prune rows with duplicates, see sortRowsByUnique. If your dataframe has an instance of Indexable, see sortRowsByKey.

For example, let's say we want to sort a dataframe of students by their first name:

>>> :{
     data Student f
         = MkStudent { studentName      :: Column f String
                     , studentAge       :: Column f Int
                     , studentMathGrade :: Column f Char
                     }
         deriving (Generic, Frameable)
     students = fromRows 
              [ MkStudent "Erika" 13 'D'
              , MkStudent "Beatrice" 13 'B'
              , MkStudent "David" 13 'A'
              , MkStudent "Albert" 12 'C'
              , MkStudent "Frank" 11 'C'
              , MkStudent "Clara" 12 'A'
              ]
:}
>>> import Data.Function (on)
>>> putStrLn $ display $ sortRowsBy (compare `on` studentName) students
studentName | studentAge | studentMathGrade
----------- | ---------- | ----------------
   "Albert" |         12 |              'C' 
 "Beatrice" |         13 |              'B'
    "Clara" |         12 |              'A'
    "David" |         13 |              'A'
    "Erika" |         13 |              'D'
    "Frank" |         11 |              'C'

The underlying sorting algorithm is timsort (via sortBy), which minimizes the number of comparisons used.

sortRowsByUnique :: Frameable t => (Row t -> Row t -> Ordering) -> Frame t -> Frame t Source #

Sort the rows of a frame using a custom comparison function.

Use the function on from Data.Function to easily create comparison functions. See the example below.

If your dataframe has an instance of Indexable, see sortRowsByKey.

For example, let's say we want to sort a dataframe of students by their first name:

>>> :{
     data Student f
         = MkStudent { studentName      :: Column f String
                     , studentAge       :: Column f Int
                     , studentMathGrade :: Column f Char
                     }
         deriving (Generic, Frameable)
     students = fromRows 
              [ MkStudent "Erika" 13 'D'
              , MkStudent "Beatrice" 13 'B'
              , MkStudent "David" 13 'A'
              , MkStudent "Albert" 12 'C'
              , MkStudent "Frank" 11 'C'
              , MkStudent "Clara" 12 'A'
              ]
:}
>>> import Data.Function (on)
>>> putStrLn $ display $ sortRowsBy (compare `on` studentName) students
studentName | studentAge | studentMathGrade
----------- | ---------- | ----------------
   "Albert" |         12 |              'C' 
 "Beatrice" |         13 |              'B'
    "Clara" |         12 |              'A'
    "David" |         13 |              'A'
    "Erika" |         13 |              'D'
    "Frank" |         11 |              'C'

The underlying sorting algorithm is timsort (via sortBy), which minimizes the number of comparisons used.

sortRowsByKey :: Indexable t => Frame t -> Frame t Source #

Sort the rows of a frame using the index defined by the Indexable typeclass.

If your dataframe does not have an instance of Indexable, see sortRowsBy.

To prune rows with duplicate keys, see sortRowsByKeyUnique.

For example:

>>> :{
     data Student f
         = MkStudent { studentName      :: Column f String
                     , studentAge       :: Column f Int
                     , studentMathGrade :: Column f Char
                     }
         deriving (Generic, Frameable)
     instance Indexable Student where
         type Key Student = String
         index = studentName
     students = fromRows 
              [ MkStudent "Erika" 13 'D'
              , MkStudent "Beatrice" 13 'B'
              , MkStudent "David" 13 'A'
              , MkStudent "Albert" 12 'C'
              , MkStudent "Frank" 11 'C'
              , MkStudent "Clara" 12 'A'
              ]
:}
>>> import Data.Function (on)
>>> putStrLn $ display $ sortRowsByKey students
studentName | studentAge | studentMathGrade
----------- | ---------- | ----------------
   "Albert" |         12 |              'C' 
 "Beatrice" |         13 |              'B'
    "Clara" |         12 |              'A'
    "David" |         13 |              'A'
    "Erika" |         13 |              'D'
    "Frank" |         11 |              'C'

The underlying sorting algorithm is timsort (via sortBy), which minimizes the number of comparisons used.

sortRowsByKeyUnique :: Indexable t => Frame t -> Frame t Source #

Sort the rows of a frame using the index defined by the Indexable typeclass, but prune rows with duplicate keys.

The underlying sorting algorithm is timsort (via sortBy), which minimizes the number of comparisons used.

sortRowsByKeyUniqueOn :: (Ord k, Indexable t) => (Key t -> k) -> Frame t -> Frame t Source #

Sort the rows of a frame by mapping the index defined by the Indexable typeclass, to another key type k. Also prune rows with duplicate keys.

The underlying sorting algorithm is timsort (via sortBy), which minimizes the number of comparisons used.

Displaying frames

display :: Frameable t => Frame t -> String Source #

Display a Frame t using default DisplayOptions.

Although this is up to you, we strongly recommend that the Show instance for Frame t be:

instance Show (Frame t) where show = display

Example:

>>> :{
     data Student f
         = MkStudent { studentName      :: Column f String
                     , studentAge       :: Column f Int
                     , studentMathGrade :: Column f Char
                     }
         deriving (Generic, Frameable)
:}
>>> students = fromRows $ Vector.fromList [MkStudent "Albert" 12 'C', MkStudent "Beatrice" 13 'B', MkStudent "Clara" 12 'A']
>>> putStrLn (display students)
studentName | studentAge | studentMathGrade
----------- | ---------- | ----------------
   "Albert" |         12 |              'C' 
 "Beatrice" |         13 |              'B'
    "Clara" |         12 |              'A'

Customizing the display of frames

displayWith :: Frameable t => DisplayOptions t -> Frame t -> String Source #

Display a Frame t using custom DisplayOptions.

Example:

>>> :{
     data Student f
         = MkStudent { studentName      :: Column f String
                     , studentAge       :: Column f Int
                     , studentMathGrade :: Column f Char
                     }
         deriving (Generic, Frameable)
:}
>>> :{
    students = fromRows 
             $ Vector.fromList 
             [ MkStudent "Albert" 12 'C'
             , MkStudent "Beatrice" 13 'B'
             , MkStudent "Clara" 12 'A'
             , MkStudent "David" 13 'A'
             , MkStudent "Erika" 13 'D'
             , MkStudent "Frank" 11 'C'
             ]
:}
>>> putStrLn (displayWith (defaultDisplayOptions{maximumNumberOfRows=2}) students)
studentName | studentAge | studentMathGrade
----------- | ---------- | ----------------
   "Albert" |         12 |              'C' 
        ... |        ... |              ...
    "Frank" |         11 |              'C'

data DisplayOptions (t :: (Type -> Type) -> Type) Source #

Control how displayWith behaves.

Constructors

DisplayOptions 

Fields

  • maximumNumberOfRows :: Int

    Maximum number of rows shown. These rows will be distributed evenly between the start of the frame and the end

  • rowDisplayFunction :: Row t -> [(String, String)]

    Function used to display rows from the frame. This should be a map from record name to value.

defaultDisplayOptions :: forall (t :: (Type -> Type) -> Type). Frameable t => DisplayOptions t Source #

Default Frame t display options.

Indexing operations

Based on integer indices

ilookup :: Frameable t => Int -> Frame t -> Maybe (Row t) Source #

Access a row from a dataframe by its integer index. Indexing starts at 0, representing the first row.

If the index is larger than the number of rows, this function returns Nothing.

To access a specific row AND column, iat is much more efficient.

To lookup a row based on a non-integer index, see lookup.

iat :: Frame t -> (Int, Frame t -> Vector a) -> Maybe a Source #

Lookup an element of the frame by row index and column

This is much more efficient than looking up an entire row using ilookup, and then selecting a specific field from a row.

To lookup an element by row key instead, see at.

Based on indexable frames

class (Frameable t, Eq (Key t), Ord (Key t)) => Indexable (t :: (Type -> Type) -> Type) where Source #

Typeclass for dataframes with an index, a column or set of columns that can be used to search through rows.

An index need not be unique, but the type of its keys must be an instance of Eq.

Associated Types

type Key (t :: (Type -> Type) -> Type) Source #

A type representing a lookup key for a dataframe. This can be a single field, or a compound key composed of multiple fields

Methods

index :: Frame t -> Vector (Key t) Source #

How to create an index from a frame (Frame t). This is generally done by using record selectors.

lookup :: Indexable t => Key t -> Frame t -> Maybe (Row t) Source #

Look up a row in a data frame by key. The specific key is defined by the Indexable instance of type t.

The first row whose index matches the supplied key is returned. If no row has a matching key, returns Nothing.

If you need to look up a particular row and column, at is much more efficient.

To lookup a row based on an integer index, see ilookup.

at :: Indexable t => Frame t -> (Key t, Frame t -> Vector a) -> Maybe a Source #

Lookup an element of a frame by row and column.

This is much more efficient than looking up an entire row using lookup, and then selecting a specific field from a row.

To lookup an element by integer row index instead, see iat.

Merging dataframes

Zipping rows in order

zipRowsWith :: (Frameable t1, Frameable t2, Frameable t3) => (Row t1 -> Row t2 -> Row t3) -> Frame t1 -> Frame t2 -> Frame t3 Source #

Zip two frames together using a combination function. Rows from each frame are matched in order; the resulting frame will only contain as many rows as the shortest of the two input frames

Merging using an index

mergeWithStrategy :: (Indexable t1, Indexable t2, Frameable t3, Key t1 ~ Key t2) => MergeStrategy (Key t1) t1 t2 t3 -> Frame t1 -> Frame t2 -> Frame t3 Source #

Merge two dataframes using a merging strategy, where the indexes of the dataframes have the same type. See mergeWithStrategyOn to merge dataframes with different indexes.

A merging strategy handles the possibility of rows missing in the left and/or right dataframes. Merge strategies can be user-defined, or you can use predefined strategies (e.g. matchedStrategy).

Note that (Key t1 ~ Key t2) means that the type of keys in in both dataframes must be the same.

In the example below, we have two dataframes: one containing store names, and one containing addresses. Both dataframes have use a unique identification number to relate their data to specific stores.

We want to build a summary of information about stores, containing each store's name and address.

>>> :{
     data Store f
         = MkStore { storeId   :: Column f Int
                   , storeName :: Column f String
                   }
         deriving (Generic, Frameable)
     instance Indexable Store where
         type Key Store = Int
         index = storeId
:}
>>> :{
     data Address f
         = MkAddress { addressStoreId     :: Column f Int
                     , addressCivicNumber :: Column f Int
                     , addressStreetName  :: Column f String
                     }
         deriving (Generic, Frameable)
     instance Show (Row Address) where
         show (MkAddress _ civicNum streetName) = mconcat [show civicNum, " ", streetName]
     instance Indexable Address where
         type Key Address = Int
         index = addressStoreId
:}
>>> :{
     data StoreSummary f
         = MkStoreSummary { storeSummaryName    :: Column f String
                          , storeSummaryAddress :: Column f (Row Address)
                          }
         deriving (Generic, Frameable)
     deriving instance Show (Row StoreSummary)
:}
>>> :{
    stores = fromRows 
             [ MkStore 1 "Maxi"
             , MkStore 2 "Metro"
             , MkStore 3 "Sobeys"
             , MkStore 4 "Loblaws"
             ]
:}
>>> :{
    addresses = fromRows
                [ MkAddress 1 1982 "14th Avenue"
                , MkAddress 2 10   "Main Street"
                , MkAddress 3 914  "Prima Street"
                -- Missing address for store id 4
                , MkAddress 5 1600 "Cosgrove Lane"
                ]
:}
>>> :{
     putStrLn
         $ display
             $ mergeWithStrategy 
                   (matchedStrategy (\_ store address -> MkStoreSummary (storeName store) address))
                   stores
                   addresses
:}
storeSummaryName | storeSummaryAddress
---------------- | -------------------
          "Maxi" |    1982 14th Avenue
         "Metro" |      10 Main Street
        "Sobeys" |    914 Prima Street

mergeWithStrategyOn Source #

Arguments

:: (Ord k, Indexable t1, Indexable t2, Frameable t3) 
=> (Key t1 -> k)

How to map the index of the left dataframe onto a key of type k

-> (Key t2 -> k)

How to map the index of the right dataframe onto a key of type k

-> MergeStrategy k t1 t2 t3 
-> Frame t1 
-> Frame t2 
-> Frame t3 

Merge two dataframes using a merging strategy, where the indexes of the dataframes are mapped to some key of type k.

See mergeWithStrategy for further notes and examples.

matchedStrategy :: (k -> Row t1 -> Row t2 -> Row t3) -> MergeStrategy k t1 t2 t3 Source #

Merge strategy which only works if both the left and right rows are found.

If you are familiar with relational databases, matchedStrategy is an inner join.

Helpers to define your own merge strategies

data These a b #

The These type represents values with two non-exclusive possibilities.

This can be useful to represent combinations of two values, where the combination is defined if either input is. Algebraically, the type These A B represents (A + B + AB), which doesn't factor easily into sums and products--a type like Either A (B, Maybe A) is unclear and awkward to use.

These has straightforward instances of Functor, Monad, &c., and behaves like a hybrid error/writer monad, as would be expected.

For zipping and unzipping of structures with These values, see Data.Align.

Constructors

This a 
That b 
These a b 

Instances

Instances details
Assoc These

Since: these-0.8

Instance details

Defined in Data.These

Methods

assoc :: These (These a b) c -> These a (These b c) #

unassoc :: These a (These b c) -> These (These a b) c #

Swap These

Since: these-0.8

Instance details

Defined in Data.These

Methods

swap :: These a b -> These b a #

Bifoldable These 
Instance details

Defined in Data.These

Methods

bifold :: Monoid m => These m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> These a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> These a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> These a b -> c #

Bifoldable1 These

Since: these-1.2

Instance details

Defined in Data.These

Methods

bifold1 :: Semigroup m => These m m -> m #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> These a b -> m #

Bifunctor These 
Instance details

Defined in Data.These

Methods

bimap :: (a -> b) -> (c -> d) -> These a c -> These b d #

first :: (a -> b) -> These a c -> These b c #

second :: (b -> c) -> These a b -> These a c #

Bitraversable These 
Instance details

Defined in Data.These

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> These a b -> f (These c d) #

Eq2 These

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> These a c -> These b d -> Bool #

Ord2 These

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> These a c -> These b d -> Ordering #

Read2 These

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (These a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [These a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (These a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [These a b] #

Show2 These

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> These a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [These a b] -> ShowS #

NFData2 These

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> These a b -> () #

Hashable2 These

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> These a b -> Int #

Generic1 (These a :: Type -> Type) 
Instance details

Defined in Data.These

Associated Types

type Rep1 (These a :: Type -> Type) 
Instance details

Defined in Data.These

Methods

from1 :: These a a0 -> Rep1 (These a) a0 #

to1 :: Rep1 (These a) a0 -> These a a0 #

Foldable (These a) 
Instance details

Defined in Data.These

Methods

fold :: Monoid m => These a m -> m #

foldMap :: Monoid m => (a0 -> m) -> These a a0 -> m #

foldMap' :: Monoid m => (a0 -> m) -> These a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> These a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> These a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> These a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> These a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> These a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> These a a0 -> a0 #

toList :: These a a0 -> [a0] #

null :: These a a0 -> Bool #

length :: These a a0 -> Int #

elem :: Eq a0 => a0 -> These a a0 -> Bool #

maximum :: Ord a0 => These a a0 -> a0 #

minimum :: Ord a0 => These a a0 -> a0 #

sum :: Num a0 => These a a0 -> a0 #

product :: Num a0 => These a a0 -> a0 #

Eq a => Eq1 (These a)

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

liftEq :: (a0 -> b -> Bool) -> These a a0 -> These a b -> Bool #

Ord a => Ord1 (These a)

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

liftCompare :: (a0 -> b -> Ordering) -> These a a0 -> These a b -> Ordering #

Read a => Read1 (These a)

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (These a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [These a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (These a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [These a a0] #

Show a => Show1 (These a)

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> These a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [These a a0] -> ShowS #

Traversable (These a) 
Instance details

Defined in Data.These

Methods

traverse :: Applicative f => (a0 -> f b) -> These a a0 -> f (These a b) #

sequenceA :: Applicative f => These a (f a0) -> f (These a a0) #

mapM :: Monad m => (a0 -> m b) -> These a a0 -> m (These a b) #

sequence :: Monad m => These a (m a0) -> m (These a a0) #

Semigroup a => Applicative (These a) 
Instance details

Defined in Data.These

Methods

pure :: a0 -> These a a0 #

(<*>) :: These a (a0 -> b) -> These a a0 -> These a b #

liftA2 :: (a0 -> b -> c) -> These a a0 -> These a b -> These a c #

(*>) :: These a a0 -> These a b -> These a b #

(<*) :: These a a0 -> These a b -> These a a0 #

Functor (These a) 
Instance details

Defined in Data.These

Methods

fmap :: (a0 -> b) -> These a a0 -> These a b #

(<$) :: a0 -> These a b -> These a a0 #

Semigroup a => Monad (These a) 
Instance details

Defined in Data.These

Methods

(>>=) :: These a a0 -> (a0 -> These a b) -> These a b #

(>>) :: These a a0 -> These a b -> These a b #

return :: a0 -> These a a0 #

NFData a => NFData1 (These a)

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

liftRnf :: (a0 -> ()) -> These a a0 -> () #

Hashable a => Hashable1 (These a)

Since: these-1.1.1

Instance details

Defined in Data.These

Methods

liftHashWithSalt :: (Int -> a0 -> Int) -> Int -> These a a0 -> Int #

(Data a, Data b) => Data (These a b) 
Instance details

Defined in Data.These

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> These a b -> c (These a b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (These a b) #

toConstr :: These a b -> Constr #

dataTypeOf :: These a b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (These a b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (These a b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> These a b -> These a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> These a b -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> These a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> These a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> These a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> These a b -> m (These a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> These a b -> m (These a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> These a b -> m (These a b) #

(Semigroup a, Semigroup b) => Semigroup (These a b) 
Instance details

Defined in Data.These

Methods

(<>) :: These a b -> These a b -> These a b #

sconcat :: NonEmpty (These a b) -> These a b #

stimes :: Integral b0 => b0 -> These a b -> These a b #

Generic (These a b) 
Instance details

Defined in Data.These

Associated Types

type Rep (These a b) 
Instance details

Defined in Data.These

Methods

from :: These a b -> Rep (These a b) x #

to :: Rep (These a b) x -> These a b #

(Read a, Read b) => Read (These a b) 
Instance details

Defined in Data.These

(Show a, Show b) => Show (These a b) 
Instance details

Defined in Data.These

Methods

showsPrec :: Int -> These a b -> ShowS #

show :: These a b -> String #

showList :: [These a b] -> ShowS #

(Binary a, Binary b) => Binary (These a b)

Since: these-0.7.1

Instance details

Defined in Data.These

Methods

put :: These a b -> Put #

get :: Get (These a b) #

putList :: [These a b] -> Put #

(NFData a, NFData b) => NFData (These a b)

Since: these-0.7.1

Instance details

Defined in Data.These

Methods

rnf :: These a b -> () #

(Eq a, Eq b) => Eq (These a b) 
Instance details

Defined in Data.These

Methods

(==) :: These a b -> These a b -> Bool #

(/=) :: These a b -> These a b -> Bool #

(Ord a, Ord b) => Ord (These a b) 
Instance details

Defined in Data.These

Methods

compare :: These a b -> These a b -> Ordering #

(<) :: These a b -> These a b -> Bool #

(<=) :: These a b -> These a b -> Bool #

(>) :: These a b -> These a b -> Bool #

(>=) :: These a b -> These a b -> Bool #

max :: These a b -> These a b -> These a b #

min :: These a b -> These a b -> These a b #

(Hashable a, Hashable b) => Hashable (These a b) 
Instance details

Defined in Data.These

Methods

hashWithSalt :: Int -> These a b -> Int #

hash :: These a b -> Int #

type Rep1 (These a :: Type -> Type) 
Instance details

Defined in Data.These

type Rep (These a b) 
Instance details

Defined in Data.These