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

Frames.Exploration

Description

Functions useful for interactively exploring and experimenting with a data set.

Synopsis

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.

pr1 :: QuasiQuoter Source #

Like pr, but takes a single type, which is used to produce a Proxy for a single-element list containing only that type. This is useful for passing a single type to a function that wants a list of types.

showFrame Source #

Arguments

:: forall rs. (ColumnHeaders rs, RecMapMethod Show ElField rs, RecordToList rs) 
=> String

Separator between fields

-> Frame (Record rs)

The Frame to be formatted to a String

-> String 

Format a Frame to a String.

printFrame Source #

Arguments

:: forall rs. (ColumnHeaders rs, RecMapMethod Show ElField rs, RecordToList rs) 
=> String

Separator between fields

-> Frame (Record rs)

The Frame to be printed to stdout

-> IO () 

Print a Frame to stdout.

takeRows :: Int -> Frame (Record rs) -> Frame (Record rs) Source #

takeRows n frame produces a new Frame made up of the first n rows of frame.

dropRows :: Int -> Frame (Record rs) -> Frame (Record rs) Source #

dropRows n frame produces a new Frame just like frame, but not including its first n rows.