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

Frames.CSV

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

Parsing

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

Instances

Instances details
Eq QuotingMode Source # 
Instance details

Defined in Frames.CSV

Show QuotingMode Source # 
Instance details

Defined in Frames.CSV

Lift QuotingMode Source # 
Instance details

Defined in Frames.CSV

data ParserOptions Source #

Instances

Instances details
Eq ParserOptions Source # 
Instance details

Defined in Frames.CSV

Show ParserOptions Source # 
Instance details

Defined in Frames.CSV

Lift ParserOptions Source # 
Instance details

Defined in Frames.CSV

defaultParser :: ParserOptions Source #

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

defaultSep :: Separator Source #

Default separator string.

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, Monad m) => Parser [Text] m [a] Source #

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

readColHeaders :: (ColumnTypeable a, Monoid a, Monad m) => ParserOptions -> Producer [Text] m () -> m [(Text, a)] Source #

Extract column names and inferred types from a CSV file.

Loading CSV Data

class ReadRec rs where Source #

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

Methods

readRec :: [Text] -> Rec (Either Text :. ElField) rs Source #

Instances

Instances details
ReadRec ('[] :: [(Symbol, Type)]) Source # 
Instance details

Defined in Frames.CSV

Methods

readRec :: [Text] -> Rec (Either Text :. ElField) '[] Source #

(Parseable t, ReadRec ts, KnownSymbol s) => ReadRec ((s :-> t) ': ts) Source # 
Instance details

Defined in Frames.CSV

Methods

readRec :: [Text] -> Rec (Either Text :. ElField) ((s :-> t) ': ts) Source #

pipeLines :: MonadSafe m => (Handle -> IO (Either IOException Text)) -> FilePath -> Producer Text m () Source #

Opens a file (in MonadSafe) and repeatedly applies the given function to the Handle to obtain lines to yield. Adapted from the moribund pipes-text package.

produceTextLines :: MonadSafe m => FilePath -> Producer Text m () Source #

Produce lines of Text.

produceTokens :: MonadSafe m => FilePath -> Separator -> Producer [Text] m () Source #

Produce lines of tokens that were separated by the given separator.

consumeTextLines :: MonadSafe m => FilePath -> Consumer Text m r Source #

Consume lines of Text, writing them to a file.

readFileLatin1Ln :: MonadSafe m => FilePath -> Producer [Text] m () Source #

Produce the lines of a latin1 (or ISO8859 Part 1) encoded file as ’T.Text’ values.

readRow :: ReadRec rs => ParserOptions -> Text -> Rec (Either Text :. ElField) rs Source #

Read a RecF from one line of CSV.

readTableMaybeOpt :: (MonadSafe m, ReadRec rs, RMap rs) => ParserOptions -> FilePath -> Producer (Rec (Maybe :. ElField) rs) m () Source #

Produce rows where any given entry can fail to parse.

pipeTableMaybeOpt :: (Monad m, ReadRec rs, RMap rs) => ParserOptions -> Pipe [Text] (Rec (Maybe :. ElField) rs) m () Source #

Stream lines of CSV data into rows of ’Rec’ values values where any given entry can fail to parse.

pipeTableEitherOpt :: (Monad m, ReadRec rs) => ParserOptions -> Pipe Text (Rec (Either Text :. ElField) rs) m () Source #

Stream lines of CSV data into rows of ’Rec’ values values where any given entry can fail to parse. In the case of a parse failure, the raw Text of that entry is retained.

readTableMaybe :: (MonadSafe m, ReadRec rs, RMap rs) => FilePath -> Producer (Rec (Maybe :. ElField) rs) m () Source #

Produce rows where any given entry can fail to parse.

pipeTableMaybe :: (Monad m, ReadRec rs, RMap rs) => Pipe [Text] (Rec (Maybe :. ElField) rs) m () Source #

Stream lines of CSV data into rows of ’Rec’ values where any given entry can fail to parse.

pipeTableEither :: (Monad m, ReadRec rs) => Pipe Text (Rec (Either Text :. ElField) rs) m () Source #

Stream lines of CSV data into rows of ’Rec’ values where any given entry can fail to parse. In the case of a parse failure, the raw Text of that entry is retained.

readTableOpt :: (MonadSafe m, ReadRec rs, RMap rs) => ParserOptions -> FilePath -> Producer (Record rs) m () Source #

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

pipeTableOpt :: (ReadRec rs, RMap rs, Monad m) => ParserOptions -> Pipe [Text] (Record rs) m () Source #

Pipe lines of CSV text into rows for which each column was successfully parsed.

readTable :: (MonadSafe m, ReadRec rs, RMap rs) => FilePath -> Producer (Record rs) m () Source #

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

pipeTable :: (ReadRec rs, RMap rs, Monad m) => Pipe [Text] (Record rs) m () Source #

Pipe lines of CSV text into rows for which each column was successfully parsed.

Writing CSV Data

produceCSV :: forall f ts m. (ColumnHeaders ts, Foldable f, Monad m, RecordToList ts, RecMapMethod ShowCSV ElField ts) => 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. If your source of Record values is a Producer, consider using pipeToCSV to keep everything streaming.

pipeToCSV :: forall ts m. (Monad m, ColumnHeaders ts, RecordToList ts, RecMapMethod ShowCSV ElField ts) => Pipe (Record ts) Text 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. This is the same as produceCSV, but adapated for cases where you have streaming input that you wish to use to produce streaming output.

writeCSV :: (ColumnHeaders ts, Foldable f, RecordToList ts, RecMapMethod ShowCSV ElField ts) => 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.