Frames-0.2.1.1: Data frames For working with tabular data files

Safe HaskellNone
LanguageHaskell2010

Frames.RecF

Synopsis

Documentation

rappend :: Rec k f as -> Rec k f bs -> Rec k f ((++) k as bs) #

Two records may be pasted together.

rtraverse :: Applicative h => (forall x. f x -> h (g x)) -> Rec u f rs -> h (Rec u 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.

pattern (:&) :: forall f r rs s. Functor f => f r -> Rec * f rs -> Rec * f ((:) * ((:->) s r) rs) Source #

pattern Nil :: forall f. Rec * f ([] *) Source #

type AllCols c ts = AllConstrained c (UnColumn ts) Source #

Enforce a constraint on the payload type of each column.

type family UnColumn ts where ... Source #

Strip the column information from each element of a list of types.

Equations

UnColumn '[] = '[] 
UnColumn ((s :-> t) ': ts) = t ': UnColumn ts 

class AsVinyl ts where Source #

Remove the column name phantom types from a record, leaving you with an unadorned Vinyl Rec.

Minimal complete definition

toVinyl, fromVinyl

Methods

toVinyl :: Functor f => Rec f ts -> Rec f (UnColumn ts) Source #

fromVinyl :: Functor f => Rec f (UnColumn ts) -> Rec f ts Source #

Instances

AsVinyl ([] *) Source # 

Methods

toVinyl :: Functor f => Rec * f [*] -> Rec * f (UnColumn [*]) Source #

fromVinyl :: Functor f => Rec * f (UnColumn [*]) -> Rec * f [*] Source #

AsVinyl ts => AsVinyl ((:) * ((:->) s t) ts) Source # 

Methods

toVinyl :: Functor f => Rec * f ((* ': (s :-> t)) ts) -> Rec * f (UnColumn ((* ': (s :-> t)) ts)) Source #

fromVinyl :: Functor f => Rec * f (UnColumn ((* ': (s :-> t)) ts)) -> Rec * f ((* ': (s :-> t)) ts) Source #

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, AllConstrained 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.

class Functor f => ShowRec f rs Source #

The ability to pretty print a Rec's fields.

Minimal complete definition

showRec'

Instances

Functor f => ShowRec f ([] *) Source # 

Methods

showRec' :: Rec * f [*] -> [String]

(KnownSymbol s, Show (f (Col' s a)), ShowRec f rs) => ShowRec f ((:) * ((:->) s a) rs) Source # 

Methods

showRec' :: Rec * f ((* ': (s :-> a)) rs) -> [String]

showRec :: ShowRec f rs => Rec f rs -> String Source #

Pretty printing of Rec values.

type family ColFun f x where ... Source #

A type function to convert a Record to a Rec. ColFun f (Rec rs) = Rec f rs.

Equations

ColFun f (Rec Identity rs) = Rec f rs 

class ColumnHeaders cs where Source #

Minimal complete definition

columnHeaders

Methods

columnHeaders :: proxy (Rec f cs) -> [String] Source #

Return the column names for a record.

Instances

ColumnHeaders ([] *) Source # 

Methods

columnHeaders :: proxy (Rec * f [*]) -> [String] Source #

(ColumnHeaders cs, KnownSymbol s) => ColumnHeaders ((:) * ((:->) s c) cs) Source # 

Methods

columnHeaders :: proxy (Rec * f ((* ': (s :-> c)) cs)) -> [String] Source #

columnHeaders :: ColumnHeaders cs => proxy (Rec f cs) -> [String] Source #

Return the column names for a record.

reifyDict :: forall c f proxy ts. (AllConstrained 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.