sv-1.3.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

Contents

Description

This module exports most of the other modules from the package. It is intended to be imported unqualified, along with some qualified imports for the Data.Sv.Decode and Data.Sv.Encode modules as needed.

import Data.Sv
import qualified Data.Sv.Decode as D
import qualified Data.Sv.Encode as E
Synopsis

Decoding

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

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

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

Load a file, parse it, and decode it.

parseDecodeNamed :: NameDecode' ByteString a -> ParseOptions -> ByteString -> DecodeValidation ByteString [a] Source #

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

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

Load a file, parse it, and decode it by column.

decode :: Traversable f => Decode' ByteString a -> f (Vector ByteString) -> DecodeValidation ByteString (f a) #

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

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

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 #

Build a Decode, given a function that returns Either.

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

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

(.:) :: Ord s => s -> Decode' s a -> NameDecode' s a infixl 5 #

Infix alias for column

Mnemonic: Dot colon names Decoders, Equal colon names Encoders.

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

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 #

flipped >>==

Encoding

encode :: Encode a -> EncodeOptions -> [a] -> ByteString #

Encode the given list using the given Encode, configured by the given EncodeOptions.

encodeToFile :: Encode a -> EncodeOptions -> [a] -> FilePath -> IO () #

Encode, writing to a file. This way is more efficient than encoding to a ByteString and then writing to file.

encodeToHandle :: Encode a -> EncodeOptions -> [a] -> Handle -> IO () #

Encode, writing the output to a file handle.

encodeBuilder :: Encode a -> EncodeOptions -> [a] -> Builder #

Encode to a ByteString Builder, which is useful if you are going to combine the output with other ByteStrings.

encodeNamed :: NameEncode a -> EncodeOptions -> [a] -> ByteString #

Encode the given list with a header using the given NameEncode, configured by the given EncodeOptions.

encodeNamedToFile :: NameEncode a -> EncodeOptions -> [a] -> FilePath -> IO () #

Encode with a header, writing to a file. This way is more efficient than encoding to a ByteString and then writing to file.

encodeNamedToHandle :: NameEncode a -> EncodeOptions -> [a] -> Handle -> IO () #

Encode with a header, writing the output to a file handle.

encodeNamedBuilder :: NameEncode a -> EncodeOptions -> [a] -> Builder #

Encode with column names to a ByteString Builder, which is useful if you are going to combine the output with other ByteStrings.

encodeRow :: Encode a -> EncodeOptions -> a -> ByteString #

Encode one row only

(=:) :: Builder -> Encode a -> NameEncode a #

Synonym for named.

Mnemonic: Dot colon names Decoders, Equal colon names Encoders.

Structure

Re-exports from contravariant, validation, and semigroupoids

class Functor f => Alt (f :: Type -> Type) where #

Laws:

<!> is associative:             (a <!> b) <!> c = a <!> (b <!> c)
<$> left-distributes over <!>:  f <$> (a <!> b) = (f <$> a) <!> (f <$> b)

If extended to an Alternative then <!> should equal <|>.

Ideally, an instance of Alt also satisfies the "left distributon" law of MonadPlus with respect to <.>:

<.> right-distributes over <!>: (a <!> b) <.> c = (a <.> c) <!> (b <.> c)

But Maybe, IO, Either a, ErrorT e m, and STM satisfy the alternative "left catch" law instead:

pure a <!> b = pure a

However, this variation cannot be stated purely in terms of the dependencies of Alt.

When and if MonadPlus is successfully refactored, this class should also be refactored to remove these instances.

The right distributive law should extend in the cases where the a Bind or Monad is provided to yield variations of the right distributive law:

(m <!> n) >>- f = (m >>- f) <!> (m >>- f)
(m <!> n) >>= f = (m >>= f) <!> (m >>= f)

Minimal complete definition

(<!>)

Methods

(<!>) :: f a -> f a -> f a infixl 3 #

<|> without a required empty

some :: Applicative f => f a -> f [a] #

many :: Applicative f => f a -> f [a] #

Instances
Alt [] 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: [a] -> [a] -> [a] #

some :: Applicative [] => [a] -> [[a]] #

many :: Applicative [] => [a] -> [[a]] #

Alt Maybe 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Maybe a -> Maybe a -> Maybe a #

some :: Applicative Maybe => Maybe a -> Maybe [a] #

many :: Applicative Maybe => Maybe a -> Maybe [a] #

Alt IO

This instance does not actually satisfy the (<.>) right distributive law It instead satisfies the "Left-Catch" law

Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: IO a -> IO a -> IO a #

some :: Applicative IO => IO a -> IO [a] #

many :: Applicative IO => IO a -> IO [a] #

Alt First 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: First a -> First a -> First a #

some :: Applicative First => First a -> First [a] #

many :: Applicative First => First a -> First [a] #

Alt Last 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Last a -> Last a -> Last a #

some :: Applicative Last => Last a -> Last [a] #

many :: Applicative Last => Last a -> Last [a] #

Alt Option 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Option a -> Option a -> Option a #

some :: Applicative Option => Option a -> Option [a] #

many :: Applicative Option => Option a -> Option [a] #

Alt First 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: First a -> First a -> First a #

some :: Applicative First => First a -> First [a] #

many :: Applicative First => First a -> First [a] #

Alt Last 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Last a -> Last a -> Last a #

some :: Applicative Last => Last a -> Last [a] #

many :: Applicative Last => Last a -> Last [a] #

Alt NonEmpty 
Instance details

Defined in Data.Functor.Alt

Alt IntMap 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: IntMap a -> IntMap a -> IntMap a #

some :: Applicative IntMap => IntMap a -> IntMap [a] #

many :: Applicative IntMap => IntMap a -> IntMap [a] #

Alt Seq 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Seq a -> Seq a -> Seq a #

some :: Applicative Seq => Seq a -> Seq [a] #

many :: Applicative Seq => Seq a -> Seq [a] #

Alt (Either a) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Either a a0 -> Either a a0 -> Either a a0 #

some :: Applicative (Either a) => Either a a0 -> Either a [a0] #

many :: Applicative (Either a) => Either a a0 -> Either a [a0] #

Alt (V1 :: Type -> Type) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: V1 a -> V1 a -> V1 a #

some :: Applicative V1 => V1 a -> V1 [a] #

many :: Applicative V1 => V1 a -> V1 [a] #

Alt (U1 :: Type -> Type) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: U1 a -> U1 a -> U1 a #

some :: Applicative U1 => U1 a -> U1 [a] #

many :: Applicative U1 => U1 a -> U1 [a] #

MonadPlus m => Alt (WrappedMonad m) 
Instance details

Defined in Data.Functor.Alt

Alt (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Proxy a -> Proxy a -> Proxy a #

some :: Applicative Proxy => Proxy a -> Proxy [a] #

many :: Applicative Proxy => Proxy a -> Proxy [a] #

Ord k => Alt (Map k) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Map k a -> Map k a -> Map k a #

some :: Applicative (Map k) => Map k a -> Map k [a] #

many :: Applicative (Map k) => Map k a -> Map k [a] #

(Bind f, Monad f) => Alt (MaybeT f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: MaybeT f a -> MaybeT f a -> MaybeT f a #

some :: Applicative (MaybeT f) => MaybeT f a -> MaybeT f [a] #

many :: Applicative (MaybeT f) => MaybeT f a -> MaybeT f [a] #

Alt f => Alt (Yoneda f) 
Instance details

Defined in Data.Functor.Yoneda

Methods

(<!>) :: Yoneda f a -> Yoneda f a -> Yoneda f a #

some :: Applicative (Yoneda f) => Yoneda f a -> Yoneda f [a] #

many :: Applicative (Yoneda f) => Yoneda f a -> Yoneda f [a] #

Alt (ReifiedFold s) 
Instance details

Defined in Control.Lens.Reified

Apply f => Alt (ListT f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: ListT f a -> ListT f a -> ListT f a #

some :: Applicative (ListT f) => ListT f a -> ListT f [a] #

many :: Applicative (ListT f) => ListT f a -> ListT f [a] #

Alternative f => Alt (WrappedApplicative f) 
Instance details

Defined in Data.Functor.Alt

Alt (Validation err) 
Instance details

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] #

Alt f => Alt (Lift f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Lift f a -> Lift f a -> Lift f a #

some :: Applicative (Lift f) => Lift f a -> Lift f [a] #

many :: Applicative (Lift f) => Lift f a -> Lift f [a] #

Alt f => Alt (Rec1 f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Rec1 f a -> Rec1 f a -> Rec1 f a #

some :: Applicative (Rec1 f) => Rec1 f a -> Rec1 f [a] #

many :: Applicative (Rec1 f) => Rec1 f a -> Rec1 f [a] #

ArrowPlus a => Alt (WrappedArrow a b) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: WrappedArrow a b a0 -> WrappedArrow a b a0 -> WrappedArrow a b a0 #

some :: Applicative (WrappedArrow a b) => WrappedArrow a b a0 -> WrappedArrow a b [a0] #

many :: Applicative (WrappedArrow a b) => WrappedArrow a b a0 -> WrappedArrow a b [a0] #

Alt f => Alt (IdentityT f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: IdentityT f a -> IdentityT f a -> IdentityT f a #

some :: Applicative (IdentityT f) => IdentityT f a -> IdentityT f [a] #

many :: Applicative (IdentityT f) => IdentityT f a -> IdentityT f [a] #

(Bind f, Monad f, Semigroup e) => Alt (ExceptT e f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: ExceptT e f a -> ExceptT e f a -> ExceptT e f a #

some :: Applicative (ExceptT e f) => ExceptT e f a -> ExceptT e f [a] #

many :: Applicative (ExceptT e f) => ExceptT e f a -> ExceptT e f [a] #

(Bind f, Monad f) => Alt (ErrorT e f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: ErrorT e f a -> ErrorT e f a -> ErrorT e f a #

some :: Applicative (ErrorT e f) => ErrorT e f a -> ErrorT e f [a] #

many :: Applicative (ErrorT e f) => ErrorT e f a -> ErrorT e f [a] #

Alt f => Alt (StateT e f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: StateT e f a -> StateT e f a -> StateT e f a #

some :: Applicative (StateT e f) => StateT e f a -> StateT e f [a] #

many :: Applicative (StateT e f) => StateT e f a -> StateT e f [a] #

Alt f => Alt (Backwards f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Backwards f a -> Backwards f a -> Backwards f a #

some :: Applicative (Backwards f) => Backwards f a -> Backwards f [a] #

many :: Applicative (Backwards f) => Backwards f a -> Backwards f [a] #

Alt (ReifiedIndexedFold i s) 
Instance details

Defined in Control.Lens.Reified

Alt f => Alt (StateT e f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: StateT e f a -> StateT e f a -> StateT e f a #

some :: Applicative (StateT e f) => StateT e f a -> StateT e f [a] #

many :: Applicative (StateT e f) => StateT e f a -> StateT e f [a] #

Alt f => Alt (WriterT w f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: WriterT w f a -> WriterT w f a -> WriterT w f a #

some :: Applicative (WriterT w f) => WriterT w f a -> WriterT w f [a] #

many :: Applicative (WriterT w f) => WriterT w f a -> WriterT w f [a] #

Alt f => Alt (WriterT w f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: WriterT w f a -> WriterT w f a -> WriterT w f a #

some :: Applicative (WriterT w f) => WriterT w f a -> WriterT w f [a] #

many :: Applicative (WriterT w f) => WriterT w f a -> WriterT w f [a] #

Alt (Decode e s) 
Instance details

Defined in Data.Sv.Decode.Type

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] #

Alt (NameDecode e s) 
Instance details

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] #

Alt f => Alt (Reverse f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Reverse f a -> Reverse f a -> Reverse f a #

some :: Applicative (Reverse f) => Reverse f a -> Reverse f [a] #

many :: Applicative (Reverse f) => Reverse f a -> Reverse f [a] #

(Alt f, Alt g) => Alt (f :*: g) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a #

some :: Applicative (f :*: g) => (f :*: g) a -> (f :*: g) [a] #

many :: Applicative (f :*: g) => (f :*: g) a -> (f :*: g) [a] #

(Alt f, Alt g) => Alt (Product f g) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Product f g a -> Product f g a -> Product f g a #

some :: Applicative (Product f g) => Product f g a -> Product f g [a] #

many :: Applicative (Product f g) => Product f g a -> Product f g [a] #

Alt f => Alt (ReaderT e f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: ReaderT e f a -> ReaderT e f a -> ReaderT e f a #

some :: Applicative (ReaderT e f) => ReaderT e f a -> ReaderT e f [a] #

many :: Applicative (ReaderT e f) => ReaderT e f a -> ReaderT e f [a] #

Alt f => Alt (M1 i c f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: M1 i c f a -> M1 i c f a -> M1 i c f a #

some :: Applicative (M1 i c f) => M1 i c f a -> M1 i c f [a] #

many :: Applicative (M1 i c f) => M1 i c f a -> M1 i c f [a] #

(Alt f, Functor g) => Alt (Compose f g) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Compose f g a -> Compose f g a -> Compose f g a #

some :: Applicative (Compose f g) => Compose f g a -> Compose f g [a] #

many :: Applicative (Compose f g) => Compose f g a -> Compose f g [a] #

Alt f => Alt (RWST r w s f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: RWST r w s f a -> RWST r w s f a -> RWST r w s f a #

some :: Applicative (RWST r w s f) => RWST r w s f a -> RWST r w s f [a] #

many :: Applicative (RWST r w s f) => RWST r w s f a -> RWST r w s f [a] #

Alt f => Alt (RWST r w s f) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: RWST r w s f a -> RWST r w s f a -> RWST r w s f a #

some :: Applicative (RWST r w s f) => RWST r w s f a -> RWST r w s f [a] #

many :: Applicative (RWST r w s f) => RWST r w s f a -> RWST r w s f [a] #

class Contravariant (f :: Type -> Type) where #

The class of contravariant functors.

Whereas in Haskell, one can think of a Functor as containing or producing values, a contravariant functor is a functor that can be thought of as consuming values.

As an example, consider the type of predicate functions a -> Bool. One such predicate might be negative x = x < 0, which classifies integers as to whether they are negative. However, given this predicate, we can re-use it in other situations, providing we have a way to map values to integers. For instance, we can use the negative predicate on a person's bank balance to work out if they are currently overdrawn:

newtype Predicate a = Predicate { getPredicate :: a -> Bool }

instance Contravariant Predicate where
  contramap f (Predicate p) = Predicate (p . f)
                                         |   `- First, map the input...
                                         `----- then apply the predicate.

overdrawn :: Predicate Person
overdrawn = contramap personBankBalance negative

Any instance should be subject to the following laws:

contramap id = id
contramap f . contramap g = contramap (g . f)

Note, that the second law follows from the free theorem of the type of contramap and the first law, so you need only check that the former condition holds.

Minimal complete definition

contramap

Methods

contramap :: (a -> b) -> f b -> f a #

(>$) :: b -> f b -> f a infixl 4 #

Replace all locations in the output with the same value. The default definition is contramap . const, but this may be overridden with a more efficient version.

Instances
Contravariant Predicate

A Predicate is a Contravariant Functor, because contramap can apply its function argument to the input of the predicate.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Predicate b -> Predicate a #

(>$) :: b -> Predicate b -> Predicate a #

Contravariant Comparison

A Comparison is a Contravariant Functor, because contramap can apply its function argument to each input of the comparison function.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Comparison b -> Comparison a #

(>$) :: b -> Comparison b -> Comparison a #

Contravariant Equivalence

Equivalence relations are Contravariant, because you can apply the contramapped function to each input to the equivalence relation.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Equivalence b -> Equivalence a #

(>$) :: b -> Equivalence b -> Equivalence a #

Contravariant Encode 
Instance details

Defined in Data.Sv.Encode.Type

Methods

contramap :: (a -> b) -> Encode b -> Encode a #

(>$) :: b -> Encode b -> Encode a #

Contravariant NameEncode 
Instance details

Defined in Data.Sv.Encode.Type

Methods

contramap :: (a -> b) -> NameEncode b -> NameEncode a #

(>$) :: b -> NameEncode b -> NameEncode a #

Contravariant (V1 :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> V1 b -> V1 a #

(>$) :: b -> V1 b -> V1 a #

Contravariant (U1 :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> U1 b -> U1 a #

(>$) :: b -> U1 b -> U1 a #

Contravariant (Op a) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Op a b -> Op a a0 #

(>$) :: b -> Op a b -> Op a a0 #

Contravariant (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Proxy b -> Proxy a #

(>$) :: b -> Proxy b -> Proxy a #

Contravariant f => Contravariant (Indexing f) 
Instance details

Defined in Control.Lens.Internal.Indexed

Methods

contramap :: (a -> b) -> Indexing f b -> Indexing f a #

(>$) :: b -> Indexing f b -> Indexing f a #

Contravariant f => Contravariant (Indexing64 f) 
Instance details

Defined in Control.Lens.Internal.Indexed

Methods

contramap :: (a -> b) -> Indexing64 f b -> Indexing64 f a #

(>$) :: b -> Indexing64 f b -> Indexing64 f a #

Contravariant f => Contravariant (Rec1 f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Rec1 f b -> Rec1 f a #

(>$) :: b -> Rec1 f b -> Rec1 f a #

Contravariant (Const a :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Const a b -> Const a a0 #

(>$) :: b -> Const a b -> Const a a0 #

Contravariant f => Contravariant (Alt f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Alt f b -> Alt f a #

(>$) :: b -> Alt f b -> Alt f a #

Contravariant m => Contravariant (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

contramap :: (a -> b) -> ErrorT e m b -> ErrorT e m a #

(>$) :: b -> ErrorT e m b -> ErrorT e m a #

Contravariant (K1 i c :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> K1 i c b -> K1 i c a #

(>$) :: b -> K1 i c b -> K1 i c a #

(Contravariant f, Contravariant g) => Contravariant (f :+: g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :+: g) b -> (f :+: g) a #

(>$) :: b -> (f :+: g) b -> (f :+: g) a #

(Contravariant f, Contravariant g) => Contravariant (f :*: g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :*: g) b -> (f :*: g) a #

(>$) :: b -> (f :*: g) b -> (f :*: g) a #

(Contravariant f, Contravariant g) => Contravariant (Product f g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Product f g b -> Product f g a #

(>$) :: b -> Product f g b -> Product f g a #

(Contravariant f, Contravariant g) => Contravariant (Sum f g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Sum f g b -> Sum f g a #

(>$) :: b -> Sum f g b -> Sum f g a #

Contravariant f => Contravariant (M1 i c f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> M1 i c f b -> M1 i c f a #

(>$) :: b -> M1 i c f b -> M1 i c f a #

(Functor f, Contravariant g) => Contravariant (f :.: g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :.: g) b -> (f :.: g) a #

(>$) :: b -> (f :.: g) b -> (f :.: g) a #

(Functor f, Contravariant g) => Contravariant (Compose f g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Compose f g b -> Compose f g a #

(>$) :: b -> Compose f g b -> Compose f g a #

class Contravariant f => Divisible (f :: Type -> Type) where #

A Divisible contravariant functor is the contravariant analogue of Applicative.

Continuing the intuition that Contravariant functors consume input, a Divisible contravariant functor also has the ability to be composed "beside" another contravariant functor.

Serializers provide a good example of Divisible contravariant functors. To begin let's start with the type of serializers for specific types:

newtype Serializer a = Serializer { runSerializer :: a -> ByteString }

This is a contravariant functor:

instance Contravariant Serializer where
  contramap f s = Serializer (runSerializer s . f)

That is, given a serializer for a (s :: Serializer a), and a way to turn bs into as (a mapping f :: b -> a), we have a serializer for b: contramap f s :: Serializer b.

Divisible gives us a way to combine two serializers that focus on different parts of a structure. If we postulate the existance of two primitive serializers - string :: Serializer String and int :: Serializer Int, we would like to be able to combine these into a serializer for pairs of Strings and Ints. How can we do this? Simply run both serializer and combine their output!

data StringAndInt = StringAndInt String Int

stringAndInt :: Serializer StringAndInt
stringAndInt = Serializer $ \(StringAndInt s i) ->
  let sBytes = runSerializer string s
      iBytes = runSerializer int i
  in sBytes <> iBytes

divide is a generalization by also taking a contramap like function to split any a into a pair. This conveniently allows you to target fields of a record, for instance, by extracting the values under two fields and combining them into a tuple.

To complete the example, here is how to write stringAndInt using a Divisible instance:

instance Divisible Serializer where
  conquer = Serializer (const mempty)

  divide toBC bSerializer cSerializer = Serializer $ \a ->
    case toBC a of
      (b, c) ->
        let bBytes = runSerializer bSerializer b
            cBytes = runSerializer cSerializer c
        in bBytes <> cBytes

stringAndInt :: Serializer StringAndInt
stringAndInt =
  divide (\(StringAndInt s i) -> (s, i)) string int

Methods

divide :: (a -> (b, c)) -> f b -> f c -> f a #

conquer :: f a #

Conquer acts as an identity for combining Divisible functors.

Instances
Divisible SettableStateVar 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Divisible Predicate 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Predicate b -> Predicate c -> Predicate a #

conquer :: Predicate a #

Divisible Comparison 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Comparison b -> Comparison c -> Comparison a #

conquer :: Comparison a #

Divisible Equivalence 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Equivalence b -> Equivalence c -> Equivalence a #

conquer :: Equivalence a #

Divisible Encode 
Instance details

Defined in Data.Sv.Encode.Type

Methods

divide :: (a -> (b, c)) -> Encode b -> Encode c -> Encode a #

conquer :: Encode a #

Divisible NameEncode 
Instance details

Defined in Data.Sv.Encode.Type

Methods

divide :: (a -> (b, c)) -> NameEncode b -> NameEncode c -> NameEncode a #

conquer :: NameEncode a #

Divisible (U1 :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> U1 b -> U1 c -> U1 a #

conquer :: U1 a #

Monoid r => Divisible (Op r) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Op r b -> Op r c -> Op r a #

conquer :: Op r a #

Divisible (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Proxy b -> Proxy c -> Proxy a #

conquer :: Proxy a #

Divisible m => Divisible (MaybeT m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> MaybeT m b -> MaybeT m c -> MaybeT m a #

conquer :: MaybeT m a #

Divisible m => Divisible (ListT m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> ListT m b -> ListT m c -> ListT m a #

conquer :: ListT m a #

Divisible f => Divisible (Rec1 f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Rec1 f b -> Rec1 f c -> Rec1 f a #

conquer :: Rec1 f a #

Monoid m => Divisible (Const m :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Const m b -> Const m c -> Const m a #

conquer :: Const m a #

Divisible f => Divisible (Alt f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Alt f b -> Alt f c -> Alt f a #

conquer :: Alt f a #

Divisible f => Divisible (IdentityT f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> IdentityT f b -> IdentityT f c -> IdentityT f a #

conquer :: IdentityT f a #

Divisible m => Divisible (ExceptT e m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> ExceptT e m b -> ExceptT e m c -> ExceptT e m a #

conquer :: ExceptT e m a #

Divisible m => Divisible (ErrorT e m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> ErrorT e m b -> ErrorT e m c -> ErrorT e m a #

conquer :: ErrorT e m a #

Divisible m => Divisible (StateT s m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> StateT s m b -> StateT s m c -> StateT s m a #

conquer :: StateT s m a #

Divisible f => Divisible (Backwards f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Backwards f b -> Backwards f c -> Backwards f a #

conquer :: Backwards f a #

Divisible m => Divisible (StateT s m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> StateT s m b -> StateT s m c -> StateT s m a #

conquer :: StateT s m a #

Divisible m => Divisible (WriterT w m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> WriterT w m b -> WriterT w m c -> WriterT w m a #

conquer :: WriterT w m a #

Divisible m => Divisible (WriterT w m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> WriterT w m b -> WriterT w m c -> WriterT w m a #

conquer :: WriterT w m a #

Divisible f => Divisible (Reverse f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Reverse f b -> Reverse f c -> Reverse f a #

conquer :: Reverse f a #

Monoid m => Divisible (Constant m :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Constant m b -> Constant m c -> Constant m a #

conquer :: Constant m a #

(Divisible f, Divisible g) => Divisible (f :*: g) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> (f :*: g) b -> (f :*: g) c -> (f :*: g) a #

conquer :: (f :*: g) a #

(Divisible f, Divisible g) => Divisible (Product f g) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Product f g b -> Product f g c -> Product f g a #

conquer :: Product f g a #

Divisible m => Divisible (ReaderT r m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> ReaderT r m b -> ReaderT r m c -> ReaderT r m a #

conquer :: ReaderT r m a #

Divisible f => Divisible (M1 i c f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c0)) -> M1 i c f b -> M1 i c f c0 -> M1 i c f a #

conquer :: M1 i c f a #

(Applicative f, Divisible g) => Divisible (f :.: g) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> (f :.: g) b -> (f :.: g) c -> (f :.: g) a #

conquer :: (f :.: g) a #

(Applicative f, Divisible g) => Divisible (Compose f g) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> Compose f g b -> Compose f g c -> Compose f g a #

conquer :: Compose f g a #

Divisible m => Divisible (RWST r w s m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> RWST r w s m b -> RWST r w s m c -> RWST r w s m a #

conquer :: RWST r w s m a #

Divisible m => Divisible (RWST r w s m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

divide :: (a -> (b, c)) -> RWST r w s m b -> RWST r w s m c -> RWST r w s m a #

conquer :: RWST r w s m a #

divided :: Divisible f => f a -> f b -> f (a, b) #

class Divisible f => Decidable (f :: Type -> Type) where #

A Decidable contravariant functor is the contravariant analogue of Alternative.

Noting the superclass constraint that f must also be Divisible, a Decidable functor has the ability to "fan out" input, under the intuition that contravariant functors consume input.

In the dicussion for Divisible, an example was demonstrated with Serializers, that turn as into ByteStrings. Divisible allowed us to serialize the product of multiple values by concatenation. By making our Serializer also Decidable- we now have the ability to serialize the sum of multiple values - for example different constructors in an ADT.

Consider serializing arbitrary identifiers that can be either Strings or Ints:

data Identifier = StringId String | IntId Int

We know we have serializers for Strings and Ints, but how do we combine them into a Serializer for Identifier? Essentially, our Serializer needs to scrutinise the incoming value and choose how to serialize it:

identifier :: Serializer Identifier
identifier = Serializer $ \identifier ->
  case identifier of
    StringId s -> runSerializer string s
    IntId i -> runSerializer int i

It is exactly this notion of choice that Decidable encodes. Hence if we add an instance of Decidable for Serializer...

instance Decidable Serializer where
  lose f = Serializer $ \a -> absurd (f a)
  choose split l r = Serializer $ \a ->
    either (runSerializer l) (runSerializer r) (split a)

Then our identifier Serializer is

identifier :: Serializer Identifier
identifier = choose toEither string int where
  toEither (StringId s) = Left s
  toEither (IntId i) = Right i

Methods

lose :: (a -> Void) -> f a #

Acts as identity to choose.

choose :: (a -> Either b c) -> f b -> f c -> f a #

Instances
Decidable SettableStateVar 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> SettableStateVar a #

choose :: (a -> Either b c) -> SettableStateVar b -> SettableStateVar c -> SettableStateVar a #

Decidable Predicate 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> Predicate a #

choose :: (a -> Either b c) -> Predicate b -> Predicate c -> Predicate a #

Decidable Comparison 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> Comparison a #

choose :: (a -> Either b c) -> Comparison b -> Comparison c -> Comparison a #

Decidable Equivalence 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> Equivalence a #

choose :: (a -> Either b c) -> Equivalence b -> Equivalence c -> Equivalence a #

Decidable Encode 
Instance details

Defined in Data.Sv.Encode.Type

Methods

lose :: (a -> Void) -> Encode a #

choose :: (a -> Either b c) -> Encode b -> Encode c -> Encode a #

Decidable (U1 :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> U1 a #

choose :: (a -> Either b c) -> U1 b -> U1 c -> U1 a #

Monoid r => Decidable (Op r) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> Op r a #

choose :: (a -> Either b c) -> Op r b -> Op r c -> Op r a #

Decidable (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> Proxy a #

choose :: (a -> Either b c) -> Proxy b -> Proxy c -> Proxy a #

Divisible m => Decidable (MaybeT m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> MaybeT m a #

choose :: (a -> Either b c) -> MaybeT m b -> MaybeT m c -> MaybeT m a #

Divisible m => Decidable (ListT m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> ListT m a #

choose :: (a -> Either b c) -> ListT m b -> ListT m c -> ListT m a #

Decidable f => Decidable (Rec1 f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> Rec1 f a #

choose :: (a -> Either b c) -> Rec1 f b -> Rec1 f c -> Rec1 f a #

Decidable f => Decidable (Alt f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> Alt f a #

choose :: (a -> Either b c) -> Alt f b -> Alt f c -> Alt f a #

Decidable f => Decidable (IdentityT f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> IdentityT f a #

choose :: (a -> Either b c) -> IdentityT f b -> IdentityT f c -> IdentityT f a #

Decidable m => Decidable (StateT s m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> StateT s m a #

choose :: (a -> Either b c) -> StateT s m b -> StateT s m c -> StateT s m a #

Decidable f => Decidable (Backwards f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> Backwards f a #

choose :: (a -> Either b c) -> Backwards f b -> Backwards f c -> Backwards f a #

Decidable m => Decidable (StateT s m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> StateT s m a #

choose :: (a -> Either b c) -> StateT s m b -> StateT s m c -> StateT s m a #

Decidable m => Decidable (WriterT w m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> WriterT w m a #

choose :: (a -> Either b c) -> WriterT w m b -> WriterT w m c -> WriterT w m a #

Decidable m => Decidable (WriterT w m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> WriterT w m a #

choose :: (a -> Either b c) -> WriterT w m b -> WriterT w m c -> WriterT w m a #

Decidable f => Decidable (Reverse f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> Reverse f a #

choose :: (a -> Either b c) -> Reverse f b -> Reverse f c -> Reverse f a #

(Decidable f, Decidable g) => Decidable (f :*: g) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> (f :*: g) a #

choose :: (a -> Either b c) -> (f :*: g) b -> (f :*: g) c -> (f :*: g) a #

(Decidable f, Decidable g) => Decidable (Product f g) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> Product f g a #

choose :: (a -> Either b c) -> Product f g b -> Product f g c -> Product f g a #

Decidable m => Decidable (ReaderT r m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> ReaderT r m a #

choose :: (a -> Either b c) -> ReaderT r m b -> ReaderT r m c -> ReaderT r m a #

Decidable f => Decidable (M1 i c f) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> M1 i c f a #

choose :: (a -> Either b c0) -> M1 i c f b -> M1 i c f c0 -> M1 i c f a #

(Applicative f, Decidable g) => Decidable (f :.: g) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> (f :.: g) a #

choose :: (a -> Either b c) -> (f :.: g) b -> (f :.: g) c -> (f :.: g) a #

(Applicative f, Decidable g) => Decidable (Compose f g) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> Compose f g a #

choose :: (a -> Either b c) -> Compose f g b -> Compose f g c -> Compose f g a #

Decidable m => Decidable (RWST r w s m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> RWST r w s m a #

choose :: (a -> Either b c) -> RWST r w s m b -> RWST r w s m c -> RWST r w s m a #

Decidable m => Decidable (RWST r w s m) 
Instance details

Defined in Data.Functor.Contravariant.Divisible

Methods

lose :: (a -> Void) -> RWST r w s m a #

choose :: (a -> Either b c) -> RWST r w s m b -> RWST r w s m c -> RWST r w s m a #

chosen :: Decidable f => f b -> f c -> f (Either b c) #

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 
Instance details

Defined in Data.Validation

Methods

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

Bifoldable Validation 
Instance details

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 
Instance details

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 
Instance details

Defined in Data.Validation

Methods

swapped :: Iso (Validation a b) (Validation c d) (Validation b a) (Validation d c) #

Validate Validation 
Instance details

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Data.Validation

Methods

rnf :: Validation e a -> () #

type Rep (Validation err a) 
Instance details

Defined in Data.Validation

type Rep (Validation err a) = D1 (MetaData "Validation" "Data.Validation" "validation-1-LV4YBn0hwbdJopARCbXXEn" 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)))