Copyright | (C) CSIRO 2017-2018 |
---|---|
License | BSD3 |
Maintainer | George Wilson <george.wilson@data61.csiro.au> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data DecodeError e
- = UnexpectedEndOfRow
- | ExpectedEndOfRow (Vector e)
- | UnknownCategoricalValue e [[e]]
- | MissingColumn e
- | MissingHeader
- | BadConfig e
- | BadParse e
- | BadDecode e
- newtype DecodeErrors e = DecodeErrors (NonEmpty (DecodeError e))
- decodeError :: DecodeError e -> DecodeValidation e a
- unexpectedEndOfRow :: DecodeValidation e a
- expectedEndOfRow :: Vector e -> DecodeValidation e a
- unknownCategoricalValue :: e -> [[e]] -> DecodeValidation e a
- missingColumn :: e -> DecodeValidation e a
- missingHeader :: DecodeValidation e a
- badConfig :: e -> DecodeValidation e a
- badParse :: e -> DecodeValidation e a
- badDecode :: e -> DecodeValidation e a
- validateEither :: Either (DecodeError e) a -> DecodeValidation e a
- validateEitherWith :: (e -> DecodeError e') -> Either e a -> DecodeValidation e' a
- validateMaybe :: DecodeError e -> Maybe b -> DecodeValidation e b
- validateTrifectaResult :: (String -> DecodeError e) -> Result a -> DecodeValidation e a
- bindValidation :: Validation e a -> (a -> Validation e b) -> Validation e b
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.
UnexpectedEndOfRow | I was looking for another field, but I am at the end of the row |
ExpectedEndOfRow (Vector e) | I should be at the end of the row, but I found extra fields |
UnknownCategoricalValue e [[e]] | This decoder was built using the |
MissingColumn e | Looked for a column with this name, but could not find it |
MissingHeader | There should have been a header but there was nothing |
BadConfig e | sv is misconfigured |
BadParse e | The parser failed, meaning decoding proper didn't even begin |
BadDecode e | Some other kind of decoding failure occured |
Instances
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.
DecodeErrors (NonEmpty (DecodeError e)) |
Instances
Convenience constructors
decodeError :: DecodeError e -> DecodeValidation e a Source #
Build a failing DecodeValidation
unexpectedEndOfRow :: DecodeValidation e a Source #
Fail with UnexpectedEndOfRow
expectedEndOfRow :: Vector 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.
missingColumn :: e -> DecodeValidation e a Source #
Fail with MissingColumn
with the given column name. This is for when a
NameDecode
looks for a column that doesn't exist.
missingHeader :: DecodeValidation e a Source #
Fail with MissingHeader
. This is for when the user asks for a header but
the input document is completely empty (that is, it has nothing that could be
considered a header).
badConfig :: e -> DecodeValidation e a Source #
Fail with badConfig
. This is for when the user has asked for something
impossible, like to decode a CSV by column name while asserting there's no
header.
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 :: Either (DecodeError e) a -> DecodeValidation e a Source #
Build a DecodeValidation
from an Either
validateEitherWith :: (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
validateTrifectaResult :: (String -> DecodeError e) -> Result a -> DecodeValidation e a Source #
Convert a Text.Trifecta Result
to a DecodeValidation
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.