sv-0.1: Encode and decode separated values (CSV, PSV, ...)

Copyright(C) CSIRO 2017-2018
LicenseBSD3
MaintainerGeorge Wilson <george.wilson@data61.csiro.au>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Sv.Decode.Error

Contents

Description

 

Synopsis

Documentation

data DecodeError e Source #

DecodeError is a value indicating what went wrong during a parse or decode. Its constructor indictates the type of error which occured, and there is usually an associated string with more finely-grained details.

Constructors

UnexpectedEndOfRow

I was looking for another field, but I am at the end of the row

ExpectedEndOfRow (Vector (SpacedField e))

I should be at the end of the row, but I found extra fields

UnknownCategoricalValue e [[e]]

This decoder was built using the categorical primitive for categorical data

BadParse e

The parser failed, meaning decoding proper didn't even begin

BadDecode e

Some other kind of decoding failure occured

Instances

Functor DecodeError Source # 

Methods

fmap :: (a -> b) -> DecodeError a -> DecodeError b #

(<$) :: a -> DecodeError b -> DecodeError a #

Eq e => Eq (DecodeError e) Source # 
Ord e => Ord (DecodeError e) Source # 
Show e => Show (DecodeError e) Source # 
Generic (DecodeError e) Source # 

Associated Types

type Rep (DecodeError e) :: * -> * #

Methods

from :: DecodeError e -> Rep (DecodeError e) x #

to :: Rep (DecodeError e) x -> DecodeError e #

NFData e => NFData (DecodeError e) Source # 

Methods

rnf :: DecodeError e -> () #

type Rep (DecodeError e) Source # 

newtype DecodeErrors e Source #

DecodeErrors is a Semigroup full of DecodeError. It is used as the error side of a DecodeValidation. When multiple errors occur, they will be collected.

Constructors

DecodeErrors (NonEmpty (DecodeError e)) 

Instances

Functor DecodeErrors Source # 

Methods

fmap :: (a -> b) -> DecodeErrors a -> DecodeErrors b #

(<$) :: a -> DecodeErrors b -> DecodeErrors a #

Eq e => Eq (DecodeErrors e) Source # 
Ord e => Ord (DecodeErrors e) Source # 
Show e => Show (DecodeErrors e) Source # 
Generic (DecodeErrors e) Source # 

Associated Types

type Rep (DecodeErrors e) :: * -> * #

Methods

from :: DecodeErrors e -> Rep (DecodeErrors e) x #

to :: Rep (DecodeErrors e) x -> DecodeErrors e #

Semigroup (DecodeErrors e) Source # 
NFData e => NFData (DecodeErrors e) Source # 

Methods

rnf :: DecodeErrors e -> () #

type Rep (DecodeErrors e) Source # 
type Rep (DecodeErrors e) = D1 * (MetaData "DecodeErrors" "Data.Sv.Decode.Type" "sv-0.1-LEjGD2ajzYS6ZNIUObPicZ" True) (C1 * (MetaCons "DecodeErrors" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (NonEmpty (DecodeError e)))))

Convenience constructors

expectedEndOfRow :: Vector (SpacedField e) -> DecodeValidation e a Source #

Fail with ExpectedEndOfRow. This takes the rest of the row, so that it can be displayed to the user.

unknownCategoricalValue :: e -> [[e]] -> DecodeValidation e a Source #

Fail with UnknownCategoricalValue. It takes the unknown value and the list of good categorical values.

This mostly exists to be used by the categorical function.

badParse :: e -> DecodeValidation e a Source #

Fail with BadParse with the given message. This is for when the parse step fails, and decoding does not even begin.

badDecode :: e -> DecodeValidation e a Source #

Fail with BadDecode with the given message. This is something of a generic error for when decoding a field goes wrong.

Conversions

validateEither' :: (e -> DecodeError e') -> Either e a -> DecodeValidation e' a Source #

Build a DecodeValidation from an Either, given a function to build the error.

validateMaybe :: DecodeError e -> Maybe b -> DecodeValidation e b Source #

Build a DecodeValidation from a Maybe. You have to supply an error to use in the Nothing case

validateMaybe' :: (a -> Maybe b) -> DecodeError e -> a -> DecodeValidation e b Source #

Build a DecodeValidation from a function that returns a Maybe You have to supply an error to use in the Nothing case

Re-exports from validation

bindValidation :: Validation e a -> (a -> Validation e b) -> Validation e b #

bindValidation binds through an Validation, which is useful for composing Validations sequentially. Note that despite having a bind function of the correct type, Validation is not a monad. The reason is, this bind does not accumulate errors, so it does not agree with the Applicative instance.

There is nothing wrong with using this function, it just does not make a valid Monad instance.