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

CopyrightOzgun Ataman Johan Tibell
LicenseBSD3
MaintainerOzgun Ataman <ozataman@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

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

Instances

Eq a => Eq (Only a) Source # 

Methods

(==) :: Only a -> Only a -> Bool #

(/=) :: Only a -> Only a -> Bool #

Ord a => Ord (Only a) Source # 

Methods

compare :: Only a -> Only a -> Ordering #

(<) :: Only a -> Only a -> Bool #

(<=) :: Only a -> Only a -> Bool #

(>) :: Only a -> Only a -> Bool #

(>=) :: Only a -> Only a -> Bool #

max :: Only a -> Only a -> Only a #

min :: Only a -> Only a -> Only a #

Read a => Read (Only a) Source # 
Show a => Show (Only a) Source # 

Methods

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

show :: Only a -> String #

showList :: [Only a] -> ShowS #

ToField a => ToRecord (Only a) Source # 

Methods

toRecord :: Only a -> Record Source #

FromField a => FromRecord (Only a) Source # 

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

Instances

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

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

Eq a => Eq (Named a) Source # 

Methods

(==) :: Named a -> Named a -> Bool #

(/=) :: Named a -> Named a -> Bool #

Ord a => Ord (Named a) Source # 

Methods

compare :: Named a -> Named a -> Ordering #

(<) :: Named a -> Named a -> Bool #

(<=) :: Named a -> Named a -> Bool #

(>) :: Named a -> Named a -> Bool #

(>=) :: Named a -> Named a -> Bool #

max :: Named a -> Named a -> Named a #

min :: Named a -> Named a -> Named a #

Read a => Read (Named a) Source # 
Show a => Show (Named a) Source # 

Methods

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

show :: Named a -> String #

showList :: [Named a] -> ShowS #

type Record = Vector ByteString Source #

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

type NamedRecord = Map ByteString ByteString Source #

A shorthand for the ByteString case of MapRow

class FromRecord a where Source #

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

Methods

parseRecord :: Record -> Parser a Source #

parseRecord :: (Generic a, GFromRecord (Rep a)) => Record -> Parser a Source #

Instances

FromField a => FromRecord [a] Source # 

Methods

parseRecord :: Record -> Parser [a] Source #

FromField a => FromRecord (Vector a) Source # 
(FromField a, Unbox a) => FromRecord (Vector a) Source # 
FromField a => FromRecord (Only a) Source # 
(FromField a, FromField b) => FromRecord (a, b) Source # 

Methods

parseRecord :: Record -> Parser (a, b) Source #

(FromField a, FromField b, FromField c) => FromRecord (a, b, c) Source # 

Methods

parseRecord :: Record -> Parser (a, b, c) Source #

(FromField a, FromField b, FromField c, FromField d) => FromRecord (a, b, c, d) Source # 

Methods

parseRecord :: Record -> Parser (a, b, c, d) Source #

(FromField a, FromField b, FromField c, FromField d, FromField e) => FromRecord (a, b, c, d, e) Source # 

Methods

parseRecord :: Record -> Parser (a, b, c, d, e) Source #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f) => FromRecord (a, b, c, d, e, f) Source # 

Methods

parseRecord :: Record -> Parser (a, b, c, d, e, f) Source #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g) => FromRecord (a, b, c, d, e, f, g) Source # 

Methods

parseRecord :: Record -> Parser (a, b, c, d, e, f, g) Source #

class FromNamedRecord a where Source #

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.

Methods

parseNamedRecord :: NamedRecord -> Parser a Source #

parseNamedRecord :: (Generic a, GFromNamedRecord (Rep a)) => NamedRecord -> Parser a Source #

class ToNamedRecord a where Source #

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]

class FromField a where Source #

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

Minimal complete definition

parseField

Methods

parseField :: Field -> Parser a Source #

Instances

FromField Char Source #

Assumes UTF-8 encoding.

FromField Double Source #

Accepts same syntax as rational.

FromField Float Source #

Accepts same syntax as rational.

FromField Int Source #

Accepts a signed decimal number.

FromField Int8 Source #

Accepts a signed decimal number.

FromField Int16 Source #

Accepts a signed decimal number.

FromField Int32 Source #

Accepts a signed decimal number.

FromField Int64 Source #

Accepts a signed decimal number.

FromField Integer Source #

Accepts a signed decimal number.

FromField Word Source #

Accepts an unsigned decimal number.

FromField Word8 Source #

Accepts an unsigned decimal number.

FromField Word16 Source #

Accepts an unsigned decimal number.

FromField Word32 Source #

Accepts an unsigned decimal number.

FromField Word64 Source #

Accepts an unsigned decimal number.

FromField () Source #

Ignores the Field. Always succeeds.

Methods

parseField :: Field -> Parser () Source #

FromField ByteString Source # 
FromField ByteString Source # 
FromField Text Source #

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

FromField Text Source #

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

FromField [Char] Source #

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

FromField a => FromField (Maybe a) Source #

Nothing if the Field is empty, Just otherwise.

Methods

parseField :: Field -> Parser (Maybe a) Source #

class ToRecord a where Source #

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 -> Record Source #

toRecord :: (Generic a, GToRecord (Rep a) Field) => a -> Record Source #

Instances

ToField a => ToRecord [a] Source # 

Methods

toRecord :: [a] -> Record Source #

ToField a => ToRecord (Vector a) Source # 

Methods

toRecord :: Vector a -> Record Source #

(ToField a, Unbox a) => ToRecord (Vector a) Source # 

Methods

toRecord :: Vector a -> Record Source #

ToField a => ToRecord (Only a) Source # 

Methods

toRecord :: Only a -> Record Source #

(ToField a, ToField b) => ToRecord (a, b) Source # 

Methods

toRecord :: (a, b) -> Record Source #

(ToField a, ToField b, ToField c) => ToRecord (a, b, c) Source # 

Methods

toRecord :: (a, b, c) -> Record Source #

(ToField a, ToField b, ToField c, ToField d) => ToRecord (a, b, c, d) Source # 

Methods

toRecord :: (a, b, c, d) -> Record Source #

(ToField a, ToField b, ToField c, ToField d, ToField e) => ToRecord (a, b, c, d, e) Source # 

Methods

toRecord :: (a, b, c, d, e) -> Record Source #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f) => ToRecord (a, b, c, d, e, f) Source # 

Methods

toRecord :: (a, b, c, d, e, f) -> Record Source #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g) => ToRecord (a, b, c, d, e, f, g) Source # 

Methods

toRecord :: (a, b, c, d, e, f, g) -> Record Source #

class ToField a where Source #

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"

Minimal complete definition

toField

Methods

toField :: a -> Field Source #

Instances

ToField Char Source #

Uses UTF-8 encoding.

Methods

toField :: Char -> Field Source #

ToField Double Source #

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

Methods

toField :: Double -> Field Source #

ToField Float Source #

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

Methods

toField :: Float -> Field Source #

ToField Int Source #

Uses decimal encoding with optional sign.

Methods

toField :: Int -> Field Source #

ToField Int8 Source #

Uses decimal encoding with optional sign.

Methods

toField :: Int8 -> Field Source #

ToField Int16 Source #

Uses decimal encoding with optional sign.

Methods

toField :: Int16 -> Field Source #

ToField Int32 Source #

Uses decimal encoding with optional sign.

Methods

toField :: Int32 -> Field Source #

ToField Int64 Source #

Uses decimal encoding with optional sign.

Methods

toField :: Int64 -> Field Source #

ToField Integer Source #

Uses decimal encoding with optional sign.

ToField Word Source #

Uses decimal encoding.

Methods

toField :: Word -> Field Source #

ToField Word8 Source #

Uses decimal encoding.

Methods

toField :: Word8 -> Field Source #

ToField Word16 Source #

Uses decimal encoding.

Methods

toField :: Word16 -> Field Source #

ToField Word32 Source #

Uses decimal encoding.

Methods

toField :: Word32 -> Field Source #

ToField Word64 Source #

Uses decimal encoding.

Methods

toField :: Word64 -> Field Source #

ToField ByteString Source # 
ToField ByteString Source # 
ToField Text Source #

Uses UTF-8 encoding.

Methods

toField :: Text -> Field Source #

ToField Text Source #

Uses UTF-8 encoding.

Methods

toField :: Text -> Field Source #

ToField [Char] Source #

Uses UTF-8 encoding.

Methods

toField :: [Char] -> Field Source #

ToField a => ToField (Maybe a) Source #

Nothing is encoded as an empty field.

Methods

toField :: Maybe a -> Field Source #

type Field = ByteString Source #

A single field within a record.

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.

Instances

Monad Parser Source # 

Methods

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

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

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser Source # 

Methods

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

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

Applicative Parser Source # 

Methods

pure :: a -> Parser a #

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

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

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

Alternative Parser Source # 

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

MonadPlus Parser Source # 

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

Monoid (Parser a) Source # 

Methods

mempty :: Parser a #

mappend :: Parser a -> Parser a -> Parser a #

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

runParser :: Parser a -> Either String a Source #

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 a Source #

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 a infixl 9 Source #

Alias for index.

unsafeIndex :: FromField a => Record -> Int -> Parser a Source #

Like index but without bounds checking.

lookup :: FromField a => NamedRecord -> ByteString -> Parser a Source #

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] -> Record Source #

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

namedRecord :: [(ByteString, ByteString)] -> NamedRecord Source #

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