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.Type

Description

 

Synopsis

Documentation

newtype Decode e s a Source #

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 Decodes, 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

Constructors

Decode 

Instances

Profunctor (Decode e) Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Decode e b c -> Decode e a d #

lmap :: (a -> b) -> Decode e b c -> Decode e a c #

rmap :: (b -> c) -> Decode e a b -> Decode e a c #

(#.) :: Coercible * c b => (b -> c) -> Decode e a b -> Decode e a c #

(.#) :: Coercible * b a => Decode e b c -> (a -> b) -> Decode e a c #

Functor (Decode e s) Source # 

Methods

fmap :: (a -> b) -> Decode e s a -> Decode e s b #

(<$) :: a -> Decode e s b -> Decode e s a #

Applicative (Decode e s) Source # 

Methods

pure :: a -> Decode e s a #

(<*>) :: Decode e s (a -> b) -> Decode e s a -> Decode e s b #

liftA2 :: (a -> b -> c) -> Decode e s a -> Decode e s b -> Decode e s c #

(*>) :: Decode e s a -> Decode e s b -> Decode e s b #

(<*) :: Decode e s a -> Decode e s b -> Decode e s a #

Apply (Decode e s) Source # 

Methods

(<.>) :: Decode e s (a -> b) -> Decode e s a -> Decode e s b #

(.>) :: Decode e s a -> Decode e s b -> Decode e s b #

(<.) :: Decode e s a -> Decode e s b -> Decode e s a #

liftF2 :: (a -> b -> c) -> Decode e s a -> Decode e s b -> Decode e s c #

Alt (Decode e s) Source # 

Methods

(<!>) :: Decode e s a -> Decode e s a -> Decode e s a #

some :: Applicative (Decode e s) => Decode e s a -> Decode e s [a] #

many :: Applicative (Decode e s) => Decode e s a -> Decode e s [a] #

type Decode' s = Decode s s Source #

Decode' is Decode with the input and error types the same. You usually want them to be the same, and most primitives are set up this way.

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 Fields. This Monad keeps track of our remaining Fields.

Constructors

DecodeState 

Instances

Profunctor DecodeState Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> DecodeState b c -> DecodeState a d #

lmap :: (a -> b) -> DecodeState b c -> DecodeState a c #

rmap :: (b -> c) -> DecodeState a b -> DecodeState a c #

(#.) :: Coercible * c b => (b -> c) -> DecodeState a b -> DecodeState a c #

(.#) :: Coercible * b a => DecodeState b c -> (a -> b) -> DecodeState a c #

MonadState Ind (DecodeState s) Source # 

Methods

get :: DecodeState s Ind #

put :: Ind -> DecodeState s () #

state :: (Ind -> (a, Ind)) -> DecodeState s a #

Monad (DecodeState s) Source # 

Methods

(>>=) :: DecodeState s a -> (a -> DecodeState s b) -> DecodeState s b #

(>>) :: DecodeState s a -> DecodeState s b -> DecodeState s b #

return :: a -> DecodeState s a #

fail :: String -> DecodeState s a #

Functor (DecodeState s) Source # 

Methods

fmap :: (a -> b) -> DecodeState s a -> DecodeState s b #

(<$) :: a -> DecodeState s b -> DecodeState s a #

Applicative (DecodeState s) Source # 

Methods

pure :: a -> DecodeState s a #

(<*>) :: DecodeState s (a -> b) -> DecodeState s a -> DecodeState s b #

liftA2 :: (a -> b -> c) -> DecodeState s a -> DecodeState s b -> DecodeState s c #

(*>) :: DecodeState s a -> DecodeState s b -> DecodeState s b #

(<*) :: DecodeState s a -> DecodeState s b -> DecodeState s a #

Apply (DecodeState s) Source # 

Methods

(<.>) :: DecodeState s (a -> b) -> DecodeState s a -> DecodeState s b #

(.>) :: DecodeState s a -> DecodeState s b -> DecodeState s b #

(<.) :: DecodeState s a -> DecodeState s b -> DecodeState s a #

liftF2 :: (a -> b -> c) -> DecodeState s a -> DecodeState s b -> DecodeState s c #

Bind (DecodeState s) Source # 

Methods

(>>-) :: DecodeState s a -> (a -> DecodeState s b) -> DecodeState s b #

join :: DecodeState s (DecodeState s a) -> DecodeState s a #

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 Ind Source #

Newtype for indices into the field vector

Constructors

Ind Int 

Instances

MonadState Ind (DecodeState s) Source # 

Methods

get :: DecodeState s Ind #

put :: Ind -> DecodeState s () #

state :: (Ind -> (a, Ind)) -> DecodeState s a #

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)))))

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.

Constructors

Failure err 
Success a 

Instances

Bitraversable Validation 

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Validation a b -> f (Validation c d) #

Bifoldable 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 

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 

Methods

swapped :: (Profunctor p, Functor f) => p (Validation b a) (f (Validation d c)) -> p (Validation a b) (f (Validation c d)) #

Validate Validation 

Methods

_Validation :: (Profunctor p, Functor f) => p (Validation e a) (f (Validation g b)) -> p (Validation e a) (f (Validation g b)) #

_Either :: (Profunctor p, Functor f) => p (Either e a) (f (Either g b)) -> p (Validation e a) (f (Validation g b)) #

Functor (Validation err) 

Methods

fmap :: (a -> b) -> Validation err a -> Validation err b #

(<$) :: a -> Validation err b -> Validation err a #

Semigroup err => Applicative (Validation err) 

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) 

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) 

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) 

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) 

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 a, Eq err) => Eq (Validation err a) 

Methods

(==) :: Validation err a -> Validation err a -> Bool #

(/=) :: Validation err a -> Validation err a -> Bool #

(Data a, Data err) => Data (Validation err a) 

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 a, Ord err) => Ord (Validation err a) 

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 a, Show err) => Show (Validation err a) 

Methods

showsPrec :: Int -> Validation err a -> ShowS #

show :: Validation err a -> String #

showList :: [Validation err a] -> ShowS #

Generic (Validation err a) 

Associated Types

type Rep (Validation err a) :: * -> * #

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) 

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) 

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) 

Methods

rnf :: Validation e a -> () #

type Rep (Validation err a) 
type Rep (Validation err a) = D1 * (MetaData "Validation" "Data.Validation" "validation-1-7Kn73lcYUHq7dRZmAdNKfW" False) ((:+:) * (C1 * (MetaCons "Failure" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * err))) (C1 * (MetaCons "Success" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))