composite-base-0.8.2.1: Shared utilities for composite-* packages.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Composite.CoRecord

Description

Module containing the sum formulation companion to Records product formulation. Values of type CoRec f rs represent a single value f r for one of the rs in rs. Heavily based on the great work by Anthony Cowley in Frames.

Synopsis

Documentation

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

CoRef f rs represents a single value of type f r for some r in rs.

Constructors

CoVal :: r rs => !(f r) -> CoRec f rs

Witness that r is an element of rs using (RElem with RIndex) from Vinyl.

Instances

Instances details
(AllHave '[Show] rs, RecApplicative rs) => Show (CoRec Identity rs) Source # 
Instance details

Defined in Composite.CoRecord

(RMap rs, RecAll Maybe rs Eq, RecApplicative rs, RecordToList rs, ReifyConstraint Eq Maybe rs) => Eq (CoRec Identity rs) Source # 
Instance details

Defined in Composite.CoRecord

Methods

(==) :: CoRec Identity rs -> CoRec Identity rs -> Bool #

(/=) :: CoRec Identity rs -> CoRec Identity rs -> Bool #

type Field = CoRec Identity Source #

The common case of a CoRec with f ~ Identity, i.e. a regular value.

coRec :: r rs => f r -> CoRec f rs Source #

Inject a value f r into a CoRec f rs given that r is one of the valid rs.

Equivalent to CoVal the constructor, but exists to parallel field.

coRecPrism :: (RecApplicative rs, r rs) => Prism' (CoRec f rs) (f r) Source #

Produce a prism for the given alternative of a CoRec.

field :: r rs => r -> Field rs Source #

Inject a value r into a Field rs given that r is one of the valid rs.

Equivalent to CoVal . Identity.

fieldVal :: forall s a rs proxy. (s :-> a) rs => proxy (s :-> a) -> a -> Field rs Source #

Inject a value a into a Field rs given that s :-> a is one of the valid rs.

Equivalent to CoVal . Identity . Val.

fieldPrism :: (RecApplicative rs, r rs) => Prism' (Field rs) r Source #

Produce a prism for the given alternative of a Field.

fieldValPrism :: (RecApplicative rs, (s :-> a) rs) => proxy (s :-> a) -> Prism' (Field rs) a Source #

Produce a prism for the given :-> alternative of a Field, given a proxy to identify which s :-> a you meant.

foldCoVal :: (forall (r :: u). RElem r rs (RIndex r rs) => f r -> b) -> CoRec f rs -> b Source #

Apply an extraction to whatever f r is contained in the given CoRec.

For example foldCoVal getConst :: CoRec (Const a) rs -> a.

mapCoRec :: (forall x. f x -> g x) -> CoRec f rs -> CoRec g rs Source #

Map a CoRec f to a CoRec g using a natural transform from f to g (forall x. f x -> g x).

traverseCoRec :: Functor h => (forall x. f x -> h (g x)) -> CoRec f rs -> h (CoRec g rs) Source #

Apply some kleisli on h to the f x contained in a CoRec f and yank the h outside. Like traverse but for CoRec.

coRecToRec :: RecApplicative rs => CoRec f rs -> Rec (Maybe :. f) rs Source #

Project a CoRec f into a Rec (Maybe :. f) where only the single r held by the CoRec is Just in the resulting record, and all other fields are Nothing.

fieldToRec :: (RMap rs, RecApplicative rs) => Field rs -> Rec Maybe rs Source #

Project a Field into a Rec Maybe where only the single r held by the Field is Just in the resulting record, and all other fields are Nothing.

class FoldRec ss ts where Source #

Typeclass which allows folding ala foldMap over a Rec, using a CoRec as the accumulator.

Methods

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

Given some combining function, an initial value, and a record, visit each field of the record using the combining function to accumulate the initial value or previous accumulation with the field of the record.

Instances

Instances details
FoldRec (ss :: [u]) ('[] :: [u]) Source # 
Instance details

Defined in Composite.CoRecord

Methods

foldRec :: forall (f :: u0 -> Type). (CoRec f ss -> CoRec f ss -> CoRec f ss) -> CoRec f ss -> Rec f '[] -> CoRec f ss Source #

(t ss, FoldRec ss ts) => FoldRec (ss :: [a]) (t ': ts :: [a]) Source # 
Instance details

Defined in Composite.CoRecord

Methods

foldRec :: forall (f :: u -> Type). (CoRec f ss -> CoRec f ss -> CoRec f ss) -> CoRec f ss -> Rec f (t ': ts) -> CoRec f ss Source #

foldRec1 :: FoldRec (r ': rs) rs => (CoRec f (r ': rs) -> CoRec f (r ': rs) -> CoRec f (r ': rs)) -> Rec f (r ': rs) -> CoRec f (r ': rs) Source #

foldRec for records with at least one field that doesn't require an initial value.

firstCoRec :: FoldRec rs rs => Rec (Maybe :. f) rs -> Maybe (CoRec f rs) Source #

Given a Rec (Maybe :. f) rs, yield a Just coRec for the first field which is Just, or Nothing if there are no Just fields in the record.

firstField :: (FoldRec rs rs, RMap rs) => Rec Maybe rs -> Maybe (Field rs) Source #

Given a Rec Maybe rs, yield a Just field for the first field which is Just, or Nothing if there are no Just fields in the record.

lastCoRec :: FoldRec rs rs => Rec (Maybe :. f) rs -> Maybe (CoRec f rs) Source #

Given a Rec (Maybe :. f) rs, yield a Just coRec for the last field which is Just, or Nothing if there are no Just fields in the record.

lastField :: (RMap rs, FoldRec rs rs) => Rec Maybe rs -> Maybe (Field rs) Source #

Given a Rec Maybe rs, yield a Just field for the last field which is Just, or Nothing if there are no Just fields in the record.

newtype Op b a Source #

Helper newtype containing a function a -> b but with the type parameters flipped so Op b has a consistent codomain for a varying domain.

Constructors

Op 

Fields

onCoRec :: forall (cs :: [* -> Constraint]) (f :: * -> *) (rs :: [*]) (b :: *) (proxy :: [* -> Constraint] -> *). (AllHave cs rs, Functor f, RecApplicative rs) => proxy cs -> (forall (a :: *). HasInstances a cs => a -> b) -> CoRec f rs -> f b Source #

Given a list of constraints cs required to apply some function, apply the function to whatever value r (not f r) which the CoRec contains.

onField :: forall (cs :: [* -> Constraint]) (rs :: [*]) (b :: *) (proxy :: [* -> Constraint] -> *). (AllHave cs rs, RecApplicative rs) => proxy cs -> (forall (a :: *). HasInstances a cs => a -> b) -> Field rs -> b Source #

Given a list of constraints cs required to apply some function, apply the function to whatever value r which the Field contains.

asA :: (r rs, RMap rs, RecApplicative rs) => Field rs -> Maybe r Source #

Given some target type r that's a possible value of Field rs, yield Just if that is indeed the value being stored by the Field, or Nothing if not.

newtype Case' f b a Source #

An extractor function f a -> b which can be passed to foldCoRec to eliminate one possible alternative of a CoRec.

Constructors

Case' 

Fields

Instances

Instances details
Functor f => Contravariant (Case' f b) Source # 
Instance details

Defined in Composite.CoRecord

Methods

contramap :: (a' -> a) -> Case' f b a -> Case' f b a' #

(>$) :: b0 -> Case' f b b0 -> Case' f b a #

type Cases' f rs b = Rec (Case' f b) rs Source #

A record of Case' eliminators for each r in rs representing the pieces of a total function from CoRec f to b.

foldCoRec :: RecApplicative (r ': rs) => Cases' f (r ': rs) b -> CoRec f (r ': rs) -> b Source #

Fold a CoRec f using Cases' which eliminate each possible value held by the CoRec, yielding the b produced by whichever case matches.

matchCoRec :: RecApplicative (r ': rs) => CoRec f (r ': rs) -> Cases' f (r ': rs) b -> b Source #

Fold a CoRec f using Cases' which eliminate each possible value held by the CoRec, yielding the b produced by whichever case matches.

Equivalent to foldCoRec but with its arguments flipped so it can be written matchCoRec coRec $ cases.

newtype Case b a Source #

Constructors

Case 

Fields

Instances

Instances details
Contravariant (Case b) Source # 
Instance details

Defined in Composite.CoRecord

Methods

contramap :: (a' -> a) -> Case b a -> Case b a' #

(>$) :: b0 -> Case b b0 -> Case b a #

type Cases rs b = Rec (Case b) rs Source #

foldField :: (RMap rs, RecApplicative (r ': rs)) => Cases (r ': rs) b -> Field (r ': rs) -> b Source #

Fold a Field using Cases which eliminate each possible value held by the Field, yielding the b produced by whichever case matches.

matchField :: (RMap rs, RecApplicative (r ': rs)) => Field (r ': rs) -> Cases (r ': rs) b -> b Source #

Fold a Field using Cases which eliminate each possible value held by the Field, yielding the b produced by whichever case matches.

Equivalent to foldCoRec but with its arguments flipped so it can be written matchCoRec coRec $ cases.

widenCoRec :: (FoldRec ss ss, RecApplicative rs, RecApplicative ss, rs ss) => CoRec f rs -> CoRec f ss Source #

Widen a CoRec f rs to a CoRec f ss given that rs ⊆ ss.

widenField :: (FoldRec ss ss, RMap rs, RMap ss, RecApplicative rs, RecApplicative ss, rs ss) => Field rs -> Field ss Source #

Widen a Field rs to a Field ss given that rs ⊆ ss.