Frames-0.1.2.1: Data frames For working with tabular data files

Safe HaskellNone
LanguageHaskell2010

Frames.CoRec

Contents

Description

Co-records: a flexible approach to sum types. melt is a good example of how such a facility is useful in Frames usage scenarios.

Consider a record with three fields A, B, and C. A record is a product of its fields; that is, it contains all of them: A, B, and C. If we want to talk about a value whose type is one of those three types, it is any one of type A, B, or C. The type CoRec '[A,B,C] corresponds to this sum type.

Synopsis

Documentation

data CoRec :: (* -> *) -> [*] -> * where Source

Generalize algebraic sum types.

Constructors

Col :: RElem a ts (RIndex a ts) => !(f a) -> CoRec f ts 

Instances

Show (CoRec (Dict Show) ts) 
(LAll Show ts, RecApplicative * ts) => Show (CoRec Identity ts) 

type Field = CoRec Identity Source

A Field of a Record is a 'CoRec Identity'.

col :: (Show a, a ts) => a -> CoRec (Dict Show) ts Source

Helper to build a Show-able CoRec

newtype Op b a Source

A function type constructor that takes its arguments in the reverse order.

Constructors

Op 

Fields

runOp :: a -> b
 

dictId :: Dict c a -> Identity a Source

Remove a Dict wrapper from a value.

showDict :: Show a => a -> Dict Show a Source

Helper to build a Dict Show

corecToRec :: RecApplicative ts => CoRec f ts -> Rec (Maybe :. f) ts Source

We can inject a a CoRec into a Rec where every field of the Rec is Nothing except for the one whose type corresponds to the type of the given CoRec variant.

corecToRec' :: RecApplicative ts => CoRec Identity ts -> Rec Maybe ts Source

Shorthand for applying corecToRec with common functors.

class FoldRec ss ts where Source

Fold a field selection function over a Rec.

Methods

foldRec :: (CoRec f ss -> CoRec f ss -> CoRec f ss) -> CoRec f ss -> Rec f ts -> CoRec f ss Source

Instances

FoldRec ss ([] *) 
((∈) * t ss, FoldRec ss ts) => FoldRec ss ((:) * t ts) 

corecMap :: (forall x. f x -> g x) -> CoRec f ts -> CoRec g ts Source

Apply a natural transformation to a variant.

corecTraverse :: Functor h => (forall x. f x -> h (g x)) -> CoRec f ts -> h (CoRec g ts) Source

This can be used to pull effects out of a CoRec.

foldRec1 :: FoldRec (t : ts) ts => (CoRec f (t : ts) -> CoRec f (t : ts) -> CoRec f (t : ts)) -> Rec f (t : ts) -> CoRec f (t : ts) Source

Fold a field selection function over a non-empty Rec.

firstField :: FoldRec ts ts => Rec (Maybe :. f) ts -> Maybe (CoRec f ts) Source

Similar to First: find the first field that is not Nothing.

lastField :: FoldRec ts ts => Rec (Maybe :. f) ts -> Maybe (CoRec f ts) Source

Similar to Last: find the last field that is not Nothing.

onCoRec :: forall cs f ts b. (AllHave cs ts, Functor f, RecApplicative ts) => Proxy cs -> (forall a. HasInstances a cs => a -> b) -> CoRec f ts -> f b Source

Apply a type class method on a CoRec. The first argument is a Proxy value for a list of Constraint constructors. For example, onCoRec [pr|Num,Ord|] (> 20) r. If only one constraint is needed, use the pr1 quasiquoter.

onField :: forall cs ts b. (AllHave cs ts, RecApplicative ts) => Proxy cs -> (forall a. HasInstances a cs => a -> b) -> Field ts -> b Source

Apply a type class method on a Field. The first argument is a Proxy value for a list of Constraint constructors. For example, onCoRec [pr|Num,Ord|] (> 20) r. If only one constraint is needed, use the pr1 quasiquoter.

reifyDicts :: forall cs f proxy ts. (AllHave cs ts, RecApplicative ts) => proxy cs -> (forall a. HasInstances a cs => f a) -> Rec f ts Source

Build a record whose elements are derived solely from a list of constraint constructors satisfied by each.

Extracting values from a CoRec/Pattern matching on a CoRec

asA :: (t ts, RecApplicative ts) => proxy t -> CoRec Identity ts -> Maybe t Source

Given a proxy of type t and a 'CoRec Identity' that might be a t, try to convert the CoRec to a t.

match :: RecApplicative (t : ts) => CoRec Identity (t : ts) -> Handlers (t : ts) b -> b Source

Pattern match on a CoRec by specifying handlers for each case. If the CoRec is non-empty this function is total. Note that the order of the Handlers has to match the type level list (t:ts).

>>> :{
let testCoRec = Col (Identity False) :: CoRec Identity [Int, String, Bool] in
match testCoRec $
      (H $ \i -> "my Int is the successor of " ++ show (i - 1))
   :& (H $ \s -> "my String is: " ++ s)
   :& (H $ \b -> "my Bool is not: " ++ show (not b) ++ " thus it is " ++ show b)
   :& RNil
:}
"my Bool is not: True thus it is False"

match' :: RecApplicative ts => CoRec Identity ts -> Handlers ts b -> Maybe b Source

Pattern match on a CoRec by specifying handlers for each case. The only case in which this can produce a Nothing is if the list ts is empty.

newtype Handler b a Source

Newtype around functions for a to b

Constructors

H (a -> b) 

type Handlers ts b = Rec (Handler b) ts Source

'Handlers ts b', is essentially a list of functions, one for each type in ts. All functions produce a value of type b. Hence, 'Handlers ts b' would represent something like the type-level list: [t -> b | t in ts ]