mad-props-0.2.0.0: Monadic DSL for building constraint solvers using basic propagators.

Copyright(c) Chris Penner 2019
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Props

Contents

Description

This module exports everything you should need to get started. Take a look at NQueens or Sudoku to see how to get started.

Synopsis

Initializing problems

type Prop a = PropT Identity a Source #

Pure version of PropT

data PropT m a Source #

A monad transformer for setting up constraint problems.

Instances
MonadTrans PropT Source # 
Instance details

Defined in Props.Internal.PropT

Methods

lift :: Monad m => m a -> PropT m a #

Monad m => Monad (PropT m) Source # 
Instance details

Defined in Props.Internal.PropT

Methods

(>>=) :: PropT m a -> (a -> PropT m b) -> PropT m b #

(>>) :: PropT m a -> PropT m b -> PropT m b #

return :: a -> PropT m a #

fail :: String -> PropT m a #

Functor m => Functor (PropT m) Source # 
Instance details

Defined in Props.Internal.PropT

Methods

fmap :: (a -> b) -> PropT m a -> PropT m b #

(<$) :: a -> PropT m b -> PropT m a #

Monad m => Applicative (PropT m) Source # 
Instance details

Defined in Props.Internal.PropT

Methods

pure :: a -> PropT m a #

(<*>) :: PropT m (a -> b) -> PropT m a -> PropT m b #

liftA2 :: (a -> b -> c) -> PropT m a -> PropT m b -> PropT m c #

(*>) :: PropT m a -> PropT m b -> PropT m b #

(<*) :: PropT m a -> PropT m b -> PropT m a #

MonadIO m => MonadIO (PropT m) Source # 
Instance details

Defined in Props.Internal.PropT

Methods

liftIO :: IO a -> PropT m a #

data PVar (f :: * -> *) a Source #

A propagator variable where the possible values a are contained in the container f.

Instances
Eq (PVar f a) Source #

Nominal equality, Ignores contents

Instance details

Defined in Props.Internal.PropT

Methods

(==) :: PVar f a -> PVar f a -> Bool #

(/=) :: PVar f a -> PVar f a -> Bool #

Ord (PVar f a) Source # 
Instance details

Defined in Props.Internal.PropT

Methods

compare :: PVar f a -> PVar f a -> Ordering #

(<) :: PVar f a -> PVar f a -> Bool #

(<=) :: PVar f a -> PVar f a -> Bool #

(>) :: PVar f a -> PVar f a -> Bool #

(>=) :: PVar f a -> PVar f a -> Bool #

max :: PVar f a -> PVar f a -> PVar f a #

min :: PVar f a -> PVar f a -> PVar f a #

Show (PVar f a) Source # 
Instance details

Defined in Props.Internal.PropT

Methods

showsPrec :: Int -> PVar f a -> ShowS #

show :: PVar f a -> String #

showList :: [PVar f a] -> ShowS #

newPVar :: (Monad m, Foldable f, Typeable f, Typeable a) => f a -> PropT m (PVar f a) Source #

Used to create a new propagator variable within the setup for your problem.

f is any Foldable container which contains each of the possible states which the variable could take.

E.g. For a sudoku solver you would use newPVar to create a variable for each cell, passing a Set Int containing the numbers [1..9].

Finding Solutions

solve :: forall a r. ((forall f x. PVar f x -> x) -> a -> r) -> Prop a -> Maybe r Source #

Pure version of solveT

solveAll :: forall a r. ((forall f x. PVar f x -> x) -> a -> r) -> Prop a -> [r] Source #

Pure version of solveAllT

Constraining variables

constrain :: Monad m => PVar f a -> PVar g b -> (a -> g b -> g b) -> PropT m () Source #

constrain the relationship between two PVars. Note that this is a ONE WAY relationship; e.g. constrain a b f will propagate constraints from a to b but not vice versa.

Given PVar f a and PVar g b as arguments, provide a function which will filter/alter the options in g according to the choice.

For a sudoku puzzle you'd have two Pvar Set Int's, each representing a cell on the board. You can constrain b to be a different value than a with the following call:

constrain a b $ \elementA setB -> S.delete elementA setB)

Take a look at some linking functions which are already provided: disjoint, equal, require

disjoint :: forall a m. (Monad m, Ord a) => PVar Set a -> PVar Set a -> PropT m () Source #

Apply the constraint that two variables may NOT be set to the same value. This constraint is bidirectional.

E.g. you might apply this constraint to two cells in the same row of sudoku grid to assert they don't contain the same value.

equal :: forall a m. (Monad m, Ord a) => PVar Set a -> PVar Set a -> PropT m () Source #

Apply the constraint that two variables MUST be set to the same value. This constraint is bidirectional.

require :: Monad m => (a -> b -> Bool) -> PVar Set a -> PVar Set b -> PropT m () Source #

Given a choice for a; filter for valid options of b using the given predicate.

E.g. if a must always be greater than b, you could require:

require (>) a b