-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | CP in Haskell through MiniZinc -- -- This library aims to link Haskell with MiniZinc. It provides an -- abstract syntax tree for the MiniZinc language, with which one can -- define MiniZinc constraint models. One can directly get the -- solution(s) of the model or separately use the corresponding modules -- of the library to pretty-print the model or parse its solution(s). @package haskelzinc @version 0.1.0.0 -- | This module parses the solutions outputed by the specified FlatZinc -- solver. It supports multiple solutions. The parser might fail if there -- is a show item in the represented MiniZinc model which alters the -- default format of the solutions' output. -- -- This parser is built using the Text.Parsec module. module Interfaces.FZSolutionParser -- | Given the path of the file where the solution(s) have been printed, -- this function reads the file, parses the solution(s) and prints them. getSolution :: FilePath -> IO () instance GHC.Show.Show Interfaces.FZSolutionParser.MValue -- | 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 syntac 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

-- -- module Interfaces.MZAST -- | An abbreviation for the type of a represented MiniZinc model. type MZModel = [Item] -- | 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). data Item -- | Commented line Comment :: String -> Item -- | Include item Include :: Filename -> Item -- | 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. Declare :: TypeInst -> Ident -> (Maybe Expr) -> Item -- | Assignment item. Assign name exp represents the assignment of -- exp to the variable name. Assign :: Ident -> Expr -> Item -- | Constraint item Constraint :: Expr -> Item -- | Solve item Solve :: Solve -> Item -- | Output item. The use of this item might cause errors in parsing the -- solution(s) of the model. Recommended use for testing purposes only. Output :: Expr -> Item -- | 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. Pred :: Ident -> [Param] -> (Maybe Expr) -> Item -- | User-defined test. Syntax similar to the Pred constructor. Test :: Ident -> [Param] -> (Maybe Expr) -> Item -- | 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. Function :: TypeInst -> Ident -> [Param] -> (Maybe Expr) -> Item -- | Annotation item. Use of annotations is not supported yet. Annotation :: Item -- | Represents an empty line in the MiniZinc model. Empty :: Item -- | The type of a MiniZinc expression's representation. data Expr -- | Represents the MiniZinc special variable _. AnonVar :: Expr -- | A MiniZinc variable Var :: Ident -> Expr -- | MiniZinc boolean value BConst :: Bool -> Expr -- | MiniZinc integer value IConst :: Int -> Expr -- | MiniZinc float value FConst :: Float -> Expr -- | MiniZinc string value SConst :: String -> Expr -- | MiniZinc arrays constructed with the MiniZinc .. operator. -- Interval a b translates to [a .. b]. Interval :: Expr -> Expr -> Expr -- | SetLit literals translates to a MiniZinc set the elements of -- which are the represented expressions in the literals list. SetLit :: [Expr] -> Expr -- | MiniZinc set comprehension. The first argument of the constructor -- represents the head expression of the comprehension, while the second -- represents the comprehension tail. SetComp :: Expr -> CompTail -> Expr -- | MiniZinc 1-dimensional arrays defined with literals, similar to the -- SetLit constructor. ArrayLit :: [Expr] -> Expr -- | MiniZinc 2-dimensional arrays defined with literals ArrayLit2D :: [[Expr]] -> Expr -- | MiniZinc array comprehension. Syntax similar to SetComp -- constructor. ArrayComp :: Expr -> CompTail -> 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. ArrayElem :: Ident -> [Expr] -> Expr -- | Bi op exp1 exp2 represents the MiniZinc expression that -- applies the binary operator op on exp1 and -- exp2. Bi :: Bop -> Expr -> Expr -> Expr -- | U op exp1 represents the MiniZinc expression that applies the -- unary operator op on exp1. U :: Uop -> Expr -> Expr -- | Call name args represents a call to the function or test -- name on arguments args. Call :: Func -> [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. ITE :: [(Expr, Expr)] -> Expr -> 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. Let :: [Item] -> Expr -> Expr -- | A generator call expression. GenCall :: Func -> CompTail -> Expr -> Expr -- | The type of a MiniZinc's type representation. data VarType Bool :: VarType Int :: VarType Float :: VarType String :: VarType -- | Set t translates to set of t. Set :: VarType -> VarType -- | Array ts ti translates to array [ts] of ti. Array :: [VarType] -> TypeInst -> VarType -- | The list type List :: TypeInst -> VarType -- | Option type Opt :: VarType -> VarType -- | A constrained type using the integer range. Range a b -- translates to a .. b. Range :: Expr -> Expr -> VarType -- | A constrained type using set literals. Elems :: [Expr] -> VarType -- | A constrained type using a previously defined set parameter. AOS :: Ident -> VarType Any :: VarType -- | The type of MiniZinc binary operators' representation. Next to each -- constructor is indicated the operator it represents. data Bop -- |
--   >
--   
Gt :: Bop -- |
--   <
--   
Lt :: Bop -- |
--   >=
--   
Gte :: Bop -- |
--   <=
--   
Lte :: Bop -- |
--   ==
--   
Eqq :: Bop -- |
--   =
--   
Eq :: Bop -- |
--   !=
--   
Neq :: Bop -- |
--   +
--   
BPlus :: Bop -- |
--   -
--   
BMinus :: Bop -- |
--   *
--   
Times :: Bop -- |
--   /
--   
Div :: Bop -- |
--   div
--   
IDiv :: Bop -- |
--   mod
--   
Mod :: Bop -- |
--   <->
--   
LRarrow :: Bop -- |
--   ->
--   
Rarrow :: Bop -- |
--   <-
--   
Larrow :: Bop -- |
--   /\
--   
And :: Bop -- |
--   \/
--   
Or :: Bop -- |
--   in
--   
In :: Bop -- |
--   subset
--   
Sub :: Bop -- |
--   superset
--   
Super :: Bop -- |
--   union
--   
Union :: Bop -- |
--   intersect
--   
Inters :: Bop -- |
--   ++
--   
Concat :: Bop -- |
--   diff
--   
Diff :: Bop -- |
--   symdiff
--   
SDiff :: Bop -- |
--   ..
--   
RangeOp :: Bop AsFunc :: Bop -> Bop -- | Represents MiniZinc unary operators. Next to each constructor is -- indicated the operator it represents. data Uop -- |
--   not
--   
Not :: Uop -- |
--   +
--   
UPlus :: Uop -- |
--   -
--   
UMinus :: Uop -- | User defined function, test or predicate in MiniZinc. The argument of -- this constructor is the name of the function. userD :: Ident -> Func -- | Prefix notation of a MiniZinc built-in binary operator. 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 -- | The type of a MiniZinc's function, test or predicate representation. data Func CName :: Ident -> Func PrefBop :: Bop -> Func -- | The type of a MiniZinc instantiation representation. data Inst -- | A par instantiation in MiniZinc. Par :: Inst -- | A var instantiation in MiniZinc. Dec :: Inst -- | The type for representing the three different kinds of solve items. data Solve Satisfy :: Solve Minimize :: Expr -> Solve Maximize :: Expr -> 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 instance GHC.Classes.Eq Interfaces.MZAST.Solve instance GHC.Classes.Eq Interfaces.MZAST.Expr instance GHC.Classes.Eq Interfaces.MZAST.VarType instance GHC.Classes.Eq Interfaces.MZAST.Item instance GHC.Classes.Eq Interfaces.MZAST.Func instance GHC.Classes.Eq Interfaces.MZAST.Inst instance GHC.Classes.Eq Interfaces.MZAST.Uop instance GHC.Classes.Eq Interfaces.MZAST.Bop -- | This module provides a pretty-printer of MiniZinc models represented -- through the MZAST module. This pretty-printer is based on the -- Text.PrettyPrint module. module Interfaces.MZPrinter -- | An abbreviation for the type of a represented MiniZinc model. type MZModel = [Item] -- | Prints the represented MiniZinc model. Essentially, this function -- applies printItem on each element of the specified model. printModel :: MZModel -> Doc -- | Prints an item of the represented model. Example: -- --
--   >>> printItem $ Pred "even" [(Dec, Int, "x")] (Just (Bi Eq (Bi Mod (Var "x") (IConst 2)) (IConst 0)))
--   predicate even(var int: x) =
--     x mod 2 = 0;
--   
printItem :: Item -> Doc -- | Prints the represented MiniZinc expressions of a model. Examples: -- --
--   >>> printExpr $ SetComp (Bi Times (IConst 2) (Var "i")) ([(["i"], Interval (IConst 1) (IConst 5))], Nothing)
--   {2 * i | i in 1..5}
--   
-- --
--   >>> printExpr $ Let [Declare Dec Int "x" (Just (IConst 3)), Declare Dec Int "y" (Just (IConst 4))] (Bi BPlus (Var "x") (Var "y"))
--   let {var int: x = 3;
--        var int: y = 4;}
--   in x + y
--   
printExpr :: Expr -> Doc -- | This module integrates constraint solving programming through MiniZinc -- in Haskell. module Interfaces.MZinHaskell -- | Interactively runs a model and outputs its solution(s). The function -- first prompts the user for the paths of the file in which the -- represented MiniZinc model will be printed and the data file if -- required. Then asks the user to choose between supported solvers and -- the desired number of solutions (only one or all supported for now). -- Finally, it uses the chosen solver and parses the solution(s). iTestModel :: MZModel -> IO () -- | Runs a model and parses its solution(s). testModel :: MZModel -> FilePath -> FilePath -> String -> String -> IO () -- | Writes the model's data file. The MZModel of the argument must -- contain only Assignment items. writeData :: MZModel -> IO ()