Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type family Elem t ts :: Bool where ...
- type family Or (a :: Bool) (b :: Bool) :: Bool where ...
- type family Not a :: Bool where ...
- type family Disjoint ss ts :: Bool where ...
- type ElemOf ts r = RElem r ts (RIndex r ts)
- class RowToColumn ts rs where
- rowToColumnAux :: Proxy ts -> Rec f rs -> [CoRec f ts]
- rowToColumn :: RowToColumn ts ts => Rec f ts -> [CoRec f ts]
- 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)]
- type family RDeleteAll ss ts where ...
- 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)]
- retroSnoc :: forall t ts. Record (t ': ts) -> Record (ts ++ '[t])
- 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])]
- class HasLength (ts :: [k]) where
- 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])
Documentation
class RowToColumn ts rs where Source #
Instances
RowToColumn (ts :: [k]) ([] :: [k]) Source # | |
Defined in Frames.Melt | |
(r ∈ ts, RowToColumn ts rs) => RowToColumn (ts :: [a]) (r ': rs :: [a]) Source # | |
Defined in Frames.Melt |
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 #
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.