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

Copyright© 2016–2018 Stack Builders
LicenseMIT
MaintainerMark Karpov <markkarpov92@gmail.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

newtype ConversionError Source #

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

Constructors

ConversionError String 
Instances
Eq ConversionError Source # 
Instance details

Defined in Data.Csv.Parser.Megaparsec

Data ConversionError Source # 
Instance details

Defined in Data.Csv.Parser.Megaparsec

Methods

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

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

toConstr :: ConversionError -> Constr #

dataTypeOf :: ConversionError -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ConversionError Source # 
Instance details

Defined in Data.Csv.Parser.Megaparsec

Read ConversionError Source # 
Instance details

Defined in Data.Csv.Parser.Megaparsec

Show ConversionError Source # 
Instance details

Defined in Data.Csv.Parser.Megaparsec

ShowErrorComponent ConversionError Source # 
Instance details

Defined in Data.Csv.Parser.Megaparsec

decode Source #

Arguments

:: FromRecord a 
=> HasHeader

Whether the data contains header that should be skipped

-> FilePath

File name (only for displaying in parse error messages, use empty string if you have none)

-> ByteString

CSV data

-> Either (ParseErrorBundle ByteString ConversionError) (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 (only for displaying in parse error messages, use empty string if you have none)

-> ByteString

CSV data

-> Either (ParseErrorBundle ByteString ConversionError) (Vector a) 

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

decodeByName Source #

Arguments

:: FromNamedRecord a 
=> FilePath

File name (only for displaying in parse error messages, use empty string if you have none)

-> ByteString

CSV data

-> Either (ParseErrorBundle ByteString ConversionError) (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 (only for displaying in parse error messages, use empty string if you have none)

-> ByteString

CSV data

-> Either (ParseErrorBundle ByteString ConversionError) (Header, Vector a) 

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