Copyright | (c) Marcellus Siegburg 2019 - 2025 |
---|---|
License | MIT |
Maintainer | marcellus.siegburg@uni-due.de |
Safe Haskell | None |
Language | Haskell2010 |
Language.Alloy.Call
Description
This module provides basic functionality to interact with Alloy. This library contains Alloy and an (internal) interface to interact with it. These libraries will be placed into the user's directory during execution. A requirement for this library to work is a Java Runtime Environment (as it is required by Alloy).
Synopsis
- alloyVersion :: String
- data CallAlloyConfig = CallAlloyConfig {
- maxInstances :: !(Maybe Integer)
- noOverflow :: !Bool
- satSolver :: !SatSolver
- timeout :: !(Maybe Int)
- data SatSolver
- defaultCallAlloyConfig :: CallAlloyConfig
- existsInstance :: (MonadIO m, MonadThrow m) => String -> m Bool
- getInstances :: (MonadIO m, MonadThrow m) => Maybe Integer -> String -> m [AlloyInstance]
- getInstancesWith :: (MonadIO m, MonadThrow m) => CallAlloyConfig -> String -> m [AlloyInstance]
- object :: MonadThrow m => String -> (Int -> a) -> String -> Int -> m a
- scoped :: String -> String -> Signature
- int :: MonadThrow m => String -> Int -> m Int
- getIdentityAs :: forall m b (a :: Type -> Type). MonadThrow m => String -> (String -> Int -> m b) -> Entry Map a -> m b
- getSingleAs :: (MonadThrow m, Ord a) => String -> (String -> Int -> m a) -> AlloySig -> m (Set a)
- getDoubleAs :: (MonadThrow m, Ord a, Ord b) => String -> (String -> Int -> m a) -> (String -> Int -> m b) -> AlloySig -> m (Set (a, b))
- getTripleAs :: (MonadThrow m, Ord a, Ord b, Ord c) => String -> (String -> Int -> m a) -> (String -> Int -> m b) -> (String -> Int -> m c) -> AlloySig -> m (Set (a, b, c))
- lookupSig :: MonadThrow m => Signature -> AlloyInstance -> m AlloySig
- unscoped :: String -> Signature
- type AlloyInstance = Entries Map
- type AlloySig = Entry Map Set
- type Entries (a :: Type -> Type -> Type) = a Signature (Entry a Set)
- data Object
- data Signature
Documentation
alloyVersion :: String Source #
The currently used Alloy version.
>>>
alloyVersion
"6.2.0"
Since: 0.6
data CallAlloyConfig Source #
Configuration for calling alloy.
Constructors
CallAlloyConfig | you should use |
Fields
|
Available SAT solvers.
Note: solvers marked as not supported by default were supported in earlier versions of Alloy, but got removed. There might be a way of integrating those manually, but this has net been tried.
Constructors
BerkMin | BerkMin
|
Glucose | Glucose
|
Glucose41 | Glucose41
|
Lingeling | Lingeling
|
MiniSat | MiniSat
|
MiniSatProver | MiniSatProver
|
PLingeling | PLingeling
|
SAT4J | SAT4J
|
SAT4JLight | SAT4J Light
|
SAT4JPMax | SAT4Ji PMax
|
Spear | Spear
|
Instances
Bounded SatSolver Source # | |
Enum SatSolver Source # | |
Defined in Language.Alloy.Internal.Call Methods succ :: SatSolver -> SatSolver # pred :: SatSolver -> SatSolver # fromEnum :: SatSolver -> Int # enumFrom :: SatSolver -> [SatSolver] # enumFromThen :: SatSolver -> SatSolver -> [SatSolver] # enumFromTo :: SatSolver -> SatSolver -> [SatSolver] # enumFromThenTo :: SatSolver -> SatSolver -> SatSolver -> [SatSolver] # | |
Read SatSolver Source # | |
Show SatSolver Source # | |
Eq SatSolver Source # | |
defaultCallAlloyConfig :: CallAlloyConfig Source #
Default configuration for calling Alloy. Defaults to:
- retrieve all instances
- do not overflow
SAT4J
Arguments
:: (MonadIO m, MonadThrow m) | |
=> String | The Alloy specification which should be loaded. |
-> m Bool | Whether there exists an instance (within the relevant scope). |
Check if there exists a model for the given specification. This function calls
Alloy retrieving one instance. If there is no such instance, it returns False
.
This function calls getInstances
.
Arguments
:: (MonadIO m, MonadThrow m) | |
=> Maybe Integer | How many instances to return; |
-> String | The Alloy specification which should be loaded. |
-> m [AlloyInstance] |
This function may be used to get all model instances for a given Alloy
specification. It calls Alloy via a Java interface and parses the raw instance
answers before returning the resulting list of AlloyInstance
s.
Arguments
:: (MonadIO m, MonadThrow m) | |
=> CallAlloyConfig | The configuration to be used. |
-> String | The Alloy specification which should be loaded. |
-> m [AlloyInstance] |
This function may be used to get all model instances for a given Alloy
specification. It calls Alloy via a Java interface and parses the raw instance
answers before returning the resulting list of AlloyInstance
s.
Parameters are set using a CallAlloyConfig
.
object :: MonadThrow m => String -> (Int -> a) -> String -> Int -> m a Source #
For retrieval of an unmixed type of values using a get... function
(should be the case for uniformly base named values;
this is usually never true for the universe (lookupSig (unscoped "univ")
))
I.e. setting and checking the String
for the base name of the value to look for,
but failing in case anything different appears (unexpectedly).
int :: MonadThrow m => String -> Int -> m Int Source #
For retrieval of Int
values using a get... function.
e.g. returning all (within Alloy) available Int values could look like this
do n <- lookupSig (unscoped "Int") getSingleAs "" int n
getIdentityAs :: forall m b (a :: Type -> Type). MonadThrow m => String -> (String -> Int -> m b) -> Entry Map a -> m b Source #
getSingleAs :: (MonadThrow m, Ord a) => String -> (String -> Int -> m a) -> AlloySig -> m (Set a) Source #
getDoubleAs :: (MonadThrow m, Ord a, Ord b) => String -> (String -> Int -> m a) -> (String -> Int -> m b) -> AlloySig -> m (Set (a, b)) Source #
getTripleAs :: (MonadThrow m, Ord a, Ord b, Ord c) => String -> (String -> Int -> m a) -> (String -> Int -> m b) -> (String -> Int -> m c) -> AlloySig -> m (Set (a, b, c)) Source #
lookupSig :: MonadThrow m => Signature -> AlloyInstance -> m AlloySig Source #
Lookup a signature within a given Alloy instance.
type AlloyInstance = Entries Map Source #
A complete Alloy instance.
type Entries (a :: Type -> Type -> Type) = a Signature (Entry a Set) Source #
A collection of signatures with associated entries.
A concrete instance of an Alloy signature.
An Alloy signature.
Instances
Show Signature Source # | |
Eq Signature Source # | |
Ord Signature Source # | |