-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A CSV parsing and encoding library -- -- cassava is a library for parsing and encoding RFC 4180 -- compliant comma-separated values (CSV) data, which is a textual -- line-oriented format commonly used for exchanging tabular data. -- -- cassava's API includes support for -- -- -- -- Moreover, this library is designed to be easy to use; for instance, -- here's a very simple example of encoding CSV data: -- --
--   >>> Data.Csv.encode [("John",27),("Jane",28)]
--   "John,27\r\nJane,28\r\n"
--   
-- -- Please refer to the documentation in Data.Csv and the included -- README for more usage examples. @package cassava @version 0.5.2.0 -- | A CSV parser. The parser defined here is RFC 4180 compliant, with the -- following extensions: -- -- -- -- The functions in this module can be used to implement e.g. a resumable -- parser that is fed input incrementally. module Data.Csv.Parser -- | 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')
--       }
--   
data DecodeOptions DecodeOptions :: {-# UNPACK #-} !Word8 -> DecodeOptions -- | Field delimiter. [decDelimiter] :: DecodeOptions -> {-# UNPACK #-} !Word8 -- | Decoding options for parsing CSV files. defaultDecodeOptions :: DecodeOptions -- | Parse a CSV file that does not include a header. csv :: DecodeOptions -> Parser Csv -- | Parse a CSV file that includes a header. csvWithHeader :: DecodeOptions -> Parser (Header, Vector NamedRecord) -- | Parse a header, including the terminating line separator. header :: Word8 -> Parser Header -- | Parse a record, not including the terminating line separator. The -- terminating line separate is not included as the last record in a CSV -- file is allowed to not have a terminating line separator. You most -- likely want to use the endOfLine parser in combination with -- this parser. record :: Word8 -> Parser Record -- | Parse a header name. Header names have the same format as regular -- fields. name :: Word8 -> Parser Name -- | Parse a field. The field may be in either the escaped or non-escaped -- format. The return value is unescaped. field :: Word8 -> Parser Field instance GHC.Show.Show Data.Csv.Parser.DecodeOptions instance GHC.Classes.Eq Data.Csv.Parser.DecodeOptions -- | This module allows for incremental decoding and encoding of CSV data. -- This is useful if you e.g. want to interleave I/O with parsing or if -- you want finer grained control over how you deal with type conversion -- errors. -- -- Decoding example: -- --
--   main :: IO ()
--   main = withFile "salaries.csv" ReadMode $ \ csvFile -> do
--       let loop !_ (Fail _ errMsg) = putStrLn errMsg >> exitFailure
--           loop acc (Many rs k)    = loop (acc + sumSalaries rs) =<< feed k
--           loop acc (Done rs)      = putStrLn $ "Total salaries: " ++
--                                     show (sumSalaries rs + acc)
--   
--           feed k = do
--               isEof <- hIsEOF csvFile
--               if isEof
--                   then return $ k B.empty
--                   else k `fmap` B.hGetSome csvFile 4096
--       loop 0 (decode NoHeader)
--     where
--       sumSalaries rs = sum [salary | Right (_ :: String, salary :: Int) <- rs]
--   
-- -- Encoding example: -- --
--   data Person = Person { name   :: !String, salary :: !Int }
--       deriving Generic
--   
--   instance FromNamedRecord Person
--   instance ToNamedRecord Person
--   instance DefaultOrdered Person
--   
--   persons :: [Person]
--   persons = [Person "John" 50000, Person "Jane" 60000]
--   
--   main :: IO ()
--   main = putStrLn $ encodeDefaultOrderedByName (go persons)
--     where
--       go (x:xs) = encodeNamedRecord x <> go xs
--   
module Data.Csv.Incremental -- | An incremental parser that when fed data eventually returns a parsed -- Header, or an error. data HeaderParser a -- | The input data was malformed. The first field contains any unconsumed -- input and second field contains information about the parse error. FailH :: !ByteString -> String -> HeaderParser a -- | The parser needs more input data before it can produce a result. Use -- an empty string to indicate that no more input data is -- available. If fed an 'B.empty string', the continuation is guaranteed -- to return either FailH or DoneH. PartialH :: (ByteString -> HeaderParser a) -> HeaderParser a -- | The parse succeeded and produced the given Header. DoneH :: !Header -> a -> HeaderParser a -- | Parse a CSV header in an incremental fashion. When done, the -- HeaderParser returns any unconsumed input in the second field -- of the DoneH constructor. decodeHeader :: HeaderParser ByteString -- | Like decodeHeader, but lets you customize how the CSV data is -- parsed. decodeHeaderWith :: DecodeOptions -> HeaderParser ByteString -- | An incremental parser that when fed data eventually produces some -- parsed records, converted to the desired type, or an error in case of -- malformed input data. data Parser a -- | The input data was malformed. The first field contains any unconsumed -- input and second field contains information about the parse error. Fail :: !ByteString -> String -> Parser a -- | The parser parsed and converted zero or more records. Any records that -- failed type conversion are returned as Left errMsg and -- the rest as Right val. Feed a ByteString to the -- continuation to continue parsing. Use an empty string to -- indicate that no more input data is available. If fed an empty -- string, the continuation is guaranteed to return either Fail or -- Done. Many :: [Either String a] -> (ByteString -> Parser a) -> Parser a -- | The parser parsed and converted some records. Any records that failed -- type conversion are returned as Left errMsg and the -- rest as Right val. Done :: [Either String a] -> Parser a -- | Is the CSV data preceded by a header? data HasHeader -- | The CSV data is preceded by a header HasHeader :: HasHeader -- | The CSV data is not preceded by a header NoHeader :: HasHeader -- | Efficiently deserialize CSV in an incremental fashion. Equivalent to -- decodeWith defaultDecodeOptions. decode :: FromRecord a => HasHeader -> Parser a -- | Like decode, but lets you customize how the CSV data is parsed. decodeWith :: FromRecord a => DecodeOptions -> HasHeader -> Parser a -- | Like decodeWith, but lets you pass an explicit parser value -- instead of using a typeclass decodeWithP :: (Record -> Parser a) -> DecodeOptions -> HasHeader -> Parser a -- | Efficiently deserialize CSV in an incremental fashion. The data is -- assumed to be preceded by a header. Returns a HeaderParser that -- when done produces a Parser for parsing the actual records. -- Equivalent to decodeByNameWith -- defaultDecodeOptions. decodeByName :: FromNamedRecord a => HeaderParser (Parser a) -- | Like decodeByName, but lets you customize how the CSV data is -- parsed. decodeByNameWith :: FromNamedRecord a => DecodeOptions -> HeaderParser (Parser a) -- | Like decodeByNameWith, but lets you pass an explicit parser -- value instead of using a typeclass decodeByNameWithP :: (NamedRecord -> Parser a) -> DecodeOptions -> HeaderParser (Parser a) -- | Efficiently serialize records in an incremental fashion. Equivalent to -- encodeWith defaultEncodeOptions. encode :: ToRecord a => Builder a -> ByteString -- | Like encode, but lets you customize how the CSV data is -- encoded. encodeWith :: ToRecord a => EncodeOptions -> Builder a -> ByteString -- | Encode a single record. encodeRecord :: ToRecord a => a -> Builder a -- | A builder for building the CSV data incrementally. Just like the -- ByteString builder, this builder should be used in a -- right-associative, foldr style. Using <> to -- compose builders in a left-associative, foldl' style makes -- the building not be incremental. data Builder a -- | Efficiently serialize named records in an incremental fashion, -- including the leading header. Equivalent to encodeWith -- defaultEncodeOptions. The header is written before any -- records and dictates the field order. encodeByName :: ToNamedRecord a => Header -> NamedBuilder a -> ByteString -- | Like encodeByName, but header and field order is dictated by -- the headerOrder method. encodeDefaultOrderedByName :: (DefaultOrdered a, ToNamedRecord a) => NamedBuilder a -> ByteString -- | Like encodeByName, but lets you customize how the CSV data is -- encoded. encodeByNameWith :: ToNamedRecord a => EncodeOptions -> Header -> NamedBuilder a -> ByteString -- | Like encodeDefaultOrderedByName, but lets you customize how the -- CSV data is encoded. encodeDefaultOrderedByNameWith :: forall a. (DefaultOrdered a, ToNamedRecord a) => EncodeOptions -> NamedBuilder a -> ByteString -- | Encode a single named record. encodeNamedRecord :: ToNamedRecord a => a -> NamedBuilder a -- | A builder for building the CSV data incrementally. Just like the -- ByteString builder, this builder should be used in a -- right-associative, foldr style. Using <> to -- compose builders in a left-associative, foldl' style makes -- the building not be incremental. data NamedBuilder a instance GHC.Show.Show Data.Csv.Incremental.More instance GHC.Classes.Eq Data.Csv.Incremental.More instance GHC.Base.Functor Data.Csv.Incremental.Parser instance GHC.Base.Functor Data.Csv.Incremental.HeaderParser instance GHC.Base.Semigroup (Data.Csv.Incremental.NamedBuilder a) instance GHC.Base.Monoid (Data.Csv.Incremental.NamedBuilder a) instance GHC.Base.Semigroup (Data.Csv.Incremental.Builder a) instance GHC.Base.Monoid (Data.Csv.Incremental.Builder a) instance GHC.Show.Show a => GHC.Show.Show (Data.Csv.Incremental.Parser a) instance GHC.Show.Show a => GHC.Show.Show (Data.Csv.Incremental.HeaderParser a) -- | This module allows for streaming decoding of CSV data. This is useful -- if you need to parse large amounts of input in constant space. The API -- also allows you to ignore type conversion errors on a per-record -- basis. module Data.Csv.Streaming -- | A stream of parsed records. If type conversion failed for the record, -- the error is returned as Left errMsg. data Records a -- | A record or an error message, followed by more records. Cons :: Either String a -> Records a -> Records a -- | End of stream, potentially due to a parse error. If a parse error -- occured, the first field contains the error message. The second field -- contains any unconsumed input. Nil :: Maybe String -> ByteString -> Records a -- | Is the CSV data preceded by a header? data HasHeader -- | The CSV data is preceded by a header HasHeader :: HasHeader -- | The CSV data is not preceded by a header NoHeader :: HasHeader -- | Efficiently deserialize CSV records in a streaming fashion. Equivalent -- to decodeWith defaultDecodeOptions. decode :: FromRecord a => HasHeader -> ByteString -> Records a -- | Like decode, but lets you customize how the CSV data is parsed. decodeWith :: FromRecord a => DecodeOptions -> HasHeader -> ByteString -> Records a -- | Efficiently deserialize CSV in a streaming fashion. The data is -- assumed to be preceded by a header. Returns Left -- errMsg if parsing the header fails. Equivalent to -- decodeByNameWith defaultDecodeOptions. decodeByName :: FromNamedRecord a => ByteString -> Either String (Header, Records a) -- | Like decodeByName, but lets you customize how the CSV data is -- parsed. decodeByNameWith :: FromNamedRecord a => DecodeOptions -> ByteString -> Either String (Header, Records a) instance GHC.Show.Show a => GHC.Show.Show (Data.Csv.Streaming.Records a) instance GHC.Base.Functor Data.Csv.Streaming.Records instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Csv.Streaming.Records a) instance Data.Foldable.Foldable Data.Csv.Streaming.Records instance Data.Traversable.Traversable Data.Csv.Streaming.Records instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Data.Csv.Streaming.Records a) -- | Low-level bytestring builders. Most users want to use the more -- type-safe Data.Csv.Incremental module instead. module Data.Csv.Builder -- | Encode a header. encodeHeader :: Header -> Builder -- | Encode a single record. encodeRecord :: ToRecord a => a -> Builder -- | Encode a single named record, given the field order. encodeNamedRecord :: ToNamedRecord a => Header -> a -> Builder -- | Encode a single named record, using the default field order. encodeDefaultOrderedNamedRecord :: (DefaultOrdered a, ToNamedRecord a) => a -> Builder -- | Like encodeHeader, but lets you customize how the CSV data is -- encoded. encodeHeaderWith :: EncodeOptions -> Header -> Builder -- | Like encodeRecord, but lets you customize how the CSV data is -- encoded. encodeRecordWith :: ToRecord a => EncodeOptions -> a -> Builder -- | Like encodeNamedRecord, but lets you customize how the CSV data -- is encoded. encodeNamedRecordWith :: ToNamedRecord a => EncodeOptions -> Header -> a -> Builder -- | Like encodeDefaultOrderedNamedRecord, but lets you customize -- how the CSV data is encoded. encodeDefaultOrderedNamedRecordWith :: forall a. (DefaultOrdered a, ToNamedRecord a) => EncodeOptions -> a -> Builder -- | This module implements encoding and decoding of comma-separated -- values (CSV) data. The implementation is RFC 4180 -- compliant, with the following extensions: -- -- module Data.Csv -- | Is the CSV data preceded by a header? data HasHeader -- | The CSV data is preceded by a header HasHeader :: HasHeader -- | The CSV data is not preceded by a header NoHeader :: HasHeader -- | 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. decode :: FromRecord a => HasHeader -> ByteString -> 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. The data is assumed to be preceded by a header. -- Equivalent to decodeByNameWith -- defaultDecodeOptions. decodeByName :: FromNamedRecord a => ByteString -> Either String (Header, Vector a) -- | Efficiently serialize CSV records as a lazy ByteString. encode :: ToRecord a => [a] -> ByteString -- | Efficiently serialize CSV records as a lazy ByteString. The -- header is written before any records and dictates the field order. encodeByName :: ToNamedRecord a => Header -> [a] -> ByteString -- | Like encodeByName, but header and field order is dictated by -- the header method. encodeDefaultOrderedByName :: (DefaultOrdered a, ToNamedRecord a) => [a] -> ByteString -- | 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’
--   
class DefaultOrdered a -- | 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 :: DefaultOrdered a => a -> Header -- | 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 :: (DefaultOrdered a, Generic a, GToNamedRecordHeader (Rep a)) => a -> Header -- | 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')
--       }
--   
data DecodeOptions DecodeOptions :: {-# UNPACK #-} !Word8 -> DecodeOptions -- | Field delimiter. [decDelimiter] :: DecodeOptions -> {-# UNPACK #-} !Word8 -- | Decoding options for parsing CSV files. defaultDecodeOptions :: DecodeOptions -- | Like decode, but lets you customize how the CSV data is parsed. decodeWith :: FromRecord a => DecodeOptions -> HasHeader -> ByteString -> Either String (Vector a) -- | Like decodeWith', but lets you specify a parser function. decodeWithP :: (Record -> Parser a) -> DecodeOptions -> HasHeader -> ByteString -> Either String (Vector a) -- | Like decodeByName, but lets you customize how the CSV data is -- parsed. decodeByNameWith :: FromNamedRecord a => DecodeOptions -> ByteString -> Either String (Header, Vector a) -- | Like decodeByNameWith, but lets you specify a parser function. decodeByNameWithP :: (NamedRecord -> Parser a) -> DecodeOptions -> ByteString -> Either String (Header, Vector a) -- | 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). data EncodeOptions EncodeOptions :: {-# UNPACK #-} !Word8 -> !Bool -> !Bool -> !Quoting -> EncodeOptions -- | Field delimiter. [encDelimiter] :: EncodeOptions -> {-# UNPACK #-} !Word8 -- | Record separator selection. True for CRLF (\r\n) and -- False for LF (\n). [encUseCrLf] :: EncodeOptions -> !Bool -- | Include a header row when encoding ToNamedRecord instances. [encIncludeHeader] :: EncodeOptions -> !Bool -- | What kind of quoting should be applied to text fields. [encQuoting] :: EncodeOptions -> !Quoting -- | Should quoting be applied to fields, and at which level? data Quoting -- | No quotes. QuoteNone :: Quoting -- | Quotes according to RFC 4180. QuoteMinimal :: Quoting -- | Always quote. QuoteAll :: Quoting -- | Encoding options for CSV files. defaultEncodeOptions :: EncodeOptions -- | Like encode, but lets you customize how the CSV data is -- encoded. encodeWith :: ToRecord a => EncodeOptions -> [a] -> ByteString -- | Like encodeByName, but lets you customize how the CSV data is -- encoded. encodeByNameWith :: ToNamedRecord a => EncodeOptions -> Header -> [a] -> ByteString -- | Like encodeDefaultOrderedByNameWith, but lets you customize how -- the CSV data is encoded. encodeDefaultOrderedByNameWith :: forall a. (DefaultOrdered a, ToNamedRecord a) => EncodeOptions -> [a] -> ByteString -- | CSV data represented as a Haskell vector of vector of bytestrings. type Csv = Vector Record -- | A record corresponds to a single line in a CSV file. type Record = Vector Field -- | A single field within a record. type Field = ByteString -- | The header corresponds to the first line a CSV file. Not all CSV files -- have a header. type Header = Vector Name -- | A header has one or more names, describing the data in the column -- following the name. type Name = ByteString -- | A record corresponds to a single line in a CSV file, indexed by the -- column name rather than the column index. type NamedRecord = HashMap ByteString ByteString -- | 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
--   
class FromRecord a parseRecord :: FromRecord a => Record -> Parser a parseRecord :: (FromRecord a, Generic a, GFromRecord (Rep a)) => Record -> Parser a -- | 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. data Parser a -- | 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. runParser :: Parser a -> Either String a -- | 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. index :: FromField a => Record -> Int -> Parser a -- | Alias for index. (.!) :: FromField a => Record -> Int -> Parser a infixl 9 .! -- | Like index but without bounds checking. unsafeIndex :: FromField a => Record -> Int -> Parser a -- | 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
--   
class ToRecord a -- | Convert a value to a record. toRecord :: ToRecord a => a -> Record -- | Convert a value to a record. toRecord :: (ToRecord a, Generic a, GToRecord (Rep a) Field) => a -> Record -- | Construct a record from a list of ByteStrings. Use -- toField to convert values to ByteStrings for use with -- record. record :: [ByteString] -> Record -- | 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) -> {- ... -}
--   
newtype Only a Only :: a -> Only a [fromOnly] :: Only a -> a -- | 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. class FromNamedRecord a parseNamedRecord :: FromNamedRecord a => NamedRecord -> Parser a parseNamedRecord :: (FromNamedRecord a, Generic a, GFromNamedRecord (Rep a)) => NamedRecord -> Parser a -- | 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. lookup :: FromField a => NamedRecord -> ByteString -> Parser a -- | Alias for lookup. (.:) :: FromField a => NamedRecord -> ByteString -> Parser a -- | 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]
--   
class ToNamedRecord a -- | Convert a value to a named record. toNamedRecord :: ToNamedRecord a => a -> NamedRecord -- | Convert a value to a named record. toNamedRecord :: (ToNamedRecord a, Generic a, GToRecord (Rep a) (ByteString, ByteString)) => a -> NamedRecord -- | Construct a named record from a list of name-value ByteString -- pairs. Use .= to construct such a pair from a name and a value. namedRecord :: [(ByteString, ByteString)] -> NamedRecord -- | Construct a pair from a name and a value. For use with -- namedRecord. namedField :: ToField a => ByteString -> a -> (ByteString, ByteString) -- | Alias for namedField. (.=) :: ToField a => ByteString -> a -> (ByteString, ByteString) -- | Construct a header from a list of ByteStrings. header :: [ByteString] -> Header -- | 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
--   
class FromField a parseField :: FromField a => Field -> Parser a -- | 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"
--   
class ToField a toField :: ToField a => a -> Field -- | 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. genericParseRecord :: (Generic a, GFromRecord (Rep a)) => Options -> Record -> Parser a -- | 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. genericToRecord :: (Generic a, GToRecord (Rep a) Field) => Options -> a -> Record -- | 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. genericParseNamedRecord :: (Generic a, GFromNamedRecord (Rep a)) => Options -> NamedRecord -> Parser a -- | 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. genericToNamedRecord :: (Generic a, GToRecord (Rep a) (ByteString, ByteString)) => Options -> a -> NamedRecord -- | 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. genericHeaderOrder :: (Generic a, GToNamedRecordHeader (Rep a)) => Options -> a -> Header -- | Options to customise how to generically encode/decode your datatype -- to/from CSV. data Options -- | Default conversion options. -- --
--   Options
--   { fieldLabelModifier = id
--   }
--   
--   
defaultOptions :: Options -- | How to convert Haskell field labels to CSV fields. fieldLabelModifier :: Options -> String -> String class GFromRecord f class GToRecord a f class GFromNamedRecord f class GToNamedRecordHeader a