haskelzinc-0.3.1.1: CP in Haskell through MiniZinc

LicenseBSD3
MaintainerKlara Marntirosian <klara.mar@cs.kuleuven.be>
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Interfaces.MZASTBase

Contents

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.

Synopsis

Documentation

type MZModel = [Item] Source #

An abbreviation for the type of a represented MiniZinc model.

Items representation

data Item Source #

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:

  • Variable, function, predicate, test and annotation declaration items are all represented with the Declare constructor.
  • Extra Comment constructor for the representation of MiniZinc comments.

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. Assign name exp represents the assignment of exp to the variable name.

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.

Instances

Eq Item Source # 

Methods

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

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

Show Item Source # 

Methods

showsPrec :: Int -> Item -> ShowS #

show :: Item -> String #

showList :: [Item] -> ShowS #

data Declaration Source #

Represents a complete variable, predicate, test or function declaration with a list of annotations (possibly empty) and maybe a body.

data DeclarationSignature Source #

Used for the representation of the signature of a variable, function, predicate, test or annotation declaration.

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 #

Show Solve Source # 

Methods

showsPrec :: Int -> Solve -> ShowS #

show :: Solve -> String #

showList :: [Solve] -> ShowS #

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 #

Show Inst Source # 

Methods

showsPrec :: Int -> Inst -> ShowS #

show :: Inst -> String #

showList :: [Inst] -> ShowS #

data Type Source #

The type of a MiniZinc's type representation.

Constructors

Bool 
Int 
Float 
String 
Set Type

Set t translates to set of t.

Array [Type] Inst Type

Array ts inst ty translates to array [ts] of inst ty.

List Inst Type

The list type

Opt Type

Option type

Ann

Annotation type

CT Expr

A constrainted type. The Expr argument should represent a MiniZinc finite set.

Range Expr Expr

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

VarType String

Type variable

Instances

Eq Type Source # 

Methods

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

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

Show Type Source # 

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Expressions representation

data AnnExpr Source #

Represents a MiniZinc expression (first argument) annotated with the annotations contained in the list of the second argument.

Constructors

AnnExpr Expr [Annotation] 

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.

SetLit [Expr]

SetLit ls translates to a MiniZinc set the elements of which are the represented expressions in the ls 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 js, the argument name is the identifier of the array and js is the list of indexes that specify the desired element. The length of js must be equal to the number of dimensions of the array.

Bi Op Expr Expr

Bi op exp1 exp2 represents the MiniZinc expression of the binary operator op applied on exp1 and exp2.

U Op Expr

U op exp represents the MiniZinc application of the unary operator (represented by) op on the expression (represented by) exp.

Call Ident [AnnExpr]

Call name args represents a call to the function, predicate or test name on arguments args. A call to an annotation is represented by the Annotation type.

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 [Item], only Item values constructed by Declare and Constraint will translate to a syntactically correct MiniZinc let expression.

GenCall Ident CompTail Expr

A generator call expression.

Instances

Eq Expr Source # 

Methods

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

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

Show Expr Source # 

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

stripExprOff :: AnnExpr -> Expr Source #

Takes an annotated expression and returns only the expression.

toSimpleExpr :: Expr -> AnnExpr Source #

Transforms an Expr to an AnnExpr with an empty list of annotations.

newtype Op Source #

Represents an operator name/symbol in MiniZinc.

Constructors

Op Ident 

Instances

Eq Op Source # 

Methods

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

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

Show Op Source # 

Methods

showsPrec :: Int -> Op -> ShowS #

show :: Op -> String #

showList :: [Op] -> ShowS #

data GArguments Source #

Used in annotations' arguments, which can be either annotations or expressions.

Constructors

A Annotation 
E Expr 

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] 

Abbreviations

data Ident Source #

MiniZinc identifiers can be simple alphanumberics of the form [A-Za-z][A-Za-z0-9_]* or quoted strings.

Constructors

Simpl String

Represents a simple identifier

Quoted String

Represents a quoted identifier

Instances

Eq Ident Source # 

Methods

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

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

Show Ident Source # 

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #