cassava-megaparsec-0.1.0: Megaparsec parser of CSV files that plays nicely with Cassava

Copyright© 2016 Stack Builders
LicenseMIT
MaintainerMark Karpov <markkarpov@openmailbox.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Csv.Parser.Megaparsec

Description

A CSV parser. The parser here is RFC 4180 compliant, with the following extensions:

  • Non-escaped fields may contain any characters except double-quotes, commas (or generally delimiter characters), carriage returns, and newlines.
  • Escaped fields may contain any characters, but double-quotes need to be escaped.

The parser provides better error messages than the parser that comes with Cassava library, while being compatible with the rest of the library.

Synopsis

Documentation

data Cec Source #

Custom error component for CSV parsing. It allows typed reporting of conversion errors.

Instances

Eq Cec Source # 

Methods

(==) :: Cec -> Cec -> Bool #

(/=) :: Cec -> Cec -> Bool #

Data Cec Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cec -> c Cec #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cec #

toConstr :: Cec -> Constr #

dataTypeOf :: Cec -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Cec) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cec) #

gmapT :: (forall b. Data b => b -> b) -> Cec -> Cec #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cec -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cec -> r #

gmapQ :: (forall d. Data d => d -> u) -> Cec -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Cec -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cec -> m Cec #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cec -> m Cec #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cec -> m Cec #

Ord Cec Source # 

Methods

compare :: Cec -> Cec -> Ordering #

(<) :: Cec -> Cec -> Bool #

(<=) :: Cec -> Cec -> Bool #

(>) :: Cec -> Cec -> Bool #

(>=) :: Cec -> Cec -> Bool #

max :: Cec -> Cec -> Cec #

min :: Cec -> Cec -> Cec #

Read Cec Source # 
Show Cec Source # 

Methods

showsPrec :: Int -> Cec -> ShowS #

show :: Cec -> String #

showList :: [Cec] -> ShowS #

ErrorComponent Cec Source # 
ShowErrorComponent Cec Source # 

decode Source #

Arguments

:: FromRecord a 
=> HasHeader

Whether the data contains header that should be skipped

-> FilePath

File name (use empty string if you have none)

-> ByteString

CSV data

-> Either (ParseError Char Cec) (Vector a) 

Deserialize CSV records form a lazy ByteString. If this fails due to incomplete or invalid input, Left is returned. Equivalent to decodeWith defaultDecodeOptions.

decodeWith Source #

Arguments

:: FromRecord a 
=> DecodeOptions

Decoding options

-> HasHeader

Whether the data contains header that should be skipped

-> FilePath

File name (use empty string if you have none)

-> ByteString

CSV data

-> Either (ParseError Char Cec) (Vector a) 

Like decode, but lets you customize how the CSV data is parsed.

decodeByName Source #

Arguments

:: FromNamedRecord a 
=> FilePath

File name (use empty string if you have none)

-> ByteString

CSV data

-> Either (ParseError Char Cec) (Header, Vector a) 

Deserialize CSV records from a lazy ByteString. If this fails due to incomplete or invalid input, Left is returned. The data is assumed to be preceded by a header. Equivalent to decodeByNameWith defaultDecodeOptions.

decodeByNameWith Source #

Arguments

:: FromNamedRecord a 
=> DecodeOptions

Decoding options

-> FilePath

File name (use empty string if you have none)

-> ByteString

CSV data

-> Either (ParseError Char Cec) (Header, Vector a) 

Like decodeByName, but lets you customize how the CSV data is parsed.