| 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
- 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)
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
| 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).
Instances
| Monad ((:->) s) Source # | |
| Functor ((:->) s) Source # | |
| Applicative ((:->) s) Source # | |
| Foldable ((:->) s) Source # | |
| Traversable ((:->) s) Source # | |
| Bounded a => Bounded ((:->) s a) Source # | |
| Enum a => Enum ((:->) s a) Source # | |
| Eq a => Eq ((:->) s a) Source # | |
| Floating a => Floating ((:->) s a) Source # | |
| Fractional a => Fractional ((:->) s a) Source # | |
| Integral a => Integral ((:->) s a) Source # | |
| Num a => Num ((:->) s a) Source # | |
| Ord a => Ord ((:->) s a) Source # | |
| Real a => Real ((:->) s a) Source # | |
| RealFloat a => RealFloat ((:->) s a) Source # | |
| RealFrac a => RealFrac ((:->) s a) Source # | |
| (KnownSymbol s, Show a) => Show ((:->) s a) Source # | |
| IsString a => IsString ((:->) s a) Source # | |
| Semigroup a => Semigroup ((:->) s a) Source # | |
| Monoid a => Monoid ((:->) s a) Source # | |
| Storable a => Storable ((:->) s a) Source # | |
| Wrapped ((:->) s0 a0) Source # | |
| (~) * ((:->) s0 a0) t0 => Rewrapped ((:->) s1 a1) t0 Source # | |
| type Unwrapped ((:->) s0 a0) Source # | |
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