Safe Haskell | None |
---|---|
Language | Haskell2010 |
Functions useful for interactively exploring and experimenting with a data set.
Synopsis
- pipePreview :: (Show b, MonadIO m, MonadMask m) => Producer a (SafeT m) () -> Int -> Pipe a b (SafeT m) () -> m ()
- select :: fs ⊆ rs => proxy fs -> Record rs -> Record fs
- lenses :: (fs ⊆ rs, Functor f) => proxy fs -> (Record fs -> f (Record fs)) -> Record rs -> f (Record rs)
- recToList :: forall a (rs :: [(Symbol, *)]). (RecMapMethod ((~) a) ElField rs, RecordToList rs) => Record rs -> [a]
- pr :: QuasiQuoter
- pr1 :: QuasiQuoter
Documentation
pipePreview :: (Show b, MonadIO m, MonadMask m) => Producer a (SafeT m) () -> Int -> Pipe a b (SafeT m) () -> m () Source #
preview src n f
prints out the first n
results of piping
src
through f
.
select :: fs ⊆ rs => proxy fs -> Record rs -> Record fs Source #
Deprecated: Use Data.Vinyl.rcast with a type application.
select (Proxy::Proxy [A,B,C])
extracts columns A
, B
, and
C
, from a larger record. Note, this is just a way of pinning down
the type of a usage of rcast
.
lenses :: (fs ⊆ rs, Functor f) => proxy fs -> (Record fs -> f (Record fs)) -> Record rs -> f (Record rs) Source #
Deprecated: Use Data.Vinyl.rsubset with a type application.
lenses (Proxy::Proxy [A,B,C])
provides a lens onto columns A
,
B
, and C
. This is just a way of pinning down the type of
rsubset
.
recToList :: forall a (rs :: [(Symbol, *)]). (RecMapMethod ((~) a) ElField rs, RecordToList rs) => Record rs -> [a] Source #
pr :: QuasiQuoter Source #
A proxy value quasiquoter; a way of passing types as
values. [pr|T|]
will splice an expression Proxy::Proxy T
, while
[pr|A,B,C|]
will splice in a value of Proxy :: Proxy
[A,B,C]
. If we have a record type with Name
and Age
among
other fields, we can write select
[pr|Name,Age|]@ for a function
that extracts those fields from a larger record.