{-|
Module      : Language.Alloy.Types
Description : Type definitions for Call Alloy library
Copyright   : (c) Marcellus Siegburg, 2019
License     : MIT
Maintainer  : marcellus.siegburg@uni-due.de

This module defines required types for the Alloy instance parser.
Unless reexported, these types are considered as internal.
-}
module Language.Alloy.Types (
  AlloyInstance, AlloySig, Annotation (..),
  Entries, Entry (..), Object (..), Relation (..), Signature (..),
  ) where

import Data.Map                         (Map)
import Data.Set                         (Set)

{-|
A complete Alloy instance.
-}
type AlloyInstance = Entries Map

{-|
A signature with all its objects and relations.
-}
type AlloySig      = Entry Map Set

{-|
A collection of Signatures with associated entries.
-}
type Entries a = a Signature (Entry a Set)

{-|
An Alloy signature.
-}
data Signature = Signature {
    Signature -> Maybe String
scope    :: Maybe String,
    Signature -> String
sigName  :: String
  } deriving (Signature -> Signature -> Bool
(Signature -> Signature -> Bool)
-> (Signature -> Signature -> Bool) -> Eq Signature
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Signature -> Signature -> Bool
$c/= :: Signature -> Signature -> Bool
== :: Signature -> Signature -> Bool
$c== :: Signature -> Signature -> Bool
Eq, Eq Signature
Eq Signature =>
(Signature -> Signature -> Ordering)
-> (Signature -> Signature -> Bool)
-> (Signature -> Signature -> Bool)
-> (Signature -> Signature -> Bool)
-> (Signature -> Signature -> Bool)
-> (Signature -> Signature -> Signature)
-> (Signature -> Signature -> Signature)
-> Ord Signature
Signature -> Signature -> Bool
Signature -> Signature -> Ordering
Signature -> Signature -> Signature
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Signature -> Signature -> Signature
$cmin :: Signature -> Signature -> Signature
max :: Signature -> Signature -> Signature
$cmax :: Signature -> Signature -> Signature
>= :: Signature -> Signature -> Bool
$c>= :: Signature -> Signature -> Bool
> :: Signature -> Signature -> Bool
$c> :: Signature -> Signature -> Bool
<= :: Signature -> Signature -> Bool
$c<= :: Signature -> Signature -> Bool
< :: Signature -> Signature -> Bool
$c< :: Signature -> Signature -> Bool
compare :: Signature -> Signature -> Ordering
$ccompare :: Signature -> Signature -> Ordering
$cp1Ord :: Eq Signature
Ord, Int -> Signature -> ShowS
[Signature] -> ShowS
Signature -> String
(Int -> Signature -> ShowS)
-> (Signature -> String)
-> ([Signature] -> ShowS)
-> Show Signature
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Signature] -> ShowS
$cshowList :: [Signature] -> ShowS
show :: Signature -> String
$cshow :: Signature -> String
showsPrec :: Int -> Signature -> ShowS
$cshowsPrec :: Int -> Signature -> ShowS
Show)

{-|
A concrete instance of an Alloy signature.
-}
data Object =
    Object {
      Object -> String
objSig     :: String,
      Object -> Int
identifier :: Int
    }
  | NumberObject {
      Object -> Int
number :: Int
    }
  | NamedObject {
      Object -> String
objName :: String
    } deriving (Object -> Object -> Bool
(Object -> Object -> Bool)
-> (Object -> Object -> Bool) -> Eq Object
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Object -> Object -> Bool
$c/= :: Object -> Object -> Bool
== :: Object -> Object -> Bool
$c== :: Object -> Object -> Bool
Eq, Eq Object
Eq Object =>
(Object -> Object -> Ordering)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Object)
-> (Object -> Object -> Object)
-> Ord Object
Object -> Object -> Bool
Object -> Object -> Ordering
Object -> Object -> Object
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Object -> Object -> Object
$cmin :: Object -> Object -> Object
max :: Object -> Object -> Object
$cmax :: Object -> Object -> Object
>= :: Object -> Object -> Bool
$c>= :: Object -> Object -> Bool
> :: Object -> Object -> Bool
$c> :: Object -> Object -> Bool
<= :: Object -> Object -> Bool
$c<= :: Object -> Object -> Bool
< :: Object -> Object -> Bool
$c< :: Object -> Object -> Bool
compare :: Object -> Object -> Ordering
$ccompare :: Object -> Object -> Ordering
$cp1Ord :: Eq Object
Ord, Int -> Object -> ShowS
[Object] -> ShowS
Object -> String
(Int -> Object -> ShowS)
-> (Object -> String) -> ([Object] -> ShowS) -> Show Object
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Object] -> ShowS
$cshowList :: [Object] -> ShowS
show :: Object -> String
$cshow :: Object -> String
showsPrec :: Int -> Object -> ShowS
$cshowsPrec :: Int -> Object -> ShowS
Show)

{-|
An Alloy relation, i.e. a collection of a tuple of 'Object's.
The collection may be a singleton, a set, a list, ...
-}
data Relation a =
    EmptyRelation
  | Single (a Object)
  | Double (a (Object, Object))
  | Triple (a (Object, Object, Object))

{-|
Specifically marked values.
-}
data Annotation = Skolem deriving (Annotation -> Annotation -> Bool
(Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool) -> Eq Annotation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Annotation -> Annotation -> Bool
$c/= :: Annotation -> Annotation -> Bool
== :: Annotation -> Annotation -> Bool
$c== :: Annotation -> Annotation -> Bool
Eq, Int -> Annotation -> ShowS
[Annotation] -> ShowS
Annotation -> String
(Int -> Annotation -> ShowS)
-> (Annotation -> String)
-> ([Annotation] -> ShowS)
-> Show Annotation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Annotation] -> ShowS
$cshowList :: [Annotation] -> ShowS
show :: Annotation -> String
$cshow :: Annotation -> String
showsPrec :: Int -> Annotation -> ShowS
$cshowsPrec :: Int -> Annotation -> ShowS
Show)

{-|
An entry is a collection of a 'Relation'.
This collection may be a singleton, a set, a list, ...
-}
data Entry a b = Entry {
    Entry a b -> Maybe Annotation
annotation :: Maybe Annotation,
    Entry a b -> a String (Relation b)
relation   :: a String (Relation b)
  }