{-# LANGUAGE BangPatterns, CPP, DeriveFunctor, ScopedTypeVariables #-}
module Data.Csv.Incremental
    (
    
      HeaderParser(..)
    , decodeHeader
    , decodeHeaderWith
    
    , Parser(..)
    
    
    , HasHeader(..)
    , decode
    , decodeWith
    , decodeWithP
    
    
    , decodeByName
    , decodeByNameWith
    , decodeByNameWithP
    
    
    
    , encode
    , encodeWith
    , encodeRecord
    , Builder
    
    
    , encodeByName
    , encodeDefaultOrderedByName
    , encodeByNameWith
    , encodeDefaultOrderedByNameWith
    , encodeNamedRecord
    , NamedBuilder
    ) where
import Control.Applicative ((<|>))
import qualified Data.Attoparsec.ByteString as A
import Data.Attoparsec.ByteString.Char8 (endOfInput)
import qualified Data.ByteString as B
import qualified Data.ByteString.Builder as Builder
import qualified Data.ByteString.Lazy as L
import Data.Semigroup as Semi (Semigroup, (<>))
import qualified Data.Vector as V
import Data.Word (Word8)
import Data.Csv.Conversion hiding (Parser, header, namedRecord, record,
                                   toNamedRecord)
import qualified Data.Csv.Conversion as Conversion
import qualified Data.Csv.Encoding as Encoding
import Data.Csv.Encoding (EncodeOptions(..), Quoting(..), recordSep)
import Data.Csv.Parser
import Data.Csv.Types
import Data.Csv.Util (endOfLine)
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid (Monoid(mappend, mempty))
import Control.Applicative ((<*))
#endif
data  a =
      
      
      
      FailH !B.ByteString String
      
      
      
      
      
    | PartialH (B.ByteString -> HeaderParser a)
      
    | DoneH !Header a
    deriving forall a b. a -> HeaderParser b -> HeaderParser a
forall a b. (a -> b) -> HeaderParser a -> HeaderParser b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> HeaderParser b -> HeaderParser a
$c<$ :: forall a b. a -> HeaderParser b -> HeaderParser a
fmap :: forall a b. (a -> b) -> HeaderParser a -> HeaderParser b
$cfmap :: forall a b. (a -> b) -> HeaderParser a -> HeaderParser b
Functor
instance Show a => Show (HeaderParser a) where
    showsPrec :: Int -> HeaderParser a -> ShowS
showsPrec Int
d (FailH ByteString
rest String
msg) = Bool -> ShowS -> ShowS
showParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
appPrec) ShowS
showStr
      where
        showStr :: ShowS
showStr = String -> ShowS
showString String
"FailH " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec (Int
appPrecforall a. Num a => a -> a -> a
+Int
1) ByteString
rest forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  String -> ShowS
showString String
" " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec (Int
appPrecforall a. Num a => a -> a -> a
+Int
1) String
msg
    showsPrec Int
_ (PartialH ByteString -> HeaderParser a
_) = String -> ShowS
showString String
"PartialH <function>"
    showsPrec Int
d (DoneH Header
hdr a
x) = Bool -> ShowS -> ShowS
showParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
appPrec) ShowS
showStr
      where
        showStr :: ShowS
showStr = String -> ShowS
showString String
"DoneH " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec (Int
appPrecforall a. Num a => a -> a -> a
+Int
1) Header
hdr forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  String -> ShowS
showString String
" " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec (Int
appPrecforall a. Num a => a -> a -> a
+Int
1) a
x
appPrec :: Int
appPrec :: Int
appPrec = Int
10
decodeHeader :: HeaderParser B.ByteString
 = DecodeOptions -> HeaderParser ByteString
decodeHeaderWith DecodeOptions
defaultDecodeOptions
decodeHeaderWith :: DecodeOptions -> HeaderParser B.ByteString
 !DecodeOptions
opts = forall a. (ByteString -> HeaderParser a) -> HeaderParser a
PartialH (IResult ByteString Header -> HeaderParser ByteString
go forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> IResult ByteString Header
parser)
  where
    parser :: ByteString -> IResult ByteString Header
parser = forall a. Parser a -> ByteString -> Result a
A.parse (Word8 -> Parser Header
header forall a b. (a -> b) -> a -> b
$ DecodeOptions -> Word8
decDelimiter DecodeOptions
opts)
    go :: IResult ByteString Header -> HeaderParser ByteString
go (A.Fail ByteString
rest [String]
_ String
msg) = forall a. ByteString -> String -> HeaderParser a
FailH ByteString
rest String
err
      where err :: String
err = String
"parse error (" forall a. [a] -> [a] -> [a]
++ String
msg forall a. [a] -> [a] -> [a]
++ String
")"
    
    
    go (A.Partial ByteString -> IResult ByteString Header
k)       = forall a. (ByteString -> HeaderParser a) -> HeaderParser a
PartialH forall a b. (a -> b) -> a -> b
$ \ ByteString
s -> IResult ByteString Header -> HeaderParser ByteString
go (ByteString -> IResult ByteString Header
k ByteString
s)
    go (A.Done ByteString
rest Header
r)     = forall a. Header -> a -> HeaderParser a
DoneH Header
r ByteString
rest
data Parser a =
      
      
      
      Fail !B.ByteString String
      
      
      
      
      
      
      
    | Many [Either String a] (B.ByteString -> Parser a)
      
      
      
    | Done [Either String a]
    deriving forall a b. a -> Parser b -> Parser a
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Parser b -> Parser a
$c<$ :: forall a b. a -> Parser b -> Parser a
fmap :: forall a b. (a -> b) -> Parser a -> Parser b
$cfmap :: forall a b. (a -> b) -> Parser a -> Parser b
Functor
instance Show a => Show (Parser a) where
    showsPrec :: Int -> Parser a -> ShowS
showsPrec Int
d (Fail ByteString
rest String
msg) = Bool -> ShowS -> ShowS
showParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
appPrec) ShowS
showStr
      where
        showStr :: ShowS
showStr = String -> ShowS
showString String
"Fail " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec (Int
appPrecforall a. Num a => a -> a -> a
+Int
1) ByteString
rest forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  String -> ShowS
showString String
" " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec (Int
appPrecforall a. Num a => a -> a -> a
+Int
1) String
msg
    showsPrec Int
d (Many [Either String a]
rs ByteString -> Parser a
_) = Bool -> ShowS -> ShowS
showParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
appPrec) ShowS
showStr
      where
        showStr :: ShowS
showStr = String -> ShowS
showString String
"Many " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec (Int
appPrecforall a. Num a => a -> a -> a
+Int
1) [Either String a]
rs forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  String -> ShowS
showString String
" <function>"
    showsPrec Int
d (Done [Either String a]
rs) = Bool -> ShowS -> ShowS
showParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
appPrec) ShowS
showStr
      where
        showStr :: ShowS
showStr = String -> ShowS
showString String
"Done " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec (Int
appPrecforall a. Num a => a -> a -> a
+Int
1) [Either String a]
rs
data More = Incomplete | Complete
          deriving (More -> More -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: More -> More -> Bool
$c/= :: More -> More -> Bool
== :: More -> More -> Bool
$c== :: More -> More -> Bool
Eq, Int -> More -> ShowS
[More] -> ShowS
More -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [More] -> ShowS
$cshowList :: [More] -> ShowS
show :: More -> String
$cshow :: More -> String
showsPrec :: Int -> More -> ShowS
$cshowsPrec :: Int -> More -> ShowS
Show)
decode :: FromRecord a
       => HasHeader     
                        
       -> Parser a
decode :: forall a. FromRecord a => HasHeader -> Parser a
decode = forall a. FromRecord a => DecodeOptions -> HasHeader -> Parser a
decodeWith DecodeOptions
defaultDecodeOptions
decodeWith :: FromRecord a
           => DecodeOptions  
           -> HasHeader      
                             
           -> Parser a
decodeWith :: forall a. FromRecord a => DecodeOptions -> HasHeader -> Parser a
decodeWith !DecodeOptions
opts HasHeader
hasHeader = forall a.
(Header -> Parser a) -> DecodeOptions -> HasHeader -> Parser a
decodeWithP forall a. FromRecord a => Header -> Parser a
parseRecord DecodeOptions
opts HasHeader
hasHeader
decodeWithP :: (Record -> Conversion.Parser a)
            -> DecodeOptions  
            -> HasHeader      
                             
            -> Parser a
decodeWithP :: forall a.
(Header -> Parser a) -> DecodeOptions -> HasHeader -> Parser a
decodeWithP Header -> Parser a
p !DecodeOptions
opts HasHeader
hasHeader = case HasHeader
hasHeader of
    HasHeader
HasHeader -> HeaderParser ByteString -> Parser a
go (DecodeOptions -> HeaderParser ByteString
decodeHeaderWith DecodeOptions
opts)
    HasHeader
NoHeader  -> forall a. [Either String a] -> (ByteString -> Parser a) -> Parser a
Many [] forall a b. (a -> b) -> a -> b
$ \ ByteString
s -> forall a.
(Header -> Parser a) -> DecodeOptions -> ByteString -> Parser a
decodeWithP' Header -> Parser a
p DecodeOptions
opts ByteString
s
  where go :: HeaderParser ByteString -> Parser a
go (FailH ByteString
rest String
msg) = forall a. ByteString -> String -> Parser a
Fail ByteString
rest String
msg
        go (PartialH ByteString -> HeaderParser ByteString
k)     = forall a. [Either String a] -> (ByteString -> Parser a) -> Parser a
Many [] forall a b. (a -> b) -> a -> b
$ \ ByteString
s' -> HeaderParser ByteString -> Parser a
go (ByteString -> HeaderParser ByteString
k ByteString
s')
        go (DoneH Header
_ ByteString
rest)   = forall a.
(Header -> Parser a) -> DecodeOptions -> ByteString -> Parser a
decodeWithP' Header -> Parser a
p DecodeOptions
opts ByteString
rest
decodeByName :: FromNamedRecord a
             => HeaderParser (Parser a)
decodeByName :: forall a. FromNamedRecord a => HeaderParser (Parser a)
decodeByName = forall a.
FromNamedRecord a =>
DecodeOptions -> HeaderParser (Parser a)
decodeByNameWith DecodeOptions
defaultDecodeOptions
decodeByNameWith :: FromNamedRecord a
                 => DecodeOptions  
                 -> HeaderParser (Parser a)
decodeByNameWith :: forall a.
FromNamedRecord a =>
DecodeOptions -> HeaderParser (Parser a)
decodeByNameWith !DecodeOptions
opts = forall a.
(NamedRecord -> Parser a)
-> DecodeOptions -> HeaderParser (Parser a)
decodeByNameWithP forall a. FromNamedRecord a => NamedRecord -> Parser a
parseNamedRecord DecodeOptions
opts
decodeByNameWithP :: (NamedRecord -> Conversion.Parser a)
                  -> DecodeOptions  
                  -> HeaderParser (Parser a)
decodeByNameWithP :: forall a.
(NamedRecord -> Parser a)
-> DecodeOptions -> HeaderParser (Parser a)
decodeByNameWithP NamedRecord -> Parser a
p !DecodeOptions
opts = HeaderParser ByteString -> HeaderParser (Parser a)
go (DecodeOptions -> HeaderParser ByteString
decodeHeaderWith DecodeOptions
opts)
  where
    go :: HeaderParser ByteString -> HeaderParser (Parser a)
go (FailH ByteString
rest String
msg) = forall a. ByteString -> String -> HeaderParser a
FailH ByteString
rest String
msg
    go (PartialH ByteString -> HeaderParser ByteString
k)     = forall a. (ByteString -> HeaderParser a) -> HeaderParser a
PartialH forall a b. (a -> b) -> a -> b
$ \ ByteString
s -> HeaderParser ByteString -> HeaderParser (Parser a)
go (ByteString -> HeaderParser ByteString
k ByteString
s)
    go (DoneH Header
hdr ByteString
rest) =
        forall a. Header -> a -> HeaderParser a
DoneH Header
hdr (forall a.
(Header -> Parser a) -> DecodeOptions -> ByteString -> Parser a
decodeWithP' (NamedRecord -> Parser a
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. Header -> Header -> NamedRecord
toNamedRecord Header
hdr) DecodeOptions
opts ByteString
rest)
decodeWithP' :: (Record -> Conversion.Parser a) -> DecodeOptions -> B.ByteString
            -> Parser a
decodeWithP' :: forall a.
(Header -> Parser a) -> DecodeOptions -> ByteString -> Parser a
decodeWithP' Header -> Parser a
p !DecodeOptions
opts = More -> [Either String a] -> IResult ByteString Header -> Parser a
go More
Incomplete [] forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> IResult ByteString Header
parser
  where
    go :: More -> [Either String a] -> IResult ByteString Header -> Parser a
go !More
_ ![Either String a]
acc (A.Fail ByteString
rest [String]
_ String
msg)
        | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Either String a]
acc  = forall a. ByteString -> String -> Parser a
Fail ByteString
rest String
err
        | Bool
otherwise = forall a. [Either String a] -> (ByteString -> Parser a) -> Parser a
Many (forall a. [a] -> [a]
reverse [Either String a]
acc) (\ ByteString
s -> forall a. ByteString -> String -> Parser a
Fail (ByteString
rest ByteString -> ByteString -> ByteString
`B.append` ByteString
s) String
err)
      where err :: String
err = String
"parse error (" forall a. [a] -> [a] -> [a]
++ String
msg forall a. [a] -> [a] -> [a]
++ String
")"
    go More
Incomplete [Either String a]
acc (A.Partial ByteString -> IResult ByteString Header
k) = forall a. [Either String a] -> (ByteString -> Parser a) -> Parser a
Many (forall a. [a] -> [a]
reverse [Either String a]
acc) ByteString -> Parser a
cont
      where cont :: ByteString -> Parser a
cont ByteString
s = More -> [Either String a] -> IResult ByteString Header -> Parser a
go More
m [] (ByteString -> IResult ByteString Header
k ByteString
s)
              where m :: More
m | ByteString -> Bool
B.null ByteString
s  = More
Complete
                      | Bool
otherwise = More
Incomplete
    go More
Complete [Either String a]
_ (A.Partial ByteString -> IResult ByteString Header
_) = forall a. String -> String -> a
moduleError String
"decodeWithP'" String
msg
        where msg :: String
msg = String
"attoparsec should never return Partial in this case"
    go More
m [Either String a]
acc (A.Done ByteString
rest Header
r)
        | ByteString -> Bool
B.null ByteString
rest = case More
m of
            More
Complete   -> forall a. [Either String a] -> Parser a
Done (forall a. [a] -> [a]
reverse [Either String a]
acc')
            More
Incomplete -> forall a. [Either String a] -> (ByteString -> Parser a) -> Parser a
Many (forall a. [a] -> [a]
reverse [Either String a]
acc') ([Either String a] -> ByteString -> Parser a
cont [])
        | Bool
otherwise   = More -> [Either String a] -> IResult ByteString Header -> Parser a
go More
m [Either String a]
acc' (ByteString -> IResult ByteString Header
parser ByteString
rest)
      where cont :: [Either String a] -> ByteString -> Parser a
cont [Either String a]
acc'' ByteString
s
                | ByteString -> Bool
B.null ByteString
s  = forall a. [Either String a] -> Parser a
Done (forall a. [a] -> [a]
reverse [Either String a]
acc'')
                | Bool
otherwise = More -> [Either String a] -> IResult ByteString Header -> Parser a
go More
Incomplete [Either String a]
acc'' (ByteString -> IResult ByteString Header
parser ByteString
s)
            acc' :: [Either String a]
acc' | Header -> Bool
blankLine Header
r = [Either String a]
acc
                 | Bool
otherwise   = let !r' :: Either String a
r' = Header -> Either String a
convert Header
r in Either String a
r' forall a. a -> [a] -> [a]
: [Either String a]
acc
    parser :: ByteString -> IResult ByteString Header
parser = forall a. Parser a -> ByteString -> Result a
A.parse (Word8 -> Parser Header
record (DecodeOptions -> Word8
decDelimiter DecodeOptions
opts) forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (Parser ByteString ()
endOfLine forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall t. Chunk t => Parser t ()
endOfInput))
    convert :: Header -> Either String a
convert = forall a. Parser a -> Either String a
runParser forall b c a. (b -> c) -> (a -> b) -> a -> c
. Header -> Parser a
p
{-# INLINE decodeWithP' #-}
blankLine :: V.Vector B.ByteString -> Bool
blankLine :: Header -> Bool
blankLine Header
v = forall a. Vector a -> Int
V.length Header
v forall a. Eq a => a -> a -> Bool
== Int
1 Bool -> Bool -> Bool
&& (ByteString -> Bool
B.null (forall a. Vector a -> a
V.head Header
v))
encode :: ToRecord a => Builder a -> L.ByteString
encode :: forall a. ToRecord a => Builder a -> ByteString
encode = forall a. ToRecord a => EncodeOptions -> Builder a -> ByteString
encodeWith EncodeOptions
Encoding.defaultEncodeOptions
encodeWith :: ToRecord a => EncodeOptions -> Builder a
                 -> L.ByteString
encodeWith :: forall a. ToRecord a => EncodeOptions -> Builder a -> ByteString
encodeWith EncodeOptions
opts Builder a
b =
    Builder -> ByteString
Builder.toLazyByteString forall a b. (a -> b) -> a -> b
$
    forall a. Builder a -> Quoting -> Word8 -> Bool -> Builder
runBuilder Builder a
b (EncodeOptions -> Quoting
encQuoting EncodeOptions
opts) (EncodeOptions -> Word8
encDelimiter EncodeOptions
opts) (EncodeOptions -> Bool
encUseCrLf EncodeOptions
opts)
encodeRecord :: ToRecord a => a -> Builder a
encodeRecord :: forall a. ToRecord a => a -> Builder a
encodeRecord a
r = forall a. (Quoting -> Word8 -> Bool -> Builder) -> Builder a
Builder forall a b. (a -> b) -> a -> b
$ \ Quoting
qtng Word8
delim Bool
useCrLf ->
    Quoting -> Word8 -> Header -> Builder
Encoding.encodeRecord Quoting
qtng Word8
delim (forall a. ToRecord a => a -> Header
toRecord a
r) forall a. Semigroup a => a -> a -> a
<> Bool -> Builder
recordSep Bool
useCrLf
newtype Builder a = Builder {
      forall a. Builder a -> Quoting -> Word8 -> Bool -> Builder
runBuilder :: Quoting -> Word8 -> Bool -> Builder.Builder
    }
instance Semi.Semigroup (Builder a) where
    Builder Quoting -> Word8 -> Bool -> Builder
f <> :: Builder a -> Builder a -> Builder a
<> Builder Quoting -> Word8 -> Bool -> Builder
g =
        forall a. (Quoting -> Word8 -> Bool -> Builder) -> Builder a
Builder forall a b. (a -> b) -> a -> b
$ \ Quoting
qtng Word8
delim Bool
useCrlf ->
        Quoting -> Word8 -> Bool -> Builder
f Quoting
qtng Word8
delim Bool
useCrlf forall a. Semigroup a => a -> a -> a
<> Quoting -> Word8 -> Bool -> Builder
g Quoting
qtng Word8
delim Bool
useCrlf
instance Monoid (Builder a) where
    mempty :: Builder a
mempty  = forall a. (Quoting -> Word8 -> Bool -> Builder) -> Builder a
Builder (\ Quoting
_ Word8
_ Bool
_ -> forall a. Monoid a => a
mempty)
    mappend :: Builder a -> Builder a -> Builder a
mappend = forall a. Semigroup a => a -> a -> a
(Semi.<>)
encodeByName :: ToNamedRecord a => Header -> NamedBuilder a -> L.ByteString
encodeByName :: forall a. ToNamedRecord a => Header -> NamedBuilder a -> ByteString
encodeByName = forall a.
ToNamedRecord a =>
EncodeOptions -> Header -> NamedBuilder a -> ByteString
encodeByNameWith EncodeOptions
Encoding.defaultEncodeOptions
encodeDefaultOrderedByName :: (DefaultOrdered a, ToNamedRecord a) =>
                              NamedBuilder a -> L.ByteString
encodeDefaultOrderedByName :: forall a.
(DefaultOrdered a, ToNamedRecord a) =>
NamedBuilder a -> ByteString
encodeDefaultOrderedByName =
    forall a.
(DefaultOrdered a, ToNamedRecord a) =>
EncodeOptions -> NamedBuilder a -> ByteString
encodeDefaultOrderedByNameWith EncodeOptions
Encoding.defaultEncodeOptions
encodeByNameWith :: ToNamedRecord a => EncodeOptions -> Header -> NamedBuilder a
                 -> L.ByteString
encodeByNameWith :: forall a.
ToNamedRecord a =>
EncodeOptions -> Header -> NamedBuilder a -> ByteString
encodeByNameWith EncodeOptions
opts Header
hdr NamedBuilder a
b =
    Builder -> ByteString
Builder.toLazyByteString forall a b. (a -> b) -> a -> b
$
    Builder
encHdr forall a. Semigroup a => a -> a -> a
<>
    forall a.
NamedBuilder a -> Header -> Quoting -> Word8 -> Bool -> Builder
runNamedBuilder NamedBuilder a
b Header
hdr (EncodeOptions -> Quoting
encQuoting EncodeOptions
opts) (EncodeOptions -> Word8
encDelimiter EncodeOptions
opts)
    (EncodeOptions -> Bool
encUseCrLf EncodeOptions
opts)
  where
    encHdr :: Builder
encHdr
      | EncodeOptions -> Bool
encIncludeHeader EncodeOptions
opts =
          Quoting -> Word8 -> Header -> Builder
Encoding.encodeRecord (EncodeOptions -> Quoting
encQuoting EncodeOptions
opts) (EncodeOptions -> Word8
encDelimiter EncodeOptions
opts) Header
hdr
          forall a. Semigroup a => a -> a -> a
<> Bool -> Builder
recordSep (EncodeOptions -> Bool
encUseCrLf EncodeOptions
opts)
      | Bool
otherwise = forall a. Monoid a => a
mempty
encodeDefaultOrderedByNameWith ::
    forall a. (DefaultOrdered a, ToNamedRecord a) =>
    EncodeOptions -> NamedBuilder a -> L.ByteString
encodeDefaultOrderedByNameWith :: forall a.
(DefaultOrdered a, ToNamedRecord a) =>
EncodeOptions -> NamedBuilder a -> ByteString
encodeDefaultOrderedByNameWith EncodeOptions
opts NamedBuilder a
b =
    Builder -> ByteString
Builder.toLazyByteString forall a b. (a -> b) -> a -> b
$
    Builder
encHdr forall a. Semigroup a => a -> a -> a
<>
    forall a.
NamedBuilder a -> Header -> Quoting -> Word8 -> Bool -> Builder
runNamedBuilder NamedBuilder a
b Header
hdr (EncodeOptions -> Quoting
encQuoting EncodeOptions
opts)
    (EncodeOptions -> Word8
encDelimiter EncodeOptions
opts) (EncodeOptions -> Bool
encUseCrLf EncodeOptions
opts)
  where
    hdr :: Header
hdr = forall a. DefaultOrdered a => a -> Header
Conversion.headerOrder (forall a. HasCallStack => a
undefined :: a)
    encHdr :: Builder
encHdr
      | EncodeOptions -> Bool
encIncludeHeader EncodeOptions
opts =
          Quoting -> Word8 -> Header -> Builder
Encoding.encodeRecord (EncodeOptions -> Quoting
encQuoting EncodeOptions
opts) (EncodeOptions -> Word8
encDelimiter EncodeOptions
opts) Header
hdr
          forall a. Semigroup a => a -> a -> a
<> Bool -> Builder
recordSep (EncodeOptions -> Bool
encUseCrLf EncodeOptions
opts)
      | Bool
otherwise = forall a. Monoid a => a
mempty
encodeNamedRecord :: ToNamedRecord a => a -> NamedBuilder a
encodeNamedRecord :: forall a. ToNamedRecord a => a -> NamedBuilder a
encodeNamedRecord a
nr = forall a.
(Header -> Quoting -> Word8 -> Bool -> Builder) -> NamedBuilder a
NamedBuilder forall a b. (a -> b) -> a -> b
$ \ Header
hdr Quoting
qtng Word8
delim Bool
useCrLf ->
    Header -> Quoting -> Word8 -> NamedRecord -> Builder
Encoding.encodeNamedRecord Header
hdr Quoting
qtng Word8
delim
    (forall a. ToNamedRecord a => a -> NamedRecord
Conversion.toNamedRecord a
nr) forall a. Semigroup a => a -> a -> a
<> Bool -> Builder
recordSep Bool
useCrLf
newtype NamedBuilder a = NamedBuilder {
      forall a.
NamedBuilder a -> Header -> Quoting -> Word8 -> Bool -> Builder
runNamedBuilder :: Header -> Quoting -> Word8 -> Bool -> Builder.Builder
    }
instance Semigroup (NamedBuilder a) where
    NamedBuilder Header -> Quoting -> Word8 -> Bool -> Builder
f <> :: NamedBuilder a -> NamedBuilder a -> NamedBuilder a
<> NamedBuilder Header -> Quoting -> Word8 -> Bool -> Builder
g =
        forall a.
(Header -> Quoting -> Word8 -> Bool -> Builder) -> NamedBuilder a
NamedBuilder forall a b. (a -> b) -> a -> b
$ \ Header
hdr Quoting
qtng Word8
delim Bool
useCrlf ->
        Header -> Quoting -> Word8 -> Bool -> Builder
f Header
hdr Quoting
qtng Word8
delim Bool
useCrlf forall a. Semigroup a => a -> a -> a
<> Header -> Quoting -> Word8 -> Bool -> Builder
g Header
hdr Quoting
qtng Word8
delim Bool
useCrlf
instance Monoid (NamedBuilder a) where
    mempty :: NamedBuilder a
mempty = forall a.
(Header -> Quoting -> Word8 -> Bool -> Builder) -> NamedBuilder a
NamedBuilder (\ Header
_ Quoting
_ Word8
_ Bool
_ -> forall a. Monoid a => a
mempty)
    mappend :: NamedBuilder a -> NamedBuilder a -> NamedBuilder a
mappend = forall a. Semigroup a => a -> a -> a
(Semi.<>)
moduleError :: String -> String -> a
moduleError :: forall a. String -> String -> a
moduleError String
func String
msg = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Data.Csv.Incremental." forall a. [a] -> [a] -> [a]
++ String
func forall a. [a] -> [a] -> [a]
++ String
": " forall a. [a] -> [a] -> [a]
++ String
msg
{-# NOINLINE moduleError #-}