Safe Haskell | None |
---|---|
Language | Haskell2010 |
Intermediate representation (IR) of a Clafer model
- type UID = String
- type CName = String
- type URL = String
- data Ir
- data IType
- data IModule = IModule {}
- data IClafer = IClafer {}
- data IElement
- data IReference = IReference {}
- data IGCard = IGCard {
- _isKeyword :: Bool
- _interval :: Interval
- type Interval = (Integer, Integer)
- data PExp = PExp {}
- type ClaferBinding = Maybe UID
- data IExp
- data IDecl = IDecl {}
- data IQuant
- type LineNo = Integer
- type ColNo = Integer
- mapIR :: (Ir -> Ir) -> IModule -> IModule
- foldMapIR :: Monoid m => (Ir -> m) -> IModule -> m
- foldIR :: (Ir -> a -> a) -> a -> IModule -> a
- iMap :: (Ir -> Ir) -> Ir -> Ir
- iFoldMap :: Monoid m => (Ir -> m) -> Ir -> m
- iFold :: (Ir -> a -> a) -> a -> Ir -> a
- unWrapIModule :: Ir -> IModule
- unWrapIElement :: Ir -> IElement
- unWrapIType :: Ir -> IType
- unWrapIClafer :: Ir -> IClafer
- unWrapIExp :: Ir -> IExp
- unWrapPExp :: Ir -> PExp
- unWrapIReference :: Ir -> Maybe IReference
- unWrapIQuant :: Ir -> IQuant
- unWrapIDecl :: Ir -> IDecl
- unWrapIGCard :: Ir -> Maybe IGCard
- mName :: Lens' IModule String
- mDecls :: Lens' IModule [IElement]
- uid :: Lens' IClafer UID
- super :: Lens' IClafer (Maybe PExp)
- reference :: Lens' IClafer (Maybe IReference)
- parentUID :: Lens' IClafer UID
- isAbstract :: Lens' IClafer Bool
- ident :: Lens' IClafer CName
- glCard :: Lens' IClafer Interval
- gcard :: Lens' IClafer (Maybe IGCard)
- elements :: Lens' IClafer [IElement]
- cinPos :: Lens' IClafer Span
- card :: Lens' IClafer (Maybe Interval)
- isMaximize :: Traversal' IElement Bool
- isHard :: Traversal' IElement Bool
- iClafer :: Traversal' IElement IClafer
- cpexp :: Traversal' IElement PExp
- ref :: Lens' IReference PExp
- isSet :: Lens' IReference Bool
- isKeyword :: Lens' IGCard Bool
- interval :: Lens' IGCard Interval
- pid :: Lens' PExp String
- inPos :: Lens' PExp Span
- iType :: Lens' PExp (Maybe IType)
- exp :: Lens' PExp IExp
- sident :: Traversal' IExp CName
- quant :: Traversal' IExp IQuant
- op :: Traversal' IExp String
- oDecls :: Traversal' IExp [IDecl]
- modName :: Traversal' IExp String
- istr :: Traversal' IExp String
- isTop :: Traversal' IExp Bool
- iint :: Traversal' IExp Integer
- idouble :: Traversal' IExp Double
- exps :: Traversal' IExp [PExp]
- bpexp :: Traversal' IExp PExp
- binding :: Traversal' IExp ClaferBinding
- isDisj :: Lens' IDecl Bool
- decls :: Lens' IDecl [CName]
- body :: Lens' IDecl PExp
Documentation
A "supertype" of all IR types
each file contains exactly one mode. A module is a list of declarations
Clafer has a list of fields that specify its properties. Some fields, marked as (o) are for generating optimized code
IClafer | |
|
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
IEClafer | |
IEConstraint | |
IEGoal | Goal (optimization objective) |
|
data IReference Source
A type of reference. -> values unique (set) ->> values non-unique (bag)
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
IGCard | |
|
type ClaferBinding = Maybe UID Source
Embedes reference to a resolved Clafer
IDeclPExp | quantified expression with declarations e.g., [ all x1; x2 : X | x1.ref != x2.ref ] |
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 |
IInt | integer number |
IDouble | real number |
IStr | string |
IClaferId | a reference to a clafer name |
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
quantifier
unWrapIModule :: Ir -> IModule Source
unWrapIElement :: Ir -> IElement Source
unWrapIType :: Ir -> IType Source
unWrapIClafer :: Ir -> IClafer Source
unWrapIExp :: Ir -> IExp Source
unWrapPExp :: Ir -> PExp Source
unWrapIReference :: Ir -> Maybe IReference Source
unWrapIQuant :: Ir -> IQuant Source
unWrapIDecl :: Ir -> IDecl Source
unWrapIGCard :: Ir -> Maybe IGCard Source
ref :: Lens' IReference PExp Source
op :: Traversal' IExp String Source
oDecls :: Traversal' IExp [IDecl] Source
exps :: Traversal' IExp [PExp] Source