Copyright | (c) 2015 Maciej Piróg |
---|---|
License | MIT |
Maintainer | maciej.adam.pirog@gmail.com |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell98 |
A
-like monad transformer equipped with the ListT
operator known from Prolog.cut
- data CutListT' m a
- newtype CutListT m a = CutListT {
- unCutListT :: m (CutListT' m a)
- retract :: Monad m => CutListT m a -> m ()
- type CutList = CutListT Identity
- cutToList :: CutList a -> [a]
- cutFromList :: [a] -> CutList a
- cut :: (Functor m, Monad m) => CutListT m ()
- cutFail :: (Functor m, Monad m) => CutListT m ()
- scope :: (Functor m, Monad m) => CutListT m a -> CutListT m a
The CutListT
transformer
A monad transformer that behaves like the list transformer, but it allows Prolog's cut operator.
CutListT | |
|
MonadTrans CutListT Source | |
Monad m => Monad (CutListT m) Source | |
Functor m => Functor (CutListT m) Source | |
(Functor m, Monad m) => Applicative (CutListT m) Source | |
Foldable m => Foldable (CutListT m) Source | |
Traversable m => Traversable (CutListT m) Source | |
(Functor m, Monad m) => Alternative (CutListT m) Source | |
(Functor m, Monad m) => MonadPlus (CutListT m) Source | |
(Functor m, Monad m) => Monoid (CutListT m a) Source | |
(Functor m, Monad m) => MonoidRZero (CutListT m a) Source |
retract :: Monad m => CutListT m a -> m () Source
Ignore the elements on the list and combine the monadic computations.
The CutList
monad
cutFromList :: [a] -> CutList a Source
Convert from a regular list
Control functions
scope :: (Functor m, Monad m) => CutListT m a -> CutListT m a Source
Delimit the scope of cuts in the argument.
Examples
takeWhile
using lists with cut
We implement the functon
using cuts:takeWhile
takeWhile :: (a -> Bool) -> [a] -> [a] takeWhile p xs = toList $ do x <- fromList xs when (not $ p x) cutFail return x