Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- type Predicate a f t = a -> Result f t
- constant :: t -> Predicate a f t
- failure :: f -> Predicate a f t
- true :: Predicate a f ()
- false :: Predicate a () t
- and :: Predicate a f t -> Predicate a f t' -> Predicate a f (t ::: t')
- or :: Predicate a f t -> Predicate a f t -> Predicate a f t
- orElse :: Predicate a f t -> Predicate a f t' -> Predicate a f (Either t t')
- (.&.) :: Predicate a f t -> Predicate a f t' -> Predicate a f (t ::: t')
- (.|.) :: Predicate a f t -> Predicate a f t -> Predicate a f t
- (|||) :: Predicate a f t -> Predicate a f t' -> Predicate a f (Either t t')
- exec :: Predicate a f t -> a -> (f -> b) -> (t -> b) -> b
- data Result f t
- result :: (f -> a) -> (Double -> t -> a) -> Result f t -> a
- fromEither :: Either f t -> Result f t
- toEither :: Result f t -> Either f t
- newtype ResultT f m t = ResultT {
- runResultT :: m (Result f t)
- resultT :: Monad m => (f -> m a) -> (Double -> t -> m a) -> ResultT f m t -> m a
- resultT' :: Monad m => (f -> m a) -> (t -> m a) -> ResultT f m t -> m a
- mapResultT :: (m (Result f t) -> n (Result f' t')) -> ResultT f m t -> ResultT f' n t'
- hoistResult :: Monad m => Result f t -> ResultT f m t
- okay :: Monad m => Double -> t -> ResultT f m t
- throwF :: Monad m => f -> ResultT f m t
- data a ::: b = a ::: b
- (#) :: a -> (a -> b) -> b
- hd :: (a ::: b) -> a
- tl :: (a ::: b) -> b
- _1 :: (a ::: b) -> a
- _2 :: (a ::: (b ::: c)) -> b
- _3 :: (a ::: (b ::: (c ::: d))) -> c
- _4 :: (a ::: (b ::: (c ::: (d ::: e)))) -> d
- _5 :: (a ::: (b ::: (c ::: (d ::: (e ::: f))))) -> e
- _6 :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: g)))))) -> f
- _7 :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: (g ::: h))))))) -> g
- _8 :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: (g ::: (h ::: i)))))))) -> h
- _9 :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: (g ::: (h ::: (i ::: j))))))))) -> i
- _1' :: (a ::: b) -> a
- _2' :: (a ::: b) -> b
- _3' :: (a ::: (b ::: c)) -> c
- _4' :: (a ::: (b ::: (c ::: d))) -> d
- _5' :: (a ::: (b ::: (c ::: (d ::: e)))) -> e
- _6' :: (a ::: (b ::: (c ::: (d ::: (e ::: f))))) -> f
- _7' :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: g)))))) -> g
- _8' :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: (g ::: h))))))) -> h
- _9' :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: (g ::: (h ::: i)))))))) -> i
Predicate
constant :: t -> Predicate a f t Source
A predicate which always returns Okay
with the given
value as metadata.
failure :: f -> Predicate a f t Source
A predicate which always returns Fail
with the given
value as metadata.
and :: Predicate a f t -> Predicate a f t' -> Predicate a f (t ::: t') Source
A predicate corresponding to the logical AND connective of two predicate.
or :: Predicate a f t -> Predicate a f t -> Predicate a f t Source
A predicate corresponding to the logical
OR connective of two predicates. It requires the
metadata of each Okay
branch to be of the same type.
If both arguments evaluate to Okay
the one with the
smaller "delta" will be preferred, or--if equal--the
left-hand argument.
orElse :: Predicate a f t -> Predicate a f t' -> Predicate a f (Either t t') Source
A predicate corresponding to the logical
OR connective of two predicates. The metadata of
each Okay
branch can be of different types.
If both arguments evaluate to Okay
the one with the
smaller "delta" will be preferred, or--if equal--the
left-hand argument.
(.&.) :: Predicate a f t -> Predicate a f t' -> Predicate a f (t ::: t') infixr 3 Source
Alias of and
.
(|||) :: Predicate a f t -> Predicate a f t' -> Predicate a f (Either t t') infixr 2 Source
Alias of orElse
.
Result
A Bool
-like type where each branch--Fail
and Okay
--carries
some metadata.
fromEither :: Either f t -> Result f t Source
ResultT | |
|
hoistResult :: Monad m => Result f t -> ResultT f m t Source
Product
A data-type for combining results of predicate evaluations.
a ::: b infixr 5 |