| Copyright | (c) Marcin Mrotek 2015 |
|---|---|
| License | BSD3 |
| Maintainer | marcin.jan.mrotek@gmail.com |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Pipes.KeyValueCsv.Internal.KeyValue
Description
- drawCell :: Monad m => StateT (Cells m r) m (Maybe Text)
- missing :: forall (f :: k -> *) (rs :: [k]). Record rs => Rec (WithKeyValueError :. f) rs
- parseKeyValue :: forall (m :: * -> *) (f :: k -> *) (rs :: [k]) (r :: *). (Given Delimiter, Monad m, Record rs) => Rec (CellParser m f) rs -> Rec (Const Text) rs -> Set Text -> Line m r -> Producer (Rec (WithKeyValueError :. f) rs) m r
- fromKeyValues :: forall (m :: * -> *) (f :: k -> *) (rs :: [k]) (x :: *). Monad m => (Text, Producer Text m x) -> Rec (CellParser m f) rs -> Rec (Const Text) rs -> Rec (WithKeyValueError :. f) rs -> m (Rec (WithKeyValueError :. f) rs, x)
- class Record k (rs :: [k])
Documentation
drawCell :: Monad m => StateT (Cells m r) m (Maybe Text) Source #
Draw a single cell from a FreeT-delimited stream.
missing :: forall (f :: k -> *) (rs :: [k]). Record rs => Rec (WithKeyValueError :. f) rs Source #
An empty record filled with Failure MissingValue.
Arguments
| :: forall (m :: * -> *) (f :: k -> *) (rs :: [k]) (r :: *). (Given Delimiter, Monad m, Record rs) | |
| => Rec (CellParser m f) rs | Parser record. |
| -> Rec (Const Text) rs | Key name record. |
| -> Set Text | Name set. |
| -> Line m r | Line to parse. |
| -> Producer (Rec (WithKeyValueError :. f) rs) m r |
Parse a single line into an one-shot producer of records with at most one Success field.
Arguments
| :: forall (m :: * -> *) (f :: k -> *) (rs :: [k]) (x :: *). Monad m | |
| => (Text, Producer Text m x) | Key-value pair. |
| -> Rec (CellParser m f) rs | Parser record. |
| -> Rec (Const Text) rs | Key name record. |
| -> Rec (WithKeyValueError :. f) rs | Current parsing result. |
| -> m (Rec (WithKeyValueError :. f) rs, x) |
Parse a key-value pair into a record with at most one Success field.