Safe Haskell | None |
---|---|
Language | Haskell2010 |
- rappend :: Rec k f as -> Rec k f bs -> Rec k f ((++) k as bs)
- rtraverse :: Applicative h => (forall x. f x -> h (g x)) -> Rec k f rs -> h (Rec k g rs)
- rdel :: CanDelete r rs => proxy r -> Rec f rs -> Rec f (RDelete r rs)
- type CanDelete r rs = (RElem r rs (RIndex r rs), RDelete r rs ⊆ rs)
- frameCons :: Functor f => f a -> Rec f rs -> Rec f ((s :-> a) : rs)
- frameConsA :: Applicative f => a -> Rec f rs -> Rec f ((s :-> a) : rs)
- frameSnoc :: Rec f rs -> f r -> Rec f (rs ++ `[r]`)
- pattern (f r) :& (Rec * f rs) :: Functor f => Rec * f ((:) * ((:->) s r) rs)
- pattern (~) [*] t ([] *) => Nil :: Rec * t t
- type AllCols c ts = LAll c (UnColumn ts)
- type family UnColumn ts
- class AsVinyl ts where
- mapMono :: (AllAre a (UnColumn ts), Functor f, AsVinyl ts) => (a -> a) -> Rec f ts -> Rec f ts
- mapMethod :: forall f c ts. (Functor f, LAll c (UnColumn ts), AsVinyl ts) => Proxy c -> (forall a. c a => a -> a) -> Rec f ts -> Rec f ts
- class Functor f => ShowRec f rs
- showRec :: ShowRec f rs => Rec f rs -> String
- type family ColFun f x
- class ColumnHeaders cs where
- columnHeaders :: proxy (Rec f cs) -> [String]
- reifyDict :: forall c f proxy ts. (LAll c ts, RecApplicative ts) => proxy c -> (forall a. c a => f a) -> Rec f ts
Documentation
rtraverse :: Applicative h => (forall x. f x -> h (g x)) -> Rec k f rs -> h (Rec k g rs)
A record may be traversed with respect to its interpretation functor. This can be used to yank (some or all) effects from the fields of the record to the outside of the record.
rdel :: CanDelete r rs => proxy r -> Rec f rs -> Rec f (RDelete r rs) Source
Delete a field from a record
type CanDelete r rs = (RElem r rs (RIndex r rs), RDelete r rs ⊆ rs) Source
A constraint that a field can be deleted from a record.
frameCons :: Functor f => f a -> Rec f rs -> Rec f ((s :-> a) : rs) Source
Add a column to the head of a row.
frameConsA :: Applicative f => a -> Rec f rs -> Rec f ((s :-> a) : rs) Source
Add a pure column to the head of a row.
frameSnoc :: Rec f rs -> f r -> Rec f (rs ++ `[r]`) Source
Add a column to the tail of a row. Note that the supplied value
should be a Col
to work with the Frames
tooling.
type AllCols c ts = LAll c (UnColumn ts) Source
Enforce a constraint on the payload type of each column.
Remove the column name phantom types from a record, leaving you
with an unadorned Vinyl Rec
.
mapMono :: (AllAre a (UnColumn ts), Functor f, AsVinyl ts) => (a -> a) -> Rec f ts -> Rec f ts Source
Map a function across a homogeneous, monomorphic Rec
.
mapMethod :: forall f c ts. (Functor f, LAll c (UnColumn ts), AsVinyl ts) => Proxy c -> (forall a. c a => a -> a) -> Rec f ts -> Rec f ts Source
Map a typeclass method across a Rec
each of whose fields
has an instance of the typeclass.
A type function to convert a Record
to a Rec
. ColFun f (Rec
rs) = Rec f rs
.
class ColumnHeaders cs where Source
columnHeaders :: proxy (Rec f cs) -> [String] Source
Return the column names for a record.
ColumnHeaders ([] *) | |
(ColumnHeaders cs, KnownSymbol s) => ColumnHeaders ((:) * ((:->) s c) cs) |
reifyDict :: forall c f proxy ts. (LAll c ts, RecApplicative ts) => proxy c -> (forall a. c a => f a) -> Rec f ts Source
Build a record whose elements are derived solely from a constraint satisfied by each.