prednote-0.36.0.2: Evaluate and display trees of predicates

Safe HaskellNone
LanguageHaskell2010

Prednote.Core

Contents

Synopsis

Predicates and their creation

newtype PredM f a Source

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.

Constructors

PredM 

Fields

runPredM :: a -> f Result
 

Instances

type Pred = PredM Identity Source

Predicates that do not run in any context.

predicate :: (a -> (Bool, Value, Condition)) -> 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".

predicateM :: Functor f => (a -> f (Bool, Value, Condition)) -> PredM f a Source

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".

contramapM :: Monad m => (a -> m b) -> PredM m b -> PredM m a Source

Like contramap but allows the mapping function to run in a monad.

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.

(&&&) :: Monad m => PredM m a -> PredM m a -> PredM m a infixr 3 Source

And. Returns True if both argument Pred return True. Is lazy in its second argment; if the first argument returns False, the second is ignored.

(|||) :: Monad m => PredM m a -> PredM m a -> PredM m a infixr 2 Source

Or. Returns True if either argument Pred returns True. Is lazy in its second argument; if the first argument returns True, the second argument is ignored.

not :: Functor m => PredM m a -> PredM m a Source

Negation. Returns True if the argument Pred returns False.

switch :: PredM m a -> PredM m b -> PredM m (Either a b) Source

Uses the appropriate Pred depending on the Either value. In test (switch l r) e, the resulting Pred returns the result of l if e is Left or the result of r if e is Right. Is lazy, so the the argument Pred that is not used is ignored.

Convenience combinators

These were written using entirely the "primitive" combinators given above.

any :: (Monad m, Applicative m) => PredM m a -> PredM m [a] Source

Like any; is True if any of the list items are True. An empty list returns False. Is lazy; will stop processing if it encounters a True item.

all :: (Monad m, Applicative m) => PredM m a -> PredM m [a] Source

Like all; is True if none of the list items is False. An empty list returns True. Is lazy; will stop processing if it encouters a False item.

maybe Source

Arguments

:: Applicative m 
=> Bool

What to return on Nothing

-> PredM m a

Analyzes Just values

-> PredM m (Maybe a) 

Create a Pred for Maybe.

Labeling

addLabel :: Functor f => [Chunk Text] -> PredM f a -> PredM f a Source

Adds descriptive text to a Pred. Gives useful information for the user. The label is added to the top Pred in the tree; any existing labels are also retained. Labels that were added last will be printed first. For an example of this, see the source code for any and all.

Constant predicates

true :: Applicative f => PredM f a Source

Always returns True

false :: Applicative f => PredM f a Source

Always returns False

same :: Applicative f => PredM f Bool Source

Always returns its argument

Evaluating predicates

test :: Pred a -> a -> Bool Source

Runs a Pred against a value, without a context.

testM :: Functor f => PredM f a -> a -> f Bool Source

Runs a Pred against a value.

runPred :: Pred a -> a -> Result Source

Runs pure Pred computations.

verboseTest :: Pred a -> a -> ([Chunk Text], 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.

newtype Condition Source

Describes the condition; for example, for a Pred Int, this might be is greater than 5; for a Pred String, this might be begins with "Hello".

Constructors

Condition [Chunk Text] 

newtype Value Source

Stores the representation of a value.

Constructors

Value [Chunk Text] 

newtype Label Source

Gives additional information about a particular Pred to aid the user when viewing the output.

Constructors

Label [Chunk Text] 

data Labeled a Source

Any type that is accompanied by a set of labels.

Constructors

Labeled [Label] a 

Instances

Functor Labeled 
Eq a => Eq (Labeled a) 
Ord a => Ord (Labeled a) 
Show a => Show (Labeled a) 

data Passed Source

A Pred that returned True

Constructors

PTerminal Value Condition

A Pred created with predicate

PAnd (Labeled Passed) (Labeled Passed)

A Pred created with &&&

POr (Either (Labeled Passed) (Labeled Failed, Labeled Passed))

A Pred created with |||

PNot (Labeled Failed)

A Pred created with not

Instances

data Failed Source

A Pred that returned False

Constructors

FTerminal Value Condition

A Pred created with predicate

FAnd (Either (Labeled Failed) (Labeled Passed, Labeled Failed))

A Pred created with &&&

FOr (Labeled Failed) (Labeled Failed)

A Pred created with |||

FNot (Labeled Passed)

A Pred created with not

Instances

newtype Result Source

The result of processing a Pred.

Constructors

Result (Labeled (Either Failed Passed)) 

Instances

splitResult :: Result -> Either (Labeled Failed) (Labeled Passed) Source

Returns whether this Result failed or passed.

resultToChunks :: Result -> [Chunk Text] Source

Obtain a list of Chunk describing the evaluation process.

passedToChunks Source

Arguments

:: Int

Number of levels of indentation

-> Labeled Passed 
-> [Chunk Text] 

Obtain a list of Chunk describing the evaluation process.

failedToChunks Source

Arguments

:: Int

Number of levels of indentation

-> Labeled Failed 
-> [Chunk Text] 

Obtain a list of Chunk describing the evaluation process.