| Copyright | (c) Marcin Mrotek 2015 |
|---|---|
| License | BSD3 |
| Maintainer | marcin.jan.mrotek@gmail.com |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Pipes.KeyValueCsv
Contents
Description
Parse CSV files with key-value headers.
- breakLines :: Monad m => (Text -> Bool) -> Lines m r -> Lines m (Lines m r)
- parseKeyValueCsv :: forall (m :: * -> *) (f :: k -> *) (g :: j -> *) (hs :: [k]) (rs :: [j]) (r :: *). (Monad m, Record hs) => Options m f g hs rs -> Producer Text m r -> m (Rec (WithKeyValueError :. f) hs, Producer (Rec (WithCsvError :. g) rs) m r)
- module Pipes.KeyValueCsv.Csv
- module Pipes.KeyValueCsv.KeyValue
- module Pipes.KeyValueCsv.Types
- class Record k (rs :: [k]) where
- data Validation e a
Documentation
breakLines :: Monad m => (Text -> Bool) -> Lines m r -> Lines m (Lines m r) Source #
Break a stream of lines into two parts, on a line that satisfies the given predicate.
All input lines up to the breaking one will be fully read, and each (not including the breaking one) will be re-yielded.
parseKeyValueCsv :: forall (m :: * -> *) (f :: k -> *) (g :: j -> *) (hs :: [k]) (rs :: [j]) (r :: *). (Monad m, Record hs) => Options m f g hs rs -> Producer Text m r -> m (Rec (WithKeyValueError :. f) hs, Producer (Rec (WithCsvError :. g) rs) m r) Source #
Read a CSV file preceded by key-value pairs.
module Pipes.KeyValueCsv.Csv
module Pipes.KeyValueCsv.KeyValue
module Pipes.KeyValueCsv.Types
class Record k (rs :: [k]) where #
Create a dummy record parametrized by Proxy. The class is named Record to signify that every possible type list is its instance.
Minimal complete definition
Methods
proxyRecord :: Rec k (Proxy k) rs #
Re-exports
data Validation e a Source #
Instances
| Bitraversable Validation Source # | |
| Bifoldable Validation Source # | |
| Bifunctor Validation Source # | |
| Swapped Validation Source # | |
| Functor (Validation e) Source # | |
| Semigroup e => Applicative (Validation e) Source # | |
| Foldable (Validation e) Source # | |
| Traversable (Validation e) Source # | |
| (Monoid e, Semigroup e) => Alternative (Validation e) Source # | |
| Alt (Validation e) Source # | |
| Semigroup e => Apply (Validation e) Source # | |
| (Eq e, Eq a) => Eq (Validation e a) Source # | |
| (Data a, Data e) => Data (Validation e a) Source # | |
| (Ord e, Ord a) => Ord (Validation e a) Source # | |
| (Show e, Show a) => Show (Validation e a) Source # | |
| Generic (Validation e a) Source # | |
| Semigroup e => Semigroup (Validation e a) Source # | |
| Monoid e => Monoid (Validation e a) Source # | |
| type Rep (Validation e a) Source # | |