cassava-megaparsec-2.1.1: Megaparsec parser of CSV files that plays nicely with Cassava
Copyright© 2016–2021 Stack Builders
LicenseMIT
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Csv.Parser.Megaparsec.Internals

Description

 
Synopsis

Documentation

newtype ConversionError Source #

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

Constructors

ConversionError String 

Instances

Instances details
Data ConversionError Source # 
Instance details

Defined in Data.Csv.Parser.Megaparsec.Internals

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 :: forall r r'. (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 #

Read ConversionError Source # 
Instance details

Defined in Data.Csv.Parser.Megaparsec.Internals

Show ConversionError Source # 
Instance details

Defined in Data.Csv.Parser.Megaparsec.Internals

Eq ConversionError Source # 
Instance details

Defined in Data.Csv.Parser.Megaparsec.Internals

Ord ConversionError Source # 
Instance details

Defined in Data.Csv.Parser.Megaparsec.Internals

ShowErrorComponent ConversionError Source # 
Instance details

Defined in Data.Csv.Parser.Megaparsec.Internals

type Parser = Parsec ConversionError ByteString Source #

Parser type that uses “custom error component” ConversionError.

csv Source #

Arguments

:: FromRecord a 
=> DecodeOptions

Decoding options

-> Parser (Vector a)

The parser that parses collection of records

Parse a CSV file that does not include a header.

csvWithHeader Source #

Arguments

:: FromNamedRecord a 
=> DecodeOptions

Decoding options

-> Parser (Header, Vector a)

The parser that parser collection of named records

Parse a CSV file that includes a header.

decodeWithC Source #

Arguments

:: (DecodeOptions -> Parser a)

Parsing function parametrized by DecodeOptions

-> DecodeOptions

Decoding options

-> HasHeader

Whether to expect a header in the input

-> FilePath

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

-> ByteString

CSV data

-> Either (ParseErrorBundle ByteString ConversionError) a 

Decode CSV data using the provided parser, skipping a leading header if necessary.

toNamedRecord :: Header -> Record -> NamedRecord Source #

Convert a Record to a NamedRecord by attaching column names. The Header and Record must be of the same length.

header :: Word8 -> Parser Header Source #

Parse a header, including the terminating line separator.

name :: Word8 -> Parser Name Source #

Parse a header name. Header names have the same format as regular fields.

record Source #

Arguments

:: Word8

Field delimiter

-> (Record -> Parser a)

How to “parse” record to get the data of interest

-> Parser a 

Parse a record, not including the terminating line separator. The terminating line separate is not included as the last record in a CSV file is allowed to not have a terminating line separator.

field :: Word8 -> Parser Field Source #

Parse a field. The field may be in either the escaped or non-escaped format. The returned value is unescaped.

escapedField :: Parser ByteString Source #

Parse an escaped field.

unescapedField :: Word8 -> Parser ByteString Source #

Parse an unescaped field.