{-# LANGUAGE BangPatterns, OverloadedStrings, ScopedTypeVariables #-}
module Data.Csv.Encoding
(
HasHeader(..)
, decode
, decodeByName
, Quoting(..)
, encode
, encodeByName
, encodeDefaultOrderedByName
, DecodeOptions(..)
, defaultDecodeOptions
, decodeWith
, decodeWithP
, decodeByNameWith
, decodeByNameWithP
, EncodeOptions(..)
, defaultEncodeOptions
, encodeWith
, encodeByNameWith
, encodeDefaultOrderedByNameWith
, encodeRecord
, encodeNamedRecord
, recordSep
) where
import Data.ByteString.Builder
import Control.Applicative as AP (Applicative(..), (<|>))
import Data.Attoparsec.ByteString.Char8 (endOfInput)
import qualified Data.Attoparsec.ByteString.Lazy as AL
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Char8 as BL8
import qualified Data.HashMap.Strict as HM
import Data.Vector (Vector)
import qualified Data.Vector as V
import Data.Word (Word8)
import Data.Monoid
import Prelude hiding (unlines)
import qualified Data.Csv.Conversion as Conversion
import Data.Csv.Conversion (FromNamedRecord, FromRecord, ToNamedRecord,
ToRecord, parseNamedRecord, parseRecord, runParser,
toNamedRecord, toRecord)
import Data.Csv.Parser hiding (csv, csvWithHeader)
import qualified Data.Csv.Parser as Parser
import Data.Csv.Types hiding (toNamedRecord)
import qualified Data.Csv.Types as Types
import Data.Csv.Util (blankLine, endOfLine, toStrict)
decode :: FromRecord a
=> HasHeader
-> L.ByteString
-> Either String (Vector a)
decode :: forall a.
FromRecord a =>
HasHeader -> ByteString -> Either String (Vector a)
decode = DecodeOptions
-> HasHeader -> ByteString -> Either String (Vector a)
forall a.
FromRecord a =>
DecodeOptions
-> HasHeader -> ByteString -> Either String (Vector a)
decodeWith DecodeOptions
defaultDecodeOptions
{-# INLINE decode #-}
decodeByName :: FromNamedRecord a
=> L.ByteString
-> Either String (Header, Vector a)
decodeByName :: forall a.
FromNamedRecord a =>
ByteString -> Either String (Header, Vector a)
decodeByName = DecodeOptions -> ByteString -> Either String (Header, Vector a)
forall a.
FromNamedRecord a =>
DecodeOptions -> ByteString -> Either String (Header, Vector a)
decodeByNameWith DecodeOptions
defaultDecodeOptions
{-# INLINE decodeByName #-}
encode :: ToRecord a => [a] -> L.ByteString
encode :: forall a. ToRecord a => [a] -> ByteString
encode = EncodeOptions -> [a] -> ByteString
forall a. ToRecord a => EncodeOptions -> [a] -> ByteString
encodeWith EncodeOptions
defaultEncodeOptions
{-# INLINE encode #-}
encodeByName :: ToNamedRecord a => Header -> [a] -> L.ByteString
encodeByName :: forall a. ToNamedRecord a => Header -> [a] -> ByteString
encodeByName = EncodeOptions -> Header -> [a] -> ByteString
forall a.
ToNamedRecord a =>
EncodeOptions -> Header -> [a] -> ByteString
encodeByNameWith EncodeOptions
defaultEncodeOptions
{-# INLINE encodeByName #-}
encodeDefaultOrderedByName :: (Conversion.DefaultOrdered a, ToNamedRecord a) =>
[a] -> L.ByteString
encodeDefaultOrderedByName :: forall a. (DefaultOrdered a, ToNamedRecord a) => [a] -> ByteString
encodeDefaultOrderedByName = EncodeOptions -> [a] -> ByteString
forall a.
(DefaultOrdered a, ToNamedRecord a) =>
EncodeOptions -> [a] -> ByteString
encodeDefaultOrderedByNameWith EncodeOptions
defaultEncodeOptions
{-# INLINE encodeDefaultOrderedByName #-}
decodeWith :: FromRecord a
=> DecodeOptions
-> HasHeader
-> L.ByteString
-> Either String (Vector a)
decodeWith :: forall a.
FromRecord a =>
DecodeOptions
-> HasHeader -> ByteString -> Either String (Vector a)
decodeWith = (DecodeOptions -> Parser (Vector a))
-> DecodeOptions
-> HasHeader
-> ByteString
-> Either String (Vector a)
forall a.
(DecodeOptions -> Parser a)
-> DecodeOptions -> HasHeader -> ByteString -> Either String a
decodeWithC ((Header -> Parser a) -> DecodeOptions -> Parser (Vector a)
forall a.
(Header -> Parser a) -> DecodeOptions -> Parser (Vector a)
csv Header -> Parser a
forall a. FromRecord a => Header -> Parser a
parseRecord)
{-# INLINE [1] decodeWith #-}
{-# RULES
"idDecodeWith" decodeWith = idDecodeWith
#-}
idDecodeWith :: DecodeOptions -> HasHeader -> L.ByteString
-> Either String (Vector (Vector B.ByteString))
idDecodeWith :: DecodeOptions
-> HasHeader -> ByteString -> Either String (Vector Header)
idDecodeWith = (DecodeOptions -> Parser (Vector Header))
-> DecodeOptions
-> HasHeader
-> ByteString
-> Either String (Vector Header)
forall a.
(DecodeOptions -> Parser a)
-> DecodeOptions -> HasHeader -> ByteString -> Either String a
decodeWithC DecodeOptions -> Parser (Vector Header)
Parser.csv
decodeWithP :: (Record -> Conversion.Parser a)
-> DecodeOptions
-> HasHeader
-> L.ByteString
-> Either String (Vector a)
decodeWithP :: forall a.
(Header -> Parser a)
-> DecodeOptions
-> HasHeader
-> ByteString
-> Either String (Vector a)
decodeWithP Header -> Parser a
_parseRecord = (DecodeOptions -> Parser (Vector a))
-> DecodeOptions
-> HasHeader
-> ByteString
-> Either String (Vector a)
forall a.
(DecodeOptions -> Parser a)
-> DecodeOptions -> HasHeader -> ByteString -> Either String a
decodeWithC ((Header -> Parser a) -> DecodeOptions -> Parser (Vector a)
forall a.
(Header -> Parser a) -> DecodeOptions -> Parser (Vector a)
csv Header -> Parser a
_parseRecord)
{-# INLINE [1] decodeWithP #-}
decodeWithC :: (DecodeOptions -> AL.Parser a) -> DecodeOptions -> HasHeader
-> BL8.ByteString -> Either String a
decodeWithC :: forall a.
(DecodeOptions -> Parser a)
-> DecodeOptions -> HasHeader -> ByteString -> Either String a
decodeWithC DecodeOptions -> Parser a
p !DecodeOptions
opts HasHeader
hasHeader = Parser a -> ByteString -> Either String a
forall a. Parser a -> ByteString -> Either String a
decodeWithP' Parser a
parser
where parser :: Parser a
parser = case HasHeader
hasHeader of
HasHeader
HasHeader -> Word8 -> Parser Header
header (DecodeOptions -> Word8
decDelimiter DecodeOptions
opts) Parser Header -> Parser a -> Parser a
forall a b.
Parser StrictByteString a
-> Parser StrictByteString b -> Parser StrictByteString b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> DecodeOptions -> Parser a
p DecodeOptions
opts
HasHeader
NoHeader -> DecodeOptions -> Parser a
p DecodeOptions
opts
{-# INLINE decodeWithC #-}
decodeByNameWith :: FromNamedRecord a
=> DecodeOptions
-> L.ByteString
-> Either String (Header, Vector a)
decodeByNameWith :: forall a.
FromNamedRecord a =>
DecodeOptions -> ByteString -> Either String (Header, Vector a)
decodeByNameWith !DecodeOptions
opts = Parser (Header, Vector a)
-> ByteString -> Either String (Header, Vector a)
forall a. Parser a -> ByteString -> Either String a
decodeWithP' ((NamedRecord -> Parser a)
-> DecodeOptions -> Parser (Header, Vector a)
forall a.
(NamedRecord -> Parser a)
-> DecodeOptions -> Parser (Header, Vector a)
csvWithHeader NamedRecord -> Parser a
forall a. FromNamedRecord a => NamedRecord -> Parser a
parseNamedRecord DecodeOptions
opts)
decodeByNameWithP :: (NamedRecord -> Conversion.Parser a)
-> DecodeOptions
-> L.ByteString
-> Either String (Header, Vector a)
decodeByNameWithP :: forall a.
(NamedRecord -> Parser a)
-> DecodeOptions -> ByteString -> Either String (Header, Vector a)
decodeByNameWithP NamedRecord -> Parser a
_parseNamedRecord !DecodeOptions
opts =
Parser (Header, Vector a)
-> ByteString -> Either String (Header, Vector a)
forall a. Parser a -> ByteString -> Either String a
decodeWithP' ((NamedRecord -> Parser a)
-> DecodeOptions -> Parser (Header, Vector a)
forall a.
(NamedRecord -> Parser a)
-> DecodeOptions -> Parser (Header, Vector a)
csvWithHeader NamedRecord -> Parser a
_parseNamedRecord DecodeOptions
opts)
data Quoting
= QuoteNone
| QuoteMinimal
| QuoteAll
deriving (Quoting -> Quoting -> Bool
(Quoting -> Quoting -> Bool)
-> (Quoting -> Quoting -> Bool) -> Eq Quoting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Quoting -> Quoting -> Bool
== :: Quoting -> Quoting -> Bool
$c/= :: Quoting -> Quoting -> Bool
/= :: Quoting -> Quoting -> Bool
Eq, Int -> Quoting -> ShowS
[Quoting] -> ShowS
Quoting -> String
(Int -> Quoting -> ShowS)
-> (Quoting -> String) -> ([Quoting] -> ShowS) -> Show Quoting
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Quoting -> ShowS
showsPrec :: Int -> Quoting -> ShowS
$cshow :: Quoting -> String
show :: Quoting -> String
$cshowList :: [Quoting] -> ShowS
showList :: [Quoting] -> ShowS
Show)
data EncodeOptions = EncodeOptions
{
EncodeOptions -> Word8
encDelimiter :: {-# UNPACK #-} !Word8
, EncodeOptions -> Bool
encUseCrLf :: !Bool
, :: !Bool
, EncodeOptions -> Quoting
encQuoting :: !Quoting
} deriving (EncodeOptions -> EncodeOptions -> Bool
(EncodeOptions -> EncodeOptions -> Bool)
-> (EncodeOptions -> EncodeOptions -> Bool) -> Eq EncodeOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EncodeOptions -> EncodeOptions -> Bool
== :: EncodeOptions -> EncodeOptions -> Bool
$c/= :: EncodeOptions -> EncodeOptions -> Bool
/= :: EncodeOptions -> EncodeOptions -> Bool
Eq, Int -> EncodeOptions -> ShowS
[EncodeOptions] -> ShowS
EncodeOptions -> String
(Int -> EncodeOptions -> ShowS)
-> (EncodeOptions -> String)
-> ([EncodeOptions] -> ShowS)
-> Show EncodeOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EncodeOptions -> ShowS
showsPrec :: Int -> EncodeOptions -> ShowS
$cshow :: EncodeOptions -> String
show :: EncodeOptions -> String
$cshowList :: [EncodeOptions] -> ShowS
showList :: [EncodeOptions] -> ShowS
Show)
defaultEncodeOptions :: EncodeOptions
defaultEncodeOptions :: EncodeOptions
defaultEncodeOptions = EncodeOptions
{ encDelimiter :: Word8
encDelimiter = Word8
44
, encUseCrLf :: Bool
encUseCrLf = Bool
True
, encIncludeHeader :: Bool
encIncludeHeader = Bool
True
, encQuoting :: Quoting
encQuoting = Quoting
QuoteMinimal
}
encodeWith :: ToRecord a => EncodeOptions -> [a] -> L.ByteString
encodeWith :: forall a. ToRecord a => EncodeOptions -> [a] -> ByteString
encodeWith EncodeOptions
opts
| Word8 -> Bool
validDelim (EncodeOptions -> Word8
encDelimiter EncodeOptions
opts) =
Builder -> ByteString
toLazyByteString
(Builder -> ByteString) -> ([a] -> Builder) -> [a] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> [Builder] -> Builder
unlines (Bool -> Builder
recordSep (EncodeOptions -> Bool
encUseCrLf EncodeOptions
opts))
([Builder] -> Builder) -> ([a] -> [Builder]) -> [a] -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Builder) -> [a] -> [Builder]
forall a b. (a -> b) -> [a] -> [b]
map (Quoting -> Word8 -> Header -> Builder
encodeRecord (EncodeOptions -> Quoting
encQuoting EncodeOptions
opts) (EncodeOptions -> Word8
encDelimiter EncodeOptions
opts)
(Header -> Builder) -> (a -> Header) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Header
forall a. ToRecord a => a -> Header
toRecord)
| Bool
otherwise = [a] -> ByteString
forall a. a
encodeOptionsError
{-# INLINE encodeWith #-}
validDelim :: Word8 -> Bool
validDelim :: Word8 -> Bool
validDelim Word8
delim = Word8
delim Word8 -> [Word8] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Word8
cr, Word8
nl, Word8
dquote]
where
nl :: Word8
nl = Word8
10
cr :: Word8
cr = Word8
13
dquote :: Word8
dquote = Word8
34
encodeOptionsError :: a
encodeOptionsError :: forall a. a
encodeOptionsError = String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"Data.Csv: " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"The 'encDelimiter' must /not/ be the quote character (i.e. " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"\") or one of the record separator characters (i.e. \\n or " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"\\r)"
encodeRecord :: Quoting -> Word8 -> Record -> Builder
encodeRecord :: Quoting -> Word8 -> Header -> Builder
encodeRecord Quoting
qtng Word8
delim = [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> Builder)
-> (Header -> [Builder]) -> Header -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> [Builder] -> [Builder]
intersperse (Word8 -> Builder
word8 Word8
delim)
([Builder] -> [Builder])
-> (Header -> [Builder]) -> Header -> [Builder]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (StrictByteString -> Builder) -> [StrictByteString] -> [Builder]
forall a b. (a -> b) -> [a] -> [b]
map StrictByteString -> Builder
byteString ([StrictByteString] -> [Builder])
-> (Header -> [StrictByteString]) -> Header -> [Builder]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (StrictByteString -> StrictByteString)
-> [StrictByteString] -> [StrictByteString]
forall a b. (a -> b) -> [a] -> [b]
map (Quoting -> Word8 -> StrictByteString -> StrictByteString
escape Quoting
qtng Word8
delim) ([StrictByteString] -> [StrictByteString])
-> (Header -> [StrictByteString]) -> Header -> [StrictByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Header -> [StrictByteString]
forall a. Vector a -> [a]
V.toList
{-# INLINE encodeRecord #-}
encodeNamedRecord :: Header -> Quoting -> Word8 -> NamedRecord -> Builder
encodeNamedRecord :: Header -> Quoting -> Word8 -> NamedRecord -> Builder
encodeNamedRecord Header
hdr Quoting
qtng Word8
delim =
Quoting -> Word8 -> Header -> Builder
encodeRecord Quoting
qtng Word8
delim (Header -> Builder)
-> (NamedRecord -> Header) -> NamedRecord -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Header -> NamedRecord -> Header
namedRecordToRecord Header
hdr
escape :: Quoting -> Word8 -> B.ByteString -> B.ByteString
escape :: Quoting -> Word8 -> StrictByteString -> StrictByteString
escape !Quoting
qtng !Word8
delim !StrictByteString
s
| (Quoting
qtng Quoting -> Quoting -> Bool
forall a. Eq a => a -> a -> Bool
== Quoting
QuoteMinimal Bool -> Bool -> Bool
&&
(Word8 -> Bool) -> StrictByteString -> Bool
B.any (\ Word8
b -> Word8
b Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
dquote Bool -> Bool -> Bool
|| Word8
b Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
delim Bool -> Bool -> Bool
|| Word8
b Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
nl Bool -> Bool -> Bool
|| Word8
b Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
cr) StrictByteString
s
) Bool -> Bool -> Bool
|| Quoting
qtng Quoting -> Quoting -> Bool
forall a. Eq a => a -> a -> Bool
== Quoting
QuoteAll
= ByteString -> StrictByteString
toStrict (ByteString -> StrictByteString)
-> (Builder -> ByteString) -> Builder -> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
toLazyByteString (Builder -> StrictByteString) -> Builder -> StrictByteString
forall a b. (a -> b) -> a -> b
$
Word8 -> Builder
word8 Word8
dquote
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> (Builder -> Word8 -> Builder)
-> Builder -> StrictByteString -> Builder
forall a. (a -> Word8 -> a) -> a -> StrictByteString -> a
B.foldl
(\ Builder
acc Word8
b -> Builder
acc Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> if Word8
b Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
dquote
then StrictByteString -> Builder
byteString StrictByteString
"\"\""
else Word8 -> Builder
word8 Word8
b)
Builder
forall a. Monoid a => a
mempty
StrictByteString
s
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Word8 -> Builder
word8 Word8
dquote
| Bool
otherwise = StrictByteString
s
where
dquote :: Word8
dquote = Word8
34
nl :: Word8
nl = Word8
10
cr :: Word8
cr = Word8
13
encodeByNameWith :: ToNamedRecord a => EncodeOptions -> Header -> [a]
-> L.ByteString
encodeByNameWith :: forall a.
ToNamedRecord a =>
EncodeOptions -> Header -> [a] -> ByteString
encodeByNameWith EncodeOptions
opts Header
hdr [a]
v
| Word8 -> Bool
validDelim (EncodeOptions -> Word8
encDelimiter EncodeOptions
opts) =
Builder -> ByteString
toLazyByteString (Bool -> Builder
rows (EncodeOptions -> Bool
encIncludeHeader EncodeOptions
opts))
| Bool
otherwise = ByteString
forall a. a
encodeOptionsError
where
rows :: Bool -> Builder
rows Bool
False = Builder
records
rows Bool
True = Quoting -> Word8 -> Header -> Builder
encodeRecord (EncodeOptions -> Quoting
encQuoting EncodeOptions
opts) (EncodeOptions -> Word8
encDelimiter EncodeOptions
opts) Header
hdr Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<>
Bool -> Builder
recordSep (EncodeOptions -> Bool
encUseCrLf EncodeOptions
opts) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
records
records :: Builder
records = Builder -> [Builder] -> Builder
unlines (Bool -> Builder
recordSep (EncodeOptions -> Bool
encUseCrLf EncodeOptions
opts))
([Builder] -> Builder) -> ([a] -> [Builder]) -> [a] -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Builder) -> [a] -> [Builder]
forall a b. (a -> b) -> [a] -> [b]
map (Header -> Quoting -> Word8 -> NamedRecord -> Builder
encodeNamedRecord Header
hdr (EncodeOptions -> Quoting
encQuoting EncodeOptions
opts) (EncodeOptions -> Word8
encDelimiter EncodeOptions
opts)
(NamedRecord -> Builder) -> (a -> NamedRecord) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> NamedRecord
forall a. ToNamedRecord a => a -> NamedRecord
toNamedRecord)
([a] -> Builder) -> [a] -> Builder
forall a b. (a -> b) -> a -> b
$ [a]
v
{-# INLINE encodeByNameWith #-}
encodeDefaultOrderedByNameWith ::
forall a. (Conversion.DefaultOrdered a, ToNamedRecord a) =>
EncodeOptions -> [a] -> L.ByteString
encodeDefaultOrderedByNameWith :: forall a.
(DefaultOrdered a, ToNamedRecord a) =>
EncodeOptions -> [a] -> ByteString
encodeDefaultOrderedByNameWith EncodeOptions
opts [a]
v
| Word8 -> Bool
validDelim (EncodeOptions -> Word8
encDelimiter EncodeOptions
opts) =
Builder -> ByteString
toLazyByteString (Bool -> Builder
rows (EncodeOptions -> Bool
encIncludeHeader EncodeOptions
opts))
| Bool
otherwise = ByteString
forall a. a
encodeOptionsError
where
hdr :: Header
hdr = (a -> Header
forall a. DefaultOrdered a => a -> Header
Conversion.headerOrder (a
forall a. HasCallStack => a
undefined :: a))
rows :: Bool -> Builder
rows Bool
False = Builder
records
rows Bool
True = Quoting -> Word8 -> Header -> Builder
encodeRecord (EncodeOptions -> Quoting
encQuoting EncodeOptions
opts) (EncodeOptions -> Word8
encDelimiter EncodeOptions
opts) Header
hdr Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<>
Bool -> Builder
recordSep (EncodeOptions -> Bool
encUseCrLf EncodeOptions
opts) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
records
records :: Builder
records = Builder -> [Builder] -> Builder
unlines (Bool -> Builder
recordSep (EncodeOptions -> Bool
encUseCrLf EncodeOptions
opts))
([Builder] -> Builder) -> ([a] -> [Builder]) -> [a] -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Builder) -> [a] -> [Builder]
forall a b. (a -> b) -> [a] -> [b]
map (Header -> Quoting -> Word8 -> NamedRecord -> Builder
encodeNamedRecord Header
hdr (EncodeOptions -> Quoting
encQuoting EncodeOptions
opts) (EncodeOptions -> Word8
encDelimiter EncodeOptions
opts)
(NamedRecord -> Builder) -> (a -> NamedRecord) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> NamedRecord
forall a. ToNamedRecord a => a -> NamedRecord
toNamedRecord)
([a] -> Builder) -> [a] -> Builder
forall a b. (a -> b) -> a -> b
$ [a]
v
{-# INLINE encodeDefaultOrderedByNameWith #-}
namedRecordToRecord :: Header -> NamedRecord -> Record
namedRecordToRecord :: Header -> NamedRecord -> Header
namedRecordToRecord Header
hdr NamedRecord
nr = (StrictByteString -> StrictByteString) -> Header -> Header
forall a b. (a -> b) -> Vector a -> Vector b
V.map StrictByteString -> StrictByteString
find Header
hdr
where
find :: StrictByteString -> StrictByteString
find StrictByteString
n = case StrictByteString -> NamedRecord -> Maybe StrictByteString
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HM.lookup StrictByteString
n NamedRecord
nr of
Maybe StrictByteString
Nothing -> String -> String -> StrictByteString
forall a. String -> String -> a
moduleError String
"namedRecordToRecord" (String -> StrictByteString) -> String -> StrictByteString
forall a b. (a -> b) -> a -> b
$
String
"header contains name " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show (StrictByteString -> String
B8.unpack StrictByteString
n) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" which is not present in the named record"
Just StrictByteString
v -> StrictByteString
v
moduleError :: String -> String -> a
moduleError :: forall a. String -> String -> a
moduleError String
func String
msg = String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"Data.Csv.Encoding." String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
func String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
": " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg
{-# NOINLINE moduleError #-}
recordSep :: Bool -> Builder
recordSep :: Bool -> Builder
recordSep Bool
False = Word8 -> Builder
word8 Word8
10
recordSep Bool
True = String -> Builder
string8 String
"\r\n"
unlines :: Builder -> [Builder] -> Builder
unlines :: Builder -> [Builder] -> Builder
unlines Builder
_ [] = Builder
forall a. Monoid a => a
mempty
unlines Builder
sep (Builder
b:[Builder]
bs) = Builder
b Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
sep Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder -> [Builder] -> Builder
unlines Builder
sep [Builder]
bs
intersperse :: Builder -> [Builder] -> [Builder]
intersperse :: Builder -> [Builder] -> [Builder]
intersperse Builder
_ [] = []
intersperse Builder
sep (Builder
x:[Builder]
xs) = Builder
x Builder -> [Builder] -> [Builder]
forall a. a -> [a] -> [a]
: Builder -> [Builder] -> [Builder]
prependToAll Builder
sep [Builder]
xs
prependToAll :: Builder -> [Builder] -> [Builder]
prependToAll :: Builder -> [Builder] -> [Builder]
prependToAll Builder
_ [] = []
prependToAll Builder
sep (Builder
x:[Builder]
xs) = Builder
sep Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
x Builder -> [Builder] -> [Builder]
forall a. a -> [a] -> [a]
: Builder -> [Builder] -> [Builder]
prependToAll Builder
sep [Builder]
xs
decodeWithP' :: AL.Parser a -> L.ByteString -> Either String a
decodeWithP' :: forall a. Parser a -> ByteString -> Either String a
decodeWithP' Parser a
p ByteString
s =
case Parser a -> ByteString -> Result a
forall a. Parser a -> ByteString -> Result a
AL.parse Parser a
p ByteString
s of
AL.Done ByteString
_ a
v -> a -> Either String a
forall a b. b -> Either a b
Right a
v
AL.Fail ByteString
left [String]
_ String
msg -> String -> Either String a
forall a b. a -> Either a b
Left String
errMsg
where
errMsg :: String
errMsg = String
"parse error (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
") at " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(if ByteString -> Int64
BL8.length ByteString
left Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> Int64
100
then (Int -> ShowS
forall a. Int -> [a] -> [a]
take Int
100 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ ByteString -> String
BL8.unpack ByteString
left) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" (truncated)"
else ShowS
forall a. Show a => a -> String
show (ByteString -> String
BL8.unpack ByteString
left))
{-# INLINE decodeWithP' #-}
csv :: (Record -> Conversion.Parser a) -> DecodeOptions
-> AL.Parser (V.Vector a)
csv :: forall a.
(Header -> Parser a) -> DecodeOptions -> Parser (Vector a)
csv Header -> Parser a
_parseRecord !DecodeOptions
opts = do
vals <- Parser StrictByteString [a]
records
return $! V.fromList vals
where
records :: Parser StrictByteString [a]
records = do
!r <- Word8 -> Parser Header
record (DecodeOptions -> Word8
decDelimiter DecodeOptions
opts)
if blankLine r
then (endOfInput *> pure []) <|> (endOfLine *> records)
else case runParser (_parseRecord r) of
Left String
msg -> String -> Parser StrictByteString [a]
forall a. String -> Parser StrictByteString a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser StrictByteString [a])
-> String -> Parser StrictByteString [a]
forall a b. (a -> b) -> a -> b
$ String
"conversion error: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg
Right a
val -> do
!vals <- (Parser StrictByteString ()
forall t. Chunk t => Parser t ()
endOfInput Parser StrictByteString ()
-> Parser StrictByteString [a] -> Parser StrictByteString [a]
forall a b.
Parser StrictByteString a
-> Parser StrictByteString b -> Parser StrictByteString b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [a] -> Parser StrictByteString [a]
forall a. a -> Parser StrictByteString a
forall (f :: * -> *) a. Applicative f => a -> f a
AP.pure []) Parser StrictByteString [a]
-> Parser StrictByteString [a] -> Parser StrictByteString [a]
forall a.
Parser StrictByteString a
-> Parser StrictByteString a -> Parser StrictByteString a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser StrictByteString ()
endOfLine Parser StrictByteString ()
-> Parser StrictByteString [a] -> Parser StrictByteString [a]
forall a b.
Parser StrictByteString a
-> Parser StrictByteString b -> Parser StrictByteString b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser StrictByteString [a]
records)
return (val : vals)
{-# INLINE csv #-}
csvWithHeader :: (NamedRecord -> Conversion.Parser a) -> DecodeOptions
-> AL.Parser (Header, V.Vector a)
NamedRecord -> Parser a
_parseNamedRecord !DecodeOptions
opts = do
!hdr <- Word8 -> Parser Header
header (DecodeOptions -> Word8
decDelimiter DecodeOptions
opts)
vals <- records hdr
let !v = [a] -> Vector a
forall a. [a] -> Vector a
V.fromList [a]
vals
return (hdr, v)
where
records :: Header -> Parser StrictByteString [a]
records Header
hdr = do
!r <- Word8 -> Parser Header
record (DecodeOptions -> Word8
decDelimiter DecodeOptions
opts)
if blankLine r
then (endOfInput *> pure []) <|> (endOfLine *> records hdr)
else case runParser (convert hdr r) of
Left String
msg -> String -> Parser StrictByteString [a]
forall a. String -> Parser StrictByteString a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser StrictByteString [a])
-> String -> Parser StrictByteString [a]
forall a b. (a -> b) -> a -> b
$ String
"conversion error: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg
Right a
val -> do
!vals <- (Parser StrictByteString ()
forall t. Chunk t => Parser t ()
endOfInput Parser StrictByteString ()
-> Parser StrictByteString [a] -> Parser StrictByteString [a]
forall a b.
Parser StrictByteString a
-> Parser StrictByteString b -> Parser StrictByteString b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [a] -> Parser StrictByteString [a]
forall a. a -> Parser StrictByteString a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []) Parser StrictByteString [a]
-> Parser StrictByteString [a] -> Parser StrictByteString [a]
forall a.
Parser StrictByteString a
-> Parser StrictByteString a -> Parser StrictByteString a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser StrictByteString ()
endOfLine Parser StrictByteString ()
-> Parser StrictByteString [a] -> Parser StrictByteString [a]
forall a b.
Parser StrictByteString a
-> Parser StrictByteString b -> Parser StrictByteString b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Header -> Parser StrictByteString [a]
records Header
hdr)
return (val : vals)
convert :: Header -> Header -> Parser a
convert Header
hdr = NamedRecord -> Parser a
_parseNamedRecord (NamedRecord -> Parser a)
-> (Header -> NamedRecord) -> Header -> Parser a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Header -> Header -> NamedRecord
Types.toNamedRecord Header
hdr