Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- data HasHeader
- decode :: FromRecord a => HasHeader -> ByteString -> Either String (Vector a)
- decodeByName :: FromNamedRecord a => ByteString -> Either String (Header, Vector a)
- encode :: ToRecord a => [a] -> ByteString
- encodeByName :: ToNamedRecord a => Header -> [a] -> ByteString
- encodeDefaultOrderedByName :: (DefaultOrdered a, ToNamedRecord a) => [a] -> ByteString
- class DefaultOrdered a where
- headerOrder :: a -> Header
- data DecodeOptions = DecodeOptions {
- decDelimiter :: !Word8
- defaultDecodeOptions :: DecodeOptions
- decodeWith :: FromRecord a => DecodeOptions -> HasHeader -> ByteString -> Either String (Vector a)
- decodeWithP :: (Record -> Parser a) -> DecodeOptions -> HasHeader -> ByteString -> Either String (Vector a)
- decodeByNameWith :: FromNamedRecord a => DecodeOptions -> ByteString -> Either String (Header, Vector a)
- decodeByNameWithP :: (NamedRecord -> Parser a) -> DecodeOptions -> ByteString -> Either String (Header, Vector a)
- data EncodeOptions = EncodeOptions {
- encDelimiter :: !Word8
- encUseCrLf :: !Bool
- encIncludeHeader :: !Bool
- encQuoting :: !Quoting
- data Quoting
- defaultEncodeOptions :: EncodeOptions
- encodeWith :: ToRecord a => EncodeOptions -> [a] -> ByteString
- encodeByNameWith :: ToNamedRecord a => EncodeOptions -> Header -> [a] -> ByteString
- encodeDefaultOrderedByNameWith :: forall a. (DefaultOrdered a, ToNamedRecord a) => EncodeOptions -> [a] -> ByteString
- type Csv = Vector Record
- type Record = Vector Field
- type Field = ByteString
- type Header = Vector Name
- type Name = ByteString
- type NamedRecord = HashMap ByteString ByteString
- class FromRecord a where
- parseRecord :: Record -> Parser a
- data Parser a
- runParser :: Parser a -> Either String a
- index :: FromField a => Record -> Int -> Parser a
- (.!) :: FromField a => Record -> Int -> Parser a
- unsafeIndex :: FromField a => Record -> Int -> Parser a
- class ToRecord a where
- record :: [ByteString] -> Record
- newtype Only a = Only {
- fromOnly :: a
- class FromNamedRecord a where
- parseNamedRecord :: NamedRecord -> Parser a
- lookup :: FromField a => NamedRecord -> ByteString -> Parser a
- (.:) :: FromField a => NamedRecord -> ByteString -> Parser a
- class ToNamedRecord a where
- toNamedRecord :: a -> NamedRecord
- namedRecord :: [(ByteString, ByteString)] -> NamedRecord
- namedField :: ToField a => ByteString -> a -> (ByteString, ByteString)
- (.=) :: ToField a => ByteString -> a -> (ByteString, ByteString)
- header :: [ByteString] -> Header
- class FromField a where
- parseField :: Field -> Parser a
- class ToField a where
- genericParseRecord :: (Generic a, GFromRecord (Rep a)) => Options -> Record -> Parser a
- genericToRecord :: (Generic a, GToRecord (Rep a) Field) => Options -> a -> Record
- genericParseNamedRecord :: (Generic a, GFromNamedRecord (Rep a)) => Options -> NamedRecord -> Parser a
- genericToNamedRecord :: (Generic a, GToRecord (Rep a) (ByteString, ByteString)) => Options -> a -> NamedRecord
- genericHeaderOrder :: (Generic a, GToNamedRecordHeader (Rep a)) => Options -> a -> Header
- data Options
- defaultOptions :: Options
- fieldLabelModifier :: Options -> String -> String
- class GFromRecord f
- class GToRecord a f
- class GFromNamedRecord f
- class GToNamedRecordHeader a
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}])
Reading/writing CSV files
Demonstration of reading from a CSV file/ writing to a CSV file using the incremental API:
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} -- from base import GHC.Generics import System.IO import System.Exit (exitFailure) -- from bytestring import Data.ByteString (ByteString, hGetSome, empty) import qualified Data.ByteString.Lazy as BL -- from cassava import Data.Csv.Incremental import Data.Csv (FromRecord, ToRecord) data Person = Person { name :: !ByteString , age :: !Int } deriving (Show, Eq, Generic) instance FromRecord Person instance ToRecord Person persons :: [Person] persons = [Person "John Doe" 19, Person "Smith" 20] writeToFile :: IO () writeToFile = do BL.writeFile "persons.csv" $ encode $ foldMap encodeRecord persons feed :: (ByteString -> Parser Person) -> Handle -> IO (Parser Person) feed k csvFile = do hIsEOF csvFile >>= \case True -> return $ k empty False -> k <$> hGetSome csvFile 4096 readFromFile :: IO () readFromFile = do withFile "persons.csv" ReadMode $ \ csvFile -> do let loop !_ (Fail _ errMsg) = do putStrLn errMsg; exitFailure loop acc (Many rs k) = loop (acc <> rs) =<< feed k csvFile loop acc (Done rs) = print (acc <> rs) loop [] (decode NoHeader) main :: IO () main = do writeToFile readFromFile
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
value, like so:Vector
ByteString
>>>
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.
Is the CSV data preceded by a header?
:: 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,
is
returned. Equivalent to Left
msg
.decodeWith
defaultDecodeOptions
:: 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,
is
returned. The data is assumed to be preceded by a header.
Equivalent to Left
msg
.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’
Nothing
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)
default headerOrder :: (Generic a, GToNamedRecordHeader (Rep a)) => a -> Header Source #
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') }
DecodeOptions | |
|
Instances
Show DecodeOptions Source # | |
Defined in Data.Csv.Parser showsPrec :: Int -> DecodeOptions -> ShowS # show :: DecodeOptions -> String # showList :: [DecodeOptions] -> ShowS # | |
Eq DecodeOptions Source # | |
Defined in Data.Csv.Parser (==) :: DecodeOptions -> DecodeOptions -> Bool # (/=) :: DecodeOptions -> DecodeOptions -> Bool # |
defaultDecodeOptions :: DecodeOptions Source #
Decoding options for parsing CSV files.
:: 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.
:: (Record -> Parser a) | Custom parser function |
-> DecodeOptions | Decoding options |
-> HasHeader | Data contains header that should be skipped |
-> ByteString | CSV data |
-> Either String (Vector a) |
Like decodeWith'
, but lets you specify a parser function.
Since: 0.5.2.0
:: 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.
:: (NamedRecord -> Parser a) | Custom parser function |
-> DecodeOptions | Decoding options |
-> ByteString | CSV data |
-> Either String (Header, Vector a) |
Like decodeByNameWith
, but lets you specify a parser function.
Since: 0.5.2.0
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
).
EncodeOptions | |
|
Instances
Show EncodeOptions Source # | |
Defined in Data.Csv.Encoding showsPrec :: Int -> EncodeOptions -> ShowS # show :: EncodeOptions -> String # showList :: [EncodeOptions] -> ShowS # | |
Eq EncodeOptions Source # | |
Defined in Data.Csv.Encoding (==) :: EncodeOptions -> EncodeOptions -> Bool # (/=) :: EncodeOptions -> EncodeOptions -> Bool # |
Should quoting be applied to fields, and at which level?
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 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
Nothing
parseRecord :: Record -> Parser a Source #
default parseRecord :: (Generic a, GFromRecord (Rep a)) => Record -> Parser a Source #
Instances
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.
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
. If you're certain that the index is not
out of bounds, using parseField
(v !
idx)unsafeIndex
is somewhat faster.
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
Nothing
Instances
record :: [ByteString] -> Record Source #
Construct a record from a list of ByteString
s. Use toField
to convert values to ByteString
s for use with record
.
Instances
Functor Only | |
Data a => Data (Only a) | |
Defined in Data.Tuple.Only 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 :: forall r r'. (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) # | |
Generic (Only a) | |
Read a => Read (Only a) | |
Show a => Show (Only a) | |
FromField a => FromRecord (Only a) Source # | |
Defined in Data.Csv.Conversion | |
ToField a => ToRecord (Only a) Source # | |
NFData a => NFData (Only a) | |
Defined in Data.Tuple.Only | |
Eq a => Eq (Only a) | |
Ord a => Ord (Only a) | |
type Rep (Only a) | |
Defined in Data.Tuple.Only |
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.
Nothing
parseNamedRecord :: NamedRecord -> Parser a Source #
default parseNamedRecord :: (Generic a, GFromNamedRecord (Rep a)) => NamedRecord -> Parser a Source #
Instances
(FromField a, FromField b, Ord a) => FromNamedRecord (Map a b) Source # | |
Defined in Data.Csv.Conversion parseNamedRecord :: NamedRecord -> Parser (Map a b) Source # | |
(Eq a, FromField a, FromField b, Hashable a) => FromNamedRecord (HashMap a b) Source # | |
Defined in Data.Csv.Conversion parseNamedRecord :: NamedRecord -> Parser (HashMap a b) Source # |
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.
(.:) :: FromField a => NamedRecord -> ByteString -> Parser a Source #
Alias for lookup
.
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]
Nothing
toNamedRecord :: a -> NamedRecord Source #
Convert a value to a named record.
default toNamedRecord :: (Generic a, GToRecord (Rep a) (ByteString, ByteString)) => a -> NamedRecord Source #
Instances
(ToField a, ToField b, Ord a) => ToNamedRecord (Map a b) Source # | |
Defined in Data.Csv.Conversion toNamedRecord :: Map a b -> NamedRecord Source # | |
(Eq a, ToField a, ToField b, Hashable a) => ToNamedRecord (HashMap a b) Source # | |
Defined in Data.Csv.Conversion toNamedRecord :: HashMap a b -> NamedRecord Source # |
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
.
(.=) :: ToField a => ByteString -> a -> (ByteString, ByteString) Source #
Alias for namedField
.
header :: [ByteString] -> Header Source #
Construct a header from a list of ByteString
s.
Field conversion
The FromField
and ToField
classes define how to convert between
Field
s and values you care about (e.g. Int
s). 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
parseField :: Field -> Parser a Source #
Instances
FromField Int16 Source # | Accepts a signed decimal number. Ignores whitespace. |
Defined in Data.Csv.Conversion | |
FromField Int32 Source # | Accepts a signed decimal number. Ignores whitespace. |
Defined in Data.Csv.Conversion | |
FromField Int64 Source # | Accepts a signed decimal number. Ignores whitespace. |
Defined in Data.Csv.Conversion | |
FromField Int8 Source # | Accepts a signed decimal number. Ignores whitespace. |
Defined in Data.Csv.Conversion | |
FromField Word16 Source # | Accepts an unsigned decimal number. Ignores whitespace. |
Defined in Data.Csv.Conversion | |
FromField Word32 Source # | Accepts an unsigned decimal number. Ignores whitespace. |
Defined in Data.Csv.Conversion | |
FromField Word64 Source # | Accepts an unsigned decimal number. Ignores whitespace. |
Defined in Data.Csv.Conversion | |
FromField Word8 Source # | Accepts an unsigned decimal number. Ignores whitespace. |
Defined in Data.Csv.Conversion | |
FromField ByteString Source # | |
Defined in Data.Csv.Conversion parseField :: Field -> Parser ByteString Source # | |
FromField ByteString Source # | |
Defined in Data.Csv.Conversion parseField :: Field -> Parser ByteString Source # | |
FromField ShortByteString Source # | |
Defined in Data.Csv.Conversion parseField :: Field -> Parser ShortByteString Source # | |
FromField Scientific Source # | Accepts the same syntax as Since: 0.5.1.0 |
Defined in Data.Csv.Conversion parseField :: Field -> Parser Scientific Source # | |
FromField Text Source # | Assumes UTF-8 encoding. Fails on invalid byte sequences. |
Defined in Data.Csv.Conversion | |
FromField Text Source # | Assumes UTF-8 encoding. Fails on invalid byte sequences. |
Defined in Data.Csv.Conversion | |
FromField ShortText Source # | Assumes UTF-8 encoding. Fails on invalid byte sequences. Since: 0.5.0.0 |
Defined in Data.Csv.Conversion parseField :: Field -> Parser ShortText Source # | |
FromField Integer Source # | Accepts a signed decimal number. Ignores whitespace. |
Defined in Data.Csv.Conversion | |
FromField Natural Source # | Accepts an unsigned decimal number. Ignores whitespace. Since: 0.5.1.0 |
Defined in Data.Csv.Conversion | |
FromField () Source # | Ignores the |
Defined in Data.Csv.Conversion parseField :: Field -> Parser () Source # | |
FromField Char Source # | Assumes UTF-8 encoding. |
Defined in Data.Csv.Conversion | |
FromField Double Source # | Accepts same syntax as |
Defined in Data.Csv.Conversion | |
FromField Float Source # | Accepts same syntax as |
Defined in Data.Csv.Conversion | |
FromField Int Source # | Accepts a signed decimal number. Ignores whitespace. |
Defined in Data.Csv.Conversion | |
FromField Word Source # | Accepts an unsigned decimal number. Ignores whitespace. |
Defined in Data.Csv.Conversion | |
FromField a => FromField (Identity a) Source # | Since: 0.5.2.0 |
Defined in Data.Csv.Conversion | |
FromField a => FromField (Maybe a) Source # | |
Defined in Data.Csv.Conversion | |
FromField [Char] Source # | Assumes UTF-8 encoding. Fails on invalid byte sequences. |
Defined in Data.Csv.Conversion | |
FromField a => FromField (Either Field a) Source # | |
Defined in Data.Csv.Conversion | |
FromField a => FromField (Const a b) Source # | Since: 0.5.2.0 |
Defined in Data.Csv.Conversion |
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"
Instances
ToField Int16 Source # | Uses decimal encoding with optional sign. |
ToField Int32 Source # | Uses decimal encoding with optional sign. |
ToField Int64 Source # | Uses decimal encoding with optional sign. |
ToField Int8 Source # | Uses decimal encoding with optional sign. |
ToField Word16 Source # | Uses decimal encoding. |
ToField Word32 Source # | Uses decimal encoding. |
ToField Word64 Source # | Uses decimal encoding. |
ToField Word8 Source # | Uses decimal encoding. |
ToField ByteString Source # | |
Defined in Data.Csv.Conversion toField :: ByteString -> Field Source # | |
ToField ByteString Source # | |
Defined in Data.Csv.Conversion toField :: ByteString -> Field Source # | |
ToField ShortByteString Source # | |
Defined in Data.Csv.Conversion toField :: ShortByteString -> Field Source # | |
ToField Scientific Source # | Uses decimal notation or scientific notation, depending on the number. Since: 0.5.1.0 |
Defined in Data.Csv.Conversion | |
ToField Text Source # | Uses UTF-8 encoding. |
ToField Text Source # | Uses UTF-8 encoding. |
ToField ShortText Source # | Uses UTF-8 encoding. Since: 0.5.0.0 |
Defined in Data.Csv.Conversion | |
ToField Integer Source # | Uses decimal encoding with optional sign. |
ToField Natural Source # | Uses decimal encoding. Since: 0.5.1.0 |
ToField Char Source # | Uses UTF-8 encoding. |
ToField Double Source # | Uses decimal notation or scientific notation, depending on the number. |
ToField Float Source # | Uses decimal notation or scientific notation, depending on the number. |
ToField Int Source # | Uses decimal encoding with optional sign. |
ToField Word Source # | Uses decimal encoding. |
ToField a => ToField (Identity a) Source # | Since: 0.5.2.0 |
ToField a => ToField (Maybe a) Source # | |
ToField [Char] Source # | Uses UTF-8 encoding. |
ToField a => ToField (Const a b) Source # | Since: 0.5.2.0 |
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
Options to customise how to generically encode/decode your datatype to/from CSV.
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 #
gparseRecord
Instances
GFromRecordSum f Record => GFromRecord (M1 i n f :: k -> Type) Source # | |
Defined in Data.Csv.Conversion gparseRecord :: forall (p :: k0). Options -> Record -> Parser (M1 i n f p) |
gtoRecord
Instances
GToRecord (U1 :: k -> Type) f Source # | |
Defined in Data.Csv.Conversion | |
(GToRecord a f, GToRecord b f) => GToRecord (a :*: b :: k -> Type) f Source # | |
Defined in Data.Csv.Conversion | |
(GToRecord a f, GToRecord b f) => GToRecord (a :+: b :: k -> Type) f Source # | |
Defined in Data.Csv.Conversion | |
ToField a => GToRecord (K1 i a :: k -> Type) Field Source # | |
Defined in Data.Csv.Conversion | |
GToRecord a f => GToRecord (M1 C c a :: k -> Type) f Source # | |
Defined in Data.Csv.Conversion | |
GToRecord a f => GToRecord (M1 D c a :: k -> Type) f Source # | |
Defined in Data.Csv.Conversion | |
GToRecord a Field => GToRecord (M1 S c a :: k -> Type) Field Source # | |
(ToField a, Selector s) => GToRecord (M1 S s (K1 i a :: k -> Type) :: k -> Type) (ByteString, ByteString) Source # | |
Defined in Data.Csv.Conversion gtoRecord :: forall (p :: k0). Options -> M1 S s (K1 i a) p -> [(ByteString, ByteString)] |
class GFromNamedRecord f Source #
gparseNamedRecord
Instances
GFromRecordSum f NamedRecord => GFromNamedRecord (M1 i n f :: k -> Type) Source # | |
Defined in Data.Csv.Conversion gparseNamedRecord :: forall (p :: k0). Options -> NamedRecord -> Parser (M1 i n f p) |
class GToNamedRecordHeader a Source #
gtoNamedRecordHeader