contracheck-applicative-0.1.0.0: Validation types/typeclass based on the contravariance.

Safe HaskellNone
LanguageHaskell2010

Control.Validation.Class

Contents

Synopsis

Checkable

The Validatable typeclass.

Note: It is not inteded to be used for testing of internal integrity of types, i.e. it does not check if a Text has a valid internal representation. For testing internal integrity please use the package (validity)[https:/stackage.orgpackage/validity]. The typeclass is split up into three parts:

  • checkChain: A list of checks that will be performed in that order. This has to be provided to give an instance. For the reason why it is given as a list and the checks are not combined via '(<>)', see the point for isValid.
  • defaulCheck: A check performing all checks of checkChain
defaultCheck = fold checkChain
  • isValid: A function determining whether a value is valid. This functions stops checking after the first of the checks from checkChain fails .This function is the reason why we need the checkChain, as a Check constructed by '(<>)' goes through all operands, so `passed $ runCheck (shortCheck <> longCheck) unvalidatedInput` evalutes the argument with longCheck even if shortCheck failed. But if we define
instance Validatable e m T where
  checkChain = CheckChain [ shortCheck, longCheck ]

then `isValid unvalidatedInput` stops after shortCheck failed.

validate :: (Validatable e m a, Functor m) => Unvalidated a -> m (Either (Seq e) a) Source #

newtype CheckChain (e :: Type) (m :: Type -> Type) (a :: Type) Source #

Constructors

CheckChain 

Fields

Instances
MFunctor (CheckChain e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Validation.Class

Methods

hoist :: Monad m => (forall a. m a -> n a) -> CheckChain e m b -> CheckChain e n b #

Contravariant (CheckChain e m) Source # 
Instance details

Defined in Control.Validation.Class

Methods

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

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

Applicative m => Divisible (CheckChain e m) Source # 
Instance details

Defined in Control.Validation.Class

Methods

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

conquer :: CheckChain e m a #

Applicative m => Decidable (CheckChain e m) Source # 
Instance details

Defined in Control.Validation.Class

Methods

lose :: (a -> Void) -> CheckChain e m a #

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

Semigroup (CheckChain e m a) Source # 
Instance details

Defined in Control.Validation.Class

Methods

(<>) :: CheckChain e m a -> CheckChain e m a -> CheckChain e m a #

sconcat :: NonEmpty (CheckChain e m a) -> CheckChain e m a #

stimes :: Integral b => b -> CheckChain e m a -> CheckChain e m a #

Monoid (CheckChain e m a) Source # 
Instance details

Defined in Control.Validation.Class

Methods

mempty :: CheckChain e m a #

mappend :: CheckChain e m a -> CheckChain e m a -> CheckChain e m a #

mconcat :: [CheckChain e m a] -> CheckChain e m a #

overChain :: (Check e m a -> Check e' n b) -> CheckChain e m a -> CheckChain e' n b Source #

(+?+) :: CheckChain e m a -> CheckChain e m a -> CheckChain e m a infixr 5 Source #

Convenience synonym.

singleChain :: Check e m a -> CheckChain e m a Source #

class Validatable (e :: Type) (m :: Type -> Type) (a :: Type) | a -> m, a -> e where Source #

Minimal complete definition

Nothing

Instances
Validatable Void Identity Bool Source # 
Instance details

Defined in Control.Validation.Class

Validatable Void Identity Char Source # 
Instance details

Defined in Control.Validation.Class

Validatable Void Identity Double Source # 
Instance details

Defined in Control.Validation.Class

Validatable Void Identity Float Source # 
Instance details

Defined in Control.Validation.Class

Validatable Void Identity Int Source # 
Instance details

Defined in Control.Validation.Class

Validatable Void Identity Int8 Source # 
Instance details

Defined in Control.Validation.Class

Validatable Void Identity Int16 Source # 
Instance details

Defined in Control.Validation.Class

Validatable Void Identity Int32 Source # 
Instance details

Defined in Control.Validation.Class

Validatable Void Identity Int64 Source # 
Instance details

Defined in Control.Validation.Class

Validatable Void Identity Integer Source # 
Instance details

Defined in Control.Validation.Class

Validatable Void Identity () Source # 
Instance details

Defined in Control.Validation.Class

Validatable Void Identity ByteString Source # 
Instance details

Defined in Control.Validation.Class

Validatable Void Identity Text Source # 
Instance details

Defined in Control.Validation.Class

(Validatable e m a, Applicative m) => Validatable e m [a] Source # 
Instance details

Defined in Control.Validation.Class

(Validatable e m a, Applicative m) => Validatable e m (Maybe a) Source # 
Instance details

Defined in Control.Validation.Class

Validatable Void Identity (TrivialCheck a) Source # 
Instance details

Defined in Control.Validation.Class

(Validatable e m b, Validatable e m a, Applicative m) => Validatable e m (Either a b) Source # 
Instance details

Defined in Control.Validation.Class

Helper for deriving Validatable

Helper for deriving Validatable

Intended for use with `-XDerivingVia` like

data X = X Int
    deriving (Validatable Void Identity) via (TrivialCheck X)
-- or with `-XStandaloneDeriving`
data Y = Y String
deriving via (TrivialCheck Y) instance (Validatable Void Identity Y) 

Reexports