claferIG-0.3.7: claferIG is an interactive tool that generates instances of Clafer models.

Safe HaskellNone

Language.Clafer.IG.AlloyIGInterface

Synopsis

Documentation

newtype AlloyIGT m a Source

An interface to the Alloy Analyzer

Constructors

AlloyIGT (StateT (Maybe AlloyIGEnv) (ReaderT Process m) a) 

Instances

MonadTrans AlloyIGT 
Monad m => Monad (AlloyIGT m) 
Functor m => Functor (AlloyIGT m) 
(Monad m, Functor m) => Applicative (AlloyIGT m) 
MonadIO m => MonadIO (AlloyIGT m) 
MonadException m => MonadException (AlloyIGT m) 

fetches :: Monad m => (AlloyIGEnv -> a) -> AlloyIGT m aSource

set :: Monad m => AlloyIGEnv -> AlloyIGT m ()Source

proc :: Monad m => AlloyIGT m ProcessSource

data AlloyIGEnv Source

Instance generator's environment

Constructors

AlloyIGEnv 

Fields

alloyModel :: String
 
sigMap :: Map String Sig
 
scopes :: Map String Integer
 
globalScope :: Integer
 

data Sig Source

Constructors

Sig 

Fields

s_name :: String
 
s_multiplicity :: Multiplicity
 
s_subset :: Maybe String
 
s_startingScope :: Maybe Integer
 

data Multiplicity Source

Constructors

One 
Lone 
Some 
Any 

Instances

data UnsatCore Source

Constructors

UnsatCore 

Fields

core :: [Span]
 

Instances

Show UnsatCore 

withinRange :: Integer -> Multiplicity -> BoolSource

getSigs :: MonadIO m => AlloyIGT m [String]Source

load :: Process -> String -> IO AlloyIGEnvSource

Call load before any other commands.

sendLoadCommand :: MonadIO m => String -> AlloyIGT m ()Source

sendNextCommand :: MonadIO m => AlloyIGT m (Maybe String)Source

Get the next solution from alloyIG

getScope :: MonadIO m => String -> AlloyIGT m IntegerSource

getScopes :: MonadIO m => AlloyIGT m [(String, Integer)]Source

sendSetScopeCommand :: MonadIO m => String -> Integer -> AlloyIGT m (Maybe String)Source

Tell alloyIG to change the scope of a sig

sendSetGlobalScopeCommand :: MonadIO m => Integer -> AlloyIGT m ()Source

Tell alloyIG to change the global scope

sendResolveCommand :: MonadIO m => AlloyIGT m ()Source

Tell alloyIG to recalculate the solution

sendSaveStateCommand :: MonadIO m => AlloyIGT m ()Source

Tell alloyIG to save the current state

sendRestoreStateCommand :: MonadIO m => AlloyIGT m ()Source

Tell alloyIG to restore the state

sendRemoveConstraintCommand :: MonadIO m => Span -> AlloyIGT m ()Source

Tell alloyIG to remove the constraint

sendUnsatCoreCommand :: MonadIO m => AlloyIGT m UnsatCoreSource

Tell alloyIG to return the unsat core of the previous operation

sendSetUnsatCoreMinimizationCommand :: MonadIO m => Integer -> AlloyIGT m ()Source

Tell alloyIG to change the unsat core minimization level. 0 -> Fastest, 1 -> Medium, 2 -> Best

sendSetBitwidthCommand :: MonadIO m => Integer -> AlloyIGT m ()Source

Tell alloyIG to change the bitwidth

sendQuitCommand :: MonadIO m => AlloyIGT m ()Source

Tell alloyIG to quit

getMsg :: MonadIO m => AlloyIGT m StringSource

readMsg :: (MonadIO m, Read r) => AlloyIGT m rSource

putMsg :: MonadIO m => String -> AlloyIGT m ()Source