monadiccp-0.5.2: Constraint Programming

Control.CP.Herbrand.Herbrand

Description

This module provides a Herbrand solver.

The type of terms is parameterized by the HTerm type class.

Synopsis

Documentation

class Ord (VarId t) => HTerm t whereSource

Herbrand terms

Associated Types

type VarId t :: *Source

data VarSupply t :: *Source

Methods

varSupply :: VarSupply tSource

supplyVar :: VarSupply t -> (t, VarSupply t)Source

mkVar :: VarId t -> tSource

isVar :: t -> Maybe (VarId t)Source

children :: t -> ([t], [t] -> t)Source

nonvar_unify :: MonadState (HState t m) m => t -> t -> m BoolSource

Instances

data Herbrand t a Source

Herbrand monad

Constructors

Herbrand 

Fields

unH :: State (HState t (Herbrand t)) a
 

Instances

Monad (Herbrand t) 
Functor (Herbrand t) 
Applicative (Herbrand t) 
HTerm t => Solver (Herbrand t)

Solver instance

HTerm t => Term (Herbrand t) t 
MonadState (HState t (Herbrand t)) (Herbrand t) 

type Heap t m = Map (VarId t) (Binding t m)Source

State

data Binding t m Source

Constructors

VAR (VarId t)

indirection to other variable

NONVAR t

bound to term

ACTION (m Bool)

attributed variable, with given action

data HState t m Source

Constructors

HState 

Fields

var_supply :: VarSupply t
 
heap :: Heap t m
 

Instances

updateState :: (HTerm t, MonadState (HState t m) m) => (HState t m -> HState t m) -> m ()Source

newvarH :: (HTerm t, MonadState (HState t m) m) => m tSource

data Unify t Source

Constructors

t Unify t 

addH :: (HTerm t, MonadState (HState t m) m) => Unify t -> m BoolSource

unify :: (HTerm t, MonadState (HState t m) m) => t -> t -> m BoolSource

unify two arbitrary terms

bindt :: (HTerm t, MonadState (HState t m) m) => VarId t -> t -> m BoolSource

bind a variable to a term

bindv :: (HTerm t, MonadState (HState t m) m) => VarId t -> VarId t -> m BoolSource

alias one variable to another

registerAction :: (HTerm t, MonadState (HState t m) m) => t -> m Bool -> m ()Source

shallow_normalize :: (HTerm t, MonadState (HState t m) m) => t -> m tSource

normalize :: (HTerm t, MonadState (HState t m) m) => t -> m tSource