Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Rec (a :: u -> Type) (b :: [u]) where
- type Record = Rec Identity
- pattern (:*:) :: a -> Rec Identity rs -> Rec Identity ((s :-> a) ': rs)
- pattern (:^:) :: Functor f => f a -> Rec f rs -> Rec f ((s :-> a) ': rs)
- pattern (:!:) :: Contravariant f => f a -> Rec f rs -> Rec f ((s :-> a) ': rs)
- newtype (s :: Symbol) :-> a = Val {
- getVal :: a
- _Val :: Iso (s :-> a) (s :-> b) a b
- val :: forall (s :: Symbol) 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) => proxy (s :-> a) -> (f a -> g (f a)) -> Rec f rs -> g (Rec f rs)
- rlensCo :: (Functor f, Functor g, RElem (s :-> a) rs) => proxy (s :-> a) -> (f a -> g (f a)) -> Rec f rs -> g (Rec f rs)
- rlensContra :: (Contravariant f, Functor g, RElem (s :-> a) rs) => 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 u. forall (cs :: [u -> Constraint]) (f :: u -> Type) (rs :: [u]) (proxy :: [u -> Constraint] -> Type). (AllHave cs rs, RecApplicative rs) => proxy cs -> (forall proxy' (a :: u). HasInstances a cs => proxy' a -> f a) -> Rec f rs
- reifyVal :: proxy (s :-> a) -> (s :-> a) -> s :-> a
- recordToNonEmpty :: RecordToList rs => Rec (Const a) (r ': rs) -> NonEmpty a
- class ReifyNames (rs :: [Type]) where
- class RecWithContext (ss :: [Type]) (ts :: [Type]) where
- rmapWithContext :: proxy ss -> (forall r. r ∈ ss => f r -> g r) -> Rec f ts -> Rec g ts
- 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 (a :: u -> Type) (b :: [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 :: *
.
RNil :: forall u (a :: u -> Type). Rec a ('[] :: [u]) | |
(:&) :: forall u (a :: u -> Type) (r :: u) (rs :: [u]). !(a r) -> !(Rec a rs) -> Rec a (r ': rs) infixr 7 |
Instances
RecSubset (Rec :: (k -> Type) -> [k] -> Type) ('[] :: [k]) (ss :: [k]) ('[] :: [Nat]) | |
Defined in Data.Vinyl.Lens type RecSubsetFCtx Rec f # rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f '[] -> g (Rec f '[])) -> Rec f ss -> g (Rec f ss) # rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f '[] # rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f '[] -> Rec f ss -> Rec f ss # | |
(RElem r ss i, RSubset rs ss is) => RecSubset (Rec :: (k -> Type) -> [k] -> Type) (r ': rs :: [k]) (ss :: [k]) (i ': is) | |
Defined in Data.Vinyl.Lens type RecSubsetFCtx Rec f # rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f (r ': rs) -> g (Rec f (r ': rs))) -> Rec f ss -> g (Rec f ss) # rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f (r ': rs) # rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f (r ': rs) -> Rec f ss -> Rec f ss # | |
RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (r ': rs :: [a]) (r' ': rs :: [a]) 'Z | |
Defined in Data.Vinyl.Lens type RecElemFCtx Rec f # | |
(RIndex r (s ': rs) ~ 'S i, RecElem (Rec :: (a -> Type) -> [a] -> Type) r r' rs rs' i) => RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (s ': rs :: [a]) (s ': rs' :: [a]) ('S i) | |
Defined in Data.Vinyl.Lens type RecElemFCtx Rec f # | |
MonadContext c ((->) (Record c) :: Type -> Type) Source # | |
Defined in Control.Monad.Composite.Context | |
(NFData x, NFData (Record xs)) => NFData (Record (x ': xs)) Source # | |
Defined in Composite.Record | |
NFData (Record ('[] :: [Type])) Source # | |
Defined in Composite.Record | |
TestCoercion f => TestCoercion (Rec f :: [u] -> Type) | |
Defined in Data.Vinyl.Core | |
TestEquality f => TestEquality (Rec f :: [u] -> Type) | |
Defined in Data.Vinyl.Core | |
Eq (Rec f ('[] :: [u])) | |
(Eq (f r), Eq (Rec f rs)) => Eq (Rec f (r ': rs)) | |
Ord (Rec f ('[] :: [u])) | |
Defined in Data.Vinyl.Core | |
(Ord (f r), Ord (Rec f rs)) => Ord (Rec f (r ': rs)) | |
Defined in Data.Vinyl.Core compare :: Rec f (r ': rs) -> Rec f (r ': rs) -> Ordering # (<) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # (<=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # (>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # (>=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # max :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) # min :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) # | |
(RMap rs, ReifyConstraint Show f rs, RecordToList rs) => Show (Rec f rs) | Records may be shown insofar as their points may be shown.
|
Generic (Rec f ('[] :: [u])) | |
Generic (Rec f rs) => Generic (Rec f (r ': rs)) | |
Semigroup (Rec f ('[] :: [u])) | |
(Semigroup (f r), Semigroup (Rec f rs)) => Semigroup (Rec f (r ': rs)) | |
Monoid (Rec f ('[] :: [u])) | |
(Monoid (f r), Monoid (Rec f rs)) => Monoid (Rec f (r ': rs)) | |
Storable (Rec f ('[] :: [u])) | |
Defined in Data.Vinyl.Core | |
(Storable (f r), Storable (Rec f rs)) => Storable (Rec f (r ': rs)) | |
Defined in Data.Vinyl.Core sizeOf :: Rec f (r ': rs) -> Int # alignment :: Rec f (r ': rs) -> Int # peekElemOff :: Ptr (Rec f (r ': rs)) -> Int -> IO (Rec f (r ': rs)) # pokeElemOff :: Ptr (Rec f (r ': rs)) -> Int -> Rec f (r ': rs) -> IO () # peekByteOff :: Ptr b -> Int -> IO (Rec f (r ': rs)) # pokeByteOff :: Ptr b -> Int -> Rec f (r ': rs) -> IO () # | |
ReifyConstraint NFData f xs => NFData (Rec f xs) | |
Defined in Data.Vinyl.Core | |
type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) | |
Defined in Data.Vinyl.Lens | |
type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) | |
Defined in Data.Vinyl.Lens | |
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) | |
Defined in Data.Vinyl.Lens | |
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) | |
Defined in Data.Vinyl.Lens | |
type Rep (Rec f (r ': rs)) | |
Defined in Data.Vinyl.Core type Rep (Rec f (r ': rs)) = C1 ('MetaCons ":&" ('InfixI 'RightAssociative 7) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f r)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rep (Rec f rs))) | |
type Rep (Rec f ('[] :: [u])) | |
Defined in Data.Vinyl.Core |
pattern (:^:) :: 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).
newtype (s :: Symbol) :-> a Source #
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
Monad ((:->) s) Source # | |
Functor ((:->) s) Source # | |
Applicative ((:->) s) Source # | |
Foldable ((:->) s) Source # | |
Defined in Composite.Record fold :: Monoid m => (s :-> m) -> m # foldMap :: Monoid m => (a -> m) -> (s :-> a) -> m # foldMap' :: Monoid m => (a -> m) -> (s :-> a) -> m # foldr :: (a -> b -> b) -> b -> (s :-> a) -> b # foldr' :: (a -> b -> b) -> b -> (s :-> a) -> b # foldl :: (b -> a -> b) -> b -> (s :-> a) -> b # foldl' :: (b -> a -> b) -> b -> (s :-> a) -> b # foldr1 :: (a -> a -> a) -> (s :-> a) -> a # foldl1 :: (a -> a -> a) -> (s :-> a) -> a # elem :: Eq a => a -> (s :-> a) -> Bool # maximum :: Ord a => (s :-> a) -> a # minimum :: Ord a => (s :-> a) -> a # | |
Traversable ((:->) s) Source # | |
KnownSymbol s => IsoHKD Identity (s :-> a :: Type) Source # | |
Bounded a => Bounded (s :-> a) Source # | |
Enum a => Enum (s :-> a) Source # | |
Defined in Composite.Record | |
Eq a => Eq (s :-> a) Source # | |
Floating a => Floating (s :-> a) Source # | |
Defined in Composite.Record sqrt :: (s :-> a) -> s :-> a # (**) :: (s :-> a) -> (s :-> a) -> s :-> a # logBase :: (s :-> a) -> (s :-> a) -> s :-> a # asin :: (s :-> a) -> s :-> a # acos :: (s :-> a) -> s :-> a # atan :: (s :-> a) -> s :-> a # sinh :: (s :-> a) -> s :-> a # cosh :: (s :-> a) -> s :-> a # tanh :: (s :-> a) -> s :-> a # asinh :: (s :-> a) -> s :-> a # acosh :: (s :-> a) -> s :-> a # atanh :: (s :-> a) -> s :-> a # log1p :: (s :-> a) -> s :-> a # expm1 :: (s :-> a) -> s :-> a # | |
Fractional a => Fractional (s :-> a) Source # | |
Integral a => Integral (s :-> a) Source # | |
Defined in Composite.Record | |
Num a => Num (s :-> a) Source # | |
Ord a => Ord (s :-> a) Source # | |
Defined in Composite.Record | |
Real a => Real (s :-> a) Source # | |
Defined in Composite.Record toRational :: (s :-> a) -> Rational # | |
RealFloat a => RealFloat (s :-> a) Source # | |
Defined in Composite.Record floatRadix :: (s :-> a) -> Integer # floatDigits :: (s :-> a) -> Int # floatRange :: (s :-> a) -> (Int, Int) # decodeFloat :: (s :-> a) -> (Integer, Int) # encodeFloat :: Integer -> Int -> s :-> a # exponent :: (s :-> a) -> Int # significand :: (s :-> a) -> s :-> a # scaleFloat :: Int -> (s :-> a) -> s :-> a # isInfinite :: (s :-> a) -> Bool # isDenormalized :: (s :-> a) -> Bool # isNegativeZero :: (s :-> a) -> Bool # | |
RealFrac a => RealFrac (s :-> a) Source # | |
(KnownSymbol s, Show a) => Show (s :-> a) Source # | |
IsString a => IsString (s :-> a) Source # | |
Defined in Composite.Record fromString :: String -> s :-> a # | |
Semigroup a => Semigroup (s :-> a) Source # | |
Monoid a => Monoid (s :-> a) Source # | |
Storable a => Storable (s :-> a) Source # | |
Defined in Composite.Record | |
NFData a => NFData (s :-> a) Source # | |
Defined in Composite.Record | |
Wrapped (s :-> a) Source # | |
(s1 :-> a1) ~ t => Rewrapped (s2 :-> a2) t Source # | |
Defined in Composite.Record | |
(KnownSymbol s, ReifyNames rs) => ReifyNames ((s :-> a) ': rs) Source # | |
type HKD Identity (s :-> a :: Type) Source # | |
Defined in Composite.Record | |
type Unwrapped (s :-> a) Source # | |
Defined in Composite.Record |
val :: forall (s :: Symbol) 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 ::Rec
Identity
'[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) => proxy (s :-> a) -> (f a -> g (f a)) -> Rec f rs -> g (Rec f rs) Source #
Synonym for rlensCo
rlensCo :: (Functor f, Functor g, RElem (s :-> a) rs) => 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 ::Rec
Maybe
'[FFoo, FBar] rec = Just 123 :^: Just "hello!" :^: Nil
Then:
view (rlensCo fBar_) rec == Just "hello!" set (rlensCo fBar_) Nothing rec == Just 123 :^: Nothing :^: Nil over (rlensCo fBar_) (fmap (map toUpper)) rec == Just 123 :^: Just "HELLO!" :^: Nil
rlensContra :: (Contravariant f, Functor g, RElem (s :-> a) rs) => 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 a contravariant functor.
For example, given:
type FFoo = "foo" :-> Int type FBar = "bar" :-> String fBar_ :: Proxy FBar fBar_ = Proxy rec ::Rec
Predicate
'[FFoo, FBar] rec = Predicate even :!: Predicate (even . length) :!: Nil
Then:
view (rlensContra fBar_) rec == Predicate even set (rlensContra fBar_) Predicate (odd . length) rec == Predicate even :!: Predicate (odd . length) :!: Nil over (rlensContra fBar_) (contramap show) rec == Predicate even :!: Predicate (odd . length . show) :!: 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)
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)
.
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)
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 u. forall (cs :: [u -> Constraint]) (f :: u -> Type) (rs :: [u]) (proxy :: [u -> Constraint] -> Type). (AllHave cs rs, RecApplicative rs) => proxy cs -> (forall proxy' (a :: u). 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.
recordToNonEmpty :: RecordToList rs => Rec (Const a) (r ': rs) -> NonEmpty a Source #
class ReifyNames (rs :: [Type]) where Source #
Instances
ReifyNames ('[] :: [Type]) Source # | |
(KnownSymbol s, ReifyNames rs) => ReifyNames ((s :-> a) ': rs) Source # | |
class RecWithContext (ss :: [Type]) (ts :: [Type]) 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
.
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 ('[] :: [Type]) Source # | |
Defined in Composite.Record | |
(r ∈ ss, RecWithContext ss ts) => RecWithContext ss (r ': ts) Source # | |
Defined in Composite.Record |
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
.
type RDeletable r rs = (r ∈ rs, RDelete r rs ⊆ rs) Source #
Constraint which reflects that an element r
can be removed from rs
using rdelete
.