| Copyright | (C) CSIRO 2017-2019 | 
|---|---|
| License | BSD3 | 
| Maintainer | George Wilson <george.wilson@data61.csiro.au> | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Sv.Decode.Type
Description
Synopsis
- newtype Decode e s a = Decode {- unwrapDecode :: Compose (DecodeState s) (Compose (Writer (Last Bool)) (DecodeValidation e)) a
 
- type Decode' s = Decode s s
- buildDecode :: (Vector s -> Ind -> (DecodeValidation e a, Last Bool, Ind)) -> Decode e s a
- newtype NameDecode e s a = Named {}
- type NameDecode' s = NameDecode s s
- newtype DecodeState s a = DecodeState {- getDecodeState :: ReaderT (Vector s) (State Ind) a
 
- runDecodeState :: DecodeState s a -> Vector s -> Ind -> (a, Ind)
- newtype Ind = Ind Int
- 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))
- type DecodeValidation e = Validation (DecodeErrors e)
- data Validation err a
Documentation
A Decode e s aa.
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 Decodes, and combinators for composing or
 otherwise manipulating them. In particular, Decode is an
 Applicative functor and an Alt from the semigroupoids package, also known
 as a SemiAlternative.
Decode is not a Monad, but we can perform monad-like operations on
 it with >>== or bindDecode
Constructors
| Decode | |
| Fields 
 | |
buildDecode :: (Vector s -> Ind -> (DecodeValidation e a, Last Bool, Ind)) -> Decode e s a Source #
Convenient constructor for Decode that handles all the newtype noise for you.
newtype NameDecode e s a Source #
NameDecode is a decoder that looks for a column by name rather than
 by position.
Constructors
| Named | |
Instances
| Functor (NameDecode e s) Source # | |
| Defined in Data.Sv.Decode.Type Methods fmap :: (a -> b) -> NameDecode e s a -> NameDecode e s b # (<$) :: a -> NameDecode e s b -> NameDecode e s a # | |
| Applicative (NameDecode e s) Source # | |
| Defined in Data.Sv.Decode.Type Methods pure :: a -> NameDecode e s a # (<*>) :: NameDecode e s (a -> b) -> NameDecode e s a -> NameDecode e s b # liftA2 :: (a -> b -> c) -> NameDecode e s a -> NameDecode e s b -> NameDecode e s c # (*>) :: NameDecode e s a -> NameDecode e s b -> NameDecode e s b # (<*) :: NameDecode e s a -> NameDecode e s b -> NameDecode e s a # | |
| Alt (NameDecode e s) Source # | |
| Defined in Data.Sv.Decode.Type Methods (<!>) :: NameDecode e s a -> NameDecode e s a -> NameDecode e s a # some :: Applicative (NameDecode e s) => NameDecode e s a -> NameDecode e s [a] # many :: Applicative (NameDecode e s) => NameDecode e s a -> NameDecode e s [a] # | |
type NameDecode' s = NameDecode s s Source #
NameDecode' is NameDecode with both type parameters the same, as
 should usually be the case
newtype DecodeState s a Source #
As we decode a row of data, we walk through its fields. This Monad
 keeps track of our position.
Constructors
| DecodeState | |
| Fields 
 | |
Instances
runDecodeState :: DecodeState s a -> Vector s -> Ind -> (a, Ind) Source #
Convenient function to run a DecodeState
Newtype for indices into the field vector
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 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.
Constructors
| DecodeErrors (NonEmpty (DecodeError e)) | 
Instances
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.
Instances
| Bitraversable Validation | |
| Defined in Data.Validation Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Validation a b -> f (Validation c d) # | |
| Bifoldable Validation | |
| Defined in Data.Validation Methods bifold :: Monoid m => Validation m m -> m # bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Validation a b -> m # bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Validation a b -> c # bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Validation a b -> c # | |
| Bifunctor Validation | |
| Defined in Data.Validation Methods bimap :: (a -> b) -> (c -> d) -> Validation a c -> Validation b d # first :: (a -> b) -> Validation a c -> Validation b c # second :: (b -> c) -> Validation a b -> Validation a c # | |
| Swapped Validation | |
| Defined in Data.Validation Methods swapped :: Iso (Validation a b) (Validation c d) (Validation b a) (Validation d c) # | |
| Validate Validation | |
| Defined in Data.Validation Methods _Validation :: Iso (Validation e a) (Validation g b) (Validation e a) (Validation g b) # _Either :: Iso (Validation e a) (Validation g b) (Either e a) (Either g b) # | |
| Functor (Validation err) | |
| Defined in Data.Validation Methods fmap :: (a -> b) -> Validation err a -> Validation err b # (<$) :: a -> Validation err b -> Validation err a # | |
| Semigroup err => Applicative (Validation err) | |
| Defined in Data.Validation Methods pure :: a -> Validation err a # (<*>) :: Validation err (a -> b) -> Validation err a -> Validation err b # liftA2 :: (a -> b -> c) -> Validation err a -> Validation err b -> Validation err c # (*>) :: Validation err a -> Validation err b -> Validation err b # (<*) :: Validation err a -> Validation err b -> Validation err a # | |
| Foldable (Validation err) | |
| Defined in Data.Validation Methods fold :: Monoid m => Validation err m -> m # foldMap :: Monoid m => (a -> m) -> Validation err a -> m # foldr :: (a -> b -> b) -> b -> Validation err a -> b # foldr' :: (a -> b -> b) -> b -> Validation err a -> b # foldl :: (b -> a -> b) -> b -> Validation err a -> b # foldl' :: (b -> a -> b) -> b -> Validation err a -> b # foldr1 :: (a -> a -> a) -> Validation err a -> a # foldl1 :: (a -> a -> a) -> Validation err a -> a # toList :: Validation err a -> [a] # null :: Validation err a -> Bool # length :: Validation err a -> Int # elem :: Eq a => a -> Validation err a -> Bool # maximum :: Ord a => Validation err a -> a # minimum :: Ord a => Validation err a -> a # sum :: Num a => Validation err a -> a # product :: Num a => Validation err a -> a # | |
| Traversable (Validation err) | |
| Defined in Data.Validation Methods traverse :: Applicative f => (a -> f b) -> Validation err a -> f (Validation err b) # sequenceA :: Applicative f => Validation err (f a) -> f (Validation err a) # mapM :: Monad m => (a -> m b) -> Validation err a -> m (Validation err b) # sequence :: Monad m => Validation err (m a) -> m (Validation err a) # | |
| Semigroup err => Apply (Validation err) | |
| Defined in Data.Validation Methods (<.>) :: Validation err (a -> b) -> Validation err a -> Validation err b # (.>) :: Validation err a -> Validation err b -> Validation err b # (<.) :: Validation err a -> Validation err b -> Validation err a # liftF2 :: (a -> b -> c) -> Validation err a -> Validation err b -> Validation err c # | |
| Alt (Validation err) | |
| Defined in Data.Validation Methods (<!>) :: Validation err a -> Validation err a -> Validation err a # some :: Applicative (Validation err) => Validation err a -> Validation err [a] # many :: Applicative (Validation err) => Validation err a -> Validation err [a] # | |
| (Eq err, Eq a) => Eq (Validation err a) | |
| Defined in Data.Validation Methods (==) :: Validation err a -> Validation err a -> Bool # (/=) :: Validation err a -> Validation err a -> Bool # | |
| (Data err, Data a) => Data (Validation err a) | |
| Defined in Data.Validation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Validation err a -> c (Validation err a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Validation err a) # toConstr :: Validation err a -> Constr # dataTypeOf :: Validation err a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Validation err a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Validation err a)) # gmapT :: (forall b. Data b => b -> b) -> Validation err a -> Validation err a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Validation err a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Validation err a -> r # gmapQ :: (forall d. Data d => d -> u) -> Validation err a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Validation err a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Validation err a -> m (Validation err a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Validation err a -> m (Validation err a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Validation err a -> m (Validation err a) # | |
| (Ord err, Ord a) => Ord (Validation err a) | |
| Defined in Data.Validation Methods compare :: Validation err a -> Validation err a -> Ordering # (<) :: Validation err a -> Validation err a -> Bool # (<=) :: Validation err a -> Validation err a -> Bool # (>) :: Validation err a -> Validation err a -> Bool # (>=) :: Validation err a -> Validation err a -> Bool # max :: Validation err a -> Validation err a -> Validation err a # min :: Validation err a -> Validation err a -> Validation err a # | |
| (Show err, Show a) => Show (Validation err a) | |
| Defined in Data.Validation Methods showsPrec :: Int -> Validation err a -> ShowS # show :: Validation err a -> String # showList :: [Validation err a] -> ShowS # | |
| Generic (Validation err a) | |
| Defined in Data.Validation Associated Types type Rep (Validation err a) :: Type -> Type # Methods from :: Validation err a -> Rep (Validation err a) x # to :: Rep (Validation err a) x -> Validation err a # | |
| Semigroup e => Semigroup (Validation e a) | |
| Defined in Data.Validation Methods (<>) :: Validation e a -> Validation e a -> Validation e a # sconcat :: NonEmpty (Validation e a) -> Validation e a # stimes :: Integral b => b -> Validation e a -> Validation e a # | |
| Monoid e => Monoid (Validation e a) | |
| Defined in Data.Validation Methods mempty :: Validation e a # mappend :: Validation e a -> Validation e a -> Validation e a # mconcat :: [Validation e a] -> Validation e a # | |
| (NFData e, NFData a) => NFData (Validation e a) | |
| Defined in Data.Validation Methods rnf :: Validation e a -> () # | |
| type Rep (Validation err a) | |
| Defined in Data.Validation type Rep (Validation err a) = D1 (MetaData "Validation" "Data.Validation" "validation-1-HVlxNVFYyCO1UG2WIS9PG8" False) (C1 (MetaCons "Failure" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 err)) :+: C1 (MetaCons "Success" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))) | |