Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module allows for streaming decoding of CSV data. This is useful if you need to parse large amounts of input in constant space. The API also allows you to ignore type conversion errors on a per-record basis.
Synopsis
- data Records a
- data HasHeader
- decode :: FromRecord a => HasHeader -> ByteString -> Records a
- decodeWith :: FromRecord a => DecodeOptions -> HasHeader -> ByteString -> Records a
- decodeByName :: FromNamedRecord a => ByteString -> Either String (Header, Records a)
- decodeByNameWith :: FromNamedRecord a => DecodeOptions -> ByteString -> Either String (Header, Records a)
Usage example
A short usage example:
for_ (decode NoHeader "John,27\r\nJane,28\r\n") $ \ (name, age :: Int) -> putStrLn $ name ++ " is " ++ show age ++ " years old"
N.B. The Foldable
instance, which is used above, skips records
that failed to convert. If you don't want this behavior, work
directly with the Cons
and Nil
constructors.
Stream representation
A stream of records is represented as a (lazy) list that may contain errors.
A stream of parsed records. If type conversion failed for the
record, the error is returned as
.Left
errMsg
Cons (Either String a) (Records a) | A record or an error message, followed by more records. |
Nil (Maybe String) ByteString | End of stream, potentially due to a parse error. If a parse error occured, the first field contains the error message. The second field contains any unconsumed input. |
Instances
Functor Records Source # | |
Foldable Records Source # | Skips records that failed to convert. |
Defined in Data.Csv.Streaming fold :: Monoid m => Records m -> m # foldMap :: Monoid m => (a -> m) -> Records a -> m # foldr :: (a -> b -> b) -> b -> Records a -> b # foldr' :: (a -> b -> b) -> b -> Records a -> b # foldl :: (b -> a -> b) -> b -> Records a -> b # foldl' :: (b -> a -> b) -> b -> Records a -> b # foldr1 :: (a -> a -> a) -> Records a -> a # foldl1 :: (a -> a -> a) -> Records a -> a # elem :: Eq a => a -> Records a -> Bool # maximum :: Ord a => Records a -> a # minimum :: Ord a => Records a -> a # | |
Traversable Records Source # | |
Eq a => Eq (Records a) Source # | |
Show a => Show (Records a) Source # | |
NFData a => NFData (Records a) Source # | |
Defined in Data.Csv.Streaming |
Decoding records
Just like in the case of non-streaming decoding, there are two ways to convert CSV records to and from and user-defined data types: index-based conversion and name-based conversion.
Index-based record conversion
See documentation on index-based conversion in Data.Csv for more information.
Is the CSV data preceded by a header?
:: FromRecord a | |
=> HasHeader | Data contains header that should be skipped |
-> ByteString | CSV data |
-> Records a |
Efficiently deserialize CSV records in a streaming fashion.
Equivalent to
.decodeWith
defaultDecodeOptions
:: FromRecord a | |
=> DecodeOptions | Decoding options |
-> HasHeader | Data contains header that should be skipped |
-> ByteString | CSV data |
-> Records a |
Like decode
, but lets you customize how the CSV data is parsed.
Name-based record conversion
See documentation on name-based conversion in Data.Csv for more information.
:: FromNamedRecord a | |
=> ByteString | CSV data |
-> Either String (Header, Records a) |
Efficiently deserialize CSV in a streaming fashion. The data is
assumed to be preceded by a header. Returns
if
parsing the header fails. Equivalent to Left
errMsg
.decodeByNameWith
defaultDecodeOptions
:: FromNamedRecord a | |
=> DecodeOptions | Decoding options |
-> ByteString | CSV data |
-> Either String (Header, Records a) |
Like decodeByName
, but lets you customize how the CSV data is
parsed.