haskelzinc-0.2.0.3: CP in Haskell through MiniZinc

Copyright(c) Some Guy, 2013 Someone Else, 2014
LicenseGPL-3
MaintainerKlara Marntirosian <klara.mar@cs.kuleuven.be>
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Interfaces.MZAST

Contents

Description

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

Synopsis

Documentation

type MZModel = [Item] Source #

An abbreviation for the type of a represented MiniZinc model.

data Item Source #

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).

Constructors

Comment String

Commented line

Include Filename

Include item

Declare TypeInst Ident (Maybe Expr)

Variable declaration item. The value Declare i t name maybe_exp represents the declaration a variable named name of type t and inst i. Use Just expression in place of maybe_exp to represent the value that initializes the declared variable. Use Nothing in place of maybe_exp to represent a variable declaration without initialization.

Assign Ident Expr

Assignment item. Assign name exp represents the assignment of exp to the variable name.

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. Pred name args exp represents the MiniZinc definition of a predicate called name, the parameters of which are the elements of the args list. exp represents the optional body of the predicate.

Test Ident [Param] (Maybe Expr)

User-defined test. Syntax similar to the Pred constructor.

Function TypeInst Ident [Param] (Maybe Expr)

User-defined function. Syntax similar to Pred and Test constructors. The additional TypeInst represents the type of the returning value of the function and the inst of the function.

Annotation

Annotation item. Use of annotations is not supported yet.

Empty

Represents an empty line in the MiniZinc model.

Instances

Eq Item Source # 

Methods

(==) :: Item -> Item -> Bool #

(/=) :: Item -> Item -> Bool #

data Expr Source #

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

Interval Expr Expr

MiniZinc arrays constructed with the MiniZinc .. operator. Interval a b translates to [a .. b].

SetLit [Expr]

SetLit literals translates to a MiniZinc set the elements of which are the represented expressions in the literals list.

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 SetLit constructor.

ArrayLit2D [[Expr]]

MiniZinc 2-dimensional arrays defined with literals

ArrayComp Expr CompTail

MiniZinc array comprehension. Syntax similar to SetComp constructor.

ArrayElem Ident [Expr]

Represents an array element. In ArrayElem name is, the argument name is the identifier of the array and is is the list of indexes that specify the desired element. The length of is must be equal to the number of dimensions of the array.

Bi Bop Expr Expr

Bi op exp1 exp2 represents the MiniZinc expression that applies the binary operator op on exp1 and exp2.

U Uop Expr

U op exp1 represents the MiniZinc expression that applies the unary operator op on exp1.

Call Func [Expr]

Call name args represents a call to the function or test name on arguments args.

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. ITE [(cond, expr1)] expr2, where the list is a singleton, translates to if cond then exp1 else exp2 endif. If the list contains more than one pairs, then the corresponding elseif-then pairs are inserted before the final else expression.

Let [Item] Expr

let-in expression. In Let items expr, the elements of items represent the bindings in the expr expression. Although items is of type [Items], only Item values constructed by Declare and Constraint will translate to a syntactically correct MiniZinc let expression.

GenCall Func CompTail Expr

A generator call expression.

Instances

Eq Expr Source # 

Methods

(==) :: Expr -> Expr -> Bool #

(/=) :: Expr -> Expr -> Bool #

data VarType Source #

The type of a MiniZinc's type representation.

Constructors

Bool 
Int 
Float 
String 
Set VarType

Set t translates to set of t.

Array [VarType] TypeInst

Array ts ti translates to array [ts] of ti.

List TypeInst

The list type

Opt VarType

Option type

Range Expr Expr

A constrained type using the integer range. Range a b translates to a .. b.

Elems [Expr]

A constrained type using set literals.

AOS Ident

A constrained type using a previously defined set parameter.

Any 

Instances

MiniZinc operators

data Bop Source #

The type of MiniZinc binary operators' representation. Next to each constructor is indicated the operator it represents.

Constructors

Gt
>
Lt
<
Gte
>=
Lte
<=
Eqq
==
Eq
=
Neq
!=
BPlus
+
BMinus
-
Times
*
Div
/
IDiv
div
Mod
mod
LRarrow
<->
Rarrow
->
Larrow
<-
And
/\
Or
\/
In
in
Sub
subset
Super
superset
Union
union
Inters
intersect
Concat
++
Diff
diff
SDiff
symdiff
RangeOp
..
AsFunc Bop 

Instances

Eq Bop Source # 

Methods

(==) :: Bop -> Bop -> Bool #

(/=) :: Bop -> Bop -> Bool #

data Uop Source #

Represents MiniZinc unary operators. Next to each constructor is indicated the operator it represents.

Constructors

Not
not
UPlus
+
UMinus
-

Instances

Eq Uop Source # 

Methods

(==) :: Uop -> Uop -> Bool #

(/=) :: Uop -> Uop -> Bool #

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.

prefbop :: Bop -> Func Source #

Prefix notation of a MiniZinc built-in binary operator.

Arithmetic calls

Logical calls

String calls

Set calls

Array calls

Option type calls

Coercion calls

Bound and domain calls

Other calls

data Func Source #

The type of a MiniZinc's function, test or predicate representation.

Constructors

CName Ident 
PrefBop Bop 

Instances

Eq Func Source # 

Methods

(==) :: Func -> Func -> Bool #

(/=) :: Func -> Func -> Bool #

data Inst Source #

The type of a MiniZinc instantiation representation.

Constructors

Par

A par instantiation in MiniZinc.

Dec

A var instantiation in MiniZinc.

Instances

Eq Inst Source # 

Methods

(==) :: Inst -> Inst -> Bool #

(/=) :: Inst -> Inst -> Bool #

data Solve Source #

The type for representing the three different kinds of solve items.

Instances

Eq Solve Source # 

Methods

(==) :: Solve -> Solve -> Bool #

(/=) :: Solve -> Solve -> Bool #