cassava-0.5.0.0: A CSV parsing and encoding library

Safe HaskellNone
LanguageHaskell2010

Data.Csv.Incremental

Contents

Description

This module allows for incremental decoding and encoding of CSV data. This is useful if you e.g. want to interleave I/O with parsing or if you want finer grained control over how you deal with type conversion errors.

Decoding example:

main :: IO ()
main = withFile "salaries.csv" ReadMode $ \ csvFile -> do
    let loop !_ (Fail _ errMsg) = putStrLn errMsg >> exitFailure
        loop acc (Many rs k)    = loop (acc + sumSalaries rs) =<< feed k
        loop acc (Done rs)      = putStrLn $ "Total salaries: " ++
                                  show (sumSalaries rs + acc)

        feed k = do
            isEof <- hIsEOF csvFile
            if isEof
                then return $ k B.empty
                else k `fmap` B.hGetSome csvFile 4096
    loop 0 (decode NoHeader)
  where
    sumSalaries rs = sum [salary | Right (_ :: String, salary :: Int) <- rs]

Encoding example:

data Person = Person { name   :: !String, salary :: !Int }
    deriving Generic

instance FromNamedRecord Person
instance ToNamedRecord Person
instance DefaultOrdered Person

persons :: [Person]
persons = [Person "John" 50000, Person "Jane" 60000]

main :: IO ()
main = putStrLn $ encodeDefaultOrderedByName (go persons)
  where
    go (x:xs) = encodeNamedRecord x <> go xs

Synopsis

Decoding

data HeaderParser a Source #

An incremental parser that when fed data eventually returns a parsed Header, or an error.

Constructors

FailH !ByteString String

The input data was malformed. The first field contains any unconsumed input and second field contains information about the parse error.

PartialH (ByteString -> HeaderParser a)

The parser needs more input data before it can produce a result. Use an empty string to indicate that no more input data is available. If fed an 'B.empty string', the continuation is guaranteed to return either FailH or DoneH.

DoneH !Header a

The parse succeeded and produced the given Header.

Instances

decodeHeader :: HeaderParser ByteString Source #

Parse a CSV header in an incremental fashion. When done, the HeaderParser returns any unconsumed input in the second field of the DoneH constructor.

decodeHeaderWith :: DecodeOptions -> HeaderParser ByteString Source #

Like decodeHeader, but lets you customize how the CSV data is parsed.

Just like in the case of non-incremental decoding, there are two ways to convert CSV records to and from and user-defined data types: index-based conversion and name-based conversion.

data Parser a Source #

An incremental parser that when fed data eventually produces some parsed records, converted to the desired type, or an error in case of malformed input data.

Constructors

Fail !ByteString String

The input data was malformed. The first field contains any unconsumed input and second field contains information about the parse error.

Many [Either String a] (ByteString -> Parser a)

The parser parsed and converted zero or more records. Any records that failed type conversion are returned as Left errMsg and the rest as Right val. Feed a ByteString to the continuation to continue parsing. Use an empty string to indicate that no more input data is available. If fed an empty string, the continuation is guaranteed to return either Fail or Done.

Done [Either String a]

The parser parsed and converted some records. Any records that failed type conversion are returned as Left errMsg and the rest as Right val.

Instances

Functor Parser Source # 

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

Show a => Show (Parser a) Source # 

Methods

showsPrec :: Int -> Parser a -> ShowS #

show :: Parser a -> String #

showList :: [Parser a] -> ShowS #

Index-based record conversion

See documentation on index-based conversion in Data.Csv for more information.

data HasHeader Source #

Is the CSV data preceded by a header?

Constructors

HasHeader

The CSV data is preceded by a header

NoHeader

The CSV data is not preceded by a header

decode Source #

Arguments

:: FromRecord a 
=> HasHeader

Data contains header that should be skipped

-> Parser a 

Efficiently deserialize CSV in an incremental fashion. Equivalent to decodeWith defaultDecodeOptions.

decodeWith Source #

Arguments

:: FromRecord a 
=> DecodeOptions

Decoding options

-> HasHeader

Data contains header that should be skipped

-> Parser 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.

decodeByName :: FromNamedRecord a => HeaderParser (Parser a) Source #

Efficiently deserialize CSV in an incremental fashion. The data is assumed to be preceeded by a header. Returns a HeaderParser that when done produces a Parser for parsing the actual records. Equivalent to decodeByNameWith defaultDecodeOptions.

decodeByNameWith Source #

Arguments

:: FromNamedRecord a 
=> DecodeOptions

Decoding options

-> HeaderParser (Parser a) 

Like decodeByName, but lets you customize how the CSV data is parsed.

Encoding

Index-based record conversion

See documentation on index-based conversion in Data.Csv for more information.

encode :: ToRecord a => Builder a -> ByteString Source #

Efficiently serialize records in an incremental fashion. Equivalent to encodeWith defaultEncodeOptions.

encodeWith :: ToRecord a => EncodeOptions -> Builder a -> ByteString Source #

Like encode, but lets you customize how the CSV data is encoded.

encodeRecord :: ToRecord a => a -> Builder a Source #

Encode a single record.

data Builder a Source #

A builder for building the CSV data incrementally. Just like the ByteString builder, this builder should be used in a right-associative, foldr style. Using <> to compose builders in a left-associative, foldl' style makes the building not be incremental.

Instances

Semigroup (Builder a) Source # 

Methods

(<>) :: Builder a -> Builder a -> Builder a #

sconcat :: NonEmpty (Builder a) -> Builder a #

stimes :: Integral b => b -> Builder a -> Builder a #

Monoid (Builder a) Source # 

Methods

mempty :: Builder a #

mappend :: Builder a -> Builder a -> Builder a #

mconcat :: [Builder a] -> Builder a #

Name-based record conversion

See documentation on name-based conversion in Data.Csv for more information.

encodeByName :: ToNamedRecord a => Header -> NamedBuilder a -> ByteString Source #

Efficiently serialize named records in an incremental fashion, including the leading header. Equivalent to encodeWith defaultEncodeOptions. The header is written before any records and dictates the field order.

encodeDefaultOrderedByName :: (DefaultOrdered a, ToNamedRecord a) => NamedBuilder a -> ByteString Source #

Like encodeByName, but header and field order is dictated by the headerOrder method.

encodeByNameWith :: ToNamedRecord a => EncodeOptions -> Header -> NamedBuilder a -> ByteString Source #

Like encodeByName, but lets you customize how the CSV data is encoded.

encodeDefaultOrderedByNameWith :: forall a. (DefaultOrdered a, ToNamedRecord a) => EncodeOptions -> NamedBuilder a -> ByteString Source #

Like encodeDefaultOrderedByName, but lets you customize how the CSV data is encoded.

encodeNamedRecord :: ToNamedRecord a => a -> NamedBuilder a Source #

Encode a single named record.

data NamedBuilder a Source #

A builder for building the CSV data incrementally. Just like the ByteString builder, this builder should be used in a right-associative, foldr style. Using <> to compose builders in a left-associative, foldl' style makes the building not be incremental.