Copyright | (c) Adam Conner-Sax 2020 |
---|---|
License | BSD-3-Clause |
Maintainer | adam_conner_sax@yahoo.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
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
- readTable :: forall rs t m. (MonadIO m, IsStream t, RMap rs, ReadRec rs, MonadCatch m) => FilePath -> t m (Record rs)
- readTableOpt :: forall rs t m. (MonadIO m, IsStream t, RMap rs, ReadRec rs, MonadCatch m) => ParserOptions -> FilePath -> t m (Record rs)
- readTableMaybe :: forall rs t m. (MonadIO m, IsStream t, RMap rs, ReadRec rs, MonadCatch m) => FilePath -> t m (Rec (Maybe :. ElField) rs)
- readTableMaybeOpt :: forall rs t m. (MonadIO m, IsStream t, RMap rs, ReadRec rs, MonadCatch m) => ParserOptions -> FilePath -> t m (Rec (Maybe :. ElField) rs)
- readTableEither :: forall rs t m. (MonadIO m, IsStream t, RMap rs, ReadRec rs, MonadCatch m) => FilePath -> t m (Rec (Either Text :. ElField) rs)
- readTableEitherOpt :: forall rs t m. (MonadIO m, IsStream t, RMap rs, ReadRec rs, MonadCatch m) => ParserOptions -> FilePath -> t m (Rec (Either Text :. ElField) rs)
- streamTable :: forall rs t m. (MonadIO m, IsStream t, RMap rs, ReadRec rs) => t m Text -> t m (Record rs)
- streamTableOpt :: forall rs t m. (MonadIO m, IsStream t, RMap rs, ReadRec rs) => ParserOptions -> t m Text -> t m (Record rs)
- streamTableMaybe :: forall rs t m. (MonadIO m, IsStream t, RMap rs, ReadRec rs) => t m Text -> t m (Rec (Maybe :. ElField) rs)
- streamTableMaybeOpt :: forall rs t m. (MonadIO m, IsStream t, RMap rs, ReadRec rs) => ParserOptions -> t m Text -> t m (Rec (Maybe :. ElField) rs)
- streamTableEither :: forall rs t m. (MonadIO m, IsStream t, RMap rs, ReadRec rs) => t m Text -> t m (Rec (Either Text :. ElField) rs)
- streamTableEitherOpt :: forall rs t m. (MonadIO m, IsStream t, RMap rs, ReadRec rs) => ParserOptions -> t m Text -> t m (Rec (Either Text :. ElField) rs)
- streamToCSV :: forall rs m t. (ColumnHeaders rs, Monad m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t) => t m (Record rs) -> t m Text
- streamCSV :: forall f rs m t. (ColumnHeaders rs, Foldable f, Monad m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t) => f (Record rs) -> t m Text
- streamToSV :: forall rs m t. (ColumnHeaders rs, Monad m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t) => Text -> t m (Record rs) -> t m Text
- streamSV :: forall f rs m t. (ColumnHeaders rs, Foldable f, Monad m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t) => Text -> f (Record rs) -> t m Text
- streamSV' :: forall rs t m f. (RecordToList rs, RApply rs, ColumnHeaders rs, IsStream t, Monad m) => Rec (Lift (->) f (Const Text)) rs -> Text -> t m (Rec f rs) -> t m Text
- writeCSV :: forall rs m f. (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod ShowCSV ElField rs, MonadAsync m, Foldable f) => FilePath -> f (Record rs) -> m ()
- writeSV :: forall rs m f. (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod ShowCSV ElField rs, MonadAsync m, Foldable f) => Text -> FilePath -> f (Record rs) -> m ()
- writeStreamSV :: forall rs m t. (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t, MonadAsync m) => Text -> FilePath -> t m (Record rs) -> m ()
- writeCSV_Show :: forall rs m f. (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod Show ElField rs, MonadAsync m, Foldable f) => FilePath -> f (Record rs) -> m ()
- writeSV_Show :: forall rs m f. (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod Show ElField rs, MonadAsync m, Foldable f) => Text -> FilePath -> f (Record rs) -> m ()
- writeStreamSV_Show :: forall rs m t. (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod Show ElField rs, IsStream t, MonadAsync m) => Text -> FilePath -> t m (Record rs) -> m ()
- streamToList :: (IsStream t, Monad m) => t m a -> m [a]
- liftFieldFormatter :: KnownField t => (Snd t -> Text) -> Lift (->) ElField (Const Text) t
- liftFieldFormatter1 :: (Functor f, KnownField t) => (f (Snd t) -> Text) -> Lift (->) (f :. ElField) (Const Text) t
- formatTextAsIs :: (KnownField t, Snd t ~ Text) => Lift (->) ElField (Const Text) t
- formatWithShow :: (KnownField t, Show (Snd t)) => Lift (->) ElField (Const Text) t
- formatWithShowCSV :: (KnownField t, ShowCSV (Snd t)) => Lift (->) ElField (Const Text) t
- writeLines :: (MonadAsync m, MonadCatch m) => FilePath -> SerialT m Text -> m ()
- writeLines' :: (MonadAsync m, MonadCatch m, IsStream t) => FilePath -> t m Text -> m ()
- word8ToTextLines :: (IsStream t, Monad m) => t m Word8 -> t m Text
read from File to Stream of Recs
:: (MonadIO m, IsStream t, RMap rs, ReadRec rs, MonadCatch m) | |
=> 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.
:: (MonadIO m, IsStream t, RMap rs, ReadRec rs, MonadCatch m) | |
=> 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.
:: (MonadIO m, IsStream t, RMap rs, ReadRec rs, MonadCatch m) | |
=> FilePath | file path |
-> t m (Rec (Maybe :. ElField) rs) | stream of |
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.
:: (MonadIO m, IsStream t, RMap rs, ReadRec rs, MonadCatch m) | |
=> ParserOptions | parsing options |
-> FilePath | file path |
-> t m (Rec (Maybe :. ElField) rs) | stream of |
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.
:: (MonadIO m, IsStream t, RMap rs, ReadRec rs, MonadCatch m) | |
=> FilePath | file path |
-> t m (Rec (Either Text :. ElField) rs) | stream of |
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.
:: (MonadIO m, IsStream t, RMap rs, ReadRec rs, MonadCatch m) | |
=> ParserOptions | parsing options |
-> FilePath | file path |
-> t m (Rec (Either Text :. ElField) rs) | stream of |
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
:: (MonadIO m, IsStream t, RMap rs, ReadRec rs) | |
=> t m Text | stream of |
-> 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.
:: (MonadIO m, IsStream t, RMap rs, ReadRec rs) | |
=> ParserOptions | parsing options |
-> t m Text | stream of |
-> 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.
:: (MonadIO m, IsStream t, RMap rs, ReadRec rs) | |
=> t m Text | stream of |
-> t m (Rec (Maybe :. ElField) rs) | stream of parsed |
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.
:: (MonadIO m, IsStream t, RMap rs, ReadRec rs) | |
=> ParserOptions | parsing options |
-> t m Text | stream of |
-> t m (Rec (Maybe :. ElField) rs) | stream of parsed |
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.
:: (MonadIO m, IsStream t, RMap rs, ReadRec rs) | |
=> t m Text | stream of |
-> t m (Rec (Either Text :. ElField) rs) | stream of parsed |
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.
:: (MonadIO m, IsStream t, RMap rs, ReadRec rs) | |
=> ParserOptions | parsing options |
-> t m Text | stream of |
-> t m (Rec (Either Text :. ElField) rs) | stream of parsed |
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
:: (ColumnHeaders rs, Monad m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t) | |
=> t m (Record rs) | stream of Records |
-> t m Text | stream of |
Given a stream of Records
, for which all fields satisfy the ShowCSV
constraint,
produce a stream of CSV Text
, one item (line) per Record
.
:: (ColumnHeaders rs, Foldable f, Monad m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t) | |
=> f (Record rs) |
|
-> t m Text | stream of |
Given a foldable of Records
, for which all fields satisfy the ShowCSV
constraint,
produce a stream of CSV Text
, one item (line) per Record
.
:: (ColumnHeaders rs, Monad m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t) | |
=> Text | column separator |
-> t m (Record rs) | stream of Records |
-> t m Text | stream of |
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.
:: (ColumnHeaders rs, Foldable f, Monad m, RecordToList rs, RecMapMethod ShowCSV ElField rs, IsStream t) | |
=> Text | column separator |
-> f (Record rs) | foldable of Records |
-> t m Text | stream of |
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.
:: (RecordToList rs, RApply rs, ColumnHeaders rs, IsStream t, Monad 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 |
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
:: (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod ShowCSV ElField rs, MonadAsync m, Foldable f) | |
=> FilePath | file path |
-> f (Record rs) |
|
-> m () |
write a foldable of Records
to a file, one line per Record
.
Use the ShowCSV
class to format each field to Text
:: (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
:: (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
:: (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod Show ElField rs, MonadAsync m, Foldable f) | |
=> FilePath | file path |
-> f (Record rs) |
|
-> m () |
write a foldable of Records
to a file, one line per Record
.
Use the Show
class to format each field to Text
:: (ColumnHeaders rs, MonadCatch m, RecordToList rs, RecMapMethod Show ElField rs, MonadAsync m, Foldable f) | |
=> Text | column separator |
-> FilePath | file path |
-> f (Record rs) |
|
-> m () |
write a foldable of Records
to a file, one line per Record
.
Use the Show
class to format each field to Text
:: (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
:: KnownField t | |
=> (Snd t -> Text) | formatting function for the type in Field |
-> 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
:: (Functor f, KnownField t) | |
=> (f (Snd t) -> Text) | formatting function for things like |
-> 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.