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 |
- newtype Decode e s a = Decode {
- unwrapDecode :: Compose (DecodeState s) (DecodeValidation e) a
- type Decode' s = Decode s s
- buildDecode :: (Vector (SpacedField s) -> Ind -> (DecodeValidation e a, Ind)) -> Decode e s a
- newtype DecodeState s a = DecodeState {
- getDecodeState :: ReaderT (Vector (SpacedField s)) (State Ind) a
- runDecodeState :: DecodeState s a -> Vector (SpacedField s) -> Ind -> (a, Ind)
- newtype Ind = Ind Int
- data DecodeError e
- = UnexpectedEndOfRow
- | ExpectedEndOfRow (Vector (SpacedField e))
- | UnknownCategoricalValue e [[e]]
- | BadParse e
- | BadDecode e
- newtype DecodeErrors e = DecodeErrors (NonEmpty (DecodeError e))
- type DecodeValidation e = Validation (DecodeErrors e)
- data Validation err a :: * -> * -> *
Documentation
A 'Decode e s a' is for decoding some fields from a CSV row into our type a
.
The second type parameter (s
) is the input string type
(usually ByteString
or Text
).
The first type parameter (e
) is the type of strings which occur in errors.
Under most circumstances you want these type paraters to coincide, but they
don't have to. They are two separate type parameters instead of one so that
Decode
can have a Profunctor
instance.
There are primitive Decode
s, and combinators for composing or
otherwise manipulating them. In particular, Decode
is an
Applicative
functor and an Alt
from the semigroupoids package.
Decode
is not a Monad
, but we can perform monad-like operations on
it with >>==
and bindDecode
Decode | |
|
buildDecode :: (Vector (SpacedField s) -> Ind -> (DecodeValidation e a, Ind)) -> Decode e s a Source #
Convenient constructor for Decode
that handles all the newtype noise for you.
newtype DecodeState s a Source #
As we decode a row of data, we walk through its Field
s. This Monad
keeps track of our remaining Field
s.
DecodeState | |
|
Profunctor DecodeState Source # | |
MonadState Ind (DecodeState s) Source # | |
Monad (DecodeState s) Source # | |
Functor (DecodeState s) Source # | |
Applicative (DecodeState s) Source # | |
Apply (DecodeState s) Source # | |
Bind (DecodeState s) Source # | |
MonadReader (Vector (SpacedField s)) (DecodeState s) Source # | |
runDecodeState :: DecodeState s a -> Vector (SpacedField s) -> Ind -> (a, Ind) Source #
Convenient function to run a DecodeState
Newtype for indices into the field vector
MonadState Ind (DecodeState s) Source # | |
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 (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 |
BadParse e | The parser failed, meaning decoding proper didn't even begin |
BadDecode e | Some other kind of decoding failure occured |
Functor DecodeError Source # | |
Eq e => Eq (DecodeError e) Source # | |
Ord e => Ord (DecodeError e) Source # | |
Show e => Show (DecodeError e) Source # | |
Generic (DecodeError e) Source # | |
NFData e => NFData (DecodeError e) Source # | |
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.
DecodeErrors (NonEmpty (DecodeError e)) |
Functor DecodeErrors Source # | |
Eq e => Eq (DecodeErrors e) Source # | |
Ord e => Ord (DecodeErrors e) Source # | |
Show e => Show (DecodeErrors e) Source # | |
Generic (DecodeErrors e) Source # | |
Semigroup (DecodeErrors e) Source # | |
NFData e => NFData (DecodeErrors e) Source # | |
type Rep (DecodeErrors e) Source # | |
type DecodeValidation e = Validation (DecodeErrors e) Source #
DecodeValidation
is the error-accumulating Applicative
underlying
Decode
data Validation err a :: * -> * -> * #
An Validation
is either a value of the type err
or a
, similar to Either
. However,
the Applicative
instance for Validation
accumulates errors using a Semigroup
on err
.
In contrast, the Applicative
for Either
returns only the first error.
A consequence of this is that Validation
has no Bind
or Monad
instance. This is because
such an instance would violate the law that a Monad's ap
must equal the
Applicative
's <*>
An example of typical usage can be found here.
Bitraversable Validation | |
Bifoldable Validation | |
Bifunctor Validation | |
Swapped Validation | |
Validate Validation | |
Functor (Validation err) | |
Semigroup err => Applicative (Validation err) | |
Foldable (Validation err) | |
Traversable (Validation err) | |
Semigroup err => Apply (Validation err) | |
Alt (Validation err) | |
(Eq a, Eq err) => Eq (Validation err a) | |
(Data a, Data err) => Data (Validation err a) | |
(Ord a, Ord err) => Ord (Validation err a) | |
(Show a, Show err) => Show (Validation err a) | |
Generic (Validation err a) | |
Semigroup e => Semigroup (Validation e a) | |
Monoid e => Monoid (Validation e a) | |
(NFData e, NFData a) => NFData (Validation e a) | |
type Rep (Validation err a) | |