cassava-0.5.1.0: A CSV parsing and encoding library

Safe HaskellNone
LanguageHaskell2010

Data.Csv

Contents

Description

This module implements encoding and decoding of comma-separated values (CSV) data. The implementation is RFC 4180 compliant, with the following extensions:

  • Empty lines are ignored.
  • Non-escaped fields may contain any characters except double-quotes, commas, carriage returns, and newlines.
  • Escaped fields may contain any characters (but double-quotes need to be escaped).

Synopsis

Usage examples

Encoding standard Haskell types:

>>> :set -XOverloadedStrings
>>> import Data.Text (Text)
>>> encode [("John" :: Text, 27 :: Int), ("Jane", 28)]
"John,27\r\nJane,28\r\n"

Since we enabled the -XOverloadedStrings extension, string literals are polymorphic and we have to supply a type signature as the compiler couldn't deduce which string type (i.e. String, ShortText, or Text) we want to use. In most cases type inference will infer the type from the context and you can omit type signatures.

Decoding standard Haskell types:

>>> import Data.Vector (Vector)
>>> decode NoHeader "John,27\r\nJane,28\r\n" :: Either String (Vector (Text, Int))
Right [("John",27),("Jane",28)]

We pass NoHeader as the first argument to indicate that the CSV input data isn't preceded by a header.

In practice, the return type of decode rarely needs to be given, as it can often be inferred from the context.

Encoding and decoding custom data types

To encode and decode your own data types you need to defined instances of either ToRecord and FromRecord or ToNamedRecord and FromNamedRecord. The former is used for encoding/decoding using the column index and the latter using the column name.

There are two ways to to define these instances, either by manually defining them or by using GHC generics to derive them automatically.

Index-based record conversion

GHC.Generics-derived:

{-# LANGUAGE DeriveGeneric #-}

import Data.Text    (Text)
import GHC.Generics (Generic)

data Person = Person { name :: !Text , salary :: !Int }
    deriving (Generic, Show)

instance FromRecord Person
instance ToRecord Person

Manually defined:

import Control.Monad (mzero)

data Person = Person { name :: !Text , salary :: !Int }
    deriving (Show)

instance FromRecord Person where
    parseRecord v
        | length v == 2 = Person <$> v .! 0 <*> v .! 1
        | otherwise     = mzero
instance ToRecord Person where
    toRecord (Person name' age') = record [
        toField name', toField age']

We can now use e.g. encode and decode to encode and decode our data type.

Encoding:

>>> encode [Person ("John" :: Text) 27]
"John,27\r\n"

Decoding:

>>> decode NoHeader "John,27\r\n" :: Either String (Vector Person)
Right [Person {name = "John", salary = 27}]

Name-based record conversion

GHC.Generics-derived:

{-# LANGUAGE DeriveGeneric #-}

import Data.Text    (Text)
import GHC.Generics (Generic)

data Person = Person { name :: !Text , salary :: !Int }
    deriving (Generic, Show)

instance FromNamedRecord Person
instance ToNamedRecord Person
instance DefaultOrdered Person

Manually defined:

data Person = Person { name :: !Text , salary :: !Int }
    deriving (Show)

instance FromNamedRecord Person where
    parseNamedRecord m = Person <$> m .: "name" <*> m .: "salary"
instance ToNamedRecord Person where
    toNamedRecord (Person name salary) = namedRecord [
        "name" .= name, "salary" .= salary]
instance DefaultOrdered Person where
    headerOrder _ = header ["name", "salary"]

We can now use e.g. encodeDefaultOrderedByName (or encodeByName with an explicit header order) and decodeByName to encode and decode our data type.

Encoding:

>>> encodeDefaultOrderedByName [Person ("John" :: Text) 27]
"name,salary\r\nJohn,27\r\n"

Decoding:

>>> decodeByName "name,salary\r\nJohn,27\r\n" :: Either String (Header, Vector Person)
Right (["name","salary"],[Person {name = "John", salary = 27}])

Treating CSV data as opaque byte strings

Sometimes you might want to work with a CSV file which contents is unknown to you. For example, you might want remove the second column of a file without knowing anything about its content. To parse a CSV file to a generic representation, just convert each record to a Vector ByteString value, like so:

>>> import Data.ByteString (ByteString)
>>> decode NoHeader "John,27\r\nJane,28\r\n" :: Either String (Vector (Vector ByteString))
Right [["John","27"],["Jane","28"]]

As the example output above shows, all the fields are returned as uninterpreted ByteString values.

Custom type conversions for fields

Most of the time the existing FromField and ToField instances do what you want. However, if you need to parse a different format (e.g. hex) but use a type (e.g. Int) for which there's already a FromField instance, you need to use a newtype. Example:

newtype Hex = Hex Int

parseHex :: ByteString -> Parser Int
parseHex = ...

instance FromField Hex where
    parseField s = Hex <$> parseHex s

Other than giving an explicit type signature, you can pattern match on the newtype constructor to indicate which type conversion you want to have the library use:

case decode NoHeader "0xff,0xaa\r\n0x11,0x22\r\n" of
    Left err -> putStrLn err
    Right v  -> forM_ v $ \ (Hex val1, Hex val2) ->
        print (val1, val2)

If a field might be in one several different formats, you can use a newtype to normalize the result:

newtype HexOrDecimal = HexOrDecimal Int

instance FromField DefaultToZero where
    parseField s = case runParser (parseField s :: Parser Hex) of
        Left err -> HexOrDecimal <$> parseField s  -- Uses Int instance
        Right n  -> pure $ HexOrDecimal n

You can use the unit type, (), to ignore a column. The parseField method for () doesn't look at the Field and thus always decodes successfully. Note that it lacks a corresponding ToField instance. Example:

case decode NoHeader "foo,1\r\nbar,22" of
    Left  err -> putStrLn err
    Right v   -> forM_ v $ \ ((), i) -> print (i :: Int)

Dealing with bad data

If your input might contain invalid fields, you can write a custom FromField instance to deal with them. Example:

newtype DefaultToZero = DefaultToZero Int

instance FromField DefaultToZero where
    parseField s = case runParser (parseField s) of
        Left err -> pure $ DefaultToZero 0
        Right n  -> pure $ DefaultToZero n

Encoding and decoding

Encoding and decoding is a two step process. To encode a value, it is first converted to a generic representation, using either ToRecord or ToNamedRecord. The generic representation is then encoded as CSV data. To decode a value the process is reversed and either FromRecord or FromNamedRecord is used instead. Both these steps are combined in the encode and decode functions.

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

-> ByteString

CSV data

-> Either String (Vector a) 

Efficiently deserialize CSV records from a lazy ByteString. If this fails due to incomplete or invalid input, Left msg is returned. Equivalent to decodeWith defaultDecodeOptions.

decodeByName Source #

Arguments

:: FromNamedRecord a 
=> ByteString

CSV data

-> Either String (Header, Vector a) 

Efficiently deserialize CSV records from a lazy ByteString. If this fails due to incomplete or invalid input, Left msg is returned. The data is assumed to be preceeded by a header. Equivalent to decodeByNameWith defaultDecodeOptions.

encode :: ToRecord a => [a] -> ByteString Source #

Efficiently serialize CSV records as a lazy ByteString.

encodeByName :: ToNamedRecord a => Header -> [a] -> ByteString Source #

Efficiently serialize CSV records as a lazy ByteString. The header is written before any records and dictates the field order.

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

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

class DefaultOrdered a where Source #

A type that has a default field order when converted to CSV. This class lets you specify how to get the headers to use for a record type that's an instance of ToNamedRecord.

To derive an instance, the type is required to only have one constructor and that constructor must have named fields (also known as selectors) for all fields.

Right: data Foo = Foo { foo :: !Int }

Wrong: data Bar = Bar Int

If you try to derive an instance using GHC generics and your type doesn't have named fields, you will get an error along the lines of:

<interactive>:9:10:
    No instance for (DefaultOrdered (M1 S NoSelector (K1 R Char) ()))
      arising from a use of ‘Data.Csv.Conversion.$gdmheader’
    In the expression: Data.Csv.Conversion.$gdmheader
    In an equation for ‘header’:
        header = Data.Csv.Conversion.$gdmheader
    In the instance declaration for ‘DefaultOrdered Foo’

Methods

headerOrder :: a -> Header Source #

The header order for this record. Should include the names used in the NamedRecord returned by toNamedRecord. Pass undefined as the argument, together with a type annotation e.g. headerOrder (undefined :: MyRecord).

headerOrder :: (Generic a, GToNamedRecordHeader (Rep a)) => a -> Header Source #

The header order for this record. Should include the names used in the NamedRecord returned by toNamedRecord. Pass undefined as the argument, together with a type annotation e.g. headerOrder (undefined :: MyRecord).

Encoding and decoding options

These functions can be used to control how data is encoded and decoded. For example, they can be used to encode data in a tab-separated format instead of in a comma-separated format.

data DecodeOptions Source #

Options that controls how data is decoded. These options can be used to e.g. decode tab-separated data instead of comma-separated data.

To avoid having your program stop compiling when new fields are added to DecodeOptions, create option records by overriding values in defaultDecodeOptions. Example:

myOptions = defaultDecodeOptions {
      decDelimiter = fromIntegral (ord '\t')
    }

Constructors

DecodeOptions 

Fields

defaultDecodeOptions :: DecodeOptions Source #

Decoding options for parsing CSV files.

decodeWith Source #

Arguments

:: FromRecord a 
=> DecodeOptions

Decoding options

-> HasHeader

Data contains header that should be skipped

-> ByteString

CSV data

-> Either String (Vector a) 

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

decodeByNameWith Source #

Arguments

:: FromNamedRecord a 
=> DecodeOptions

Decoding options

-> ByteString

CSV data

-> Either String (Header, Vector a) 

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

data EncodeOptions Source #

Options that controls how data is encoded. These options can be used to e.g. encode data in a tab-separated format instead of in a comma-separated format.

To avoid having your program stop compiling when new fields are added to EncodeOptions, create option records by overriding values in defaultEncodeOptions. Example:

myOptions = defaultEncodeOptions {
      encDelimiter = fromIntegral (ord '\t')
    }

N.B. The encDelimiter must not be the quote character (i.e. ") or one of the record separator characters (i.e. \n or \r).

Constructors

EncodeOptions 

Fields

data Quoting Source #

Should quoting be applied to fields, and at which level?

Constructors

QuoteNone

No quotes.

QuoteMinimal

Quotes according to RFC 4180.

QuoteAll

Always quote.

defaultEncodeOptions :: EncodeOptions Source #

Encoding options for CSV files.

encodeWith :: ToRecord a => EncodeOptions -> [a] -> ByteString Source #

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

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

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

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

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

Core CSV types

type Csv = Vector Record Source #

CSV data represented as a Haskell vector of vector of bytestrings.

type Record = Vector Field Source #

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

type Field = ByteString Source #

A single field within a record.

type Header = Vector Name Source #

The header corresponds to the first line a CSV file. Not all CSV files have a header.

type Name = ByteString Source #

A header has one or more names, describing the data in the column following the name.

type NamedRecord = HashMap ByteString ByteString Source #

A record corresponds to a single line in a CSV file, indexed by the column name rather than the column index.

Type conversion

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

Index-based conversion lets you convert CSV records to and from user-defined data types by referring to a field's position (its index) in the record. The first column in a CSV file is given index 0, the second index 1, and so on.

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

Instances

FromField a => FromRecord [a] Source # 

Methods

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

FromField a => FromRecord (Only a) Source # 
FromField a => FromRecord (Vector a) Source # 
(FromField a, Unbox a) => FromRecord (Vector 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 #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l) => FromRecord (a, b, c, d, e, f, g, h, i, j, k, l) Source # 

Methods

parseRecord :: Record -> Parser (a, b, c, d, e, f, g, h, i, j, k, l) Source #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m) => FromRecord (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 

Methods

parseRecord :: Record -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n) => FromRecord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 

Methods

parseRecord :: Record -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o) => FromRecord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 

Methods

parseRecord :: Record -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

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 #

MonadFail Parser Source #

Since: 0.5.0.0

Methods

fail :: String -> 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 #

Semigroup (Parser a) Source #

Since: 0.5.0.0

Methods

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

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

stimes :: Integral b => b -> 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.

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.

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 #

Convert a value to a record.

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

Convert a value to a record.

Instances

ToField a => ToRecord [a] Source # 

Methods

toRecord :: [a] -> Record Source #

ToField a => ToRecord (Only a) Source # 

Methods

toRecord :: Only 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, 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 #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l) => ToRecord (a, b, c, d, e, f, g, h, i, j, k, l) Source # 

Methods

toRecord :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Record Source #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m) => ToRecord (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 

Methods

toRecord :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Record Source #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n) => ToRecord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 

Methods

toRecord :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Record Source #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n, ToField o) => ToRecord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 

Methods

toRecord :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Record Source #

record :: [ByteString] -> Record Source #

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

newtype Only a :: * -> * #

The 1-tuple type or single-value "collection".

This type is structurally equivalent to the Identity type, but its intent is more about serving as the anonymous 1-tuple type missing from Haskell for attaching typeclass instances.

Parameter usage example:

encodeSomething (Only (42::Int))

Result usage example:

xs <- decodeSomething
forM_ xs $ \(Only id) -> {- ... -}

Constructors

Only 

Fields

Instances

Functor Only 

Methods

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

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

Eq a => Eq (Only a) 

Methods

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

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

Data a => Data (Only a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Only a -> c (Only a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Only a) #

toConstr :: Only a -> Constr #

dataTypeOf :: Only a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Only a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Only a)) #

gmapT :: (forall b. Data b => b -> b) -> Only a -> Only a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Only a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Only a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Only a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Only a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

Ord a => Ord (Only a) 

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) 
Show a => Show (Only a) 

Methods

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

show :: Only a -> String #

showList :: [Only a] -> ShowS #

Generic (Only a) 

Associated Types

type Rep (Only a) :: * -> * #

Methods

from :: Only a -> Rep (Only a) x #

to :: Rep (Only a) x -> Only a #

NFData a => NFData (Only a) 

Methods

rnf :: Only a -> () #

ToField a => ToRecord (Only a) Source # 

Methods

toRecord :: Only a -> Record Source #

FromField a => FromRecord (Only a) Source # 
type Rep (Only a) 
type Rep (Only a) = D1 (MetaData "Only" "Data.Tuple.Only" "Only-0.1-1dkiXHtbc8zGqo2Q6b73I6" True) (C1 (MetaCons "Only" PrefixI True) (S1 (MetaSel (Just Symbol "fromOnly") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

Name-based record conversion

Name-based conversion lets you convert CSV records to and from user-defined data types by referring to a field's name. The names of the fields are defined by the first line in the file, also known as the header. Name-based conversion is more robust to changes in the file structure e.g. to reording or addition of columns, but can be a bit slower.

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

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.

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 ToNamedRecord Person where
    toNamedRecord (Person name age) = namedRecord [
        "name" .= name, "age" .= age]

Methods

toNamedRecord :: a -> NamedRecord Source #

Convert a value to a named record.

toNamedRecord :: (Generic a, GToRecord (Rep a) (ByteString, ByteString)) => a -> NamedRecord Source #

Convert a value to a named record.

Instances

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.

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

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

header :: [ByteString] -> Header Source #

Construct a header from a list of ByteStrings.

Field conversion

The FromField and ToField classes define how to convert between Fields and values you care about (e.g. Ints). Most of the time you don't need to write your own instances as the standard ones cover most use cases.

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. Ignores whitespace.

FromField Float Source #

Accepts same syntax as rational. Ignores whitespace.

FromField Int Source #

Accepts a signed decimal number. Ignores whitespace.

FromField Int8 Source #

Accepts a signed decimal number. Ignores whitespace.

FromField Int16 Source #

Accepts a signed decimal number. Ignores whitespace.

FromField Int32 Source #

Accepts a signed decimal number. Ignores whitespace.

FromField Int64 Source #

Accepts a signed decimal number. Ignores whitespace.

FromField Integer Source #

Accepts a signed decimal number. Ignores whitespace.

FromField Word Source #

Accepts an unsigned decimal number. Ignores whitespace.

FromField Word8 Source #

Accepts an unsigned decimal number. Ignores whitespace.

FromField Word16 Source #

Accepts an unsigned decimal number. Ignores whitespace.

FromField Word32 Source #

Accepts an unsigned decimal number. Ignores whitespace.

FromField Word64 Source #

Accepts an unsigned decimal number. Ignores whitespace.

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

Accepts an unsigned decimal number. Ignores whitespace.

Since: 0.5.1.0

FromField ShortByteString Source # 
FromField Scientific Source #

Accepts the same syntax as rational. Ignores whitespace.

Since: 0.5.1.0

FromField ShortText Source #

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

Since: 0.5.0.0

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 #

FromField a => FromField (Either Field a) Source #

Left field if conversion failed, Right otherwise.

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

Uses decimal encoding.

Since: 0.5.1.0

ToField ShortByteString Source # 
ToField Scientific Source #

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

Since: 0.5.1.0

ToField ShortText Source #

Uses UTF-8 encoding.

Since: 0.5.0.0

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 #

Generic record conversion

There may be times that you do not want to manually write out class instances for record conversion, but you can't rely upon the default instances (e.g. you can't create field names that match the actual column names in expected data).

For example, consider you have a type MyType where you have prefixed certain columns with an underscore, but in the actual data they're not. You can then write:

myOptions :: Options
myOptions = defaultOptions { fieldLabelmodifier = rmUnderscore }
  where
    rmUnderscore ('_':str) = str
    rmUnderscore str       = str

instance ToNamedRecord MyType where
  toNamedRecord = genericToNamedRecord myOptions

instance FromNamedRecord MyType where
  parseNamedRecord = genericParseNamedRecord myOptions

instance DefaultOrdered MyType where
  headerOrder = genericHeaderOrder myOptions

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

A configurable CSV record parser. This function applied to defaultOptions is used as the default for parseRecord when the type is an instance of Generic.

Since: 0.5.1.0

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

A configurable CSV record creator. This function applied to defaultOptions is used as the default for toRecord when the type is an instance of Generic.

Since: 0.5.1.0

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

A configurable CSV named record parser. This function applied to defaultOptions is used as the default for parseNamedRecord when the type is an instance of Generic.

Since: 0.5.1.0

genericToNamedRecord :: (Generic a, GToRecord (Rep a) (ByteString, ByteString)) => Options -> a -> NamedRecord Source #

A configurable CSV named record creator. This function applied to defaultOptions is used as the default for toNamedRecord when the type is an instance of Generic.

Since: 0.5.1.0

genericHeaderOrder :: (Generic a, GToNamedRecordHeader (Rep a)) => Options -> a -> Header Source #

A configurable CSV header record generator. This function applied to defaultOptions is used as the default for headerOrder when the type is an instance of Generic.

Since: 0.5.1.0

Generic type conversion options

data Options Source #

Options to customise how to generically encode/decode your datatype to/from CSV.

Since: 0.5.1.0

Instances

defaultOptions :: Options Source #

Default conversion options.

  Options
  { fieldLabelModifier = id
  }
  

Since: 0.5.1.0

fieldLabelModifier :: Options -> String -> String Source #

How to convert Haskell field labels to CSV fields.

Since: 0.5.1.0

Generic type conversion class name

NOTE: Only the class names are exposed in order to make it possible to write type signatures referring to these classes

class GFromRecord f Source #

Minimal complete definition

gparseRecord

Instances

GFromRecordSum * f Record => GFromRecord * (M1 i n f) Source # 

Methods

gparseRecord :: Options -> Record -> Parser (f p)

class GToRecord a f Source #

Minimal complete definition

gtoRecord

Instances

GToRecord * U1 f Source # 

Methods

gtoRecord :: Options -> f p -> [f]

ToField a => GToRecord * (K1 i a) Field Source # 

Methods

gtoRecord :: Options -> Field p -> [f]

(GToRecord * a f, GToRecord * b f) => GToRecord * ((:+:) a b) f Source # 

Methods

gtoRecord :: Options -> f p -> [f]

(GToRecord * a f, GToRecord * b f) => GToRecord * ((:*:) a b) f Source # 

Methods

gtoRecord :: Options -> f p -> [f]

GToRecord * a f => GToRecord * (M1 D c a) f Source # 

Methods

gtoRecord :: Options -> f p -> [f]

GToRecord * a f => GToRecord * (M1 C c a) f Source # 

Methods

gtoRecord :: Options -> f p -> [f]

GToRecord * a Field => GToRecord * (M1 S c a) Field Source # 

Methods

gtoRecord :: Options -> Field p -> [f]

(ToField a, Selector Meta s) => GToRecord * (M1 S s (K1 i a)) (ByteString, ByteString) Source # 

Methods

gtoRecord :: Options -> (ByteString, ByteString) p -> [f]

class GFromNamedRecord f Source #

Minimal complete definition

gparseNamedRecord

Instances

GFromRecordSum * f NamedRecord => GFromNamedRecord * (M1 i n f) Source # 

class GToNamedRecordHeader a Source #

Minimal complete definition

gtoNamedRecordHeader

Instances

GToNamedRecordHeader * U1 Source # 

Methods

gtoNamedRecordHeader :: Options -> a p -> [Name]

(GToNamedRecordHeader * a, GToNamedRecordHeader * b) => GToNamedRecordHeader * ((:*:) a b) Source # 

Methods

gtoNamedRecordHeader :: Options -> a p -> [Name]

GToNamedRecordHeader * a => GToNamedRecordHeader * (M1 D c a) Source # 

Methods

gtoNamedRecordHeader :: Options -> a p -> [Name]

GToNamedRecordHeader * a => GToNamedRecordHeader * (M1 C c a) Source # 

Methods

gtoNamedRecordHeader :: Options -> a p -> [Name]

DefaultOrdered (M1 S (MetaSel (Nothing Symbol) srcpk srcstr decstr) a ()) => GToNamedRecordHeader * (M1 S (MetaSel (Nothing Symbol) srcpk srcstr decstr) a) Source #

Instance to ensure that you cannot derive DefaultOrdered for constructors without selectors.

Methods

gtoNamedRecordHeader :: Options -> a p -> [Name]

Selector Meta s => GToNamedRecordHeader * (M1 S s a) Source # 

Methods

gtoNamedRecordHeader :: Options -> a p -> [Name]