call-alloy-0.3.0.3: A simple library to call Alloy given a specification
Copyright(c) Marcellus Siegburg 2019 - 2021
LicenseMIT
Maintainermarcellus.siegburg@uni-due.de
Safe HaskellNone
LanguageHaskell2010

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

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

existsInstance Source #

Arguments

:: 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.

getInstances Source #

Arguments

:: Maybe Integer

How many instances to return; Nothing for all.

-> 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 AlloyInstances.

getInstancesWith Source #

Arguments

:: 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 AlloyInstances. Parameters are set using a CallAlloyConfig.

getIdentityAs :: (MonadError s m, IsString s) => String -> (String -> Int -> m b) -> Entry Map a -> m b Source #

Retrieve a single value of a given AlloySig. The Value will be created by applying the given mapping function from object name and Int to value. The mapping has to be injective (for all expected cases). Successful if the signature's relation is a single value.

getSingleAs :: (IsString s, MonadError s m, Ord a) => String -> (String -> Int -> m a) -> AlloySig -> m (Set a) Source #

Retrieve a set of values of a given AlloySig. Values will be created by applying the given mapping function from object Name and Int to value. The mapping has to be injective (for all expected cases). Successful if the signature's relation is a set (or empty).

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 #

Retrieve a binary relation of values of given AlloySig. Values will be created by applying the given mapping functions from object Name and Int to the value. The mapping has to be injective (for all expected cases). Successful if the signature's relation is binary (or empty).

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 #

Retrieve a ternary relation of values of a given AlloySig. Values will be created by applying the given mapping functions from object Name and Int to the value. The mapping has to be injective (for all expected cases). Successful if the signature's relation is ternary (or empty).

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.

scoped :: String -> String -> Signature Source #

Create a Signature given its scope and name.

unscoped :: String -> Signature Source #

Create an unscoped Signature given its name.

data Object Source #

A concrete instance of an Alloy signature.

Instances

Instances details
Eq Object Source # 
Instance details

Defined in Language.Alloy.Types

Methods

(==) :: Object -> Object -> Bool #

(/=) :: Object -> Object -> Bool #

Ord Object Source # 
Instance details

Defined in Language.Alloy.Types

Show Object Source # 
Instance details

Defined in Language.Alloy.Types

data Signature Source #

An Alloy signature.

Instances

Instances details
Eq Signature Source # 
Instance details

Defined in Language.Alloy.Types

Ord Signature Source # 
Instance details

Defined in Language.Alloy.Types

Show Signature Source # 
Instance details

Defined in Language.Alloy.Types

type Entries a = a Signature (Entry a Set) Source #

A collection of signatures with associated entries.

type AlloySig = Entry Map Set Source #

A signature with all its objects and relations.

type AlloyInstance = Entries Map Source #

A complete Alloy instance.