Copyright | (c) Some Guy, 2013 Someone Else, 2014 |
---|---|
License | GPL-3 |
Maintainer | Klara Marntirosian <klara.mar@cs.kuleuven.be> |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
This module provides an interface of the MiniZinc 2.0 language in Haskell through the definition of an abstract syntax tree of the MiniZinc language. With the use of this module, one can represent MiniZinc models in Haskell code. The abstract syntax tree is based on the MiniZinc 2.0 spesification.
However, the module does not check semantical correctness of the represented model. For example, it does not detect typos in the use of previously declared identifiers.
Featrues not supported yet
- Annotations
- type MZModel = [Item]
- data Item
- data Expr
- = AnonVar
- | Var Ident
- | BConst Bool
- | IConst Int
- | FConst Float
- | SConst String
- | Interval Expr Expr
- | SetLit [Expr]
- | SetComp Expr CompTail
- | ArrayLit [Expr]
- | ArrayLit2D [[Expr]]
- | ArrayComp Expr CompTail
- | ArrayElem Ident [Expr]
- | Bi Bop Expr Expr
- | U Uop Expr
- | Call Func [Expr]
- | ITE [(Expr, Expr)] Expr
- | Let [Item] Expr
- | GenCall Func CompTail Expr
- data VarType
- data Bop
- data Uop
- userD :: Ident -> Func
- prefbop :: Bop -> Func
- mz_abs :: Func
- mz_sum :: Func
- mz_max :: Func
- mz_min :: Func
- mz_pow :: Func
- mz_sqrt :: Func
- mz_exp :: Func
- mz_ln :: Func
- mz_log :: Func
- mz_log10 :: Func
- mz_log2 :: Func
- mz_sin :: Func
- mz_cos :: Func
- mz_tan :: Func
- mz_sinh :: Func
- mz_cosh :: Func
- mz_tanh :: Func
- mz_asin :: Func
- mz_acos :: Func
- mz_atan :: Func
- mz_asinh :: Func
- mz_acosh :: Func
- mz_atanh :: Func
- mz_forall :: Func
- mz_xorall :: Func
- mz_show :: Func
- mz_show_int :: Func
- mz_show_float :: Func
- mz_concat :: Func
- mz_join :: Func
- mz_card :: Func
- mz_array_union :: Func
- mz_length :: Func
- mz_index_set :: Func
- mz_index_set_1of2 :: Func
- mz_index_set_2of2 :: Func
- mz_array1d :: Func
- mz_array2d :: Func
- mz_array3d :: Func
- mz_array4d :: Func
- mz_array5d :: Func
- mz_array6d :: Func
- mz_occurs :: Func
- mz_absent :: Func
- mz_deopt :: Func
- mz_ceil :: Func
- mz_floor :: Func
- mz_round :: Func
- mz_bool2int :: Func
- mz_int2float :: Func
- mz_set2array :: Func
- mz_lb :: Func
- mz_ub :: Func
- mz_lb_array :: Func
- mz_ub_array :: Func
- mz_dom :: Func
- mz_dom_array :: Func
- mz_dom_size :: Func
- mz_assert :: Func
- mz_abort :: Func
- mz_trace :: Func
- mz_fix :: Func
- mz_is_fixed :: Func
- data Func
- data Inst
- data Solve
- type CompTail = ([Generator], Maybe Expr)
- type Generator = ([Ident], Expr)
- type TypeInst = (Inst, VarType)
- type Param = (Inst, VarType, Ident)
- type Ident = String
- type Filename = String
Documentation
The type of a MiniZinc's top-level program item representation. MiniZinc defines 8 kinds of items. This module defines a representation for 12 kinds of items. The additional 4 come from representing MiniZinc commented lines and empty lines as items, and from using 3 distinct Item constructors for representing user defined calls (predicates, tests and functions).
Comment String | Commented line |
Include Filename | Include item |
Declare TypeInst Ident (Maybe Expr) | Variable declaration item.
The value |
Assign Ident Expr | Assignment item. |
Constraint Expr | 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. |
Pred Ident [Param] (Maybe Expr) | User-defined predicate. |
Test Ident [Param] (Maybe Expr) | User-defined test. Syntax similar to the |
Function TypeInst Ident [Param] (Maybe Expr) | User-defined function. Syntax similar to |
Annotation | Annotation item. Use of annotations is not supported yet. |
Empty | Represents an empty line in the MiniZinc model. |
The type of a MiniZinc expression's representation.
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 |
Interval Expr Expr | MiniZinc arrays constructed with the MiniZinc |
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 Bop Expr Expr |
|
U Uop Expr |
|
Call Func [Expr] |
|
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 Func CompTail Expr | A generator call expression. |
The type of a MiniZinc's type representation.
Bool | |
Int | |
Float | |
String | |
Set VarType |
|
Array [VarType] TypeInst |
|
List TypeInst | The list type |
Opt VarType | Option type |
Range Expr Expr | A constrained type using the integer range. |
Elems [Expr] | A constrained type using set literals. |
AOS Ident | A constrained type using a previously defined set parameter. |
Any |
MiniZinc operators
The type of MiniZinc binary operators' representation. Next to each constructor is indicated the operator it represents.
Represents MiniZinc unary operators. Next to each constructor is indicated the operator it represents.
MiniZinc built-in calls
userD :: Ident -> Func Source #
User defined function, test or predicate in MiniZinc. The argument of this constructor is the name of the function.
Arithmetic calls
Logical calls
String calls
mz_show_int :: Func Source #
mz_show_float :: Func Source #
Set calls
Array calls
mz_index_set :: Func Source #
mz_array1d :: Func Source #
mz_array2d :: Func Source #
mz_array3d :: Func Source #
mz_array4d :: Func Source #
mz_array5d :: Func Source #
mz_array6d :: Func Source #
Option type calls
Coercion calls
mz_bool2int :: Func Source #
mz_int2float :: Func Source #
mz_set2array :: Func Source #
Bound and domain calls
mz_lb_array :: Func Source #
mz_ub_array :: Func Source #
mz_dom_array :: Func Source #
mz_dom_size :: Func Source #
Other calls
mz_is_fixed :: Func Source #
The type of a MiniZinc's function, test or predicate representation.
The type of a MiniZinc instantiation representation.
The type for representing the three different kinds of solve items.