{-# LANGUAGE OverloadedStrings #-}
module Language.Alloy.Functions (
getIdentityAs, getSingleAs, getDoubleAs, getTripleAs,
int, object,
lookupSig,
scoped, unscoped,
) where
import qualified Data.Set as S (fromList, toList)
import qualified Data.Map as M (lookup, keys)
import Control.Monad.Except (MonadError, throwError)
import Data.List (intercalate)
import Data.Map (Map)
import Data.Set (Set)
import Data.String (IsString, fromString)
import Language.Alloy.Types (
AlloyInstance,
AlloySig,
Entry (..),
Object (..),
Relation (..),
Signature (..),
showSignature,
)
scoped :: String -> String -> Signature
scoped :: String -> String -> Signature
scoped = Maybe String -> String -> Signature
Signature (Maybe String -> String -> Signature)
-> (String -> Maybe String) -> String -> String -> Signature
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe String
forall a. a -> Maybe a
Just
unscoped :: String -> Signature
unscoped :: String -> Signature
unscoped = Maybe String -> String -> Signature
Signature Maybe String
forall a. Maybe a
Nothing
traverseSet
:: (Ord a, Applicative f)
=> (a2 -> f a)
-> Set a2
-> f (Set a)
traverseSet :: forall a (f :: * -> *) a2.
(Ord a, Applicative f) =>
(a2 -> f a) -> Set a2 -> f (Set a)
traverseSet a2 -> f a
f = ([a] -> Set a) -> f [a] -> f (Set a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [a] -> Set a
forall a. Ord a => [a] -> Set a
S.fromList (f [a] -> f (Set a)) -> (Set a2 -> f [a]) -> Set a2 -> f (Set a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a2 -> f a) -> [a2] -> f [a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse a2 -> f a
f ([a2] -> f [a]) -> (Set a2 -> [a2]) -> Set a2 -> f [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set a2 -> [a2]
forall a. Set a -> [a]
S.toList
int
:: (IsString s, MonadError s m, Semigroup s)
=> String
-> Int
-> m Int
int :: forall s (m :: * -> *).
(IsString s, MonadError s m, Semigroup s) =>
String -> Int -> m Int
int = String -> (Int -> Int) -> String -> Int -> m Int
forall s (m :: * -> *) a.
(IsString s, MonadError s m, Semigroup s) =>
String -> (Int -> a) -> String -> Int -> m a
object String
"" Int -> Int
forall a. a -> a
id
object
:: (IsString s, MonadError s m, Semigroup s)
=> String
-> (Int -> a)
-> String
-> Int
-> m a
object :: forall s (m :: * -> *) a.
(IsString s, MonadError s m, Semigroup s) =>
String -> (Int -> a) -> String -> Int -> m a
object String
s Int -> a
f String
s' Int
g =
if String
s String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
s
then s -> m a
forall a. s -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (s -> m a) -> s -> m a
forall a b. (a -> b) -> a -> b
$ s
"expected an object of name " s -> s -> s
forall a. Semigroup a => a -> a -> a
<> String -> s
forall a. IsString a => String -> a
fromString String
s
s -> s -> s
forall a. Semigroup a => a -> a -> a
<> s
" but got an object of name "
s -> s -> s
forall a. Semigroup a => a -> a -> a
<> String -> s
forall a. IsString a => String -> a
fromString String
s' s -> s -> s
forall a. Semigroup a => a -> a -> a
<> s
"."
else a -> m a
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> m a) -> a -> m a
forall a b. (a -> b) -> a -> b
$ Int -> a
f Int
g
specifyObject
:: (String -> Int -> m a)
-> Object
-> m a
specifyObject :: forall (m :: * -> *) a. (String -> Int -> m a) -> Object -> m a
specifyObject String -> Int -> m a
f Object
o = case Object
o of
NumberObject Int
i -> String -> Int -> m a
f String
"" Int
i
Object String
n Int
i -> String -> Int -> m a
f String
n Int
i
NamedObject String
g -> String -> m a
forall a. HasCallStack => String -> a
error (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ String
"there is no way of converting Object "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
g
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\nPlease open an issue at https://github.com/marcellussiegburg/call-alloy stating what you tried to attempt"
getIdentityAs
:: (MonadError s m, IsString s)
=> String
-> (String -> Int -> m b)
-> Entry Map a
-> m b
getIdentityAs :: forall s (m :: * -> *) b (a :: * -> *).
(MonadError s m, IsString s) =>
String -> (String -> Int -> m b) -> Entry Map a -> m b
getIdentityAs String
s String -> Int -> m b
f Entry Map a
inst = do
Object
e <- (Relation a -> m Object) -> String -> Entry Map a -> m Object
forall s (m :: * -> *) (a :: * -> *) b.
(IsString s, MonadError s m) =>
(Relation a -> m b) -> String -> Entry Map a -> m b
lookupRel Relation a -> m Object
forall s (m :: * -> *) (a :: * -> *).
(IsString s, MonadError s m) =>
Relation a -> m Object
identity String
s Entry Map a
inst
(String -> Int -> m b) -> Object -> m b
forall (m :: * -> *) a. (String -> Int -> m a) -> Object -> m a
specifyObject String -> Int -> m b
f Object
e
getSingleAs
:: (IsString s, MonadError s m, Ord a)
=> String
-> (String -> Int -> m a)
-> AlloySig
-> m (Set a)
getSingleAs :: forall s (m :: * -> *) a.
(IsString s, MonadError s m, Ord a) =>
String -> (String -> Int -> m a) -> AlloySig -> m (Set a)
getSingleAs String
s String -> Int -> m a
f AlloySig
inst = do
Set Object
set <- (Relation Set -> m (Set Object))
-> String -> AlloySig -> m (Set Object)
forall s (m :: * -> *) (a :: * -> *) b.
(IsString s, MonadError s m) =>
(Relation a -> m b) -> String -> Entry Map a -> m b
lookupRel Relation Set -> m (Set Object)
forall s (m :: * -> *) (a :: * -> *).
(IsString s, MonadError s m, Monoid (a Object)) =>
Relation a -> m (a Object)
single String
s AlloySig
inst
(Object -> m a) -> Set Object -> m (Set a)
forall a (f :: * -> *) a2.
(Ord a, Applicative f) =>
(a2 -> f a) -> Set a2 -> f (Set a)
traverseSet ((String -> Int -> m a) -> Object -> m a
forall (m :: * -> *) a. (String -> Int -> m a) -> Object -> m a
specifyObject String -> Int -> m a
f) Set Object
set
getDoubleAs
:: (IsString s, MonadError s m, Ord a, Ord b)
=> String
-> (String -> Int -> m a)
-> (String -> Int -> m b)
-> AlloySig
-> m (Set (a, b))
getDoubleAs :: forall s (m :: * -> *) a b.
(IsString s, MonadError s m, Ord a, Ord b) =>
String
-> (String -> Int -> m a)
-> (String -> Int -> m b)
-> AlloySig
-> m (Set (a, b))
getDoubleAs String
s String -> Int -> m a
f String -> Int -> m b
g AlloySig
inst = do
Set (Object, Object)
set <- (Relation Set -> m (Set (Object, Object)))
-> String -> AlloySig -> m (Set (Object, Object))
forall s (m :: * -> *) (a :: * -> *) b.
(IsString s, MonadError s m) =>
(Relation a -> m b) -> String -> Entry Map a -> m b
lookupRel Relation Set -> m (Set (Object, Object))
forall s (m :: * -> *) (a :: * -> *).
(IsString s, MonadError s m, Monoid (a (Object, Object))) =>
Relation a -> m (a (Object, Object))
double String
s AlloySig
inst
((Object, Object) -> m (a, b))
-> Set (Object, Object) -> m (Set (a, b))
forall a (f :: * -> *) a2.
(Ord a, Applicative f) =>
(a2 -> f a) -> Set a2 -> f (Set a)
traverseSet (Object, Object) -> m (a, b)
applyMapping Set (Object, Object)
set
where
applyMapping :: (Object, Object) -> m (a, b)
applyMapping (Object
x, Object
y) = (,)
(a -> b -> (a, b)) -> m a -> m (b -> (a, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Int -> m a) -> Object -> m a
forall (m :: * -> *) a. (String -> Int -> m a) -> Object -> m a
specifyObject String -> Int -> m a
f Object
x
m (b -> (a, b)) -> m b -> m (a, b)
forall a b. m (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (String -> Int -> m b) -> Object -> m b
forall (m :: * -> *) a. (String -> Int -> m a) -> Object -> m a
specifyObject String -> Int -> m b
g Object
y
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))
getTripleAs :: forall s (m :: * -> *) a b c.
(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))
getTripleAs String
s String -> Int -> m a
f String -> Int -> m b
g String -> Int -> m c
h AlloySig
inst = do
Set (Object, Object, Object)
set <- (Relation Set -> m (Set (Object, Object, Object)))
-> String -> AlloySig -> m (Set (Object, Object, Object))
forall s (m :: * -> *) (a :: * -> *) b.
(IsString s, MonadError s m) =>
(Relation a -> m b) -> String -> Entry Map a -> m b
lookupRel Relation Set -> m (Set (Object, Object, Object))
forall s (m :: * -> *) (a :: * -> *).
(IsString s, MonadError s m,
Monoid (a (Object, Object, Object))) =>
Relation a -> m (a (Object, Object, Object))
triple String
s AlloySig
inst
((Object, Object, Object) -> m (a, b, c))
-> Set (Object, Object, Object) -> m (Set (a, b, c))
forall a (f :: * -> *) a2.
(Ord a, Applicative f) =>
(a2 -> f a) -> Set a2 -> f (Set a)
traverseSet (Object, Object, Object) -> m (a, b, c)
applyMapping Set (Object, Object, Object)
set
where
applyMapping :: (Object, Object, Object) -> m (a, b, c)
applyMapping (Object
x, Object
y, Object
z) = (,,)
(a -> b -> c -> (a, b, c)) -> m a -> m (b -> c -> (a, b, c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Int -> m a) -> Object -> m a
forall (m :: * -> *) a. (String -> Int -> m a) -> Object -> m a
specifyObject String -> Int -> m a
f Object
x
m (b -> c -> (a, b, c)) -> m b -> m (c -> (a, b, c))
forall a b. m (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (String -> Int -> m b) -> Object -> m b
forall (m :: * -> *) a. (String -> Int -> m a) -> Object -> m a
specifyObject String -> Int -> m b
g Object
y
m (c -> (a, b, c)) -> m c -> m (a, b, c)
forall a b. m (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (String -> Int -> m c) -> Object -> m c
forall (m :: * -> *) a. (String -> Int -> m a) -> Object -> m a
specifyObject String -> Int -> m c
h Object
z
lookupRel
:: (IsString s, MonadError s m)
=> (Relation a -> m b)
-> String
-> Entry Map a
-> m b
lookupRel :: forall s (m :: * -> *) (a :: * -> *) b.
(IsString s, MonadError s m) =>
(Relation a -> m b) -> String -> Entry Map a -> m b
lookupRel Relation a -> m b
kind String
rel Entry Map a
e = case String -> Map String (Relation a) -> Maybe (Relation a)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup String
rel (Entry Map a -> Map String (Relation a)
forall (a :: * -> * -> *) (b :: * -> *).
Entry a b -> a String (Relation b)
relation Entry Map a
e) of
Maybe (Relation a)
Nothing -> s -> m b
forall a. s -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (s -> m b) -> s -> m b
forall a b. (a -> b) -> a -> b
$ String -> s
forall a. IsString a => String -> a
fromString (String -> s) -> String -> s
forall a b. (a -> b) -> a -> b
$ String
"relation " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. IsString a => String -> a
fromString String
rel
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is missing in the Alloy instance"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"; available are: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " (Map String (Relation a) -> [String]
forall k a. Map k a -> [k]
M.keys (Map String (Relation a) -> [String])
-> Map String (Relation a) -> [String]
forall a b. (a -> b) -> a -> b
$ Entry Map a -> Map String (Relation a)
forall (a :: * -> * -> *) (b :: * -> *).
Entry a b -> a String (Relation b)
relation Entry Map a
e)
Just Relation a
r -> Relation a -> m b
kind Relation a
r
lookupSig
:: (IsString s, MonadError s m)
=> Signature
-> AlloyInstance
-> m AlloySig
lookupSig :: forall s (m :: * -> *).
(IsString s, MonadError s m) =>
Signature -> AlloyInstance -> m AlloySig
lookupSig Signature
s AlloyInstance
insta = case Signature -> AlloyInstance -> Maybe AlloySig
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Signature
s AlloyInstance
insta of
Maybe AlloySig
Nothing -> s -> m AlloySig
forall a. s -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (s -> m AlloySig) -> s -> m AlloySig
forall a b. (a -> b) -> a -> b
$ String -> s
forall a. IsString a => String -> a
fromString (String -> s) -> String -> s
forall a b. (a -> b) -> a -> b
$ Signature -> String
showSignature Signature
s
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is missing in the Alloy instance"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"; available are: \"" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\", " (Signature -> String
showSignature (Signature -> String) -> [Signature] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AlloyInstance -> [Signature]
forall k a. Map k a -> [k]
M.keys AlloyInstance
insta)
Just AlloySig
e -> AlloySig -> m AlloySig
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return AlloySig
e
identity
:: (IsString s, MonadError s m)
=> Relation a
-> m Object
identity :: forall s (m :: * -> *) (a :: * -> *).
(IsString s, MonadError s m) =>
Relation a -> m Object
identity (Id Object
r) = Object -> m Object
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Object
r
identity Relation a
_ = s -> m Object
forall a. s -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError s
"Relation is (unexpectedly) not exactly a single element"
single
:: (IsString s, MonadError s m, Monoid (a Object))
=> Relation a
-> m (a Object)
single :: forall s (m :: * -> *) (a :: * -> *).
(IsString s, MonadError s m, Monoid (a Object)) =>
Relation a -> m (a Object)
single Relation a
EmptyRelation = a Object -> m (a Object)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a Object
forall a. Monoid a => a
mempty
single (Single a Object
r) = a Object -> m (a Object)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a Object
r
single Relation a
_ = s -> m (a Object)
forall a. s -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError s
"Relation is (unexpectedly) a mapping"
double
:: (IsString s, MonadError s m, Monoid (a (Object, Object)))
=> Relation a
-> m (a (Object, Object))
double :: forall s (m :: * -> *) (a :: * -> *).
(IsString s, MonadError s m, Monoid (a (Object, Object))) =>
Relation a -> m (a (Object, Object))
double Relation a
EmptyRelation = a (Object, Object) -> m (a (Object, Object))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a (Object, Object)
forall a. Monoid a => a
mempty
double (Double a (Object, Object)
r) = a (Object, Object) -> m (a (Object, Object))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a (Object, Object)
r
double Relation a
_ = s -> m (a (Object, Object))
forall a. s -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError s
"Relation is not a binary mapping"
triple
:: (IsString s, MonadError s m, Monoid (a (Object, Object, Object)))
=> Relation a
-> m (a (Object, Object, Object))
triple :: forall s (m :: * -> *) (a :: * -> *).
(IsString s, MonadError s m,
Monoid (a (Object, Object, Object))) =>
Relation a -> m (a (Object, Object, Object))
triple Relation a
EmptyRelation = a (Object, Object, Object) -> m (a (Object, Object, Object))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a (Object, Object, Object)
forall a. Monoid a => a
mempty
triple (Triple a (Object, Object, Object)
r) = a (Object, Object, Object) -> m (a (Object, Object, Object))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a (Object, Object, Object)
r
triple Relation a
_ = s -> m (a (Object, Object, Object))
forall a. s -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError s
"Relation is not a ternary mapping"