clafer-0.3.5: clafer compiles Clafer models to other formats, such as Alloy, XML, HTML, Dot.

Safe HaskellSafe-Inferred

Language.Clafer.Intermediate.Intclafer

Description

Intermediate representation (IR) of a Clafer model

Synopsis

Documentation

type UID = StringSource

unique identifier of a clafer

type CName = StringSource

clafer name as declared in the source model

data IType Source

Constructors

TBoolean 
TString 
TInteger 
TReal 
TClafer [String] 

Instances

Eq IType 
Ord IType 
Show IType 

data IModule Source

each file contains exactly one mode. A module is a list of declarations

Constructors

IModule 

Fields

mName :: String

always empty for now because we don't have syntax for declaring modules

mDecls :: [IElement]

List of top-level elements

Instances

Eq IModule 
Ord IModule 
Show IModule 

data IClafer Source

Clafer has a list of fields that specify its properties. Some fields, marked as (o) are for generating optimized code

Constructors

IClafer 

Fields

cinPos :: Span

the position of the syntax in source code

isAbstract :: Bool

whether abstract or not (i.e., concrete)

gcard :: Maybe IGCard

group cardinality

ident :: CName

name declared in the model

uid :: UID

a unique identifier

super :: ISuper

superclafers

card :: Maybe Interval

clafer cardinality

glCard :: Interval

(o) global cardinality

elements :: [IElement]

nested elements

Instances

Eq IClafer 
Ord IClafer 
Show IClafer 

data IElement Source

Clafer's subelement is either a clafer, a constraint, or a goal (objective) This is a wrapper type needed to have polymorphic lists of elements

Constructors

IEClafer IClafer 
IEConstraint 

Fields

isHard :: Bool

whether hard or not (soft)

cpexp :: PExp

the container of the actual expression

IEGoal

Goal (optimization objective)

Fields

isMaximize :: Bool
 
cpexp :: PExp

the container of the actual expression

Instances

Eq IElement 
Ord IElement 
Show IElement 

data ISuper Source

A list of superclafers. -> overlaping unique (set) ->> overlapping non-unique (bag) : non overlapping (disjoint)

Constructors

ISuper 

Fields

isOverlapping :: Bool
 
supers :: [PExp]
 

Instances

Eq ISuper 
Ord ISuper 
Show ISuper 

data IGCard Source

Group cardinality is specified as an interval. It may also be given by a keyword. xor 1..1 isKeyword = True 1..1 1..1 isKeyword = False

Constructors

IGCard 

Fields

isKeyword :: Bool
 
interval :: Interval
 

Instances

Eq IGCard 
Ord IGCard 
Show IGCard 

type Interval = (Integer, Integer)Source

(Min, Max) integer interval. -1 denotes *

data PExp Source

This is expression container (parent). It has meta information about an actual expression exp

Constructors

PExp 

Fields

iType :: Maybe IType

the inferred type

pid :: String

non-empty unique id for expressions with span, "" for noSpan

inPos :: Span

position in the input Clafer file

exp :: IExp

the actual expression

Instances

Eq PExp 
Ord PExp 
Show PExp 

data IExp Source

Constructors

IDeclPExp

quantified expression with declarations e.g., [ all x1; x2 : X | x1.ref != x2.ref ]

Fields

quant :: IQuant
 
oDecls :: [IDecl]
 
bpexp :: PExp
 
IFunExp

expression with a unary function, e.g., -1 binary function, e.g., 2 + 3 ternary function, e.g., if x then 4 else 5

Fields

op :: String
 
exps :: [PExp]
 
IInt Integer

integer number

IDouble Double

real number

IStr String

string

IClaferId

a reference to a clafer name

Fields

modName :: String

module name - currently not used and empty since we have no module system

sident :: CName

name of the clafer being referred to

isTop :: Bool

identifier refers to a top-level definition

Instances

Eq IExp 
Ord IExp 
Show IExp 

data IDecl Source

For IFunExp standard set of operators includes: 1. Unary operators: ! - not (logical) # - set counting operator - - negation (arithmetic) max - maximum (created for goals) min - minimum (created for goals) 2. Binary operators: <=> - equivalence => - implication || - disjunction xor - exclusive or && - conjunction < - less than > - greater than = - equality <= - less than or equal >= - greater than or equal != - inequality in - belonging to a set/being a subset nin - not belonging to a set/not being a subset + - addition/string concatenation - - substraction * - multiplication / - division ++ - set union -- - set difference & - set intersection <: - domain restriction :> - range restriction . - relational join 3. Ternary operators ifthenelse -- if then else

Local declaration disj x1; x2 : X ++ Y y1 : Y

Constructors

IDecl 

Fields

isDisj :: Bool

is disjunct

decls :: [CName]

a list of local names

body :: PExp

set to which local names refer to

Instances

Eq IDecl 
Ord IDecl 
Show IDecl 

data IQuant Source

quantifier

Constructors

INo

does not exist

ILone

less than one

IOne

exactly one

ISome

at least one (i.e., exists)

IAll

for all

Instances

Eq IQuant 
Ord IQuant 
Show IQuant 

type LineNo = IntegerSource

type ColNo = IntegerSource

mapIR :: (Ir -> Ir) -> IModule -> IModuleSource

map over IR

foldMapIR :: Monoid m => (Ir -> m) -> IModule -> mSource

foldMap over IR

foldIR :: (Ir -> a -> a) -> a -> IModule -> aSource

fold the IR

iMap :: (Ir -> Ir) -> Ir -> IrSource

iFoldMap :: Monoid m => (Ir -> m) -> Ir -> mSource

iFold :: (Ir -> a -> a) -> a -> Ir -> aSource