Frames-streamly-0.1.1.1: A streamly layer for Frames I/O
Copyright(c) Adam Conner-Sax 2020
LicenseBSD-3-Clause
Maintaineradam_conner_sax@yahoo.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Frames.Streamly.CSV

Description

This module can be used in-place of Frames.CSV in order to use streamly streams where Frames uses pipes. This module adds some functionality for formatting in more flexible ways than the pipes version in Frames. It allows us of Show instances, in addition to the ShowCSV class included in Frames. And it allows one-off specification of a format as well. See the example for more details.

Synopsis

Strict version of ReadRec

class StrictReadRec rs where Source #

Instances

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

Defined in Frames.Streamly.CSV

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

Defined in Frames.Streamly.CSV

Methods

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

read from File to Stream of Recs

readTable Source #

Arguments

:: forall rs t m. (MonadAsync m, MonadCatch m, IsStream t, RMap rs, StrictReadRec rs) 
=> FilePath

file path

-> t m (Record rs)

stream of Records

Stream Table from a file path, dropping rows where any field fails to parse | Use default options NB: If the inferred/given rs is different from the actual file row-type, things will go awry.

readTableOpt Source #

Arguments

:: forall rs t m. (MonadAsync m, MonadCatch m, IsStream t, RMap rs, StrictReadRec rs) 
=> ParserOptions

parsing options

-> FilePath

file path

-> t m (Record rs)

stream of Records

Stream Table from a file path, dropping rows where any field fails to parse NB: If the inferred/given rs is different from the actual file row-type, things will go awry.

readTableMaybe Source #

Arguments

:: forall rs t m. (MonadAsync m, MonadCatch m, IsStream t, RMap rs, ReadRec rs) 
=> FilePath

file path

-> t m (Rec (Maybe :. ElField) rs)

stream of Maybe :. ElField records after parsing.

Stream a table from a file path, using the default options. Results composed with the Maybe functor. Unparsed fields are returned as Nothing. NB: If the inferred/given rs is different from the actual file row-type, things will go awry.

readTableMaybeOpt Source #

Arguments

:: forall rs t m. (MonadAsync m, MonadCatch m, IsStream t, RMap rs, ReadRec rs) 
=> ParserOptions

parsing options

-> FilePath

file path

-> t m (Rec (Maybe :. ElField) rs)

stream of Maybe :. ElField records after parsing.

Stream a table from a file path. Results composed with the Maybe functor. Unparsed fields are returned as Nothing. NB: If the inferred/given rs is different from the actual file row-type, things will go awry.

readTableEither Source #

Arguments

:: forall rs t m. (MonadAsync m, MonadCatch m, IsStream t, RMap rs, ReadRec rs) 
=> FilePath

file path

-> t m (Rec (Either Text :. ElField) rs)

stream of Either :. ElField records after parsing.

Stream a table from a file path. Results composed with the Either Text functor. Unparsed fields are returned as a Left containing the string that failed to parse. Uses default options. NB: If the inferred/given rs is different from the actual file row-type, things will go awry.

readTableEitherOpt Source #

Arguments

:: forall rs t m. (MonadAsync m, MonadCatch m, IsStream t, RMap rs, ReadRec rs) 
=> ParserOptions

parsing options

-> FilePath

file path

-> t m (Rec (Either Text :. ElField) rs)

stream of Either :. ElField records after parsing.

Stream a table from a file path. Results composed with the Either Text functor. Unparsed fields are returned as a Left containing the string that failed to parse. NB: If the inferred/given rs is different from the actual file row-type, things will go awry.

convert streaming Text to streaming Records

streamTable Source #

Arguments

:: forall rs t m. (MonadAsync m, IsStream t, RMap rs, StrictReadRec rs) 
=> t m Text

stream of Text rows

-> t m (Record rs)

stream of Records

Convert a stream of lines of Text to a table, dropping rows where any field fails to parse. Use default options. NB: If the inferred/given rs is different from the actual file row-type, things will go awry.

streamTableOpt Source #

Arguments

:: forall rs t m. (MonadAsync m, IsStream t, RMap rs, StrictReadRec rs) 
=> ParserOptions

parsing options

-> t m Text

stream of Text rows

-> t m (Record rs)

stream of Records

Convert a stream of lines of Text Word8 to a table, dropping rows where any field fails to parse. NB: If the inferred/given rs is different from the actual file row-type, things will go awry.

streamTableMaybe Source #

Arguments

:: forall rs t m. (MonadAsync m, IsStream t, RMap rs, ReadRec rs) 
=> t m Text

stream of Text rows

-> t m (Rec (Maybe :. ElField) rs)

stream of parsed Maybe :. ElField rows

Convert a stream of lines of Text to a table.

NB: If the inferred/given rs is different from the actual file row-type, things will..go awry.

streamTableMaybeOpt Source #

Arguments

:: forall rs t m. (MonadAsync m, IsStream t, RMap rs, ReadRec rs) 
=> ParserOptions

parsing options

-> t m Text

stream of Text rows

-> t m (Rec (Maybe :. ElField) rs)

stream of parsed Maybe :. ElField rows

Convert a stream of lines of Text to a table .

NB: If the inferred/given rs is different from the actual file row-type, things will..go awry.

streamTableEither Source #

Arguments

:: forall rs t m. (MonadAsync m, IsStream t, RMap rs, ReadRec rs) 
=> t m Text

stream of Text rows

-> t m (Rec (Either Text :. ElField) rs)

stream of parsed Either :. ElField rows

Convert a stream of lines of Text to a table Each field is returned in an Either Text functor. Right a for successful parses and Left Text when parsing fails, containing the text that failed to Parse.

NB: If the inferred/given rs is different from the actual file row-type, things will go awry.

streamTableEitherOpt Source #

Arguments

:: forall rs t m. (MonadAsync m, IsStream t, RMap rs, ReadRec rs) 
=> ParserOptions

parsing options

-> t m Text

stream of Text rows

-> t m (Rec (Either Text :. ElField) rs)

stream of parsed Either :. ElField rows

Convert a stream of lines of Text to records. Each field is returned in an Either Text functor. Right a for successful parses and Left Text when parsing fails, containing the text that failed to Parse.

NB: If the inferred/given rs is different from the actual file row-type, things will..go awry.

Produce (streaming) Text from Records

streamToCSV Source #

Arguments

:: forall rs m t. (ColumnHeaders rs, MonadIO m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t) 
=> t m (Record rs)

stream of Records

-> t m Text

stream of Text rows

Given a stream of Records, for which all fields satisfy the ShowCSV constraint, produce a stream of CSV Text, one item (line) per Record.

streamCSV Source #

Arguments

:: forall f rs m t. (ColumnHeaders rs, Foldable f, MonadIO m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t) 
=> f (Record rs)

Foldable of Records

-> t m Text

stream of Text rows

Given a foldable of Records, for which all fields satisfy the ShowCSV constraint, produce a stream of CSV Text, one item (line) per Record.

streamToSV Source #

Arguments

:: forall rs m t. (ColumnHeaders rs, MonadIO m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t) 
=> Text

column separator

-> t m (Record rs)

stream of Records

-> t m Text

stream of Text rows

Given a stream of Records, for which all fields satisfy the ShowCSV constraint, produce a stream of Text, one item (line) per Record with the specified separator between fields.

streamSV Source #

Arguments

:: forall f rs m t. (ColumnHeaders rs, Foldable f, MonadIO m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t) 
=> Text

column separator

-> f (Record rs)

foldable of Records

-> t m Text

stream of Text rows

Given a foldable of Records, for which all fields satisfy the ShowCSV constraint, produce a stream of Text, one item (line) per Record with the specified separator between fields.

streamSV' Source #

Arguments

:: forall rs t m f. (RecordToList rs, RApply rs, ColumnHeaders rs, IsStream t, MonadAsync m) 
=> Rec (Lift (->) f (Const Text)) rs

Vinyl record of formatting functions for the row-type.

-> Text

column separator

-> t m (Rec f rs)

stream of Records

-> t m Text

stream of Text rows

Given a record of functions to map each field to Text, transform a stream of records into a stream of lines of Text, headers first, with headers/fields separated by the given separator.

write Records to Text File

writeCSV Source #

Arguments

:: forall rs m f. (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod ShowCSV ElField rs, MonadAsync m, Foldable f) 
=> FilePath

file path

-> f (Record rs)

Foldable of Records

-> m () 

write a foldable of Records to a file, one line per Record. Use the ShowCSV class to format each field to Text

writeSV Source #

Arguments

:: forall rs m f. (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod ShowCSV ElField rs, MonadAsync m, Foldable f) 
=> Text

column separator

-> FilePath

file path

-> f (Record rs)

Foldable of Records

-> m () 

write a foldable of Records to a file, one line per Record. Use the ShowCSV class to format each field to Text

writeStreamSV Source #

Arguments

:: forall rs m t. (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t, MonadAsync m) 
=> Text

column separator

-> FilePath

path

-> t m (Record rs)

stream of Records

-> m () 

write a stream of Records to a file, one line per Record. Use the ShowCSV class to format each field to Text

writeCSV_Show Source #

Arguments

:: forall rs m f. (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod Show ElField rs, MonadAsync m, Foldable f) 
=> FilePath

file path

-> f (Record rs)

Foldable of Records

-> m () 

write a foldable of Records to a file, one line per Record. Use the Show class to format each field to Text

writeSV_Show Source #

Arguments

:: forall rs m f. (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod Show ElField rs, MonadAsync m, Foldable f) 
=> Text

column separator

-> FilePath

file path

-> f (Record rs)

Foldable of Records

-> m () 

write a foldable of Records to a file, one line per Record. Use the Show class to format each field to Text

writeStreamSV_Show Source #

Arguments

:: forall rs m t. (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod Show ElField rs, IsStream t, MonadAsync m) 
=> Text

column separator

-> FilePath

file path

-> t m (Record rs)

stream of Records

-> m () 

write a stream of Records to a file, one line per Record. Use the Show class to format each field to Text

Utilities

streamToList :: (IsStream t, Monad m) => t m a -> m [a] Source #

Convert a streamly stream into a (lazy) list

liftFieldFormatter Source #

Arguments

:: KnownField t 
=> (Snd t -> Text)

formatting function for the type in Field t

-> Lift (->) ElField (Const Text) t

formatting function in the form required to use in row-formatters.

lift a field formatting function into the right form to append to a Rec of formatters

liftFieldFormatter1 Source #

Arguments

:: (Functor f, KnownField t) 
=> (f (Snd t) -> Text)

formatting function for things like Maybe a

-> Lift (->) (f :. ElField) (Const Text) t 

lift a composed-field formatting function into the right form to append to a Rec of formatters | Perhaps to format a parsed file with Maybe or Either composed with ElField

formatTextAsIs :: (KnownField t, Snd t ~ Text) => Lift (->) ElField (Const Text) t Source #

Format a Text field as-is.

formatWithShow :: (KnownField t, Show (Snd t)) => Lift (->) ElField (Const Text) t Source #

Format a field using the Show instance of the contained type

formatWithShowCSV :: (KnownField t, ShowCSV (Snd t)) => Lift (->) ElField (Const Text) t Source #

Format a field using the Frames.ShowCSV instance of the contained type

writeLines :: (MonadAsync m, MonadCatch m) => FilePath -> SerialT m Text -> m () Source #

write a stream of Text to a file, one line per stream item. | Monomorphised to serial streams for ease of use.

writeLines' :: (MonadAsync m, MonadCatch m, IsStream t) => FilePath -> t m Text -> m () Source #

write a stream of Text to a file, one line per stream item.

word8ToTextLines :: (IsStream t, MonadIO m) => t m Word8 -> t m Text Source #

Convert a stream of Word8 to lines of Text by decoding as UTF8 and splitting on "n"

debugging