| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Composite.Record
- data Rec u a b :: forall u. (u -> *) -> [u] -> * where
- type Record = Rec Identity
- pattern (:*:) :: forall a rs s. a -> Rec * Identity rs -> Rec * Identity ((:) * ((:->) s a) rs)
- pattern (:^:) :: forall f a rs s. Functor f => f a -> Rec * f rs -> Rec * f ((:) * ((:->) s a) rs)
- newtype s :-> a = Val {
- getVal :: a
- val :: forall s a. a -> Identity (s :-> a)
- valName :: forall s a. KnownSymbol s => (s :-> a) -> Text
- valWithName :: forall s a. KnownSymbol s => (s :-> a) -> (Text, a)
- type RElem r rs = RElem r rs (RIndex r rs)
- rlens :: (Functor g, RElem (s :-> a) rs, Functor g) => proxy (s :-> a) -> (a -> g a) -> Rec Identity rs -> g (Rec Identity rs)
- rlens' :: (Functor f, Functor g, RElem (s :-> a) rs, Functor g) => proxy (s :-> a) -> (f a -> g (f a)) -> Rec f rs -> g (Rec f rs)
- type family AllHave (cs :: [u -> Constraint]) (as :: [u]) :: Constraint where ...
- type family HasInstances (a :: u) (cs :: [u -> Constraint]) :: Constraint where ...
- type family ValuesAllHave (cs :: [u -> Constraint]) (as :: [u]) :: Constraint where ...
- zipRecsWith :: (forall a. f a -> g a -> h a) -> Rec f as -> Rec g as -> Rec h as
- reifyDicts :: forall cs f rs proxy. (AllHave cs rs, RecApplicative rs) => proxy cs -> (forall proxy' a. HasInstances a cs => proxy' a -> f a) -> Rec f rs
- recordToNonEmpty :: Rec (Const a) (r ': rs) -> NonEmpty a
- class ReifyNames rs where
- class RecWithContext ss ts where
- type family RDelete (r :: u) (rs :: [u]) where ...
- type RDeletable r rs = (r ∈ rs, RDelete r rs ⊆ rs)
- rdelete :: RDeletable r rs => proxy r -> Rec f rs -> Rec f (RDelete r rs)
Documentation
data Rec u a b :: forall u. (u -> *) -> [u] -> * where #
A record is parameterized by a universe u, an interpretation f and a
list of rows rs. The labels or indices of the record are given by
inhabitants of the kind u; the type of values at any label r :: u is
given by its interpretation f r :: *.
Instances
| MonadContext c ((->) (Record c)) Source # | |
| TestCoercion u f => TestCoercion [u] (Rec u f) | |
| TestEquality u f => TestEquality [u] (Rec u f) | |
| Eq (Rec u f ([] u)) | |
| (Eq (f r), Eq (Rec a f rs)) => Eq (Rec a f ((:) a r rs)) | |
| Ord (Rec u f ([] u)) | |
| (Ord (f r), Ord (Rec a f rs)) => Ord (Rec a f ((:) a r rs)) | |
| RecAll u f rs Show => Show (Rec u f rs) | Records may be shown insofar as their points may be shown.
|
| Monoid (Rec u f ([] u)) | |
| (Monoid (f r), Monoid (Rec a f rs)) => Monoid (Rec a f ((:) a r rs)) | |
| Storable (Rec u f ([] u)) | |
| (Storable (f r), Storable (Rec a f rs)) => Storable (Rec a f ((:) a r rs)) | |
pattern (:*:) :: forall a rs s. a -> Rec * Identity rs -> Rec * Identity ((:) * ((:->) s a) rs) infixr 5 Source #
pattern (:^:) :: forall f a rs s. Functor f => f a -> Rec * f rs -> Rec * f ((:) * ((:->) s a) rs) infixr 5 Source #
Bidirectional pattern matching the first field of a record using :-> values and any functor.
This pattern is bidirectional meaning you can use it either as a pattern or a constructor, e.g.
let rec = Just 123 :^: Just "foo" :^: RNil
Just foo :^: Just bar :^: RNil = rec
Mnemonic: ^ for products (record) of products (functor).
Some value of type a tagged with a symbol indicating its field name or label. Used as the usual type of elements in a Rec or Record.
Recommended pronunciation: record val.
Instances
val :: forall s a. a -> Identity (s :-> a) Source #
Convenience function to make an with a particular symbol, used for named field construction.Identity (s :-> a)
For example:
type FFoo = "foo" :-> Int
type FBar = "bar" :-> String
type FBaz = "baz" :-> Double
type MyRecord = [FFoo, FBar, FBaz]
myRecord1 :: Record MyRecord
myRecord1
= val "foo" 123
:& val "bar" "foobar"
:& val "baz" 3.21
:& RNil
myRecord2 :: Record MyRecord
myRecord2 = rcast
$ val "baz" 3.21
:& val "foo" 123
:& val "bar" "foobar"
:& RNil
In this example, both myRecord1 and myRecord2 have the same value, since rcast can reorder records.
valName :: forall s a. KnownSymbol s => (s :-> a) -> Text Source #
Reflect the type level name of a named value s :-> a to a Text. For example, given "foo" :-> Int, yields "foo" :: Text
valWithName :: forall s a. KnownSymbol s => (s :-> a) -> (Text, a) Source #
Extract the value and reflect the name of a named value.
rlens :: (Functor g, RElem (s :-> a) rs, Functor g) => proxy (s :-> a) -> (a -> g a) -> Rec Identity rs -> g (Rec Identity rs) Source #
Lens to a particular field of a record using the Identity functor.
For example, given:
type FFoo = "foo" :-> Int type FBar = "bar" :-> String fBar_ :: Proxy FBar fBar_ = Proxy rec ::RecIdentity'[FFoo, FBar] rec = 123 :*: "hello!" :*: Nil
Then:
view (rlens fBar_) rec == "hello!" set (rlens fBar_) "goodbye!" rec == 123 :*: "goodbye!" :*: Nil over (rlens fBar_) (map toUpper) rec == 123 :*: "HELLO!" :*: Nil
rlens' :: (Functor f, Functor g, RElem (s :-> a) rs, Functor g) => proxy (s :-> a) -> (f a -> g (f a)) -> Rec f rs -> g (Rec f rs) Source #
Lens to a particular field of a record using any functor.
For example, given:
type FFoo = "foo" :-> Int type FBar = "bar" :-> String fBar_ :: Proxy FBar fBar_ = Proxy rec ::RecMaybe'[FFoo, FBar] rec = Just 123 :^: Just "hello!" :^: Nil
Then:
view (rlens' fBar_) rec == Just "hello!" set (rlens' fBar_) Nothing rec == Just 123 :^: Nothing :^: Nil over (rlens' fBar_) (fmap (map toUpper)) rec == Just 123 :^: Just "HELLO!" :^: Nil
type family AllHave (cs :: [u -> Constraint]) (as :: [u]) :: Constraint where ... Source #
Type function which produces the cross product of constraints cs and types as.
For example, AllHave '[Eq, Ord] '[Int, Text] is equivalent to (Eq Int, Ord Int, Eq Text, Ord Text)
Equations
| AllHave cs '[] = () | |
| AllHave cs (a ': as) = (HasInstances a cs, AllHave cs as) |
type family HasInstances (a :: u) (cs :: [u -> Constraint]) :: Constraint where ... Source #
Type function which produces a constraint on a for each constraint in cs.
For example, HasInstances Int '[Eq, Ord] is equivalent to (Eq Int, Ord Int).
Equations
| HasInstances a '[] = () | |
| HasInstances a (c ': cs) = (c a, HasInstances a cs) |
type family ValuesAllHave (cs :: [u -> Constraint]) (as :: [u]) :: Constraint where ... Source #
Type function which produces the cross product of constraints cs and the values carried in a record rs.
For example, ValuesAllHave '[Eq, Ord] '["foo" :-> Int, "bar" :-> Text] is equivalent to (Eq Int, Ord Int, Eq Text, Ord Text)
Equations
| ValuesAllHave cs '[] = () | |
| ValuesAllHave cs ((s :-> a) ': as) = (HasInstances a cs, ValuesAllHave cs as) |
zipRecsWith :: (forall a. f a -> g a -> h a) -> Rec f as -> Rec g as -> Rec h as Source #
zipWith for Rec's.
reifyDicts :: forall cs f rs proxy. (AllHave cs rs, RecApplicative rs) => proxy cs -> (forall proxy' a. HasInstances a cs => proxy' a -> f a) -> Rec f rs Source #
Given a list of constraints cs, apply some function for each r in the target record type rs with proof that those constraints hold for r,
generating a record with the result of each application.
class ReifyNames rs where Source #
Minimal complete definition
Methods
Instances
| ReifyNames ([] *) Source # | |
| (KnownSymbol s, ReifyNames rs) => ReifyNames ((:) * ((:->) s a) rs) Source # | |
class RecWithContext ss ts where Source #
Class with rmap but which gives the natural transformation evidence that the value its working over is contained within the overall record ss.
Minimal complete definition
Methods
rmapWithContext :: proxy ss -> (forall r. r ∈ ss => f r -> g r) -> Rec f ts -> Rec g ts Source #
Apply a natural transformation from f to g to each field of the given record, except that the natural transformation can be mildly unnatural by having
evidence that r is in ss.
Instances
| RecWithContext ss ([] *) Source # | |
| ((∈) * r ss, RecWithContext ss ts) => RecWithContext ss ((:) * r ts) Source # | |
type family RDelete (r :: u) (rs :: [u]) where ... Source #
Type function which removes the first element r from a list rs, and doesn't expand if r is not present in rs.