| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Box.Csv
Contents
Description
A csv process based on attoparsec and the box library
Synopsis
- data CsvConfig = CsvConfig {}
- defaultCsvConfig :: CsvConfig
- data Header
- rowEmitter :: CsvConfig -> (Char -> Parser a) -> CoEmitter IO (Either Text a)
- rowCommitter :: CsvConfig -> (a -> [Text]) -> CoCommitter IO a
- runCsv :: CsvConfig -> (Char -> Parser a) -> IO [Either Text a]
- sep :: Char -> Parser ()
- field_ :: Char -> Parser Text
- field :: Char -> Parser Text
- skipField_ :: Char -> Parser ()
- skipField :: Char -> Parser ()
- int :: Parser Int
- int' :: Char -> Parser Int
- double :: Parser Double
- double' :: Char -> Parser Double
- fields :: Char -> Parser [Text]
- ints :: Char -> Parser [Int]
- doubles :: Char -> Parser [Double]
- day' :: Char -> Parser Day
- tod' :: Char -> Parser TimeOfDay
- localtime' :: Char -> Parser LocalTime
Documentation
csv file configuration
Constructors
| CsvConfig | |
Instances
| Eq CsvConfig Source # | |
| Show CsvConfig Source # | |
| Generic CsvConfig Source # | |
| type Rep CsvConfig Source # | |
Defined in Box.Csv type Rep CsvConfig = D1 ('MetaData "CsvConfig" "Box.Csv" "box-csv-0.2.0-7GhFxJeLMLLAAK4EeBTXsI" 'False) (C1 ('MetaCons "CsvConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "file") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FilePath) :*: (S1 ('MetaSel ('Just "fsep") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Char) :*: S1 ('MetaSel ('Just "header") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Header)))) | |
defaultCsvConfig :: CsvConfig Source #
default csv file details
>>>defaultCsvConfigCsvConfig {file = "./other/time_series_covid19_deaths_global_narrow.csv", fsep = ',', header = HasHXL}
test data from https://data.humdata.org/dataset/novel-coronavirus-2019-ncov-cases
Type of header rows. Note the modern propensity for multiple header rows.
rowCommitter :: CsvConfig -> (a -> [Text]) -> CoCommitter IO a Source #
commits printed csv rows
>>>let testConfig = CsvConfig "./test/test.csv" ',' NoHeader>>>let ctest = rowCommitter testConfig (fmap (Text.intercalate "," . fmap (Text.pack . show)))
>>>(\c -> commit c [[1..10::Int]]) <$|> ctestTrue
>>>emit <$|> rowEmitter testConfig intsJust (Right [1,2,3,4,5,6,7,8,9,10])
runCsv :: CsvConfig -> (Char -> Parser a) -> IO [Either Text a] Source #
Run a parser across all lines of a file.
>>>r1 <- runCsv defaultCsvConfig fields>>>length r142562
>>>length [x | (Left x) <- r1]0
>>>take 2 $ drop 2 [x | (Right x) <- r1][["","Afghanistan","33.0","65.0","2020-06-29","733","AFG","142","34","\r"],["","Afghanistan","33.0","65.0","2020-06-28","721","AFG","142","34","\r"]]
parsers
sep :: Char -> Parser () Source #
Most parsing and building routines implicity assume a character acting as a separator of fields, and newlines separating rows.
>>>A.parse (sep ',') ",ok"Done "ok" ()
field_ :: Char -> Parser Text Source #
an unquoted field Does not consume the separator token
>>>A.parse (field_ ',') "field,ok"Done ",ok" "field"
field :: Char -> Parser Text Source #
an unquoted field Consume the separator token
>>>A.parse (field ',') "field,ok"Done "ok" "field"
skipField_ :: Char -> Parser () Source #
skipping a field
>>>A.parse (skipField_ ',') "field,ok"Done ",ok" ()
skipField :: Char -> Parser () Source #
skipping a field
>>>A.parse (skipField ',') "field,ok"Done "ok" ()
int' :: Char -> Parser Int Source #
int parser, consumes separator
>>>A.parse (int' ',') "234,ok"Done "ok" 234
Parse a Double.
This parser accepts an optional leading sign character, followed by
at most one decimal digit. The syntax is similar to that accepted by
the read function, with the exception that a trailing '.' is
consumed.
Examples
These examples use this helper:
r ::Parsera ->Text->Resulta r p s =feed(parsep s)mempty
Examples with behaviour identical to read, if you feed an empty
continuation to the first result:
r double "3" == Done "" 3.0 r double "3.1" == Done "" 3.1 r double "3e4" == Done "" 30000.0 r double "3.1e4" == Done "" 31000.0 r double "3e" == Done "e" 3.0
Examples with behaviour identical to read:
r double ".3" == Fail ".3" _ _ r double "e3" == Fail "e3" _ _
Example of difference from read:
r double "3.foo" == Done "foo" 3.0
This function does not accept string representations of "NaN" or "Infinity".
double' :: Char -> Parser Double Source #
double parser, consumes separator
>>>A.parse (double' ',') "234.000,ok"Done "ok" 234.0
fields :: Char -> Parser [Text] Source #
Parser for a csv row of [Text].
>>>A.parseOnly (fields ',') "field1,field2\r"Right ["field1","field2\r"]
ints :: Char -> Parser [Int] Source #
parser for a csv row of [Int]
>>>A.parseOnly (ints ',') "1,2,3"Right [1,2,3]
doubles :: Char -> Parser [Double] Source #
parser for a csv row of [Double]
>>>A.parseOnly (doubles ',') "1,2,3"Right [1.0,2.0,3.0]
day' :: Char -> Parser Day Source #
Day parser, consumes separator
>>>A.parse (day' ',') "2020-07-01,ok"Done "ok" 2020-07-01