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

Safe HaskellNone
LanguageHaskell2010

Frames.CSV

Contents

Description

Infer row types from comma-separated values (CSV) data and read that data from files. Template Haskell is used to generate the necessary types so that you can write type safe programs referring to those types.

Synopsis

Documentation

data QuotingMode Source #

Constructors

NoQuoting

No quoting enabled. The separator may not appear in values

RFC4180Quoting QuoteChar

Quoted values with the given quoting character. Quotes are escaped by doubling them. Mostly RFC4180 compliant, except doesn't support newlines in values

defaultParser :: ParserOptions Source #

Default ParseOptions get column names from a header line, and use commas to separate columns.

defaultSep :: Separator Source #

Default separator string.

Parsing

tokenizeRow :: ParserOptions -> Text -> [Text] Source #

Helper to split a Text on commas and strip leading and trailing whitespace from each resulting chunk.

reassembleRFC4180QuotedParts :: Separator -> QuoteChar -> [Text] -> [Text] Source #

Post processing applied to a list of tokens split by the separator which should have quoted sections reassembeld

prefixInference :: (ColumnTypeable a, Monoid a) => ParserOptions -> Handle -> IO [a] Source #

Infer column types from a prefix (up to 1000 lines) of a CSV file.

readColHeaders :: (ColumnTypeable a, Monoid a) => ParserOptions -> FilePath -> IO [(Text, a)] Source #

Extract column names and inferred types from a CSV file.

Loading Data

class ReadRec rs where Source #

Parsing each component of a RecF from a list of text chunks, one chunk per record component.

Minimal complete definition

readRec

Methods

readRec :: [Text] -> Rec Maybe rs Source #

Instances

ReadRec ([] *) Source # 

Methods

readRec :: [Text] -> Rec * Maybe [*] Source #

(Parseable t, ReadRec ts) => ReadRec ((:) * ((:->) s t) ts) Source # 

Methods

readRec :: [Text] -> Rec * Maybe ((* ': (s :-> t)) ts) Source #

readRow :: ReadRec rs => ParserOptions -> Text -> Rec Maybe rs Source #

Read a RecF from one line of CSV.

readTableMaybeOpt :: (MonadIO m, ReadRec rs) => ParserOptions -> FilePath -> Producer (Rec Maybe rs) m () Source #

Produce rows where any given entry can fail to parse.

readTableMaybe :: (MonadIO m, ReadRec rs) => FilePath -> Producer (Rec Maybe rs) m () Source #

Produce rows where any given entry can fail to parse.

readTableOpt' :: forall m rs. (MonadPlus m, MonadIO m, ReadRec rs) => ParserOptions -> FilePath -> m (Record rs) Source #

Returns a MonadPlus producer of rows for which each column was successfully parsed. This is typically slower than readTableOpt.

readTable' :: forall m rs. (MonadPlus m, MonadIO m, ReadRec rs) => FilePath -> m (Record rs) Source #

Returns a MonadPlus producer of rows for which each column was successfully parsed. This is typically slower than readTable.

readTableOpt :: forall m rs. (MonadIO m, ReadRec rs) => ParserOptions -> FilePath -> Producer (Record rs) m () Source #

Returns a producer of rows for which each column was successfully parsed.

readTable :: forall m rs. (MonadIO m, ReadRec rs) => FilePath -> Producer (Record rs) m () Source #

Returns a producer of rows for which each column was successfully parsed.

Template Haskell

recDec :: [(Text, Q Type)] -> Q Type Source #

Generate a column type.

sanitizeTypeName :: Text -> Text Source #

Massage a column name from a CSV file into a valid Haskell type identifier.

mkColTDec :: TypeQ -> Name -> DecQ Source #

Declare a type synonym for a column.

mkColPDec :: Name -> TypeQ -> Text -> DecsQ Source #

Declare a singleton value of the given column type and lenses for working with that column.

colDec :: ColumnTypeable a => Text -> Text -> a -> DecsQ Source #

For each column, we declare a type synonym for its type, and a Proxy value of that type.

declareColumn :: Text -> Name -> DecsQ Source #

Splice for manually declaring a column of a given type. For example, declareColumn "x2" ''Double will declare a type synonym type X2 = "x2" :-> Double and a lens x2.

Default CSV Parsing

data RowGen a Source #

Control how row and named column types are generated.

Constructors

RowGen 

Fields

  • columnNames :: [String]

    Use these column names. If empty, expect a header row in the data file to provide column names.

  • tablePrefix :: String

    A common prefix to use for every generated declaration.

  • separator :: Separator

    The string that separates the columns on a row.

  • rowTypeName :: String

    The row type that enumerates all columns.

  • columnUniverse :: Proxy a

    A type that identifies all the types that can be used to classify a column. This is essentially a type-level list of types. See colQ.

colQ :: Name -> Q Exp Source #

Shorthand for a Proxy value of ColumnUniverse applied to the given type list.

rowGen :: RowGen Columns Source #

A default RowGen. This instructs the type inference engine to get column names from the data file, use the default column separator (a comma), infer column types from the default Columns set of types, and produce a row type with name Row.

tableType :: String -> FilePath -> DecsQ Source #

Generate a type for each row of a table. This will be something like Record ["x" :-> a, "y" :-> b, "z" :-> c].

tableTypes :: String -> FilePath -> DecsQ Source #

Like tableType, but additionally generates a type synonym for each column, and a proxy value of that type. If the CSV file has column names "foo", "bar", and "baz", then this will declare type Foo = "foo" :-> Int, for example, foo = rlens (Proxy :: Proxy Foo), and foo' = rlens' (Proxy :: Proxy Foo).

Customized Data Set Parsing

tableType' :: forall a. (ColumnTypeable a, Monoid a) => RowGen a -> FilePath -> DecsQ Source #

Generate a type for a row of a table. This will be something like Record ["x" :-> a, "y" :-> b, "z" :-> c]. Column type synonyms are not generated (see tableTypes').

tableTypesText' :: forall a. (ColumnTypeable a, Monoid a) => RowGen a -> FilePath -> DecsQ Source #

Generate a type for a row of a table all of whose columns remain unparsed Text values.

tableTypes' :: forall a. (ColumnTypeable a, Monoid a) => RowGen a -> FilePath -> DecsQ Source #

Like tableType', but additionally generates a type synonym for each column, and a proxy value of that type. If the CSV file has column names "foo", "bar", and "baz", then this will declare type Foo = "foo" :-> Int, for example, foo = rlens (Proxy :: Proxy Foo), and foo' = rlens' (Proxy :: Proxy Foo).

Writing CSV Data

produceCSV :: forall f ts m. (ColumnHeaders ts, AsVinyl ts, Foldable f, Monad m, RecAll Identity (UnColumn ts) Show) => f (Record ts) -> Producer String m () Source #

yield a header row with column names followed by a line of text for each Record with each field separated by a comma.

writeCSV :: (ColumnHeaders ts, AsVinyl ts, Foldable f, RecAll Identity (UnColumn ts) Show) => FilePath -> f (Record ts) -> IO () Source #

Write a header row with column names followed by a line of text for each Record to the given file.