Maintainer | bastiaan.heeren@ou.nl |
---|---|
Stability | provisional |
Portability | portable (depends on ghc) |
Safe Haskell | Safe |
Language | Haskell98 |
Datatype for representing a derivation (parameterized both in the terms and the steps)
- data Derivation s a
- emptyDerivation :: a -> Derivation s a
- prepend :: (a, s) -> Derivation s a -> Derivation s a
- extend :: Derivation s a -> (s, a) -> Derivation s a
- isEmpty :: Derivation s a -> Bool
- derivationLength :: Derivation s a -> Int
- terms :: Derivation s a -> [a]
- steps :: Derivation s a -> [s]
- triples :: Derivation s a -> [(a, s, a)]
- firstTerm :: Derivation s a -> a
- lastTerm :: Derivation s a -> a
- lastStep :: Derivation s a -> Maybe s
- withoutLast :: Derivation s a -> Derivation s a
- updateSteps :: (a -> s -> a -> t) -> Derivation s a -> Derivation t a
- derivationM :: Monad m => (s -> m ()) -> (a -> m ()) -> Derivation s a -> m ()
Data type
data Derivation s a Source
BiFunctor Derivation Source | |
Functor (Derivation s) Source | |
(Show s, Show a) => Show (Derivation s a) Source |
Constructing a derivation
emptyDerivation :: a -> Derivation s a Source
prepend :: (a, s) -> Derivation s a -> Derivation s a Source
extend :: Derivation s a -> (s, a) -> Derivation s a Source
Querying a derivation
isEmpty :: Derivation s a -> Bool Source
Tests whether the derivation is empty
derivationLength :: Derivation s a -> Int Source
Returns the number of steps in a derivation
terms :: Derivation s a -> [a] Source
All terms in a derivation
steps :: Derivation s a -> [s] Source
All steps in a derivation
triples :: Derivation s a -> [(a, s, a)] Source
The triples of a derivation, consisting of the before term, the step, and the after term.
firstTerm :: Derivation s a -> a Source
lastTerm :: Derivation s a -> a Source
lastStep :: Derivation s a -> Maybe s Source
withoutLast :: Derivation s a -> Derivation s a Source
updateSteps :: (a -> s -> a -> t) -> Derivation s a -> Derivation t a Source
derivationM :: Monad m => (s -> m ()) -> (a -> m ()) -> Derivation s a -> m () Source
Apply a monadic function to each term, and to each step