mad-props-0.1.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 Source #

A propagator variable where the possible values are contained in the MonoFoldable type f.

Instances
Eq (PVar f) Source #

Nominal equality, Ignores contents

Instance details

Defined in Props.Internal.PropT

Methods

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

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

Ord (PVar f) Source #

Nominal ordering, Ignores contents.

Instance details

Defined in Props.Internal.PropT

Methods

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

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

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

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

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

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

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

Show (PVar f) Source # 
Instance details

Defined in Props.Internal.PropT

Methods

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

show :: PVar f -> String #

showList :: [PVar f] -> ShowS #

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

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

f is any MonoFoldable container which contains each of the possible states which the variable could take. In practice this most standard containers make a good candidate, it's easy to define a your own instance if needed.

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

Finding Solutions

solve :: (Functor f, Typeable (Element g)) => Prop (f (PVar g)) -> Maybe (f (Element g)) Source #

Pure version of solveT

solveAll :: (Functor f, Typeable (Element g)) => Prop (f (PVar g)) -> [f (Element g)] Source #

Pure version of solveAllT

Constraining variables

constrain :: (Monad m, Typeable g, Typeable (Element f)) => PVar f -> PVar g -> (Element f -> g -> g) -> 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 and PVar g as arguments, provide a function which will filter/alter the options in g according to the choice.

For a sudoku puzzle f and g each represent cells on the board. If f ~ Set Int and g ~ Set Int, then you might pass a constraint filter:

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, Typeable a, 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, Typeable a, 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, Typeable a, Ord a, Typeable b) => (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