Frames-0.7.1: Data frames For working with tabular data files
Safe HaskellNone
LanguageHaskell2010

Frames.Melt

Synopsis

Documentation

type family Elem t ts :: Bool where ... Source #

Equations

Elem t '[] = 'False 
Elem t (t ': ts) = 'True 
Elem t (s ': ts) = Elem t ts 

type family Or (a :: Bool) (b :: Bool) :: Bool where ... Source #

Equations

Or 'True b = 'True 
Or a b = b 

type family Not a :: Bool where ... Source #

Equations

Not 'True = 'False 
Not 'False = 'True 

type family Disjoint ss ts :: Bool where ... Source #

Equations

Disjoint '[] ts = 'True 
Disjoint (s ': ss) ts = Or (Not (Elem s ts)) (Disjoint ss ts) 

type ElemOf ts r = RElem r ts (RIndex r ts) Source #

class RowToColumn ts rs where Source #

Methods

rowToColumnAux :: Proxy ts -> Rec f rs -> [CoRec f ts] Source #

Instances

Instances details
RowToColumn (ts :: [k]) ('[] :: [k]) Source # 
Instance details

Defined in Frames.Melt

Methods

rowToColumnAux :: forall (f :: k0 -> Type). Proxy ts -> Rec f '[] -> [CoRec f ts] Source #

(r ts, RowToColumn ts rs) => RowToColumn (ts :: [a]) (r ': rs :: [a]) Source # 
Instance details

Defined in Frames.Melt

Methods

rowToColumnAux :: forall (f :: k -> Type). Proxy ts -> Rec f (r ': rs) -> [CoRec f ts] Source #

rowToColumn :: RowToColumn ts ts => Rec f ts -> [CoRec f ts] Source #

Transform a record into a list of its fields, retaining proof that each field is part of the whole.

meltAux :: forall vs ss ts. (vs ts, ss ts, Disjoint ss ts ~ 'True, ts (vs ++ ss), ColumnHeaders vs, RowToColumn vs vs) => Record ts -> [Record (("value" :-> CoRec ElField vs) ': ss)] Source #

type family RDeleteAll ss ts where ... Source #

Equations

RDeleteAll '[] ts = ts 
RDeleteAll (s ': ss) ts = RDeleteAll ss (RDelete s ts) 

meltRow' :: forall proxy vs ts ss. (vs ts, ss ts, vs ~ RDeleteAll ss ts, Disjoint ss ts ~ 'True, ts (vs ++ ss), ColumnHeaders vs, RowToColumn vs vs) => proxy ss -> Record ts -> [Record (("value" :-> CoRec ElField vs) ': ss)] Source #

This is melt, but the variables are at the front of the record, which reads a bit odd.

retroSnoc :: forall t ts. Record (t ': ts) -> Record (ts ++ '[t]) Source #

Turn a cons into a snoc after the fact.

meltRow :: (vs ts, ss ts, vs ~ RDeleteAll ss ts, Disjoint ss ts ~ 'True, ts (vs ++ ss), ColumnHeaders vs, RowToColumn vs vs) => proxy ss -> Record ts -> [Record (ss ++ '["value" :-> CoRec ElField vs])] Source #

Like melt in the reshape2 package for the R language. It stacks multiple columns into a single column over multiple rows. Takes a specification of the id columns that remain unchanged. The remaining columns will be stacked.

Suppose we have a record, r :: Record [Name,Age,Weight]. If we apply melt [pr1|Name|] r, we get two values with type Record [Name, "value" :-> CoRec Identity [Age,Weight]]. The first will contain Age in the value column, and the second will contain Weight in the value column.

class HasLength (ts :: [k]) where Source #

Methods

hasLength :: proxy ts -> Int Source #

Instances

Instances details
HasLength ('[] :: [k]) Source # 
Instance details

Defined in Frames.Melt

Methods

hasLength :: proxy '[] -> Int Source #

HasLength ts => HasLength (t ': ts :: [k]) Source # 
Instance details

Defined in Frames.Melt

Methods

hasLength :: proxy (t ': ts) -> Int Source #

melt :: forall vs ts ss proxy. (vs ts, ss ts, vs ~ RDeleteAll ss ts, HasLength vs, Disjoint ss ts ~ 'True, ts (vs ++ ss), ColumnHeaders vs, RowToColumn vs vs) => proxy ss -> FrameRec ts -> FrameRec (ss ++ '["value" :-> CoRec ElField vs]) Source #

Applies meltRow to each row of a FrameRec.