License | BSD3 |
---|---|
Maintainer | Klara Marntirosian <klara.mar@cs.kuleuven.be> |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
Interfaces.MZASTBase
Description
This module provides an interface for the MiniZinc 2.1 language. With the use of this module, one can represent MiniZinc models in Haskell code. The syntax is based on the MiniZinc 2.1 spesification. However, this module provides a low-level interface to the MiniZinc language. A more human friendly interface is provided in Interfaces.MZAST.
Enumerated types are not supported yet.
- type MZModel = [Item]
- data Item
- data Declaration = Declaration DeclarationSignature [Annotation] (Maybe AnnExpr)
- data DeclarationSignature
- data Solve
- = Satisfy [Annotation]
- | Minimize [Annotation] Expr
- | Maximize [Annotation] Expr
- data Inst
- data Type
- data AnnExpr = AnnExpr Expr [Annotation]
- data Expr
- = AnonVar
- | Var Ident
- | BConst Bool
- | IConst Int
- | FConst Float
- | SConst String
- | SetLit [Expr]
- | SetComp Expr CompTail
- | ArrayLit [Expr]
- | ArrayLit2D [[Expr]]
- | ArrayComp Expr CompTail
- | ArrayElem Ident [Expr]
- | Bi Op Expr Expr
- | U Op Expr
- | Call Ident [AnnExpr]
- | ITE [(Expr, Expr)] Expr
- | Let [Item] Expr
- | GenCall Ident CompTail Expr
- stripExprOff :: AnnExpr -> Expr
- toSimpleExpr :: Expr -> AnnExpr
- newtype Op = Op Ident
- data GArguments
- = A Annotation
- | E Expr
- data Annotation = Annotation String [GArguments]
- type CompTail = ([Generator], Maybe Expr)
- type Generator = ([Ident], Expr)
- type Param = (Inst, Type, Ident)
- data Ident
- stringToIdent :: String -> Ident
- identToString :: Ident -> String
- type Filename = String
Documentation
Items representation
Represents MiniZinc items, the first-class entities of the MiniZinc language.
Correspondence between MiniZinc items and the constructors of Item
values is not
one-to-one:
Constructors
Comment String | Commented line |
Include Filename | Include item |
Declare Declaration | A declaration item. Can represent a MiniZinc variable, predicate, test, function or annotation declaration. This is specified by the constructor's argument. |
Assign Ident AnnExpr | Assignment item. |
Constraint AnnExpr | Constraint item |
Solve Solve | Solve item |
Output Expr | Output item. The use of this item might cause errors in parsing the solution(s) of the model. Recommended use for testing purposes only. |
data Declaration Source #
Represents a complete variable, predicate, test or function declaration with a list of annotations (possibly empty) and maybe a body.
Constructors
Declaration DeclarationSignature [Annotation] (Maybe AnnExpr) |
Instances
data DeclarationSignature Source #
Used for the representation of the signature of a variable, function, predicate, test or annotation declaration.
Constructors
Variable Param | |
Predicate Ident [Param] | |
Test Ident [Param] | |
Function Param [Param] | |
Annotation' String [Param] |
Instances
The type for representing the three different kinds of solve items.
Constructors
Satisfy [Annotation] | |
Minimize [Annotation] Expr | |
Maximize [Annotation] Expr |
The type of a MiniZinc instantiation representation.
The type of a MiniZinc's type representation.
Constructors
Bool | |
Int | |
Float | |
String | |
Set Type |
|
Array [Type] Inst Type |
|
List Inst Type | The list type |
Opt Type | Option type |
Ann | Annotation type |
CT Expr | A constrainted type. The |
Range Expr Expr | A constrained type using the integer range. |
VarType String | Type variable |
Expressions representation
Represents a MiniZinc expression (first argument) annotated with the annotations contained in the list of the second argument.
Constructors
AnnExpr Expr [Annotation] |
The type of a MiniZinc expression's representation.
Constructors
AnonVar | Represents the MiniZinc special variable |
Var Ident | A MiniZinc variable. |
BConst Bool | MiniZinc boolean value. |
IConst Int | MiniZinc integer value. |
FConst Float | MiniZinc float value. |
SConst String | MiniZinc string value. |
SetLit [Expr] |
|
SetComp Expr CompTail | MiniZinc set comprehension. The first argument of the constructor represents the head expression of the comprehension, while the second represents the comprehension tail. |
ArrayLit [Expr] | MiniZinc 1-dimensional arrays defined with literals, similar to the |
ArrayLit2D [[Expr]] | MiniZinc 2-dimensional arrays defined with literals. |
ArrayComp Expr CompTail | MiniZinc array comprehension. Syntax similar to |
ArrayElem Ident [Expr] | Represents an array element. In |
Bi Op Expr Expr |
|
U Op Expr |
|
Call Ident [AnnExpr] |
|
ITE [(Expr, Expr)] Expr | The if-then-else conditional. If the first argument of the constructor is an
empty list, the translation to MiniZinc will fail. |
Let [Item] Expr |
|
GenCall Ident CompTail Expr | A generator call expression. |
stripExprOff :: AnnExpr -> Expr Source #
Takes an annotated expression and returns only the expression.
toSimpleExpr :: Expr -> AnnExpr Source #
Represents an operator name/symbol in MiniZinc.
data GArguments Source #
Used in annotations' arguments, which can be either annotations or expressions.
Constructors
A Annotation | |
E Expr |
Instances
data Annotation Source #
Represents a call to a MiniZinc annotation. First argument represents the annotation's name and second argument contains the annotation's arguments, if any.
Constructors
Annotation String [GArguments] |
Instances
Abbreviations
MiniZinc identifiers can be simple alphanumberics of the form [A-Za-z][A-Za-z0-9_]*
or quoted strings.
stringToIdent :: String -> Ident Source #
identToString :: Ident -> String Source #