| Copyright | (c) Ivan Lazar Miljenovic |
|---|---|
| License | MIT |
| Maintainer | Ivan.Miljenovic@gmail.com |
| Safe Haskell | None |
| Language | Haskell2010 |
Streaming.Cassava
Description
Stream CSV data in/out using Cassava.
A common use-case is to stream CSV-encoded data in from a file.
You may be tempted to use readFile from
Data.ByteString.Streaming to obtain the file contents, but if you
do you're likely to run into exceptions such as:
hGetBufSome: illegal operation (handle is closed)
One solution is to use the streaming-with package for the IO aspects. You can then write something like:
withBinaryFileContents "myFile.csv" $
doSomethingWithStreamingCSV
. decodeByName
Synopsis
- decode :: (MonadError CsvParseException m, FromRecord a) => HasHeader -> ByteStream m r -> Stream (Of a) m r
- decodeWith :: (MonadError CsvParseException m, FromRecord a) => DecodeOptions -> HasHeader -> ByteStream m r -> Stream (Of a) m r
- decodeWithErrors :: (Monad m, FromRecord a) => DecodeOptions -> HasHeader -> ByteStream m r -> Stream (Of (Either CsvParseException a)) m (Either (CsvParseException, ByteStream m r) r)
- newtype CsvParseException = CsvParseException String
- decodeByName :: (MonadError CsvParseException m, FromNamedRecord a) => ByteStream m r -> Stream (Of a) m r
- decodeByNameWith :: (MonadError CsvParseException m, FromNamedRecord a) => DecodeOptions -> ByteStream m r -> Stream (Of a) m r
- decodeByNameWithErrors :: (Monad m, FromNamedRecord a) => DecodeOptions -> ByteStream m r -> Stream (Of (Either CsvParseException a)) m (Either (CsvParseException, ByteStream m r) r)
- encode :: (ToRecord a, Monad m) => Maybe Header -> Stream (Of a) m r -> ByteStream m r
- encodeDefault :: forall a m r. (ToRecord a, DefaultOrdered a, Monad m) => Stream (Of a) m r -> ByteStream m r
- encodeWith :: (ToRecord a, Monad m) => EncodeOptions -> Maybe Header -> Stream (Of a) m r -> ByteStream m r
- encodeByName :: (ToNamedRecord a, Monad m) => Header -> Stream (Of a) m r -> ByteStream m r
- encodeByNameDefault :: forall a m r. (DefaultOrdered a, ToNamedRecord a, Monad m) => Stream (Of a) m r -> ByteStream m r
- encodeByNameWith :: (ToNamedRecord a, Monad m) => EncodeOptions -> Header -> Stream (Of a) m r -> ByteStream m r
- class FromRecord a where
- parseRecord :: Record -> Parser a
- class FromNamedRecord a where
- parseNamedRecord :: NamedRecord -> Parser a
- class ToRecord a where
- class ToNamedRecord a where
- toNamedRecord :: a -> NamedRecord
- class DefaultOrdered a where
- headerOrder :: a -> Header
- data HasHeader
- type Header = Vector Name
- header :: [ByteString] -> Header
- type Name = ByteString
- data DecodeOptions = DecodeOptions {
- decDelimiter :: !Word8
- defaultDecodeOptions :: DecodeOptions
- data EncodeOptions = EncodeOptions {
- encDelimiter :: !Word8
- encUseCrLf :: !Bool
- encIncludeHeader :: !Bool
- encQuoting :: !Quoting
- defaultEncodeOptions :: EncodeOptions
Decoding
decode :: (MonadError CsvParseException m, FromRecord a) => HasHeader -> ByteStream m r -> Stream (Of a) m r Source #
Use defaultOptions for decoding the provided CSV.
decodeWith :: (MonadError CsvParseException m, FromRecord a) => DecodeOptions -> HasHeader -> ByteStream m r -> Stream (Of a) m r Source #
Return back a stream of values from the provided CSV, stopping at the first error.
If you wish to instead ignore errors, consider using
decodeWithErrors with either mapMaybe or .effects
. partitionEithers
Unlike decodeWithErrors, any remaining input is discarded.
decodeWithErrors :: (Monad m, FromRecord a) => DecodeOptions -> HasHeader -> ByteStream m r -> Stream (Of (Either CsvParseException a)) m (Either (CsvParseException, ByteStream m r) r) Source #
Return back a stream with an attempt at type conversion, and either the previous result or any overall parsing errors with the remainder of the input.
partitionEithers may be useful when using this function.
newtype CsvParseException Source #
Constructors
| CsvParseException String |
Instances
| Eq CsvParseException Source # | |
Defined in Streaming.Cassava Methods (==) :: CsvParseException -> CsvParseException -> Bool # (/=) :: CsvParseException -> CsvParseException -> Bool # | |
| Show CsvParseException Source # | |
Defined in Streaming.Cassava Methods showsPrec :: Int -> CsvParseException -> ShowS # show :: CsvParseException -> String # showList :: [CsvParseException] -> ShowS # | |
| IsString CsvParseException Source # | |
Defined in Streaming.Cassava Methods fromString :: String -> CsvParseException # | |
| Exception CsvParseException Source # | |
Defined in Streaming.Cassava Methods toException :: CsvParseException -> SomeException # | |
Named decoding
decodeByName :: (MonadError CsvParseException m, FromNamedRecord a) => ByteStream m r -> Stream (Of a) m r Source #
Use defaultOptions for decoding the provided CSV.
decodeByNameWith :: (MonadError CsvParseException m, FromNamedRecord a) => DecodeOptions -> ByteStream m r -> Stream (Of a) m r Source #
Return back a stream of values from the provided CSV, stopping at the first error.
A header is required to determine the order of columns, but then discarded.
If you wish to instead ignore errors, consider using
decodeByNameWithErrors with either mapMaybe or .effects
. partitionEithers
Unlike decodeByNameWithErrors, any remaining input is
discarded.
decodeByNameWithErrors :: (Monad m, FromNamedRecord a) => DecodeOptions -> ByteStream m r -> Stream (Of (Either CsvParseException a)) m (Either (CsvParseException, ByteStream m r) r) Source #
Return back a stream with an attempt at type conversion, but where the order of columns doesn't have to match the order of fields of your actual type.
This requires/assumes a header in the CSV stream, which is discarded after parsing.
partitionEithers may be useful when using this function.
Encoding
encode :: (ToRecord a, Monad m) => Maybe Header -> Stream (Of a) m r -> ByteStream m r Source #
Encode a stream of values with the default options.
Optionally prefix the stream with headers (the header function
may be useful).
encodeDefault :: forall a m r. (ToRecord a, DefaultOrdered a, Monad m) => Stream (Of a) m r -> ByteStream m r Source #
Encode a stream of values with the default options and a derived header prefixed.
encodeWith :: (ToRecord a, Monad m) => EncodeOptions -> Maybe Header -> Stream (Of a) m r -> ByteStream m r Source #
Encode a stream of values with the provided options.
Optionally prefix the stream with headers (the header function
may be useful).
Named encoding
encodeByName :: (ToNamedRecord a, Monad m) => Header -> Stream (Of a) m r -> ByteStream m r Source #
Select the columns that you wish to encode from your data structure using default options (which currently includes printing the header).
encodeByNameDefault :: forall a m r. (DefaultOrdered a, ToNamedRecord a, Monad m) => Stream (Of a) m r -> ByteStream m r Source #
Use the default ordering to encode all fields/columns.
encodeByNameWith :: (ToNamedRecord a, Monad m) => EncodeOptions -> Header -> Stream (Of a) m r -> ByteStream m r Source #
Select the columns that you wish to encode from your data structure.
Header printing respects encIncludeheader.
Re-exports
class FromRecord a where #
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 = mzeroMinimal complete definition
Nothing
Methods
parseRecord :: Record -> Parser a #
Instances
class FromNamedRecord a where #
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.
Minimal complete definition
Nothing
Methods
parseNamedRecord :: NamedRecord -> Parser a #
Instances
| (FromField a, FromField b, Ord a) => FromNamedRecord (Map a b) | |
Defined in Data.Csv.Conversion Methods parseNamedRecord :: NamedRecord -> Parser (Map a b) # | |
| (Eq a, FromField a, FromField b, Hashable a) => FromNamedRecord (HashMap a b) | |
Defined in Data.Csv.Conversion Methods parseNamedRecord :: NamedRecord -> Parser (HashMap a b) # | |
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
Minimal complete definition
Nothing
Instances
class ToNamedRecord a where #
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]Minimal complete definition
Nothing
Instances
| (ToField a, ToField b, Ord a) => ToNamedRecord (Map a b) | |
Defined in Data.Csv.Conversion Methods toNamedRecord :: Map a b -> NamedRecord # | |
| (Eq a, ToField a, ToField b, Hashable a) => ToNamedRecord (HashMap a b) | |
Defined in Data.Csv.Conversion Methods toNamedRecord :: HashMap a b -> NamedRecord # | |
class DefaultOrdered a where #
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’Minimal complete definition
Nothing
Methods
headerOrder :: 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)
Is the CSV data preceded by a header?
The header corresponds to the first line a CSV file. Not all CSV files have a header.
header :: [ByteString] -> Header #
Construct a header from a list of ByteStrings.
type Name = ByteString #
A header has one or more names, describing the data in the column following the name.
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 # | |
defaultDecodeOptions :: DecodeOptions #
Decoding options for parsing CSV files.
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 # | |
defaultEncodeOptions :: EncodeOptions #
Encoding options for CSV files.