Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type (:~:) r1 r2 = (r1 <: r2, r2 <: r1)
- (<-:) :: sing r -> f (el $ r) -> Rec el f `[r]`
- class xs <: ys
- (<+>) :: Rec el f as -> Rec el f bs -> Rec el f (as ++ bs)
- (<<*>>) :: Rec el (Lift (->) f g) rs -> Rec el f rs -> Rec el g rs
- (<<$>>) :: (forall x. f x -> g x) -> Rec el f rs -> Rec el g rs
- (=:) :: Applicative f => sing k -> (el $ k) -> Rec el f `[k]`
- (~=) :: (Eq (Rec el f xs), xs :~: ys) => Rec el f xs -> Rec el f ys -> Bool
- data Rec el f rrs where
- data Semantics = forall s t . (TyRep t, TyRep s) => t :~> s
Documentation
type (:~:) r1 r2 = (r1 <: r2, r2 <: r1) Source
If two records types are subtypes of each other, that means that they differ only in order of fields.
(<-:) :: sing r -> f (el $ r) -> Rec el f `[r]` infixr 6 Source
Shorthand for a record with a single field. This is useful for
Applicative
or Monad
ic intialization of records as in the idiom:
dist $ myField <-: someIO <+> yourField <-: otherIO
One record is a subtype of another if the fields of the latter are a subset of the fields of the former.
(=:) :: Applicative f => sing k -> (el $ k) -> Rec el f `[k]` Source
Shorthand for a record with a single field. Lifts the field's value into the chosen functor automatically.
(~=) :: (Eq (Rec el f xs), xs :~: ys) => Rec el f xs -> Rec el f ys -> Bool Source
Term-level record congruence.
data Rec el f rrs where Source
A record is parameterized by a universe u
, list of rows rs
, a large
elimination el
, and a type constructor f
to be applied to the
interpretation el r
of each of those r
.
(Eq (f (($) * k el r)), Eq (Rec k el f rs)) => Eq (Rec k el f ((:) k r rs)) | |
Eq (Rec k el f ([] k)) | |
(Storable (($) * k el r), Storable (Rec k el Identity rs)) => Storable (Rec k el Identity ((:) k r rs)) | |
Storable (Rec k el Identity ([] k)) | |
(Monoid (($) * k el r), Monoid (Rec k el f rs), Applicative f) => Monoid (Rec k el f ((:) k r rs)) | |
Monoid (Rec k el f ([] k)) | |
FoldRec (Rec k el f ([] k)) a | |
((~) * t (($) * k el r), FoldRec (Rec k el f rs) (f t)) => FoldRec (Rec k el f ((:) k r rs)) (f t) |