{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE ScopedTypeVariables   #-}

{- |
   Module      : Streaming.Cassava
   Description : Cassava support for the streaming library
   Copyright   : (c) Ivan Lazar Miljenovic
   License     : MIT
   Maintainer  : Ivan.Miljenovic@gmail.com

   Stream CSV data in\/out using
   [Cassava](http://hackage.haskell.org/package/cassava).

   A common use-case is to stream CSV-encoded data in from a file.
   You may be tempted to use 'B.readFile' from
   "Data.ByteString.Streaming" to obtain the file contents, but if you
   do you're likely to run into exceptions such as:

   > hGetBufSome: illegal operation (handle is closed)

   One solution is to use the
   [streaming-with](https://hackage.haskell.org/package/streaming-with)
   package for the IO aspects.  You can then write something like:

   @
     withBinaryFileContents \"myFile.csv\" $
       doSomethingWithStreamingCSV
       . 'decodeByName'
   @

 -}
module Streaming.Cassava
  ( -- * Decoding
    decode
  , decodeWith
  , decodeWithErrors
  , CsvParseException (..)
    -- ** Named decoding
  , decodeByName
  , decodeByNameWith
  , decodeByNameWithErrors
    -- * Encoding
  , encode
  , encodeDefault
  , encodeWith
    -- ** Named encoding
  , encodeByName
  , encodeByNameDefault
  , encodeByNameWith
    -- * Re-exports
  , 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           Streaming                     (Of, Stream)
import           Streaming.ByteString          (ByteStream)
import qualified Streaming.ByteString          as B
import qualified Streaming.ByteString.Internal as B
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)

--------------------------------------------------------------------------------

-- | Use 'defaultOptions' for decoding the provided CSV.
decode :: (MonadError CsvParseException m, FromRecord a)
          => HasHeader -> ByteStream m r
          -> Stream (Of a) m r
decode :: HasHeader -> ByteStream m r -> Stream (Of a) m r
decode = DecodeOptions -> HasHeader -> ByteStream m r -> Stream (Of a) m r
forall (m :: * -> *) a r.
(MonadError CsvParseException m, FromRecord a) =>
DecodeOptions -> HasHeader -> ByteStream m r -> Stream (Of a) m r
decodeWith DecodeOptions
defaultDecodeOptions

-- | Return back a stream of values from the provided CSV, stopping at
--   the first error.
--
--   If you wish to instead ignore errors, consider using
--   'decodeWithErrors' with either 'S.mapMaybe' or @'S.effects'
--   . 'S.partitionEithers'@.
--
--   Unlike 'decodeWithErrors', any remaining input is discarded.
decodeWith :: (MonadError CsvParseException m, FromRecord a)
              => DecodeOptions -> HasHeader
              -> ByteStream m r -> Stream (Of a) m r
decodeWith :: DecodeOptions -> HasHeader -> ByteStream m r -> Stream (Of a) m r
decodeWith DecodeOptions
opts HasHeader
hdr ByteStream m r
bs = Stream
  (Of (Either CsvParseException a))
  m
  (Either (CsvParseException, ByteStream m r) r)
-> Stream (Of a) m (Either (CsvParseException, ByteStream 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
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream m r) r)
forall (m :: * -> *) a r.
(Monad m, FromRecord a) =>
DecodeOptions
-> HasHeader
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream m r) r)
decodeWithErrors DecodeOptions
opts HasHeader
hdr ByteStream m r
bs)
                         Stream (Of a) m (Either (CsvParseException, ByteStream m r) r)
-> (Either (CsvParseException, ByteStream 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, ByteStream m r) -> Stream (Of a) m r)
-> (r -> Stream (Of a) m r)
-> Either (CsvParseException, ByteStream 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, ByteStream m r) -> CsvParseException)
-> (CsvParseException, ByteStream m r)
-> Stream (Of a) m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CsvParseException, ByteStream 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

-- | Return back a stream with an attempt at type conversion, and
--   either the previous result or any overall parsing errors with the
--   remainder of the input.
--
--   'S.partitionEithers' may be useful when using this function.
decodeWithErrors :: (Monad m, FromRecord a) => DecodeOptions -> HasHeader
                    -> ByteStream m r
                    -> Stream (Of (Either CsvParseException a)) m (Either (CsvParseException, ByteStream m r) r)
decodeWithErrors :: DecodeOptions
-> HasHeader
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream m r) r)
decodeWithErrors DecodeOptions
opts = Parser a
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream m r) r)
forall (m :: * -> *) a r.
Monad m =>
Parser a
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream m r) r)
runParser (Parser a
 -> ByteStream m r
 -> Stream
      (Of (Either CsvParseException a))
      m
      (Either (CsvParseException, ByteStream m r) r))
-> (HasHeader -> Parser a)
-> HasHeader
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream 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 -> ByteStream m r
             -> Stream (Of (Either CsvParseException a)) m (Either (CsvParseException, ByteStream m r) r)
runParser :: Parser a
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream m r) r)
runParser = Parser a
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream 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.unconsChunk 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
        -- This is primarily just to
        -- return the @r@ value, but also
        -- acts as a check on the parser.
        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.unconsChunk 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)

--------------------------------------------------------------------------------

-- | Use 'defaultOptions' for decoding the provided CSV.
decodeByName :: (MonadError CsvParseException m, FromNamedRecord a)
                => ByteStream m r -> Stream (Of a) m r
decodeByName :: ByteStream m r -> Stream (Of a) m r
decodeByName = DecodeOptions -> ByteStream m r -> Stream (Of a) m r
forall (m :: * -> *) a r.
(MonadError CsvParseException m, FromNamedRecord a) =>
DecodeOptions -> ByteStream m r -> Stream (Of a) m r
decodeByNameWith DecodeOptions
defaultDecodeOptions

-- | Return back a stream of values from the provided CSV, stopping at
--   the first error.
--
--   A header is required to determine the order of columns, but then
--   discarded.
--
--   If you wish to instead ignore errors, consider using
--   'decodeByNameWithErrors' with either 'S.mapMaybe' or @'S.effects'
--   . 'S.partitionEithers'@.
--
--   Unlike 'decodeByNameWithErrors', any remaining input is
--   discarded.
decodeByNameWith :: (MonadError CsvParseException m, FromNamedRecord a)
                    => DecodeOptions
                    -> ByteStream m r -> Stream (Of a) m r
decodeByNameWith :: DecodeOptions -> ByteStream m r -> Stream (Of a) m r
decodeByNameWith DecodeOptions
opts ByteStream m r
bs = Stream
  (Of (Either CsvParseException a))
  m
  (Either (CsvParseException, ByteStream m r) r)
-> Stream (Of a) m (Either (CsvParseException, ByteStream 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
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream m r) r)
forall (m :: * -> *) a r.
(Monad m, FromNamedRecord a) =>
DecodeOptions
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream m r) r)
decodeByNameWithErrors DecodeOptions
opts ByteStream m r
bs)
                           Stream (Of a) m (Either (CsvParseException, ByteStream m r) r)
-> (Either (CsvParseException, ByteStream 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, ByteStream m r) -> Stream (Of a) m r)
-> (r -> Stream (Of a) m r)
-> Either (CsvParseException, ByteStream 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, ByteStream m r) -> CsvParseException)
-> (CsvParseException, ByteStream m r)
-> Stream (Of a) m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CsvParseException, ByteStream 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

-- | Return back a stream with an attempt at type conversion, but
--   where the order of columns doesn't have to match the order of
--   fields of your actual type.
--
--   This requires\/assumes a header in the CSV stream, which is
--   discarded after parsing.
--
--   'S.partitionEithers' may be useful when using this function.
decodeByNameWithErrors :: (Monad m, FromNamedRecord a) => DecodeOptions
                          -> ByteStream m r
                          -> Stream (Of (Either CsvParseException a)) m (Either (CsvParseException, ByteStream m r) r)
decodeByNameWithErrors :: DecodeOptions
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream m r) r)
decodeByNameWithErrors = HeaderParser (Parser a)
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream 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)
 -> ByteStream m r
 -> Stream
      (Of (Either CsvParseException a))
      m
      (Either (CsvParseException, ByteStream m r) r))
-> (DecodeOptions -> HeaderParser (Parser a))
-> DecodeOptions
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream 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
-> ByteStream m r
-> Stream
     (Of (Either CsvParseException a))
     m
     (Either (CsvParseException, ByteStream 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.unconsChunk 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 a stream of values with the default options.
--
--   Optionally prefix the stream with headers (the 'header' function
--   may be useful).
encode :: (ToRecord a, Monad m) => Maybe Header
          -> Stream (Of a) m r -> ByteStream m r
encode :: Maybe Header -> Stream (Of a) m r -> ByteStream m r
encode = EncodeOptions
-> Maybe Header -> Stream (Of a) m r -> ByteStream m r
forall a (m :: * -> *) r.
(ToRecord a, Monad m) =>
EncodeOptions
-> Maybe Header -> Stream (Of a) m r -> ByteStream m r
encodeWith EncodeOptions
defaultEncodeOptions

-- | Encode a stream of values with the default options and a derived
--   header prefixed.
encodeDefault :: forall a m r. (ToRecord a, DefaultOrdered a, Monad m)
                 => Stream (Of a) m r -> ByteStream m r
encodeDefault :: Stream (Of a) m r -> ByteStream m r
encodeDefault = Maybe Header -> Stream (Of a) m r -> ByteStream m r
forall a (m :: * -> *) r.
(ToRecord a, Monad m) =>
Maybe Header -> Stream (Of a) m r -> ByteStream 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)))

-- | Encode a stream of values with the provided options.
--
--   Optionally prefix the stream with headers (the 'header' function
--   may be useful).
encodeWith :: (ToRecord a, Monad m) => EncodeOptions -> Maybe Header
              -> Stream (Of a) m r -> ByteStream m r
encodeWith :: EncodeOptions
-> Maybe Header -> Stream (Of a) m r -> ByteStream m r
encodeWith EncodeOptions
opts Maybe Header
mhdr = Stream (Of ByteString) m r -> ByteStream m r
forall (m :: * -> *) r.
Monad m =>
Stream (Of ByteString) m r -> ByteStream m r
B.fromChunks
                       (Stream (Of ByteString) m r -> ByteStream m r)
-> (Stream (Of a) m r -> Stream (Of ByteString) m r)
-> Stream (Of a) m r
-> ByteStream 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

--------------------------------------------------------------------------------

-- | Use the default ordering to encode all fields\/columns.
encodeByNameDefault :: forall a m r. (DefaultOrdered a, ToNamedRecord a, Monad m)
                       => Stream (Of a) m r -> ByteStream m r
encodeByNameDefault :: Stream (Of a) m r -> ByteStream m r
encodeByNameDefault = Header -> Stream (Of a) m r -> ByteStream m r
forall a (m :: * -> *) r.
(ToNamedRecord a, Monad m) =>
Header -> Stream (Of a) m r -> ByteStream m r
encodeByName (a -> Header
forall a. DefaultOrdered a => a -> Header
headerOrder (a
forall a. HasCallStack => a
undefined :: a))

-- | Select the columns that you wish to encode from your data
--   structure using default options (which currently includes
--   printing the header).
encodeByName :: (ToNamedRecord a, Monad m) => Header
                -> Stream (Of a) m r -> ByteStream m r
encodeByName :: Header -> Stream (Of a) m r -> ByteStream m r
encodeByName = EncodeOptions -> Header -> Stream (Of a) m r -> ByteStream m r
forall a (m :: * -> *) r.
(ToNamedRecord a, Monad m) =>
EncodeOptions -> Header -> Stream (Of a) m r -> ByteStream m r
encodeByNameWith EncodeOptions
defaultEncodeOptions

-- | Select the columns that you wish to encode from your data
--   structure.
--
--   Header printing respects 'encIncludeheader'.
encodeByNameWith :: (ToNamedRecord a, Monad m) => EncodeOptions -> Header
                    -> Stream (Of a) m r -> ByteStream m r
encodeByNameWith :: EncodeOptions -> Header -> Stream (Of a) m r -> ByteStream m r
encodeByNameWith EncodeOptions
opts Header
hdr = Stream (Of ByteString) m r -> ByteStream m r
forall (m :: * -> *) r.
Monad m =>
Stream (Of ByteString) m r -> ByteStream m r
B.fromChunks
                            (Stream (Of ByteString) m r -> ByteStream m r)
-> (Stream (Of a) m r -> Stream (Of ByteString) m r)
-> Stream (Of a) m r
-> ByteStream 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