nondeterminism-1.0: A monad and monad transformer for nondeterministic computations.

Safe HaskellSafe-Inferred

Control.Monad.Amb

Contents

Synopsis

Overview

A nondeterministic computation makes a series of choices which it can then backtrack to. As an example, here is a program which computes Pythagorean triples of a certain size.

import Control.Monad
import Control.Monad.Amb

pyTriple :: (Num t, Ord t) => t -> Amb r (t, t, t)
pyTriple n = do a <- anIntegerBetween 1 n
                b <- anIntegerBetween (a + 1) n
                c <- anIntegerBetween (b + 1) n
                when (a*a + b*b /= c*c) fail'
                return (a,b,c)

You can run this computation and ask for one or more of its possible values.

>>> oneValue $ pyTriple 20
(3,4,5)
>>> allValues $ pyTriple 20
[(3,4,5),(5,12,13),(6,8,10),(8,15,17),(9,12,15),(12,16,20)]

Creating computations

amb :: Monad m => [b] -> AmbT r m bSource

Just for fun. This is McCarthy's amb operator and is a synonym for aMemberOf.

aPartitionOfSize :: (Eq a, Monad m) => Int -> [a] -> AmbT r m [[a]]Source

Generate all partitions of a given size of this list.

aPartitionOf :: (Eq t, Monad m) => [t] -> AmbT r m [[t]]Source

Generate all partitions of this list.

aPermutationOf :: Monad m => [a] -> AmbT r m [a]Source

Generate all permutations of a list.

aSplitOf :: Monad m => [a] -> AmbT r m ([a], [a])Source

Generate all splits of a list.

anIntegerBetween :: (Monad m, Num b, Ord b) => b -> b -> AmbT r m bSource

Generate all numbers between the given bounds, inclusive.

aSubsetOf :: Monad m => [AmbT r m a] -> AmbT r m [a]Source

Generate each subset of any size from the given list.

aMemberOf :: Monad m => [b] -> AmbT r m bSource

Generate each element of the given list.

aBoolean :: Monad m => AmbT r m BoolSource

The most basic primitive that everything else is built out of. Generates True and False.

fail' :: Monad m => AmbT r m bSource

Terminate this branch of the computation.

either' :: Monad m => AmbT r m b -> AmbT r m b -> AmbT r m bSource

Nondeterministically choose either of the two computations

Running computations

isPossible :: Amb Bool Bool -> BoolSource

Run a nondeterministic computation and return True if any result is True, False otherwise.

isPossibleT :: Monad m => AmbT Bool m Bool -> m BoolSource

Run a nondeterministic computation and return True if any result is True, False otherwise.

isNecessary :: Amb Bool Bool -> BoolSource

Run a nondeterministic computation and return True if all possible results are True, False otherwise.

isNecessaryT :: Monad m => AmbT Bool m Bool -> m BoolSource

Run a nondeterministic computation and return True if all possible results are True, False otherwise.

allValues :: Amb t t -> [t]Source

Run a nondeterministic computation and return a list of all results that the computation can produce. Note that this function is not lazy its result.

allValuesT :: Monad m => AmbT t m t -> m [t]Source

Run a nondeterministic computation and return a list of all results that the computation can produce. Note that this function is not lazy its result.

oneValue :: Amb a a -> aSource

Run a nondeterministic computation and return a result of that computation.

oneValueT :: Monad m => AmbT b m b -> m bSource

Run a nondeterministic computation and return a result of that computation.

Low-level internals

tell' :: Monad m => [r] -> AmbT r m ()Source

A helper to inject state into the backtracking stack

tellState :: (Monoid s, MonadState s m) => s -> m ()Source

A helper to inject state into the backtracking stack

uponFailure :: Monad m => AmbT r m a -> AmbT r m ()Source

When the nondeterministic computation backtracks past this state, execute this nondeterministic computation. Generally used to undo side effects.

runAmbT :: Monad m => AmbT t m t -> m (t, [t])Source

Run the nondeterministic computation. This is internal.

runAmbTI :: Monad m => AmbT a m a -> AmbT a m a -> m (a, [a])Source

Run the nondeterministic computation. This is internal.

ambCC :: ((a -> AmbT r m a1) -> AmbT r m a) -> AmbT r m aSource

call/cc lifted into the nondeterministic monad. This implements the backtracking behaviour which allows Amb to try different code paths and return multiple results.

forEffects :: Monad m => ((t, [t]) -> r) -> (t1 -> AmbT t m t) -> AmbT t m t1 -> m rSource

A low-level internal function which executes a nondeterministic computation for its nondeterministic side-effects, such as its ability to produce different results.

Types

data AmbT r m a Source

AmbT r m a is a computation whose current value is of type a and which will ultimately return a value of type r. The same as ContT.

Constructors

AmbT 

Fields

unAmbT :: StateT (AmbT r m r) (ContT r (StateT [r] m)) a

From left to right:

  • the computation to run on failure
  • the continuation captured when making nondeterministic choices
  • record keeping of solutions found so far

Instances

MonadTrans (AmbT r) 
Monad m => Monad (AmbT r m) 

type AmbT' m a = forall r. AmbT r m aSource