| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Frames.CoRec
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.
- data CoRec :: (* -> *) -> [*] -> * where
- type Field = CoRec Identity
- col :: (Show a, a ∈ ts) => a -> CoRec (Dict Show) ts
- newtype Op b a = Op {- runOp :: a -> b
 
- dictId :: Dict c a -> Identity a
- showDict :: Show a => a -> Dict Show a
- corecToRec :: RecApplicative ts => CoRec f ts -> Rec (Maybe :. f) ts
- corecToRec' :: RecApplicative ts => CoRec Identity ts -> Rec Maybe ts
- class FoldRec ss ts where
- corecMap :: (forall x. f x -> g x) -> CoRec f ts -> CoRec g ts
- corecTraverse :: Functor h => (forall x. f x -> h (g x)) -> CoRec f ts -> h (CoRec g ts)
- 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)
- firstField :: FoldRec ts ts => Rec (Maybe :. f) ts -> Maybe (CoRec f ts)
- lastField :: FoldRec ts ts => Rec (Maybe :. f) ts -> Maybe (CoRec f ts)
- 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
- onField :: forall cs ts b. (AllHave cs ts, RecApplicative ts) => Proxy cs -> (forall a. HasInstances a cs => a -> b) -> Field ts -> b
- reifyDicts :: forall cs f proxy ts. (AllHave cs ts, RecApplicative ts) => proxy cs -> (forall a. HasInstances a cs => f a) -> Rec f ts
- asA :: (t ∈ ts, RecApplicative ts) => proxy t -> CoRec Identity ts -> Maybe t
- match :: RecApplicative (t : ts) => CoRec Identity (t : ts) -> Handlers (t : ts) b -> b
- match' :: RecApplicative ts => CoRec Identity ts -> Handlers ts b -> Maybe b
- newtype Handler b a = H (a -> b)
- type Handlers ts b = Rec (Handler b) ts
Documentation
A function type constructor that takes its arguments in the reverse order.
corecToRec :: RecApplicative ts => CoRec f ts -> Rec (Maybe :. f) ts Source
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.
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.
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"