csv-conduit-0.6.3: A flexible, fast, conduit-based CSV parser library for Haskell.

Stabilityexperimental
MaintainerOzgun Ataman <ozataman@gmail.com>
Safe HaskellNone

Data.CSV.Conduit.Conversion

Contents

Description

This module has been shamelessly taken from Johan Tibell's nicely put together cassava package, which itself borrows the approach from Bryan OSullivans widely used aeson package.

We make the necessary adjustments and some simplifications here to bolt this parsing interface onto our underlying CSV typeclass.

Synopsis

Type conversion

newtype Only a Source

Haskell lacks a single-element tuple type, so if you CSV data with just one column you can use the Only type to represent a single-column result.

Constructors

Only 

Fields

fromOnly :: a
 

Instances

Eq a => Eq (Only a) 
Ord a => Ord (Only a) 
Read a => Read (Only a) 
Show a => Show (Only a) 
ToField a => ToRecord (Only a) 
FromField a => FromRecord (Only a) 

newtype Named a Source

A wrapper around custom haskell types that can directly be converted/parsed from an incoming CSV stream.

We define this wrapper to stop GHC from complaining about overlapping instances. Just use getNamed to get your object out of the wrapper.

Constructors

Named 

Fields

getNamed :: a
 

Instances

(FromNamedRecord a, ToNamedRecord a, CSV s (MapRow ByteString)) => CSV s (Named a)

Conversion of stream directly to/from a custom complex haskell type.

Eq a => Eq (Named a) 
Ord a => Ord (Named a) 
Read a => Read (Named a) 
Show a => Show (Named a) 

type Record = Vector ByteStringSource

A record corresponds to a single line in a CSV file.

type NamedRecord = Map ByteString ByteStringSource

A shorthand for the ByteString case of MapRow

class FromRecord a whereSource

A type that can be converted from a single CSV record, with the possibility of failure.

When writing an instance, use empty, mzero, or fail to make a conversion fail, e.g. if a Record has the wrong number of columns.

Given this example data:

 John,56
 Jane,55

here's an example type and instance:

 data Person = Person { name :: !Text, age :: !Int }

 instance FromRecord Person where
     parseRecord v
         | length v == 2 = Person <$>
                           v .! 0 <*>
                           v .! 1
         | otherwise     = mzero

Instances

FromField a => FromRecord [a] 
FromField a => FromRecord (Vector a) 
(FromField a, Unbox a) => FromRecord (Vector a) 
FromField a => FromRecord (Only a) 
(FromField a, FromField b) => FromRecord (a, b) 
(FromField a, FromField b, FromField c) => FromRecord (a, b, c) 
(FromField a, FromField b, FromField c, FromField d) => FromRecord (a, b, c, d) 
(FromField a, FromField b, FromField c, FromField d, FromField e) => FromRecord (a, b, c, d, e) 
(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f) => FromRecord (a, b, c, d, e, f) 
(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g) => FromRecord (a, b, c, d, e, f, g) 

class FromNamedRecord a whereSource

A type that can be converted from a single CSV record, with the possibility of failure.

When writing an instance, use empty, mzero, or fail to make a conversion fail, e.g. if a Record has the wrong number of columns.

Given this example data:

 name,age
 John,56
 Jane,55

here's an example type and instance:

 {-# LANGUAGE OverloadedStrings #-}

 data Person = Person { name :: !Text, age :: !Int }

 instance FromRecord Person where
     parseNamedRecord m = Person <$>
                          m .: "name" <*>
                          m .: "age"

Note the use of the OverloadedStrings language extension which enables ByteString values to be written as string literals.

class ToNamedRecord a whereSource

A type that can be converted to a single CSV record.

An example type and instance:

 data Person = Person { name :: !Text, age :: !Int }

 instance ToRecord Person where
     toNamedRecord (Person name age) = namedRecord [
         "name" .= name, "age" .= age]

Instances

class FromField a whereSource

A type that can be converted from a single CSV field, with the possibility of failure.

When writing an instance, use empty, mzero, or fail to make a conversion fail, e.g. if a Field can't be converted to the given type.

Example type and instance:

 {-# LANGUAGE OverloadedStrings #-}

 data Color = Red | Green | Blue

 instance FromField Color where
     parseField s
         | s == "R"  = pure Red
         | s == "G"  = pure Green
         | s == "B"  = pure Blue
         | otherwise = mzero

Methods

parseField :: Field -> Parser aSource

Instances

FromField Char

Assumes UTF-8 encoding.

FromField Double

Accepts same syntax as rational.

FromField Float

Accepts same syntax as rational.

FromField Int

Accepts a signed decimal number.

FromField Int8

Accepts a signed decimal number.

FromField Int16

Accepts a signed decimal number.

FromField Int32

Accepts a signed decimal number.

FromField Int64

Accepts a signed decimal number.

FromField Integer

Accepts a signed decimal number.

FromField Word

Accepts an unsigned decimal number.

FromField Word8

Accepts an unsigned decimal number.

FromField Word16

Accepts an unsigned decimal number.

FromField Word32

Accepts an unsigned decimal number.

FromField Word64

Accepts an unsigned decimal number.

FromField ()

Ignores the Field. Always succeeds.

FromField ByteString 
FromField ByteString 
FromField Text

Assumes UTF-8 encoding. Fails on invalid byte sequences.

FromField Text

Assumes UTF-8 encoding. Fails on invalid byte sequences.

FromField [Char]

Assumes UTF-8 encoding. Fails on invalid byte sequences.

FromField a => FromField (Maybe a)

Nothing if the Field is empty, Just otherwise.

class ToRecord a whereSource

A type that can be converted to a single CSV record.

An example type and instance:

 data Person = Person { name :: !Text, age :: !Int }

 instance ToRecord Person where
     toRecord (Person name age) = record [
         toField name, toField age]

Outputs data on this form:

 John,56
 Jane,55

Methods

toRecord :: a -> RecordSource

Instances

ToField a => ToRecord [a] 
ToField a => ToRecord (Vector a) 
(ToField a, Unbox a) => ToRecord (Vector a) 
ToField a => ToRecord (Only a) 
(ToField a, ToField b) => ToRecord (a, b) 
(ToField a, ToField b, ToField c) => ToRecord (a, b, c) 
(ToField a, ToField b, ToField c, ToField d) => ToRecord (a, b, c, d) 
(ToField a, ToField b, ToField c, ToField d, ToField e) => ToRecord (a, b, c, d, e) 
(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f) => ToRecord (a, b, c, d, e, f) 
(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g) => ToRecord (a, b, c, d, e, f, g) 

class ToField a whereSource

A type that can be converted to a single CSV field.

Example type and instance:

 {-# LANGUAGE OverloadedStrings #-}

 data Color = Red | Green | Blue

 instance ToField Color where
     toField Red   = "R"
     toField Green = "G"
     toField Blue  = "B"

Methods

toField :: a -> FieldSource

Instances

ToField Char

Uses UTF-8 encoding.

ToField Double

Uses decimal notation or scientific notation, depending on the number.

ToField Float

Uses decimal notation or scientific notation, depending on the number.

ToField Int

Uses decimal encoding with optional sign.

ToField Int8

Uses decimal encoding with optional sign.

ToField Int16

Uses decimal encoding with optional sign.

ToField Int32

Uses decimal encoding with optional sign.

ToField Int64

Uses decimal encoding with optional sign.

ToField Integer

Uses decimal encoding with optional sign.

ToField Word

Uses decimal encoding.

ToField Word8

Uses decimal encoding.

ToField Word16

Uses decimal encoding.

ToField Word32

Uses decimal encoding.

ToField Word64

Uses decimal encoding.

ToField ByteString 
ToField ByteString 
ToField Text

Uses UTF-8 encoding.

ToField Text

Uses UTF-8 encoding.

ToField [Char]

Uses UTF-8 encoding.

ToField a => ToField (Maybe a)

Nothing is encoded as an empty field.

Parser

data Parser a Source

Conversion of a field to a value might fail e.g. if the field is malformed. This possibility is captured by the Parser type, which lets you compose several field conversions together in such a way that if any of them fail, the whole record conversion fails.

runParser :: Parser a -> Either String aSource

Run a Parser, returning either Left errMsg or Right result. Forces the value in the Left or Right constructors to weak head normal form.

You most likely won't need to use this function directly, but it's included for completeness.

Accessors

index :: FromField a => Record -> Int -> Parser aSource

Retrieve the nth field in the given record. The result is empty if the value cannot be converted to the desired type. Raises an exception if the index is out of bounds.

index is a simple convenience function that is equivalent to parseField (v ! idx). If you're certain that the index is not out of bounds, using unsafeIndex is somewhat faster.

(.!) :: FromField a => Record -> Int -> Parser aSource

Alias for index.

unsafeIndex :: FromField a => Record -> Int -> Parser aSource

Like index but without bounds checking.

lookup :: FromField a => NamedRecord -> ByteString -> Parser aSource

Retrieve a field in the given record by name. The result is empty if the field is missing or if the value cannot be converted to the desired type.

namedField :: ToField a => ByteString -> a -> (ByteString, ByteString)Source

Construct a pair from a name and a value. For use with namedRecord.

record :: [ByteString] -> RecordSource

Construct a record from a list of ByteStrings. Use toField to convert values to ByteStrings for use with record.

namedRecord :: [(ByteString, ByteString)] -> NamedRecordSource

Construct a named record from a list of name-value ByteString pairs. Use .= to construct such a pair from a name and a value.