Copyright | (c) Marcellus Siegburg 2019 - 2021 |
---|---|
License | MIT |
Maintainer | marcellus.siegburg@uni-due.de |
Safe Haskell | None |
Language | Haskell2010 |
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
- data CallAlloyConfig
- defaultCallAlloyConfig :: CallAlloyConfig
- existsInstance :: String -> IO Bool
- getInstances :: Maybe Integer -> String -> IO [AlloyInstance]
- getInstancesWith :: CallAlloyConfig -> String -> IO [AlloyInstance]
- getSingle :: (IsString s, MonadError s m) => String -> AlloySig -> m (Set Object)
- getDouble :: (IsString s, MonadError s m) => String -> AlloySig -> m (Set (Object, Object))
- getTriple :: (IsString s, MonadError s m) => String -> AlloySig -> m (Set (Object, Object, Object))
- getSingleAs :: (IsString s, MonadError s m, Ord a) => String -> (String -> Int -> m a) -> AlloySig -> m (Set a)
- getDoubleAs :: (IsString s, MonadError s m, Ord a, Ord b) => String -> (String -> Int -> m a) -> (String -> Int -> m b) -> AlloySig -> m (Set (a, b))
- getTripleAs :: (IsString s, MonadError s 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))
- int :: (IsString s, MonadError s m, Semigroup s) => String -> Int -> m Int
- object :: (IsString s, MonadError s m, Semigroup s) => String -> (Int -> a) -> String -> Int -> m a
- lookupSig :: (IsString s, MonadError s m) => Signature -> AlloyInstance -> m AlloySig
- objectName :: Object -> String
- relToMap :: (IsString s, MonadError s m, Ord k, Ord v) => (a -> (k, v)) -> Set a -> m (Map k (Set v))
- scoped :: String -> String -> Signature
- unscoped :: String -> Signature
- data Object
- data Signature
- type Entries a = a Signature (Entry a Set)
- type AlloySig = Entry Map Set
- type AlloyInstance = Entries Map
Documentation
data CallAlloyConfig Source #
Configuration for calling alloy. These are:
- maximal number of instances to retrieve (
Nothing
for all) - whether to not overflow when calculating numbers within Alloy
- an timeout after which to forcibly kill Alloy (retrieving only instances that were returned before killing the process)
defaultCallAlloyConfig :: CallAlloyConfig Source #
Default configuration for calling Alloy. Defaults to:
- retrieve all instances
- do not overflow
:: String | The Alloy specification which should be loaded. |
-> IO 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
.
:: Maybe Integer | How many instances to return; |
-> String | The Alloy specification which should be loaded. |
-> IO [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.
:: CallAlloyConfig | The configuration to be used. |
-> String | The Alloy specification which should be loaded. |
-> IO [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
.
getSingle :: (IsString s, MonadError s m) => String -> AlloySig -> m (Set Object) Source #
Deprecated: use the typed version getSingleAs instead
Retrieve a set of objects of a given AlloySig
.
Successful if the signature's relation is a set (or empty).
getDouble :: (IsString s, MonadError s m) => String -> AlloySig -> m (Set (Object, Object)) Source #
Deprecated: use the typed version getDoubleAs instead
Retrieve a binary relation of objects of a given AlloySig
.
Successful if the signature's relation is binary (or empty).
getTriple :: (IsString s, MonadError s m) => String -> AlloySig -> m (Set (Object, Object, Object)) Source #
Deprecated: use the typed version getTripleAs instead
Retrieve a ternary relation of objects of a given AlloySig
.
Successful if the signature's relation is ternary (or empty).
getSingleAs :: (IsString s, MonadError s m, Ord a) => String -> (String -> Int -> m a) -> AlloySig -> m (Set a) Source #
getDoubleAs :: (IsString s, MonadError s m, Ord a, Ord b) => String -> (String -> Int -> m a) -> (String -> Int -> m b) -> AlloySig -> m (Set (a, b)) Source #
getTripleAs :: (IsString s, MonadError s 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 #
int :: (IsString s, MonadError s m, Semigroup s) => 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
object :: (IsString s, MonadError s m, Semigroup s) => 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).
lookupSig :: (IsString s, MonadError s m) => Signature -> AlloyInstance -> m AlloySig Source #
Lookup a signature within a given Alloy instance.
objectName :: Object -> String Source #
Deprecated: use the typed versions of get... e.g. getSingleAs instead of getSingle
Retrieve an object's name.
relToMap :: (IsString s, MonadError s m, Ord k, Ord v) => (a -> (k, v)) -> Set a -> m (Map k (Set v)) Source #
Deprecated: use binaryToMap instead
A concrete instance of an Alloy signature.
An Alloy signature.
type Entries a = a Signature (Entry a Set) Source #
A collection of signatures with associated entries.
type AlloyInstance = Entries Map Source #
A complete Alloy instance.