{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Streaming.Cassava
(
decode
, decodeWith
, decodeWithErrors
, CsvParseException (..)
, decodeByName
, decodeByNameWith
, decodeByNameWithErrors
, encode
, encodeDefault
, encodeWith
, encodeByName
, encodeByNameDefault
, encodeByNameWith
, FromRecord (..)
, FromNamedRecord (..)
, ToRecord (..)
, ToNamedRecord (..)
, DefaultOrdered (..)
, HasHeader (..)
, Header
, header
, Name
, DecodeOptions(..)
, defaultDecodeOptions
, EncodeOptions(..)
, defaultEncodeOptions
) where
import qualified Data.ByteString as DB
import qualified Data.ByteString.Lazy as DBL
import Data.ByteString.Streaming (ByteString)
import qualified Data.ByteString.Streaming as B
import qualified Data.ByteString.Streaming.Internal as B
import Streaming (Of, Stream)
import qualified Streaming.Prelude as S
import Data.Csv (DecodeOptions (..),
DefaultOrdered (..),
EncodeOptions (..),
FromNamedRecord (..),
FromRecord (..), Header,
Name, ToNamedRecord (..),
ToRecord (..),
defaultDecodeOptions,
defaultEncodeOptions,
encIncludeHeader, header)
import Data.Csv.Incremental (HasHeader (..),
HeaderParser (..),
Parser (..))
import qualified Data.Csv.Incremental as CI
import Control.Exception (Exception (..))
import Control.Monad.Error.Class (MonadError, throwError)
import Control.Monad.Trans.Class (lift)
import Data.Bifunctor (first)
import Data.String (IsString (..))
import Data.Typeable (Typeable)
decode :: (MonadError CsvParseException m, FromRecord a)
=> HasHeader -> ByteString m r
-> Stream (Of a) m r
decode :: HasHeader -> ByteString m r -> Stream (Of a) m r
decode = DecodeOptions -> HasHeader -> ByteString m r -> Stream (Of a) m r
forall (m :: * -> *) a r.
(MonadError CsvParseException m, FromRecord a) =>
DecodeOptions -> HasHeader -> ByteString m r -> Stream (Of a) m r
decodeWith DecodeOptions
defaultDecodeOptions
decodeWith :: (MonadError CsvParseException m, FromRecord a)
=> DecodeOptions -> HasHeader
-> ByteString m r -> Stream (Of a) m r
decodeWith :: DecodeOptions -> HasHeader -> ByteString m r -> Stream (Of a) m r
decodeWith DecodeOptions
opts HasHeader
hdr ByteString m r
bs = Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
-> Stream (Of a) m (Either (CsvParseException, ByteString m r) r)
forall e (m :: * -> *) a r.
MonadError e m =>
Stream (Of (Either e a)) m r -> Stream (Of a) m r
getValues (DecodeOptions
-> HasHeader
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
forall (m :: * -> *) a r.
(Monad m, FromRecord a) =>
DecodeOptions
-> HasHeader
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
decodeWithErrors DecodeOptions
opts HasHeader
hdr ByteString m r
bs)
Stream (Of a) m (Either (CsvParseException, ByteString m r) r)
-> (Either (CsvParseException, ByteString m r) r
-> Stream (Of a) m r)
-> Stream (Of a) m r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ((CsvParseException, ByteString m r) -> Stream (Of a) m r)
-> (r -> Stream (Of a) m r)
-> Either (CsvParseException, ByteString m r) r
-> Stream (Of a) m r
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (CsvParseException -> Stream (Of a) m r
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (CsvParseException -> Stream (Of a) m r)
-> ((CsvParseException, ByteString m r) -> CsvParseException)
-> (CsvParseException, ByteString m r)
-> Stream (Of a) m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CsvParseException, ByteString m r) -> CsvParseException
forall a b. (a, b) -> a
fst) r -> Stream (Of a) m r
forall (m :: * -> *) a. Monad m => a -> m a
return
decodeWithErrors :: (Monad m, FromRecord a) => DecodeOptions -> HasHeader
-> ByteString m r
-> Stream (Of (Either CsvParseException a)) m (Either (CsvParseException, ByteString m r) r)
decodeWithErrors :: DecodeOptions
-> HasHeader
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
decodeWithErrors DecodeOptions
opts = Parser a
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
forall (m :: * -> *) a r.
Monad m =>
Parser a
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
runParser (Parser a
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r))
-> (HasHeader -> Parser a)
-> HasHeader
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DecodeOptions -> HasHeader -> Parser a
forall a. FromRecord a => DecodeOptions -> HasHeader -> Parser a
CI.decodeWith DecodeOptions
opts
runParser :: (Monad m) => Parser a -> ByteString m r
-> Stream (Of (Either CsvParseException a)) m (Either (CsvParseException, ByteString m r) r)
runParser :: Parser a
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
runParser = Parser a
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
forall c b.
Parser c
-> ByteStream m b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
loop
where
feed :: (ByteString -> Parser c)
-> ByteStream m b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
feed ByteString -> Parser c
f ByteStream m b
str = do
Either b (ByteString, ByteStream m b)
nxt <- m (Either b (ByteString, ByteStream m b))
-> Stream
(Of (Either CsvParseException c))
m
(Either b (ByteString, ByteStream m b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ByteStream m b -> m (Either b (ByteString, ByteStream m b))
forall (m :: * -> *) r.
Monad m =>
ByteStream m r -> m (Either r (ByteString, ByteStream m r))
B.nextChunk ByteStream m b
str)
let g :: ByteString
-> ByteStream m b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
g = Parser c
-> ByteStream m b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
loop (Parser c
-> ByteStream m b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b))
-> (ByteString -> Parser c)
-> ByteString
-> ByteStream m b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Parser c
f
case Either b (ByteString, ByteStream m b)
nxt of
Left b
r -> Either (CsvParseException, ByteStream m b) b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (CsvParseException, ByteStream m b) b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b))
-> Either (CsvParseException, ByteStream m b) b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
forall a b. (a -> b) -> a -> b
$ b -> Either (CsvParseException, ByteStream m b) b
forall a b. b -> Either a b
Right b
r
Right (ByteString
chunk, ByteStream m b
rest) -> ByteString
-> ByteStream m b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
g ByteString
chunk ByteStream m b
rest
loop :: Parser c
-> ByteStream m b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
loop Parser c
p ByteStream m b
str = case Parser c
p of
Fail ByteString
bs String
err -> Either (CsvParseException, ByteStream m b) b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CsvParseException, ByteStream m b)
-> Either (CsvParseException, ByteStream m b) b
forall a b. a -> Either a b
Left (String -> CsvParseException
CsvParseException String
err, ByteString -> ByteStream m b -> ByteStream m b
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
B.consChunk ByteString
bs ByteStream m b
str))
Many [Either String c]
es ByteString -> Parser c
get -> [Either String c] -> Stream (Of (Either CsvParseException c)) m ()
forall c.
[Either String c] -> Stream (Of (Either CsvParseException c)) m ()
withEach [Either String c]
es Stream (Of (Either CsvParseException c)) m ()
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (ByteString -> Parser c)
-> ByteStream m b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
feed ByteString -> Parser c
get ByteStream m b
str
Done [Either String c]
es -> do [Either String c] -> Stream (Of (Either CsvParseException c)) m ()
forall c.
[Either String c] -> Stream (Of (Either CsvParseException c)) m ()
withEach [Either String c]
es
Either b (ByteString, ByteStream m b)
nxt <- m (Either b (ByteString, ByteStream m b))
-> Stream
(Of (Either CsvParseException c))
m
(Either b (ByteString, ByteStream m b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ByteStream m b -> m (Either b (ByteString, ByteStream m b))
forall (m :: * -> *) r.
Monad m =>
ByteStream m r -> m (Either r (ByteString, ByteStream m r))
B.nextChunk ByteStream m b
str)
Either (CsvParseException, ByteStream m b) b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either (CsvParseException, ByteStream m b) b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b))
-> Either (CsvParseException, ByteStream m b) b
-> Stream
(Of (Either CsvParseException c))
m
(Either (CsvParseException, ByteStream m b) b)
forall a b. (a -> b) -> a -> b
$ case Either b (ByteString, ByteStream m b)
nxt of
Left b
r -> b -> Either (CsvParseException, ByteStream m b) b
forall a b. b -> Either a b
Right b
r
Right (ByteString, ByteStream m b)
_ -> (CsvParseException, ByteStream m b)
-> Either (CsvParseException, ByteStream m b) b
forall a b. a -> Either a b
Left (CsvParseException
"Unconsumed input", ByteStream m b
str)
withEach :: [Either String c] -> Stream (Of (Either CsvParseException c)) m ()
withEach = [Either CsvParseException c]
-> Stream (Of (Either CsvParseException c)) m ()
forall (m :: * -> *) (f :: * -> *) a.
(Monad m, Foldable f) =>
f a -> Stream (Of a) m ()
S.each ([Either CsvParseException c]
-> Stream (Of (Either CsvParseException c)) m ())
-> ([Either String c] -> [Either CsvParseException c])
-> [Either String c]
-> Stream (Of (Either CsvParseException c)) m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either String c -> Either CsvParseException c)
-> [Either String c] -> [Either CsvParseException c]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> CsvParseException)
-> Either String c -> Either CsvParseException c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first String -> CsvParseException
CsvParseException)
decodeByName :: (MonadError CsvParseException m, FromNamedRecord a)
=> ByteString m r -> Stream (Of a) m r
decodeByName :: ByteString m r -> Stream (Of a) m r
decodeByName = DecodeOptions -> ByteString m r -> Stream (Of a) m r
forall (m :: * -> *) a r.
(MonadError CsvParseException m, FromNamedRecord a) =>
DecodeOptions -> ByteString m r -> Stream (Of a) m r
decodeByNameWith DecodeOptions
defaultDecodeOptions
decodeByNameWith :: (MonadError CsvParseException m, FromNamedRecord a)
=> DecodeOptions
-> ByteString m r -> Stream (Of a) m r
decodeByNameWith :: DecodeOptions -> ByteString m r -> Stream (Of a) m r
decodeByNameWith DecodeOptions
opts ByteString m r
bs = Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
-> Stream (Of a) m (Either (CsvParseException, ByteString m r) r)
forall e (m :: * -> *) a r.
MonadError e m =>
Stream (Of (Either e a)) m r -> Stream (Of a) m r
getValues (DecodeOptions
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
forall (m :: * -> *) a r.
(Monad m, FromNamedRecord a) =>
DecodeOptions
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
decodeByNameWithErrors DecodeOptions
opts ByteString m r
bs)
Stream (Of a) m (Either (CsvParseException, ByteString m r) r)
-> (Either (CsvParseException, ByteString m r) r
-> Stream (Of a) m r)
-> Stream (Of a) m r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ((CsvParseException, ByteString m r) -> Stream (Of a) m r)
-> (r -> Stream (Of a) m r)
-> Either (CsvParseException, ByteString m r) r
-> Stream (Of a) m r
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (CsvParseException -> Stream (Of a) m r
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (CsvParseException -> Stream (Of a) m r)
-> ((CsvParseException, ByteString m r) -> CsvParseException)
-> (CsvParseException, ByteString m r)
-> Stream (Of a) m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CsvParseException, ByteString m r) -> CsvParseException
forall a b. (a, b) -> a
fst) r -> Stream (Of a) m r
forall (m :: * -> *) a. Monad m => a -> m a
return
decodeByNameWithErrors :: (Monad m, FromNamedRecord a) => DecodeOptions
-> ByteString m r
-> Stream (Of (Either CsvParseException a)) m (Either (CsvParseException, ByteString m r) r)
decodeByNameWithErrors :: DecodeOptions
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
decodeByNameWithErrors = HeaderParser (Parser a)
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
forall (m :: * -> *) a b.
Monad m =>
HeaderParser (Parser a)
-> ByteStream m b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b)
loopH (HeaderParser (Parser a)
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r))
-> (DecodeOptions -> HeaderParser (Parser a))
-> DecodeOptions
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DecodeOptions -> HeaderParser (Parser a)
forall a.
FromNamedRecord a =>
DecodeOptions -> HeaderParser (Parser a)
CI.decodeByNameWith
where
loopH :: HeaderParser (Parser a)
-> ByteStream m b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b)
loopH HeaderParser (Parser a)
ph ByteStream m b
str = case HeaderParser (Parser a)
ph of
FailH ByteString
bs String
err -> Either (CsvParseException, ByteStream m b) b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CsvParseException, ByteStream m b)
-> Either (CsvParseException, ByteStream m b) b
forall a b. a -> Either a b
Left (String -> CsvParseException
CsvParseException String
err, ByteString -> ByteStream m b -> ByteStream m b
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
B.consChunk ByteString
bs ByteStream m b
str))
PartialH ByteString -> HeaderParser (Parser a)
get -> (ByteString -> HeaderParser (Parser a))
-> ByteStream m b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b)
feedH ByteString -> HeaderParser (Parser a)
get ByteStream m b
str
DoneH Header
_ Parser a
p -> Parser a
-> ByteStream m b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b)
forall (m :: * -> *) a r.
Monad m =>
Parser a
-> ByteString m r
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteString m r) r)
runParser Parser a
p ByteStream m b
str
feedH :: (ByteString -> HeaderParser (Parser a))
-> ByteStream m b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b)
feedH ByteString -> HeaderParser (Parser a)
f ByteStream m b
str = do
Either b (ByteString, ByteStream m b)
nxt <- m (Either b (ByteString, ByteStream m b))
-> Stream
(Of (Either CsvParseException a))
m
(Either b (ByteString, ByteStream m b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ByteStream m b -> m (Either b (ByteString, ByteStream m b))
forall (m :: * -> *) r.
Monad m =>
ByteStream m r -> m (Either r (ByteString, ByteStream m r))
B.nextChunk ByteStream m b
str)
let g :: ByteString
-> ByteStream m b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b)
g = HeaderParser (Parser a)
-> ByteStream m b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b)
loopH (HeaderParser (Parser a)
-> ByteStream m b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b))
-> (ByteString -> HeaderParser (Parser a))
-> ByteString
-> ByteStream m b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> HeaderParser (Parser a)
f
case Either b (ByteString, ByteStream m b)
nxt of
Left b
r -> Either (CsvParseException, ByteStream m b) b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (CsvParseException, ByteStream m b) b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b))
-> Either (CsvParseException, ByteStream m b) b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b)
forall a b. (a -> b) -> a -> b
$ b -> Either (CsvParseException, ByteStream m b) b
forall a b. b -> Either a b
Right b
r
Right (ByteString
chunk, ByteStream m b
rest) -> ByteString
-> ByteStream m b
-> Stream
(Of (Either CsvParseException a))
m
(Either (CsvParseException, ByteStream m b) b)
g ByteString
chunk ByteStream m b
rest
encode :: (ToRecord a, Monad m) => Maybe Header
-> Stream (Of a) m r -> ByteString m r
encode :: Maybe Header -> Stream (Of a) m r -> ByteString m r
encode = EncodeOptions
-> Maybe Header -> Stream (Of a) m r -> ByteString m r
forall a (m :: * -> *) r.
(ToRecord a, Monad m) =>
EncodeOptions
-> Maybe Header -> Stream (Of a) m r -> ByteString m r
encodeWith EncodeOptions
defaultEncodeOptions
encodeDefault :: forall a m r. (ToRecord a, DefaultOrdered a, Monad m)
=> Stream (Of a) m r -> ByteString m r
encodeDefault :: Stream (Of a) m r -> ByteString m r
encodeDefault = Maybe Header -> Stream (Of a) m r -> ByteString m r
forall a (m :: * -> *) r.
(ToRecord a, Monad m) =>
Maybe Header -> Stream (Of a) m r -> ByteString m r
encode (Header -> Maybe Header
forall a. a -> Maybe a
Just (a -> Header
forall a. DefaultOrdered a => a -> Header
headerOrder (a
forall a. HasCallStack => a
undefined :: a)))
encodeWith :: (ToRecord a, Monad m) => EncodeOptions -> Maybe Header
-> Stream (Of a) m r -> ByteString m r
encodeWith :: EncodeOptions
-> Maybe Header -> Stream (Of a) m r -> ByteString m r
encodeWith EncodeOptions
opts Maybe Header
mhdr = Stream (Of ByteString) m r -> ByteString m r
forall (m :: * -> *) r.
Monad m =>
Stream (Of ByteString) m r -> ByteStream m r
B.fromChunks
(Stream (Of ByteString) m r -> ByteString m r)
-> (Stream (Of a) m r -> Stream (Of ByteString) m r)
-> Stream (Of a) m r
-> ByteString m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stream (Of [ByteString]) m r -> Stream (Of ByteString) m r
forall (m :: * -> *) (f :: * -> *) a r.
(Monad m, Foldable f) =>
Stream (Of (f a)) m r -> Stream (Of a) m r
S.concat
(Stream (Of [ByteString]) m r -> Stream (Of ByteString) m r)
-> (Stream (Of a) m r -> Stream (Of [ByteString]) m r)
-> Stream (Of a) m r
-> Stream (Of ByteString) m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r
forall r.
Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r
addHeaders
(Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r)
-> (Stream (Of a) m r -> Stream (Of [ByteString]) m r)
-> Stream (Of a) m r
-> Stream (Of [ByteString]) m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> [ByteString])
-> Stream (Of a) m r -> Stream (Of [ByteString]) m r
forall (m :: * -> *) a b r.
Monad m =>
(a -> b) -> Stream (Of a) m r -> Stream (Of b) m r
S.map a -> [ByteString]
forall v. ToRecord v => v -> [ByteString]
enc
where
addHeaders :: Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r
addHeaders = (Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r)
-> (Header
-> Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r)
-> Maybe Header
-> Stream (Of [ByteString]) m r
-> Stream (Of [ByteString]) m r
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r
forall a. a -> a
id ([ByteString]
-> Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r
forall (m :: * -> *) a r.
Monad m =>
a -> Stream (Of a) m r -> Stream (Of a) m r
S.cons ([ByteString]
-> Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r)
-> (Header -> [ByteString])
-> Header
-> Stream (Of [ByteString]) m r
-> Stream (Of [ByteString]) m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Header -> [ByteString]
forall v. ToRecord v => v -> [ByteString]
enc) Maybe Header
mhdr
enc :: (ToRecord v) => v -> [DB.ByteString]
enc :: v -> [ByteString]
enc = ByteString -> [ByteString]
DBL.toChunks (ByteString -> [ByteString])
-> (v -> ByteString) -> v -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EncodeOptions -> Builder v -> ByteString
forall a. ToRecord a => EncodeOptions -> Builder a -> ByteString
CI.encodeWith EncodeOptions
opts (Builder v -> ByteString) -> (v -> Builder v) -> v -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> Builder v
forall a. ToRecord a => a -> Builder a
CI.encodeRecord
encodeByNameDefault :: forall a m r. (DefaultOrdered a, ToNamedRecord a, Monad m)
=> Stream (Of a) m r -> ByteString m r
encodeByNameDefault :: Stream (Of a) m r -> ByteString m r
encodeByNameDefault = Header -> Stream (Of a) m r -> ByteString m r
forall a (m :: * -> *) r.
(ToNamedRecord a, Monad m) =>
Header -> Stream (Of a) m r -> ByteString m r
encodeByName (a -> Header
forall a. DefaultOrdered a => a -> Header
headerOrder (a
forall a. HasCallStack => a
undefined :: a))
encodeByName :: (ToNamedRecord a, Monad m) => Header
-> Stream (Of a) m r -> ByteString m r
encodeByName :: Header -> Stream (Of a) m r -> ByteString m r
encodeByName = EncodeOptions -> Header -> Stream (Of a) m r -> ByteString m r
forall a (m :: * -> *) r.
(ToNamedRecord a, Monad m) =>
EncodeOptions -> Header -> Stream (Of a) m r -> ByteString m r
encodeByNameWith EncodeOptions
defaultEncodeOptions
encodeByNameWith :: (ToNamedRecord a, Monad m) => EncodeOptions -> Header
-> Stream (Of a) m r -> ByteString m r
encodeByNameWith :: EncodeOptions -> Header -> Stream (Of a) m r -> ByteString m r
encodeByNameWith EncodeOptions
opts Header
hdr = Stream (Of ByteString) m r -> ByteString m r
forall (m :: * -> *) r.
Monad m =>
Stream (Of ByteString) m r -> ByteStream m r
B.fromChunks
(Stream (Of ByteString) m r -> ByteString m r)
-> (Stream (Of a) m r -> Stream (Of ByteString) m r)
-> Stream (Of a) m r
-> ByteString m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stream (Of [ByteString]) m r -> Stream (Of ByteString) m r
forall (m :: * -> *) (f :: * -> *) a r.
(Monad m, Foldable f) =>
Stream (Of (f a)) m r -> Stream (Of a) m r
S.concat
(Stream (Of [ByteString]) m r -> Stream (Of ByteString) m r)
-> (Stream (Of a) m r -> Stream (Of [ByteString]) m r)
-> Stream (Of a) m r
-> Stream (Of ByteString) m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r
forall r.
Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r
addHeaders
(Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r)
-> (Stream (Of a) m r -> Stream (Of [ByteString]) m r)
-> Stream (Of a) m r
-> Stream (Of [ByteString]) m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> [ByteString])
-> Stream (Of a) m r -> Stream (Of [ByteString]) m r
forall (m :: * -> *) a b r.
Monad m =>
(a -> b) -> Stream (Of a) m r -> Stream (Of b) m r
S.map a -> [ByteString]
enc
where
opts' :: EncodeOptions
opts' = EncodeOptions
opts { encIncludeHeader :: Bool
encIncludeHeader = Bool
False }
addHeaders :: Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r
addHeaders
| EncodeOptions -> Bool
encIncludeHeader EncodeOptions
opts = [ByteString]
-> Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r
forall (m :: * -> *) a r.
Monad m =>
a -> Stream (Of a) m r -> Stream (Of a) m r
S.cons ([ByteString]
-> Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r)
-> (Header -> [ByteString])
-> Header
-> Stream (Of [ByteString]) m r
-> Stream (Of [ByteString]) m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
DBL.toChunks
(ByteString -> [ByteString])
-> (Header -> ByteString) -> Header -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EncodeOptions -> Builder Header -> ByteString
forall a. ToRecord a => EncodeOptions -> Builder a -> ByteString
CI.encodeWith EncodeOptions
opts' (Builder Header -> ByteString)
-> (Header -> Builder Header) -> Header -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Header -> Builder Header
forall a. ToRecord a => a -> Builder a
CI.encodeRecord (Header
-> Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r)
-> Header
-> Stream (Of [ByteString]) m r
-> Stream (Of [ByteString]) m r
forall a b. (a -> b) -> a -> b
$ Header
hdr
| Bool
otherwise = Stream (Of [ByteString]) m r -> Stream (Of [ByteString]) m r
forall a. a -> a
id
enc :: a -> [ByteString]
enc = ByteString -> [ByteString]
DBL.toChunks (ByteString -> [ByteString])
-> (a -> ByteString) -> a -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EncodeOptions -> Header -> NamedBuilder a -> ByteString
forall a.
ToNamedRecord a =>
EncodeOptions -> Header -> NamedBuilder a -> ByteString
CI.encodeByNameWith EncodeOptions
opts' Header
hdr (NamedBuilder a -> ByteString)
-> (a -> NamedBuilder a) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> NamedBuilder a
forall a. ToNamedRecord a => a -> NamedBuilder a
CI.encodeNamedRecord
getValues :: (MonadError e m) => Stream (Of (Either e a)) m r -> Stream (Of a) m r
getValues :: Stream (Of (Either e a)) m r -> Stream (Of a) m r
getValues = (Either e a -> m a)
-> Stream (Of (Either e a)) m r -> Stream (Of a) m r
forall (m :: * -> *) a b r.
Monad m =>
(a -> m b) -> Stream (Of a) m r -> Stream (Of b) m r
S.mapM ((e -> m a) -> (a -> m a) -> Either e a -> m a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either e -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return)
newtype CsvParseException = CsvParseException String
deriving (CsvParseException -> CsvParseException -> Bool
(CsvParseException -> CsvParseException -> Bool)
-> (CsvParseException -> CsvParseException -> Bool)
-> Eq CsvParseException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CsvParseException -> CsvParseException -> Bool
$c/= :: CsvParseException -> CsvParseException -> Bool
== :: CsvParseException -> CsvParseException -> Bool
$c== :: CsvParseException -> CsvParseException -> Bool
Eq, Int -> CsvParseException -> ShowS
[CsvParseException] -> ShowS
CsvParseException -> String
(Int -> CsvParseException -> ShowS)
-> (CsvParseException -> String)
-> ([CsvParseException] -> ShowS)
-> Show CsvParseException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CsvParseException] -> ShowS
$cshowList :: [CsvParseException] -> ShowS
show :: CsvParseException -> String
$cshow :: CsvParseException -> String
showsPrec :: Int -> CsvParseException -> ShowS
$cshowsPrec :: Int -> CsvParseException -> ShowS
Show, Typeable)
instance IsString CsvParseException where
fromString :: String -> CsvParseException
fromString = String -> CsvParseException
CsvParseException
instance Exception CsvParseException where
displayException :: CsvParseException -> String
displayException (CsvParseException String
e) = String
"Error parsing csv: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
e