csv-conduit-0.1: A flexible, fast, conduit-based CSV parser library for Haskell.

Safe HaskellSafe-Infered

Data.CSV.Conduit

Contents

Synopsis

Documentation

class CSVeable s r whereSource

Represents types r that can be converted from an underlying stream of type s.

Example processing using MapRow Text isntance:

 test :: IO ()
 test = runResourceT $ 
   sourceFile test/BigFile.csv $= 
   decode utf8 $=
   intoCSV defCSVSettings $=
   myMapRowProcessingConduit $=
   fromCSV defCSVSettings $=
   encode utf8 $$
   sinkFile test/BigFileOut.csv

Methods

rowToStr :: CSVSettings -> r -> sSource

Convert a CSV row into strict ByteString equivalent.

intoCSV :: MonadResource m => CSVSettings -> Conduit s m rSource

Turn a stream of s into a stream of CSV row type

fromCSV :: MonadResource m => CSVSettings -> Conduit r m sSource

Turn a stream of CSV row type back into a stream of s

Instances

(CSVeable s (Row s'), Ord s', IsString s) => CSVeable s (MapRow s')

Generic MapRow instance; any stream type with a Row instance automatically gets a MapRow instance.

CSVeable ByteString (Row ByteString)

Row instance using ByteString

CSVeable ByteString (Row Text)

Row instance using Text based on ByteString stream

CSVeable Text (Row Text)

Row instance using Text

data CSVSettings Source

Settings for a CSV file. This library is intended to be flexible and offer a way to process the majority of text data files out there.

Constructors

CSVS 

Fields

csvSep :: !Char

Separator character to be used in between fields

csvQuoteChar :: !(Maybe Char)

Quote character that may sometimes be present around fields. If Nothing is given, the library will never expect quotation even if it is present.

csvOutputQuoteChar :: !(Maybe Char)

Quote character that should be used in the output.

csvOutputColSep :: !Char

Field separator that should be used in the output.

defCSVSettings :: CSVSettingsSource

Default settings for a CSV file.

 csvSep = ','
 csvQuoteChar = Just '"'
 csvOutputQuoteChar = Just '"'
 csvOutputColSep = ','

type MapRow a = Map a aSource

A MapRow is a dictionary based on Map

type Row a = [a]Source

A Row is just a list of fields

Convenience Functions

readCSVFile :: (MonadUnsafeIO m, MonadThrow m, MonadBaseControl IO m, MonadIO m, CSVeable ByteString a) => CSVSettings -> FilePath -> m [a]Source

Read the entire contents of a CSV file into memory

mapCSVFileSource

Arguments

:: (MonadIO m, MonadUnsafeIO m, MonadThrow m, MonadBaseControl IO m, CSVeable ByteString a, CSVeable ByteString b) 
=> CSVSettings

Settings to use both for input and output

-> (a -> b)

A mapping function

-> FilePath

Input file

-> FilePath

Output file

-> m () 

Map over the rows of a CSV file. Don't be scared by the type signature, this can just run in IO.