License | BSD3 |
---|---|
Maintainer | Klara Marntirosian <klara.mar@cs.kuleuven.be>, Ruben Pieters |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
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.
- data GItem (a :: DSorOther) where
- Include' :: String -> GItem OK
- Comment' :: String -> GItem OK
- Declare' :: Declaration -> GItem OK
- Var' :: Inst -> Type -> String -> GItem DS
- Function' :: Inst -> Type -> String -> [GItem DS] -> GItem DS
- Predicate' :: String -> [GItem DS] -> GItem DS
- Test' :: String -> [GItem DS] -> GItem DS
- Annot' :: String -> [GItem DS] -> GItem OK
- Assign' :: Ident -> Expr -> GItem OK
- Solve' :: Solve -> GItem OK
- Constrain' :: AnnExpr -> GItem OK
- Output' :: [Expr] -> GItem OK
- include :: String -> GItem OK
- constraint :: Expr -> GItem OK
- output :: [Expr] -> GItem OK
- (%) :: String -> GItem OK
- solve :: Solve -> GItem OK
- satisfy :: Solve
- minimize :: Expr -> Solve
- maximize :: Expr -> Solve
- (=.) :: Assignable a => a -> Expr -> GItem OK
- var :: Varr i => Type -> String -> GItem i
- par :: Varr i => Type -> String -> GItem i
- ann :: String -> GItem DS
- predicate :: String -> [GItem DS] -> GItem DS
- function :: Inst -> Type -> String -> [GItem DS] -> GItem DS
- test :: String -> [GItem DS] -> GItem DS
- true :: Expr
- false :: Expr
- bool :: Bool -> Expr
- int :: Int -> Expr
- float :: Float -> Expr
- string :: String -> Expr
- if_ :: Expr -> Expr -> [(Expr, Expr)]
- then_ :: (Expr -> [(Expr, Expr)]) -> Expr -> [(Expr, Expr)]
- elseif_ :: [(Expr, Expr)] -> Expr -> Expr -> [(Expr, Expr)]
- else_ :: [(Expr, Expr)] -> Expr -> Expr
- intSet :: [Int] -> Expr
- floatSet :: [Float] -> Expr
- stringSet :: [String] -> Expr
- mapSet :: (a -> Expr) -> [a] -> Expr
- set :: [Expr] -> Expr
- (#/.) :: Expr -> [CompTail] -> Expr
- boolArray :: [Bool] -> Expr
- intArray :: [Int] -> Expr
- floatArray :: [Float] -> Expr
- stringArray :: [String] -> Expr
- boolArray2 :: [[Bool]] -> Expr
- intArray2 :: [[Int]] -> Expr
- floatArray2 :: [[Float]] -> Expr
- stringArray2 :: [[String]] -> Expr
- mapArray :: (a -> Expr) -> [a] -> Expr
- mapArray2 :: (a -> Expr) -> [[a]] -> Expr
- array :: [Expr] -> Expr
- array2 :: [[Expr]] -> Expr
- (#|.) :: Expr -> [CompTail] -> Expr
- (!.) :: String -> [Expr] -> Expr
- (@@) :: [String] -> Expr -> CompTail
- where_ :: CompTail -> Expr -> CompTail
- forall :: [CompTail] -> String -> Expr -> Expr
- prefCall :: String -> [Expr] -> Expr
- infCall :: String -> Expr -> Expr -> Expr
- prefOp :: String -> Op
- infOp :: String -> Op
- let_ :: [GItem i] -> Expr -> Expr
- ($$) :: String -> Type
- annotation :: String -> [GItem DS] -> GItem OK
- (|:) :: Annotatable a => a -> Annotation -> a
- type ModelData = GItem OK
- declareOnly :: DeclarationSignature -> Declaration
- turnToItem :: GItem a -> Item
- module Interfaces.MZASTBase
Items
data GItem (a :: DSorOther) where Source #
Include' :: String -> GItem OK | |
Comment' :: String -> GItem OK | |
Declare' :: Declaration -> GItem OK | |
Var' :: Inst -> Type -> String -> GItem DS | |
Function' :: Inst -> Type -> String -> [GItem DS] -> GItem DS | |
Predicate' :: String -> [GItem DS] -> GItem DS | |
Test' :: String -> [GItem DS] -> GItem DS | |
Annot' :: String -> [GItem DS] -> GItem OK | |
Assign' :: Ident -> Expr -> GItem OK | |
Solve' :: Solve -> GItem OK | |
Constrain' :: AnnExpr -> GItem OK | |
Output' :: [Expr] -> GItem OK |
include :: String -> GItem OK Source #
Represents an include item in the MiniZinc model. The argument is the filepath.
constraint :: Expr -> GItem OK Source #
Represents a non-annotated constraint item in the MiniZinc model.
output :: [Expr] -> GItem OK 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 -> GItem OK Source #
Represents a comment in the MiniZinc model. Example:
>>>
(%) "comment goes here"
% comment goes here
Finalizes 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.
(=.) :: Assignable a => a -> Expr -> GItem OK infixl 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:
Assigning to an already declared variable, predicate, test or function
x
:
>>>
"x" =. 1
Assigning a value to a variable on declaration:
>>>
par Int "x" =. 1
Not to be confused with the equality operator, represented in haskelzinc by =.=
.
ann :: String -> GItem DS Source #
Creates the representation of a variable of type ann
. Use this
function in the declaration of the arguments of a user-defined
annotation.
Example:
>>>
annotation "int_search" [par Array[Int] Dec Int, ann "select", ann "explore"]
annotation int_search(array[int] of var int: x, ann: select, ann: explore);
:: String | The name of the predicate |
-> [GItem DS] | The signature of the predicate's arguments |
-> GItem DS |
Creates a predicate declaration item. Use the (=.) operator to assign it a body.
:: Inst | The inst of the function's returning value |
-> Type | The type of the function's returning value |
-> String | The name of the function |
-> [GItem DS] | The signature of the function's arguments |
-> GItem DS |
Creates a function declaration item. Use the (=.) operator to assign it a body.
Creates a test declaration item. Use the (=.) operator to assign it a body.
Expressions
Constants
Used to represent a MiniZinc integer
constant.
Example:
>>>
constraint $ "x" !=. 1
constraint x != 1;
float :: Float -> Expr Source #
Used to represent a MiniZinc float constant. In most cases,
just a Haskell Float
value is sufficient for the representation
of the MiniZinc float
value. This function is provided for when
it is necessary to use.
string :: String -> Expr Source #
Used to represent a MiniZinc string constant. This function is necessary for
the representation of MiniZinc string literals. Just a Haskell String
value
is not sufficient.
Conditional
Sets
intSet :: [Int] -> Expr Source #
Used to represent a MiniZinc set of integers. Its first argument is a list of the set's elements.
Example:
>>>
intSet [1, 3, 5]
{1, 3, 5}
floatSet :: [Float] -> Expr Source #
Used to represent a MiniZinc set of floats. Its first argument is a list of the set's elements.
stringSet :: [String] -> Expr Source #
Used to represent a MiniZinc set of strings. Its first argument is a list of the set's elements.
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 Expr
s after applying f
on the elements of
ls
.
set :: [Expr] -> Expr Source #
Used to represent a set of arbitrary type.
Example:
>>>
set [1, 3, 5]
{1, 3, 5}
haskelzinc does not check for type correctness of the represented MiniZinc set expression. The example below will compile.
Example:
>>>
set [1.0, 3, string "asd"]
{1.0, 3, "asd"}
For a safer set representation, use functions intSet
, floatSet
and stringSet
.
(#/.) :: 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:
>>>
2 *. "i" #/. [["i"] @@ 0 ... 5]
{2 * i | i in 0 .. 5}
Arrays
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.
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 1-dimensional MiniZinc array by mapping, as in the case of
mapSet
.
mapArray2 :: (a -> Expr) -> [[a]] -> Expr Source #
mapArray2 f lss
represents a 2-dimensional MiniZinc array by mapping f
to all
elements of all lists in lss
.
array :: [Expr] -> Expr Source #
Represents a 1-dimensional array of arbitrary type. Same safety remarks apply here as with
function set
.
array2 :: [[Expr]] -> Expr Source #
Represents a 2-dimensional array of arbitrary type. Same safety remarks apply here as with
function set
.
Represents a MiniZinc array access.
Examples:
>>>
"array"!.[1]
array[1]
>>>
"matrix"!.["i", "j"]
matrix[i,j]
Comprehension tail
(@@) :: [String] -> 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:
>>>
"i" *. "j" #/. [["i", "j"] @@ 0 ... 5 `where_` ("i" !=. "j")]
{i * j | i, j in 0 .. 5 where i != j}
Generator calls
:: [CompTail] | Generator expressions' representation |
-> String | 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"] @@ "S1", ["j"] @@ "S2"] "sum" ("x"!.["i", "j"])
sum(i in S1, j in S2) (x[i, j])
>>>
forall [["c"] @@ "C"] "forall" (
>>>
forall [["s"] @@ "S"] "sum" (mz_bool2int["bs"!.["s"] =.= "c"])
>>>
=.= "result"!.["c"])
forall(c in C) (sum(s in S) (bool2int(bs[s] = c)) = result[c])
User defined operations
Used to represent a prefix call to a function, test or predicate.
:: String | The name of the called operation |
-> Expr | A representation of the left operand |
-> Expr | A representation of the right operand |
-> Expr |
Used to represent an infix (quoted) call to a function, test or predicate.
let_ :: [GItem i] -> Expr -> Expr Source #
Creates a MiniZinc let-expression.
Example:
>>>
predicate "posProd"[var Int "x", var Int "y"] =.
>>>
let_ [ var Int "z"
>>>
, constraint $ "z" =.= "x" *. "y"]
>>>
("z" >. 0)
predicate posProd(var int: x, var int: y) = let {var int: z; constraint z = x * y;} in z > 0;
Types
Annotations
annotation :: String -> [GItem DS] -> GItem OK Source #
Creates an annotation declaration item. Annotations
(|:) :: Annotatable a => a -> Annotation -> a infixl 4 Source #
Adds a representation of an annotation to components that can be annotated.
Others
turnToItem :: GItem a -> Item Source #
module Interfaces.MZASTBase