kure-2.4.2: Combinators for Strategic Programming

Portabilityghc
Stabilitybeta
MaintainerNeil Sculthorpe <neil@ittc.ku.edu>
Safe HaskellSafe-Inferred

Language.KURE.Combinators

Contents

Description

This module provides various monadic and arrow combinators that are particularly useful when working with translations.

Synopsis

Monad Combinators

Monads with a Catch

class Monad m => MonadCatch m whereSource

Monads with a catch for fail. The following law is expected to hold:

 fail msg `catchM` f == f msg

Methods

catchM :: m a -> (String -> m a) -> m aSource

Catch a failing monadic computation.

Instances

MonadCatch KureMonad

KureMonad is the minimal monad that can be an instance of MonadCatch.

(Monad (Translate c m a), MonadCatch m) => MonadCatch (Translate c m a)

Lifting through a Reader transformer, where (c,a) is the read-only environment.

(<<+) :: MonadCatch m => m a -> m a -> m aSource

A monadic catch that ignores the error message.

catchesM :: MonadCatch m => [m a] -> m aSource

Select the first monadic computation that succeeds, discarding any thereafter.

tryM :: MonadCatch m => a -> m a -> m aSource

Catch a failing monadic computation, making it succeed with a constant value.

mtryM :: (MonadCatch m, Monoid a) => m a -> m aSource

Catch a failing monadic computation, making it succeed with mempty.

attemptM :: MonadCatch m => m a -> m (Either String a)Source

Catch a failing monadic computation, making it succeed with an error message.

testM :: MonadCatch m => m a -> m BoolSource

Determine if a monadic computation succeeds.

notM :: MonadCatch m => m a -> m ()Source

Fail if the Monad succeeds; succeed with () if it fails.

modFailMsg :: MonadCatch m => (String -> String) -> m a -> m aSource

Modify the error message of a failing monadic computation. Successful computations are unaffected.

setFailMsg :: MonadCatch m => String -> m a -> m aSource

Set the error message of a failing monadic computation. Successful computations are unaffected.

prefixFailMsg :: MonadCatch m => String -> m a -> m aSource

Add a prefix to the error message of a failing monadic computation. Successful computations are unaffected.

withPatFailMsg :: MonadCatch m => String -> m a -> m aSource

Use the given error message whenever a monadic pattern match failure occurs.

Conditionals

guardMsg :: Monad m => Bool -> String -> m ()Source

Similar to guard, but invokes fail rather than mzero.

guardM :: Monad m => Bool -> m ()Source

As guardMsg, but with a default error message.

ifM :: Monad m => m Bool -> m a -> m a -> m aSource

if-then-else lifted over a monadic predicate.

whenM :: Monad m => m Bool -> m a -> m aSource

If the monadic predicate holds then perform the monadic action, else fail.

unlessM :: Monad m => m Bool -> m a -> m aSource

If the monadic predicate holds then fail, else perform the monadic action.

Arrow Combinators

Categories with a Catch

class Category arr => CategoryCatch arr whereSource

Categorys with failure and catching. The following law is expected to hold:

 failT msg `catchT` f == f msg

Methods

failT :: String -> arr a bSource

The failing Category.

catchT :: arr a b -> (String -> arr a b) -> arr a bSource

A catch on Categorys.

Instances

(Category (Lens c m), MonadCatch m) => CategoryCatch (Lens c m)

A Lens is deemed to have failed (and thus can be caught) if either it fails on the way down, or, crucially, if it would fail on the way up for an unmodified value. However, actual failure on the way up is not caught (as by then it is too late to use an alternative Lens). This means that, in theory, a use of catch could cause a succeeding Lens application to fail. But provided lens is used correctly, this should never happen.

(Category (Translate c m), MonadCatch m) => CategoryCatch (Translate c m)

The Kleisli Category induced by m, lifting through a Reader transformer, where c is the read-only environment.

(<+) :: CategoryCatch arr => arr a b -> arr a b -> arr a bSource

Left-biased choice.

readerT :: ArrowApply arr => (a -> arr a b) -> arr a bSource

Look at the argument to the Arrow before choosing which Arrow to use.

acceptR :: (CategoryCatch arr, ArrowApply arr) => (a -> Bool) -> String -> arr a aSource

Look at the argument to an Arrow, and choose to be either the identity arrow or a failure.

accepterR :: (CategoryCatch arr, ArrowApply arr) => arr a Bool -> String -> arr a aSource

Look at the argument to an Arrow, and choose to be either the identity arrow or a failure. This is a generalisation of acceptR to any Arrow.

tryR :: CategoryCatch arr => arr a a -> arr a aSource

Catch a failing CategoryCatch, making it into an identity.

attemptR :: (CategoryCatch arr, Arrow arr) => arr a a -> arr a (Bool, a)Source

Catch a failing Arrow, making it succeed with a Boolean flag. Useful when defining anyR instances.

changedR :: (CategoryCatch arr, ArrowApply arr, Eq a) => arr a a -> arr a aSource

Makes an Arrow fail if the result value equals the argument value.

repeatR :: CategoryCatch arr => arr a a -> arr a aSource

Repeat a CategoryCatch until it fails, then return the result before the failure. Requires at least the first attempt to succeed.

(>+>) :: (CategoryCatch arr, ArrowApply arr) => arr a a -> arr a a -> arr a aSource

Attempt two Arrows in sequence, succeeding if one or both succeed.

orR :: (CategoryCatch arr, ArrowApply arr) => [arr a a] -> arr a aSource

Sequence a list of Arrows, succeeding if any succeed.

andR :: Category arr => [arr a a] -> arr a aSource

Sequence a list of Categorys, succeeding if all succeed.

catchesT :: CategoryCatch arr => [arr a b] -> arr a bSource

Select the first CategoryCatch that succeeds, discarding any thereafter.

Basic Routing

The names result and argument are taken from Conal Elliott's semantic editor combinators.

result :: Arrow arr => (b -> c) -> arr a b -> arr a cSource

Apply a pure function to the result of an Arrow.

argument :: Arrow arr => (a -> b) -> arr b c -> arr a cSource

Apply a pure function to the argument to an Arrow.

toFst :: Arrow arr => arr a b -> arr (a, x) bSource

Apply an Arrow to the first element of a pair, discarding the second element.

toSnd :: Arrow arr => arr a b -> arr (x, a) bSource

Apply an Arrow to the second element of a pair, discarding the first element.

swap :: Arrow arr => arr (a, b) (b, a)Source

A pure Arrow that swaps the elements of a pair.

fork :: Arrow arr => arr a (a, a)Source

A pure Arrow that duplicates its argument.

forkFirst :: Arrow arr => arr a b -> arr a (b, a)Source

Tag the result of an Arrow with its argument.

forkSecond :: Arrow arr => arr a b -> arr a (a, b)Source

Tag the result of an Arrow with its argument.

constant :: Arrow arr => b -> arr a bSource

An arrow with a constant result.