simple-ltl-2.1.0: A simple LTL checker

Safe HaskellSafe
LanguageHaskell2010

LTL

Description

This module provides a simple way of applying LTL formulas to lists, or streams of input, to determine if a given formula matches some or all of that input.

Formulas are written exactly as you would in LTL, but using names instead of the typical symbols, for example:

always (is even `until` is odd)

Use run to apply a formula to a list of inputs, returning either Left if it needs more input to determine the truth of the formula, or Right if it could determine truth from some prefix of that input.

Use step to advance a formula by a single input. The return value has the same meaning as run, but allows you to apply it in cases whether you don't necessarily have all the inputs at once, such as feeding input gradually within a conduit to check for logic failures.

For the meaning of almost all the functions in the module, see https://en.wikipedia.org/wiki/Linear_temporal_logic

Synopsis

Documentation

type LTL a = Machine a (Result a) Source #

newtype Machine a b Source #

Constructors

Machine 

Fields

Instances
Functor (Machine a) Source # 
Instance details

Defined in LTL

Methods

fmap :: (a0 -> b) -> Machine a a0 -> Machine a b #

(<$) :: a0 -> Machine a b -> Machine a a0 #

data Reason a Source #

Instances
Functor Reason Source # 
Instance details

Defined in LTL

Methods

fmap :: (a -> b) -> Reason a -> Reason b #

(<$) :: a -> Reason b -> Reason a #

Show a => Show (Reason a) Source # 
Instance details

Defined in LTL

Methods

showsPrec :: Int -> Reason a -> ShowS #

show :: Reason a -> String #

showList :: [Reason a] -> ShowS #

Generic (Reason a) Source # 
Instance details

Defined in LTL

Associated Types

type Rep (Reason a) :: Type -> Type #

Methods

from :: Reason a -> Rep (Reason a) x #

to :: Rep (Reason a) x -> Reason a #

NFData a => NFData (Reason a) Source # 
Instance details

Defined in LTL

Methods

rnf :: Reason a -> () #

type Rep (Reason a) Source # 
Instance details

Defined in LTL

type Result a = Maybe (Reason a) Source #

run :: Machine a b -> [a] -> Either (Machine a b) b Source #

neg :: LTL a -> LTL a Source #

Negate a formula: ¬ p

top :: LTL a Source #

⊤, or "true"

bottom :: String -> LTL a Source #

⊥, or "false"

accept :: (a -> LTL a) -> LTL a Source #

Given an input element, provide a formula to determine its truth. These can be nested, making it possible to have conditional formulas. Consider the following:

always (accept (n -> next (eq (succ n))))

One way to read this would be: "for every input n, always accept n if its next element is the successor".

reject :: (a -> LTL a) -> LTL a Source #

The opposite in meaning to accept, defined simply as 'neg . accept'.

and :: LTL a -> LTL a -> LTL a Source #

Boolean conjunction: ∧

or :: LTL a -> LTL a -> LTL a Source #

Boolean disjunction: ∨

next :: LTL a -> LTL a Source #

The "next" temporal modality, typically written 'X p' or '◯ p'.

until :: LTL a -> LTL a -> LTL a Source #

The "until" temporal modality, typically written 'p U q'.

weakUntil :: LTL a -> LTL a -> LTL a Source #

Weak until.

release :: LTL a -> LTL a -> LTL a Source #

Release, the dual of until.

strongRelease :: LTL a -> LTL a -> LTL a Source #

Strong release.

implies :: LTL a -> LTL a -> LTL a Source #

Logical implication: p → q

eventually :: LTL a -> LTL a Source #

Eventually the formula will hold, typically written F p or ◇ p.

always :: LTL a -> LTL a Source #

Always the formula must hold, typically written G p or □ p.

truth :: Bool -> LTL a Source #

True if the given Haskell boolean is true.

test :: (a -> Bool) -> LTL a Source #

Another name for is.

is :: (a -> Bool) -> LTL a Source #

True if the given predicate on the input is true.

eq :: Eq a => a -> LTL a Source #

Check for equality with the input.

showResult :: Show a => Either (LTL a) (Result a) -> String Source #

Render a step result as a string.