Safe Haskell | None |
---|
- class CSV s r where
- rowToStr :: CSVSettings -> r -> s
- intoCSV :: MonadResource m => CSVSettings -> GLInfConduit s m r
- fromCSV :: MonadResource m => CSVSettings -> GInfConduit r m s
- writeHeaders :: (MonadResource m, CSV s (Row r), IsString s) => CSVSettings -> GConduit (MapRow r) m s
- readCSVFile :: CSV ByteString a => CSVSettings -> FilePath -> IO [a]
- writeCSVFile :: CSV ByteString a => CSVSettings -> FilePath -> IOMode -> [a] -> IO ()
- transformCSV :: (MonadResource m, CSV s a, CSV s' b) => CSVSettings -> Source m s -> Conduit a m b -> Sink s' m () -> m ()
- mapCSVFile :: (MonadResource m, CSV ByteString a, CSV ByteString b) => CSVSettings -> (a -> [b]) -> FilePath -> FilePath -> m ()
- data CSVSettings = CSVS {
- csvSep :: !Char
- csvQuoteChar :: !(Maybe Char)
- csvOutputQuoteChar :: !(Maybe Char)
- csvOutputColSep :: !Char
- defCSVSettings :: CSVSettings
- type MapRow a = Map a a
- type Row a = [a]
- runResourceT :: MonadBaseControl IO m => ResourceT m a -> m a
Key Operations
Represents types r
that are CSV-like and can be converted
to/from an underlying stream of type s
.
Example #1: Basics Using Convenience API
import Data.Conduit import Data.Conduit.Binary import Data.Conduit.List as CL import Data.CSV.Conduit myProcessor :: Conduit (Row Text) m (Row Text) myProcessor = CL.map reverse test = runResourceT $ transformCSV defCSVSettings (sourceFile "input.csv") myProcessor (sinkFile "output.csv")
Example #2: Basics Using Conduit API
import Data.Conduit import Data.Conduit.Binary import Data.CSV.Conduit myProcessor :: Conduit (MapRow Text) m (MapRow Text) myProcessor = undefined test = runResourceT $ sourceFile "test/BigFile.csv" $= intoCSV defCSVSettings $= myProcessor $= (writeHeaders defCSVSettings >> fromCSV defCSVSettings) $$ sinkFile "test/BigFileOut.csv"
rowToStr :: CSVSettings -> r -> sSource
Convert a CSV row into strict ByteString equivalent.
intoCSV :: MonadResource m => CSVSettings -> GLInfConduit s m rSource
Turn a stream of s
into a stream of CSV row type. An example
would be parsing a ByteString stream as rows of MapRow
Text
.
fromCSV :: MonadResource m => CSVSettings -> GInfConduit r m sSource
Turn a stream of CSV row type back into a stream of s
. An
example would be rendering a stream of Row
ByteString
rows as
Text
.
(CSV s (Row s'), Ord s', IsString s) => CSV s (MapRow s') | Generic |
CSV ByteString (Row ByteString) |
|
CSV ByteString (Row Text) |
|
CSV Text (Row Text) |
writeHeaders :: (MonadResource m, CSV s (Row r), IsString s) => CSVSettings -> GConduit (MapRow r) m sSource
Write headers AND the row into the output stream, once. Just
chain this using the Monad
instance in your pipeline:
... =$= writeHeaders settings >> fromCSV settings $$ sinkFile "..."
Convenience Functions
:: CSV ByteString a | |
=> CSVSettings | Settings to use in deciphering stream |
-> FilePath | Input file |
-> IO [a] |
Read the entire contents of a CSV file into memory.
An easy way to run this function would be runResourceT
after
feeding it all the arguments.
:: CSV ByteString a | |
=> CSVSettings | CSV Settings |
-> FilePath | Target file |
-> IOMode | Write vs. append mode |
-> [a] | List of rows |
-> IO () |
Write CSV data into file.
:: (MonadResource m, CSV s a, CSV s' b) | |
=> CSVSettings | Settings to be used for input and output |
-> Source m s | A raw stream data source. Ex: 'sourceFile inFile' |
-> Conduit a m b | A transforming conduit |
-> Sink s' m () | A raw stream data sink. Ex: 'sinkFile outFile' |
-> m () |
General purpose CSV transformer. Apply a list-like processing
function from List
to the rows of a CSV stream. You
need to provide a stream data source, a transformer and a stream
data sink.
An easy way to run this function would be runResourceT
after
feeding it all the arguments.
Example - map a function over the rows of a CSV file:
transformCSV set (sourceFile inFile) (C.map f) (sinkFile outFile)
:: (MonadResource m, CSV ByteString a, CSV 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. Provided for convenience for historical reasons.
An easy way to run this function would be runResourceT
after
feeding it all the arguments.
Important Types
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.
CSVS | |
|
defCSVSettings :: CSVSettingsSource
Default settings for a CSV file.
csvSep = ',' csvQuoteChar = Just '"' csvOutputQuoteChar = Just '"' csvOutputColSep = ','
Re-exported For Convenience
runResourceT :: MonadBaseControl IO m => ResourceT m a -> m a
Unwrap a ResourceT
transformer, and call all registered release actions.
Note that there is some reference counting involved due to resourceForkIO
.
If multiple threads are sharing the same collection of resources, only the
last call to runResourceT
will deallocate the resources.
Since 0.3.0