| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
System.IO.Streams.Csv
Description
This module exports functions which can be used to read instances
 of the cassava classes FromRecord and FromNamedRecord from an
 io-streams InputStream ByteString.
It also exports functions which can write instances of ToRecord
 and ToNamedRecord to an io-streams OutputStream ByteString.
See the System.IO.Streams.Csv.Tutorial module for a simple tutorial.
Synopsis
- newtype StreamDecodingError = StreamDecodingError String
- decodeStream :: FromRecord a => HasHeader -> InputStream ByteString -> IO (InputStream (Either String a))
- decodeStreamWith :: FromRecord a => DecodeOptions -> HasHeader -> InputStream ByteString -> IO (InputStream (Either String a))
- decodeStreamByName :: FromNamedRecord a => InputStream ByteString -> IO (InputStream (Either String a))
- decodeStreamByNameWith :: FromNamedRecord a => DecodeOptions -> InputStream ByteString -> IO (InputStream (Either String a))
- onlyValidRecords :: InputStream (Either String a) -> IO (InputStream a)
- encodeStream :: ToRecord a => OutputStream ByteString -> IO (OutputStream a)
- encodeStreamWith :: ToRecord a => EncodeOptions -> OutputStream ByteString -> IO (OutputStream a)
- encodeStreamByName :: ToNamedRecord a => Header -> OutputStream ByteString -> IO (OutputStream a)
- encodeStreamByNameWith :: ToNamedRecord a => EncodeOptions -> Header -> OutputStream ByteString -> IO (OutputStream a)
- defaultEncodeOptions :: EncodeOptions
- data Quoting
- data EncodeOptions = EncodeOptions {- encDelimiter :: !Word8
- encUseCrLf :: !Bool
- encIncludeHeader :: !Bool
- encQuoting :: !Quoting
 
- defaultDecodeOptions :: DecodeOptions
- data DecodeOptions = DecodeOptions {- decDelimiter :: !Word8
 
- data HasHeader
Decoding CSV
These functions convert an io-streams InputStream
 ByteString stream into one that decodes CSV records and
 produces these decoded records.
Each of the decoding functions produce an InputStream
 which yields an Either value.  Left String represents
 a record which failed type conversion.  Right a is a
 successfully decoded record.
See the tutorial in System.IO.Streams.Csv.Tutorial for
 details on how to use the onlyValidRecords function to
 transform the decoding streams so that they only produce
 valid records and throw exceptions for bad records.
newtype StreamDecodingError Source #
Exception thrown when stream decoding cannot continue due to an error.
Constructors
| StreamDecodingError String | 
Instances
| Show StreamDecodingError Source # | |
| Defined in System.IO.Streams.Csv.Decode Methods showsPrec :: Int -> StreamDecodingError -> ShowS # show :: StreamDecodingError -> String # showList :: [StreamDecodingError] -> ShowS # | |
| Exception StreamDecodingError Source # | |
| Defined in System.IO.Streams.Csv.Decode Methods toException :: StreamDecodingError -> SomeException # fromException :: SomeException -> Maybe StreamDecodingError # | |
Arguments
| :: FromRecord a | |
| => HasHeader | Whether to skip a header or not. | 
| -> InputStream ByteString | Upstream. | 
| -> IO (InputStream (Either String a)) | An  | 
Create an InputStream which decodes CSV records from the given
 upstream data source.
Equivalent to decodeStreamWith defaultDecodeOptions.
Arguments
| :: FromRecord a | |
| => DecodeOptions | CSV decoding options. | 
| -> HasHeader | Whether to skip a header or not. | 
| -> InputStream ByteString | Upstream. | 
| -> IO (InputStream (Either String a)) | An  | 
Create an InputStream which decodes CSV records from the given
 upstream data source.
Arguments
| :: FromNamedRecord a | |
| => InputStream ByteString | Upstream. | 
| -> IO (InputStream (Either String a)) | An  | 
Create an InputStream which decodes CSV records from the given
 upstream data source.  Data should be preceded by a header.
Equivalent to decodeStreamByNameWith defaultDecodeOptions.
decodeStreamByNameWith Source #
Arguments
| :: FromNamedRecord a | |
| => DecodeOptions | CSV decoding options. | 
| -> InputStream ByteString | Upstream. | 
| -> IO (InputStream (Either String a)) | An  | 
Create an InputStream which decodes CSV records from the given
 upstream data source.  Data should be preceded by a header.
Arguments
| :: InputStream (Either String a) | Upstream. | 
| -> IO (InputStream a) | An  | 
Creates a new InputStream which only sends valid CSV records
 downstream.  The first invalid record will throw an exception.
Encoding CSV
These functions convert an io-streams OutputStream
 ByteString stream into one that encodes records into CSV
 format before sending them downstream.
Arguments
| :: ToRecord a | |
| => OutputStream ByteString | Downstream. | 
| -> IO (OutputStream a) | New  | 
Create a new OutputStream that can be fed ToRecord values
 which are converted to CSV.  The records are encoded into
 ByteStrings and passed on to the given downstream OutputStream.
Equivalent to encodeStreamWith defaultEncodeOptions.
Arguments
| :: ToRecord a | |
| => EncodeOptions | Encoding options. | 
| -> OutputStream ByteString | Downstream. | 
| -> IO (OutputStream a) | New  | 
Create a new OutputStream that can be fed ToRecord values
 which are converted to CSV.  The records are encoded into
 ByteStrings and passed on to the given downstream OutputStream.
Arguments
| :: ToNamedRecord a | |
| => Header | CSV Header. | 
| -> OutputStream ByteString | Downstream. | 
| -> IO (OutputStream a) | New  | 
Create a new OutputStream which can be fed ToNamedRecord
 values that will be converted into CSV.  The records are encoded
 into ByteStrings and passed on to the given downstream
 OutputStream.
Equivalent to encodeStreamByNameWith defaultEncodeOptions.
encodeStreamByNameWith Source #
Arguments
| :: ToNamedRecord a | |
| => EncodeOptions | Encoding options. | 
| -> Header | CSV Header. | 
| -> OutputStream ByteString | Downstream. | 
| -> IO (OutputStream a) | New  | 
Create a new OutputStream which can be fed ToNamedRecord
 values that will be converted into CSV.  The records are encoded
 into ByteStrings and passed on to the given downstream
 OutputStream.
Convenience Exports
Export data types from Data.Csv
defaultEncodeOptions :: EncodeOptions #
Encoding options for CSV files.
Should quoting be applied to fields, and at which level?
Constructors
| QuoteNone | No quotes. | 
| QuoteMinimal | Quotes according to RFC 4180. | 
| QuoteAll | Always quote. | 
data EncodeOptions #
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 
 | |
Instances
| Eq EncodeOptions | |
| Defined in Data.Csv.Encoding Methods (==) :: EncodeOptions -> EncodeOptions -> Bool # (/=) :: EncodeOptions -> EncodeOptions -> Bool # | |
| Show EncodeOptions | |
| Defined in Data.Csv.Encoding Methods showsPrec :: Int -> EncodeOptions -> ShowS # show :: EncodeOptions -> String # showList :: [EncodeOptions] -> ShowS # | |
defaultDecodeOptions :: DecodeOptions #
Decoding options for parsing CSV files.
data DecodeOptions #
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 
 | |
Instances
| Eq DecodeOptions | |
| Defined in Data.Csv.Parser Methods (==) :: DecodeOptions -> DecodeOptions -> Bool # (/=) :: DecodeOptions -> DecodeOptions -> Bool # | |
| Show DecodeOptions | |
| Defined in Data.Csv.Parser Methods showsPrec :: Int -> DecodeOptions -> ShowS # show :: DecodeOptions -> String # showList :: [DecodeOptions] -> ShowS # | |