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

Contents

Description

This module contains data structures, combinators, and primitives for decoding an Sv into a list of your Haskell datatype.

A file can be read with parseDecodeFromFile. If you already have the text data in memory, it can be decoded with parseDecode. You will need a Decode for your desired type.

A Decode can be built using the primitives in this file. Decode is an Applicative and an Alt, allowing for composition of these values with <*> and <!>

The primitive Decodes in this file which use ByteString expect UTF-8 encoding. The Decode type has an instance of Profunctor, so you can lmap or alterInput to reencode on the way in.

This module is intended to be imported qualified like so

import qualified Data.Sv.Decode as D

Synopsis

The types

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.

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

type DecodeValidation e = Validation (DecodeErrors e) Source #

DecodeValidation is the error-accumulating Applicative underlying Decode

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

Running Decodes

decode :: Decode' s a -> Sv s -> DecodeValidation s [a] Source #

Decodes a sv into a list of its values using the provided Decode

parseDecode :: Decode' ByteString a -> ParseOptions ByteString -> ByteString -> DecodeValidation ByteString [a] Source #

Parse a ByteString as an Sv, and then decode it with the given decoder.

This version uses Trifecta to parse the ByteString, which is assumed to be UTF-8 encoded. If you want a different library, use parseDecode'.

parseDecode' :: SvParser s -> Decode' s a -> ParseOptions s -> s -> DecodeValidation s [a] Source #

Parse text as an Sv, and then decode it with the given decoder.

This version lets you choose which parsing library to use by providing an SvParser. Common selections are trifecta and attoparsecByteString.

parseDecodeFromFile :: MonadIO m => Decode' ByteString a -> ParseOptions ByteString -> FilePath -> m (DecodeValidation ByteString [a]) Source #

Load a file, parse it, and decode it.

This version uses Trifecta to parse the file, which is assumed to be UTF-8 encoded.

parseDecodeFromFile' :: MonadIO m => SvParser s -> Decode' s a -> ParseOptions s -> FilePath -> m (DecodeValidation s [a]) Source #

Load a file, parse it, and decode it.

This version lets you choose which parsing library to use by providing an SvParser. Common selections are trifecta and attoparsecByteString.

Convenience constructors and functions

decodeMay :: DecodeError e -> (s -> Maybe a) -> Decode e s a Source #

Build a Decode, given a function that returns Maybe.

Return the given error if the function returns Nothing.

decodeEither :: (s -> Either (DecodeError e) a) -> Decode e s a Source #

Build a Decode, given a function that returns Either.

decodeEither' :: (e -> DecodeError e') -> (s -> Either e a) -> Decode e' s a Source #

Build a Decode, given a function that returns Either, and a function to build the error.

mapErrors :: (e -> x) -> Decode e s a -> Decode x s a Source #

Map over the errors of a Decode

To map over the other two parameters, use the Profunctor instance.

alterInput :: (e -> x) -> (t -> s) -> Decode e s a -> Decode x t a Source #

This transforms a Decode' s a into a Decode' t a. It needs functions in both directions because the errors can include fragments of the input.

alterInput :: (s -> t) -> (t -> s) -> Decode' s a -> Decode' t a

Primitive Decodes

Field-based

contents :: Decode e s s Source #

Get the contents of a field without doing any decoding. This never fails.

untrimmed :: Monoid s => (HorizontalSpace -> s) -> Decode e s s Source #

Returns the field contents. This keeps the spacing around an unquoted field.

raw :: Decode e s (SpacedField s) Source #

Succeeds with the whole field structure, including spacing and quoting information

char :: Decode' ByteString Char Source #

Get a field that's a single char. This will fail if there are mulitple characters in the field.

byteString :: Decode' ByteString ByteString Source #

Get the contents of a field as a bytestring.

Alias for contents

utf8 :: Decode' ByteString Text Source #

Get the contents of a UTF-8 encoded field as Text

This will also work for ASCII text, as ASCII is a subset of UTF-8

lazyUtf8 :: Decode' ByteString Text Source #

Get the contents of a field as a lazy Text

lazyByteString :: Decode' ByteString ByteString Source #

Get the contents of a field as a lazy ByteString

string :: Decode' ByteString String Source #

Get the contents of a field as a String

int :: Decode' ByteString Int Source #

Decode a UTF-8 ByteString field as an Int

float :: Decode' ByteString Float Source #

Decode a UTF-8 ByteString field as a Float

double :: Decode' ByteString Double Source #

Decode a UTF-8 ByteString field as a Double

boolean :: (IsString s, Ord s) => Decode' s Bool Source #

Decode a field as a Bool

This aims to be tolerant to different forms a boolean might take.

boolean' :: Ord s => (String -> s) -> Decode' s Bool Source #

Decode a field as a Bool. This version lets you provide the fromString function that's right for you, since IsString on a ByteString will do the wrong thing in the case of many encodings such as UTF-16 or UTF-32.

This aims to be tolerant to different forms a boolean might take.

ignore :: Decode e s () Source #

Throw away the contents of a field. This is useful for skipping unneeded fields.

replace :: a -> Decode e s a Source #

Throw away the contents of a field, and return the given value.

exactly :: (Semigroup s, Eq s, IsString s) => s -> Decode' s s Source #

Decode exactly the given string, or else fail.

emptyField :: (Eq s, IsString s, Semigroup s) => Decode' s () Source #

Succeed only when the given field is the empty string.

The empty string surrounded in quotes or spaces is still the empty string.

Row-based

row :: Decode e s (Vector s) Source #

Grab the whole row as a Vector

rowWithSpacing :: Decode e s (Vector (SpacedField s)) Source #

Grab the whole row, including all spacing and quoting information, as a Vector

Combinators

choice :: Decode e s a -> Decode e s a -> Decode e s a Source #

Choose the leftmost Decode that succeeds. Alias for <!>

element :: NonEmpty (Decode e s a) -> Decode e s a Source #

Choose the leftmost Decode that succeeds. Alias for asum1

optionalField :: Decode e s a -> Decode e s (Maybe a) Source #

Try the given Decode. If it fails, succeed without consuming anything.

This usually isn't what you want. ignoreFailure and orEmpty are more likely what you are after.

ignoreFailure :: Decode e s a -> Decode e s (Maybe a) Source #

Try the given Decode. If it fails, instead succeed with Nothing.

orEmpty :: (Eq s, IsString s, Semigroup s) => Decode' s a -> Decode' s (Maybe a) Source #

If the field is the empty string, succeed with Nothing. Otherwise try the given Decode.

either :: Decode e s a -> Decode e s b -> Decode e s (Either a b) Source #

Try the first, then try the second, and wrap the winner in an Either.

This is left-biased, meaning if they both succeed, left wins.

orElse :: Decode e s a -> a -> Decode e s a Source #

Try the given decoder, otherwise succeed with the given value.

orElseE :: Decode e s b -> a -> Decode e s (Either a b) Source #

Try the given decoder, or if it fails succeed with the given value, in an Either.

categorical :: (Ord s, Show a) => [(a, s)] -> Decode' s a Source #

Decode categorical data, given a list of the values and the strings which match them.

Usually this is used with sum types with nullary constructors.

data TrafficLight = Red | Amber | Green
categorical [(Red, "red"), (Amber, "amber"), (Green, "green")]

categorical' :: forall s a. (Ord s, Show a) => [(a, [s])] -> Decode' s a Source #

Decode categorical data, given a list of the values and lists of strings which match them.

This version allows for multiple strings to match each value, which is useful for when the categories are inconsistently labelled.

data TrafficLight = Red | Amber | Green
categorical' [(Red, ["red", "R"]), (Amber, ["amber", "orange", "A"]), (Green, ["green", "G"])]

For another example of its usage, see the source for boolean.

(>>==) :: Decode e s a -> (a -> DecodeValidation e b) -> Decode e s b infixl 1 Source #

This can be used to build a Decode whose value depends on the result of another Decode. This is especially useful since Decode is not a Monad.

If you need something like this but with more power, look at bindDecode

(==<<) :: (a -> DecodeValidation e b) -> Decode e s a -> Decode e s b infixr 1 Source #

flipped >>==

bindDecode :: Decode e s a -> (a -> Decode e s b) -> Decode e s b Source #

Bind through a Decode.

This bind does not agree with the Applicative instance because it does not accumulate multiple error values. This is a violation of the Monad laws, meaning Decode is not a Monad.

That is not to say that there is anything wrong with using this function. It can be quite useful.

Building Decodes from Readable

decodeRead :: Readable a => Decode' ByteString a Source #

Use the Readable instance to try to decode the given value.

decodeRead' :: Readable a => ByteString -> Decode' ByteString a Source #

Use the Readable instance to try to decode the given value, or fail with the given error message.

decodeReadWithMsg :: Readable a => (ByteString -> e) -> Decode e ByteString a Source #

Use the Readable instance to try to decode the given value, or use the value to build an error message.

Building Decodes from parsers

withTrifecta :: Parser a -> Decode' ByteString a Source #

Build a Decode from a Trifecta parser

withAttoparsec :: Parser a -> Decode' ByteString a Source #

Build a Decode from an Attoparsec parser

withParsec :: Parsec ByteString () a -> Decode' ByteString a Source #

Build a Decode from a Parsec parser

Working with errors

onError :: Decode e s a -> (DecodeErrors e -> Decode e s a) -> Decode e s a Source #

Run a Decode, and based on its errors build a new Decode.

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.

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

Implementation details

runDecode :: Decode e s a -> Vector (SpacedField s) -> Ind -> (DecodeValidation e a, Ind) Source #

Convenience to get the underlying function out of a Decode in a useful form

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.

mkDecode :: (s -> DecodeValidation e a) -> Decode e s a Source #

Build a Decode from a function.

This version gives you just the contents of the field, with no information about the spacing or quoting around that field.

mkDecodeWithQuotes :: (Field s -> DecodeValidation e a) -> Decode e s a Source #

Build a Decode from a function.

This version gives you access to the whole Field, which includes information about whether quotes were used, and if so which ones.

mkDecodeWithSpaces :: (SpacedField s -> DecodeValidation e a) -> Decode e s a Source #

Build a Decode from a function.

This version gives you access to the whole SpacedField, which includes information about spacing both before and after the field, and about quotes if they were used.

promote :: Decode' s a -> Record s -> DecodeValidation s a Source #

promotes a Decode to work on a whole Record at once. This does not need to be called by the user. Instead use decode.