{-# LANGUAGE BangPatterns, CPP, DeriveFunctor #-}
module Data.Csv.Streaming
(
Records(..)
, HasHeader(..)
, decode
, decodeWith
, decodeByName
, decodeByNameWith
) where
import Control.DeepSeq (NFData(rnf))
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BL8
import Data.Foldable (Foldable(..))
import Prelude hiding (foldr)
import Data.Csv.Conversion
import Data.Csv.Incremental hiding (decode, decodeByName, decodeByNameWith,
decodeWith)
import qualified Data.Csv.Incremental as I
import Data.Csv.Parser
import Data.Csv.Types
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>), (<*>), pure)
import Data.Traversable (Traversable(..))
#endif
#if !MIN_VERSION_bytestring(0,10,0)
import qualified Data.ByteString.Lazy.Internal as BL
#endif
data Records a
=
Cons (Either String a) (Records a)
| Nil (Maybe String) BL.ByteString
deriving (Records a -> Records a -> Bool
forall a. Eq a => Records a -> Records a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Records a -> Records a -> Bool
$c/= :: forall a. Eq a => Records a -> Records a -> Bool
== :: Records a -> Records a -> Bool
$c== :: forall a. Eq a => Records a -> Records a -> Bool
Eq, forall a b. a -> Records b -> Records a
forall a b. (a -> b) -> Records a -> Records 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 -> Records b -> Records a
$c<$ :: forall a b. a -> Records b -> Records a
fmap :: forall a b. (a -> b) -> Records a -> Records b
$cfmap :: forall a b. (a -> b) -> Records a -> Records b
Functor, Int -> Records a -> ShowS
forall a. Show a => Int -> Records a -> ShowS
forall a. Show a => [Records a] -> ShowS
forall a. Show a => Records a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Records a] -> ShowS
$cshowList :: forall a. Show a => [Records a] -> ShowS
show :: Records a -> String
$cshow :: forall a. Show a => Records a -> String
showsPrec :: Int -> Records a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Records a -> ShowS
Show)
instance Foldable Records where
foldr :: forall a b. (a -> b -> b) -> b -> Records a -> b
foldr = forall a b. (a -> b -> b) -> b -> Records a -> b
foldrRecords
#if MIN_VERSION_base(4,6,0)
foldl' :: forall b a. (b -> a -> b) -> b -> Records a -> b
foldl' = forall b a. (b -> a -> b) -> b -> Records a -> b
foldlRecords'
#endif
foldrRecords :: (a -> b -> b) -> b -> Records a -> b
foldrRecords :: forall a b. (a -> b -> b) -> b -> Records a -> b
foldrRecords a -> b -> b
f = b -> Records a -> b
go
where
go :: b -> Records a -> b
go b
z (Cons (Right a
x) Records a
rs) = a -> b -> b
f a
x (b -> Records a -> b
go b
z Records a
rs)
go b
z (Cons (Left String
_) Records a
rs) = b -> Records a -> b
go b
z Records a
rs
go b
z Records a
_ = b
z
{-# INLINE foldrRecords #-}
#if MIN_VERSION_base(4,6,0)
foldlRecords' :: (a -> b -> a) -> a -> Records b -> a
foldlRecords' :: forall b a. (b -> a -> b) -> b -> Records a -> b
foldlRecords' a -> b -> a
f = a -> Records b -> a
go
where
go :: a -> Records b -> a
go a
z (Cons (Right b
x) Records b
rs) = let z' :: a
z' = a -> b -> a
f a
z b
x in a
z' seq :: forall a b. a -> b -> b
`seq` a -> Records b -> a
go a
z' Records b
rs
go a
z (Cons (Left String
_) Records b
rs) = a -> Records b -> a
go a
z Records b
rs
go a
z Records b
_ = a
z
{-# INLINE foldlRecords' #-}
#endif
instance Traversable Records where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Records a -> f (Records b)
traverse a -> f b
_ (Nil Maybe String
merr ByteString
rest) = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Maybe String -> ByteString -> Records a
Nil Maybe String
merr ByteString
rest
traverse a -> f b
f (Cons Either String a
x Records a
xs) = forall a. Either String a -> Records a -> Records a
Cons forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {a}. Either a a -> f (Either a b)
traverseElem Either String a
x forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f Records a
xs
where
traverseElem :: Either a a -> f (Either a b)
traverseElem (Left a
err) = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left a
err
traverseElem (Right a
y) = forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
y
instance NFData a => NFData (Records a) where
rnf :: Records a -> ()
rnf (Cons Either String a
r Records a
rs) = forall a. NFData a => a -> ()
rnf Either String a
r seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf Records a
rs
#if MIN_VERSION_bytestring(0,10,0)
rnf (Nil Maybe String
errMsg ByteString
rest) = forall a. NFData a => a -> ()
rnf Maybe String
errMsg seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf ByteString
rest
#else
rnf (Nil errMsg rest) = rnf errMsg `seq` rnfLazyByteString rest
rnfLazyByteString :: BL.ByteString -> ()
rnfLazyByteString BL.Empty = ()
rnfLazyByteString (BL.Chunk _ b) = rnfLazyByteString b
#endif
decode :: FromRecord a
=> HasHeader
-> BL.ByteString
-> Records a
decode :: forall a. FromRecord a => HasHeader -> ByteString -> Records a
decode = forall a.
FromRecord a =>
DecodeOptions -> HasHeader -> ByteString -> Records a
decodeWith DecodeOptions
defaultDecodeOptions
decodeWith :: FromRecord a
=> DecodeOptions
-> HasHeader
-> BL.ByteString
-> Records a
decodeWith :: forall a.
FromRecord a =>
DecodeOptions -> HasHeader -> ByteString -> Records a
decodeWith !DecodeOptions
opts HasHeader
hasHeader ByteString
s0 =
forall {a}. [ByteString] -> Parser a -> Records a
go (ByteString -> [ByteString]
BL.toChunks ByteString
s0) (forall a. FromRecord a => DecodeOptions -> HasHeader -> Parser a
I.decodeWith DecodeOptions
opts HasHeader
hasHeader)
where
go :: [ByteString] -> Parser a -> Records a
go [ByteString]
ss (Done [Either String a]
xs) = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. Either String a -> Records a -> Records a
Cons (forall a. Maybe String -> ByteString -> Records a
Nil forall a. Maybe a
Nothing ([ByteString] -> ByteString
BL.fromChunks [ByteString]
ss)) [Either String a]
xs
go [ByteString]
ss (Fail ByteString
rest String
err) = forall a. Maybe String -> ByteString -> Records a
Nil (forall a. a -> Maybe a
Just String
err) ([ByteString] -> ByteString
BL.fromChunks (ByteString
restforall a. a -> [a] -> [a]
:[ByteString]
ss))
go [] (Many [Either String a]
xs ByteString -> Parser a
k) = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. Either String a -> Records a -> Records a
Cons ([ByteString] -> Parser a -> Records a
go [] (ByteString -> Parser a
k ByteString
B.empty)) [Either String a]
xs
go (ByteString
s:[ByteString]
ss) (Many [Either String a]
xs ByteString -> Parser a
k) = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. Either String a -> Records a -> Records a
Cons ([ByteString] -> Parser a -> Records a
go [ByteString]
ss (ByteString -> Parser a
k ByteString
s)) [Either String a]
xs
decodeByName :: FromNamedRecord a
=> BL.ByteString
-> Either String (Header, Records a)
decodeByName :: forall a.
FromNamedRecord a =>
ByteString -> Either String (Header, Records a)
decodeByName = forall a.
FromNamedRecord a =>
DecodeOptions -> ByteString -> Either String (Header, Records a)
decodeByNameWith DecodeOptions
defaultDecodeOptions
decodeByNameWith :: FromNamedRecord a
=> DecodeOptions
-> BL.ByteString
-> Either String (Header, Records a)
decodeByNameWith :: forall a.
FromNamedRecord a =>
DecodeOptions -> ByteString -> Either String (Header, Records a)
decodeByNameWith !DecodeOptions
opts ByteString
s0 = forall {a}.
[ByteString]
-> HeaderParser (Parser a) -> Either String (Header, Records a)
go (ByteString -> [ByteString]
BL.toChunks ByteString
s0) (forall a.
FromNamedRecord a =>
DecodeOptions -> HeaderParser (Parser a)
I.decodeByNameWith DecodeOptions
opts)
where
go :: [ByteString]
-> HeaderParser (Parser a) -> Either String (Header, Records a)
go [ByteString]
ss (DoneH Header
hdr Parser a
p) = forall a b. b -> Either a b
Right (Header
hdr, forall {a}. [ByteString] -> Parser a -> Records a
go2 [ByteString]
ss Parser a
p)
go [ByteString]
ss (FailH ByteString
rest String
err) = forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ String
err forall a. [a] -> [a] -> [a]
++ String
" at " forall a. [a] -> [a] -> [a]
++
forall a. Show a => a -> String
show (ByteString -> String
BL8.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BL.fromChunks forall a b. (a -> b) -> a -> b
$ ByteString
rest forall a. a -> [a] -> [a]
: [ByteString]
ss)
go [] (PartialH ByteString -> HeaderParser (Parser a)
k) = [ByteString]
-> HeaderParser (Parser a) -> Either String (Header, Records a)
go [] (ByteString -> HeaderParser (Parser a)
k ByteString
B.empty)
go (ByteString
s:[ByteString]
ss) (PartialH ByteString -> HeaderParser (Parser a)
k) = [ByteString]
-> HeaderParser (Parser a) -> Either String (Header, Records a)
go [ByteString]
ss (ByteString -> HeaderParser (Parser a)
k ByteString
s)
go2 :: [ByteString] -> Parser a -> Records a
go2 [ByteString]
ss (Done [Either String a]
xs) = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. Either String a -> Records a -> Records a
Cons (forall a. Maybe String -> ByteString -> Records a
Nil forall a. Maybe a
Nothing ([ByteString] -> ByteString
BL.fromChunks [ByteString]
ss)) [Either String a]
xs
go2 [ByteString]
ss (Fail ByteString
rest String
err) = forall a. Maybe String -> ByteString -> Records a
Nil (forall a. a -> Maybe a
Just String
err) ([ByteString] -> ByteString
BL.fromChunks (ByteString
restforall a. a -> [a] -> [a]
:[ByteString]
ss))
go2 [] (Many [Either String a]
xs ByteString -> Parser a
k) = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. Either String a -> Records a -> Records a
Cons ([ByteString] -> Parser a -> Records a
go2 [] (ByteString -> Parser a
k ByteString
B.empty)) [Either String a]
xs
go2 (ByteString
s:[ByteString]
ss) (Many [Either String a]
xs ByteString -> Parser a
k) = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. Either String a -> Records a -> Records a
Cons ([ByteString] -> Parser a -> Records a
go2 [ByteString]
ss (ByteString -> Parser a
k ByteString
s)) [Either String a]
xs