| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Prednote.Core
Contents
- newtype PredM f a = PredM {}
- type Pred = PredM Identity
- predicate :: Show a => Text -> (a -> Bool) -> Pred a
- predicateM :: (Show a, Functor f) => Text -> (a -> f Bool) -> PredM f a
- (&&&) :: Monad m => PredM m a -> PredM m a -> PredM m a
- (|||) :: Monad m => PredM m a -> PredM m a -> PredM m a
- not :: Functor m => PredM m a -> PredM m a
- switch :: PredM m a -> PredM m b -> PredM m (Either a b)
- any :: (Functor m, Monad m, Applicative m) => PredM m a -> PredM m [a]
- all :: (Functor m, Monad m, Applicative m) => PredM m a -> PredM m [a]
- data Nothing
- maybe :: Functor m => PredM m Nothing -> PredM m a -> PredM m (Maybe a)
- addLabel :: Functor f => Text -> PredM f a -> PredM f a
- true :: (Show a, Applicative f) => PredM f a
- false :: (Show a, Applicative f) => PredM f a
- same :: Applicative f => PredM f Bool
- test :: Pred a -> a -> Bool
- testM :: Functor f => PredM f a -> a -> f Bool
- runPred :: Pred a -> a -> Result
- verboseTest :: Pred a -> a -> ([Chunk], Bool)
- verboseTestStdout :: Pred a -> a -> IO Bool
- newtype Condition = Condition [Chunk]
- newtype Value = Value Text
- newtype Label = Label Text
- data Labeled a = Labeled [Label] a
- data Passed
- data Failed
- newtype Result = Result (Labeled (Either Failed Passed))
- splitResult :: Result -> Either (Labeled Failed) (Labeled Passed)
- resultToChunks :: Result -> [Chunk]
- passedToChunks :: Int -> Labeled Passed -> [Chunk]
- failedToChunks :: Int -> Labeled Failed -> [Chunk]
Predicates and their creation
Predicates. Is an instance of Contravariant, which allows you
to change the type using contramap. Though the constructor is
exported, ordinarily you shouldn't need to use it; other functions
in this module create PredM and manipulate them as needed.
The f type variable is an arbitrary context; ordinarily this type
will be an instance of Monad, and some of the bindings in this
module require this. That allows you to run predicate computations
that run in some sort of context, allowing you to perform IO,
examine state, or whatever. If you only want to do pure
computations, just use the Pred type synonym.
Instances
| Contravariant (PredM f) | |
| Show (PredM f a) |
predicate :: Show a => Text -> (a -> Bool) -> Pred a Source
Creates a new Pred that do not run in any context. In
predicate cond f, cond describes the condition, while f gives
the predicate function. For example, if f is (> 5), then
cond might be "is greater than 5".
Arguments
| :: (Show a, Functor f) | |
| => Text | |
| -> (a -> f Bool) | Predicate function; this is in an arbitrary context, allowing
you to perform IO, examine and change state, etc. If you do not
need to use a context, see |
| -> PredM f a |
Creates a new PredM that run in some arbitrary context. In
predicateM cond f, cond describes the condition, while f
gives the predicate function. For example, if f is (> 5), then
cond might be "is greater than 5".
Predicate combinators
Primitive combinators
You might consider these combinators to be "primitive" in the
sense that you can build a Pred for any user-defined type by
using these combinators alone, along with contramap. Use
&&&, |||, and contramap to analyze product types. Use switch
and contramap to analyze sum types. For a simple example, see the
source code for maybe, which is a simple sum type. For more
complicated examples, see the source code for any and all, as
a list is a sum type where one of the summands is a (recursive!)
product type.
Convenience combinators
These were written using entirely the "primitive" combinators given above.
Labeling
Constant predicates
same :: Applicative f => PredM f Bool Source
Always returns its argument
Evaluating predicates
verboseTest :: Pred a -> a -> ([Chunk], Bool) Source
verboseTestStdout :: Pred a -> a -> IO Bool Source
Like verboseTest, but results are printed to standard output.
Primarily for use in debugging or in a REPL.
Results and converting them to Chunks
Usually you will not need these functions and types, as the functions and types above should meet most use cases; however, these are here so the test suites can use them, and in case you need them.
Gives additional information about a particular Pred to aid the
user when viewing the output.
Any type that is accompanied by a set of labels.
The result of processing a Pred.
splitResult :: Result -> Either (Labeled Failed) (Labeled Passed) Source
Returns whether this Result failed or passed.
resultToChunks :: Result -> [Chunk] Source
Obtain a list of Chunk describing the evaluation process.
Obtain a list of Chunk describing the evaluation process.