haskelzinc-0.3.0.9: 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 defines a more human-friendly interface for the MiniZinc 2.1 language, on top of Interfaces.MZASTBase. With the use of this module, one can represent MiniZinc models in Haskell code.

Synopsis

Items

include :: String -> Item Source #

Represents an include item in the MiniZinc model. The argument is the filepath.

constraint :: Expr -> Item Source #

Represents a non-annotated constraint item in the MiniZinc model.

output :: [Expr] -> Item Source #

Represents an output item in the MiniZinc model. The elements in the list argument represent the elements of the MiniZinc array passed to the output item.

Example:

>>> output [string "x = ", mz_show[var "x"]]
output ["x = ", show(x)];

If the represented model contains an output item that changes the default format of the solver's solutions, then a custom parser will be needed to get the solver's results back in Haskell. See Interfaces.FZSolutionParser.

(%) :: String -> Item Source #

Represents a comment in the MiniZinc model. Example:

>>> (%) "comment goes here"
% comment goes here

(=.) :: Assignable a => a -> Expr -> Assigned a infix 1 Source #

The operator that represents assignment in MiniZinc code. One can assign a non- annotated expression to a variable, predicate, test or function either on declaration or later.

To annotate the expression, use haskelzinc operator |:.

Examples:

To assign to an already declared variable, predicate, test or function x, use:

>>> "x" =. int 1

To assign a value to a variable on declaration, use:

>>> declare $ variable "x" Par Int =. int 1

Not to be confused with the equality operator, represented in haskelzinc by =.=.

declare :: Declaration -> Item Source #

Used to represent declaration items of MiniZinc. These are variable, function, predicate, test and annotation declaration items.

variable :: Inst -> Type -> Ident -> Declaration Source #

Used together with declare to represent a variable declaration item.

>>> declare $ variable Dec Int "x"

predicate :: Ident -> [Param] -> Declaration Source #

Used together with declare to represent a predicate declaration item.

>>> declare $ predicate "even"[(Dec, Int, "x")] =. var "x" `_mod_` int 2
predicate even(var int: x) = x mod 2;

function :: Inst -> Type -> Ident -> [Param] -> Declaration Source #

Used together with declare to represent a function declaration item.

>>> declare $ function Dec Int "addFive" [(Dec, Int, "x")] =. var "x" +. int 5
function var int: addFive(var int: x) = x + 5;

test :: Ident -> [Param] -> Declaration Source #

Used together with declare to represent a test declaration item.

annotation :: Ident -> [Param] -> Declaration Source #

Used together with declare to represent an annotation declaration item.

solve :: Solve -> Item Source #

Represents a solve item in the MiniZinc model. Used together with one of satisfy, minimize or maximize functions.

satisfy :: Solve Source #

Finilizes the representation of a non-annotated solve item. Use |: operator to annotate it.

minimize :: Expr -> Solve Source #

Finilizes the representation of a non-annotated solve item. Use |: operator to annotate it.

maximize :: Expr -> Solve Source #

Finilizes the representation of a non-annotated solve item. Use |: operator to annotate it.

Expressions

Constants

true :: Expr Source #

MiniZinc boolean constant true.

false :: Expr Source #

MiniZinc boolean constant false.

var :: Ident -> Expr Source #

Used when refering to an already defined variable.

Example:

>>> constraint $ var "x" !=. int 1
constraint x != 1;

int :: Int -> Expr Source #

Used to represent a MiniZinc integer constant. Example:

>>> constraint $ var "x" !=. int 1
constraint x != 1;

float :: Float -> Expr Source #

Used to represent a MiniZinc float constant.

string :: String -> Expr Source #

Used to represent a MiniZinc string constant.

Conditional

if_ :: Expr -> Expr -> [(Expr, Expr)] Source #

Used together with then_ and elseif_ / else_ to represent an if-then-else MiniZinc expression. In case of multiple alternatives, use elseif_, but the last alternative should be represented with the use of else_.

Example:

>>> if_ true `then_` int 1 `else_` int 0
if true then 1 else 0 endif;

then_ :: (Expr -> [(Expr, Expr)]) -> Expr -> [(Expr, Expr)] Source #

cf. if_

elseif_ :: [(Expr, Expr)] -> Expr -> Expr -> [(Expr, Expr)] Source #

cf. if_

else_ :: [(Expr, Expr)] -> Expr -> Expr Source #

cf. if_

Sets

intSet :: [Int] -> Expr Source #

Used to represent a MiniZinc set of integers.

floatSet :: [Float] -> Expr Source #

Used to represent a MiniZinc set of floats.

stringSet :: [String] -> Expr Source #

Used to represent a MiniZinc set of strings.

mapSet :: (a -> Expr) -> [a] -> Expr Source #

Used to represent a MiniZinc set. In mapSet f ls, the elements of the MiniZinc set are represented by the resulting Exprs after applying f on the elements of ls.

set :: [Expr] -> Expr Source #

set = SetLit

(#/.) :: Expr -> [CompTail] -> Expr infix 2 Source #

Creates the representation of a MiniZinc set comprehension. In expr #/. cts, expr represents the head expression of the set comprehension and cts is a list of its generator expressions' representations.

Example:

>>> int 2 *. var "i" #/. [["i"] @@ int 0 ... int 5]
{2 * i | i in 0 .. 5}

Arrays

boolArray :: [Bool] -> Expr Source #

Used to represent a MiniZinc array of booleans.

intArray :: [Int] -> Expr Source #

Used to represent a MiniZinc array of integers.

floatArray :: [Float] -> Expr Source #

Used to represent a MiniZinc array of floats.

stringArray :: [String] -> Expr Source #

Used to represent a MiniZinc array of strings.

boolArray2 :: [[Bool]] -> Expr Source #

Used to represent a 2-dimensional MiniZinc array of booleans.

intArray2 :: [[Int]] -> Expr Source #

Used to represent a 2-dimensional MiniZinc array of integers.

floatArray2 :: [[Float]] -> Expr Source #

Used to represent a 2-dimensional MiniZinc array of floats.

stringArray2 :: [[String]] -> Expr Source #

Used to represent a 2-dimensional MiniZinc array of strings.

mapArray :: (a -> Expr) -> [a] -> Expr Source #

Represents a one-dimensional MiniZinc array by mapping.

mapArray2 :: (a -> Expr) -> [[a]] -> Expr Source #

mapArray2 f lss represents a two-dimensional MiniZinc array by mapping f to all elements of all lists in lss.

array :: [Expr] -> Expr Source #

array = ArrayLit

array2 :: [[Expr]] -> Expr Source #

array2 = ArrayLit2

(#|.) :: Expr -> [CompTail] -> Expr infix 2 Source #

Similar to #/. for array comprehensions.

(!.) infix 9 Source #

Arguments

:: Ident

Array's name

-> [Expr]

Indexes of the desired element

-> Expr 

Represents a MiniZinc array access.

Exaamples:

>>> "array"!.[int 1]
array[1]
>>> "matrix"!.[var "i", var "j"]
matrix[i,j]

Comprehension tail

(@@) :: [Ident] -> Expr -> CompTail infix 5 Source #

Used to construct the representation of a comprehension tail with a single generator expression. See the example in the documentation for #/..

where_ :: CompTail -> Expr -> CompTail infix 4 Source #

Adds a representation for a MiniZinc where clause in a generator expression.

Example:

>>> var "i" *. var "j" #/. [["i", "j"] @@ int 0 ... int 5 `where_` (var "i" !=. var "j")]
{i * j | i, j in 0 .. 5 where i != j}

Generator calls

forall Source #

Arguments

:: [CompTail]

Generator expressions' representation

-> Ident

The name of the called operation

-> Expr

The head expression of the underlying array comprehension

-> Expr 

Used for the representation of a generator call.

Examples:

>>> forall [["i"] @@ var "S", ["j"] @@ var "S"] "sum" ("x"!.[var"i", var "j"]) =.= var "y"
sum(i in S, j in S) (x[i, j]) = y
>>> forall [["c"] @@ var "C"] "forall" (
>>> forall [["s"] @@ var "S"] "sum" (mz_bool2int["bs"!.[var "s"] =.= var "c"])
>>> =.= "result"!.[var "c"])
forall(c in C) (sum(s in S) (bool2int(bs[s] = c)) = result[c])

Types

ctvar :: Ident -> Type Source #

Represents a constrained type defined by a set parameter.

Example:

>>> declare $ variable Dec Int "one2three" =. intSet [1, 2, 3]
var int: one2three = {1, 2, 3};
>>> declare $ variable Dec (ctvar "one2three") "x"
var one2three: x;

($$) :: Ident -> Type Source #

Represents a type variable.

Annotations

(|:) :: Annotatable a => a -> Annotation -> a infixl 4 Source #

Adds a representation of an annotation to components that can be annotated.