| 16784 |      1 | (*  Title:      HOL/Matrix/cplex/CplexMatrixConverter.ML
 | 
|  |      2 |     ID:         $Id$
 | 
|  |      3 |     Author:     Steven Obua
 | 
|  |      4 | *)
 | 
|  |      5 | 
 | 
|  |      6 | signature MATRIX_BUILDER =
 | 
|  |      7 | sig
 | 
|  |      8 |     type vector
 | 
|  |      9 |     type matrix
 | 
|  |     10 |     
 | 
|  |     11 |     val empty_vector : vector
 | 
|  |     12 |     val empty_matrix : matrix
 | 
|  |     13 | 		       
 | 
|  |     14 |     exception Nat_expected of int
 | 
|  |     15 |     val set_elem : vector -> int -> string -> vector			
 | 
|  |     16 |     val set_vector : matrix -> int -> vector -> matrix
 | 
|  |     17 | end;
 | 
|  |     18 | 
 | 
|  |     19 | signature CPLEX_MATRIX_CONVERTER = 
 | 
|  |     20 | sig
 | 
|  |     21 |     structure cplex : CPLEX
 | 
|  |     22 |     structure matrix_builder : MATRIX_BUILDER 
 | 
|  |     23 |     type vector = matrix_builder.vector
 | 
|  |     24 |     type matrix = matrix_builder.matrix
 | 
|  |     25 |     type naming = int * (int -> string) * (string -> int)
 | 
|  |     26 |     
 | 
|  |     27 |     exception Converter of string
 | 
|  |     28 | 
 | 
|  |     29 |     (* program must fulfill is_normed_cplexProg and must be an element of the image of elim_nonfree_bounds *)
 | 
|  |     30 |     (* convert_prog maximize c A b naming *)
 | 
|  |     31 |     val convert_prog : cplex.cplexProg -> bool * vector * matrix * vector * naming
 | 
|  |     32 | 
 | 
|  |     33 |     (* results must be optimal, converts_results returns the optimal value as string and the solution as vector *)
 | 
|  |     34 |     (* convert_results results name2index *)
 | 
|  |     35 |     val convert_results : cplex.cplexResult -> (string -> int) -> string * vector
 | 
|  |     36 | end;
 | 
|  |     37 | 
 | 
|  |     38 | functor MAKE_CPLEX_MATRIX_CONVERTER (structure cplex: CPLEX and matrix_builder: MATRIX_BUILDER) : CPLEX_MATRIX_CONVERTER =
 | 
|  |     39 | struct
 | 
|  |     40 | 
 | 
|  |     41 | structure cplex = cplex
 | 
|  |     42 | structure matrix_builder = matrix_builder
 | 
|  |     43 | type matrix = matrix_builder.matrix
 | 
|  |     44 | type vector = matrix_builder.vector		
 | 
|  |     45 | type naming = int * (int -> string) * (string -> int)
 | 
|  |     46 | 		     
 | 
|  |     47 | open matrix_builder 
 | 
|  |     48 | open cplex
 | 
|  |     49 |      
 | 
|  |     50 | exception Converter of string;
 | 
|  |     51 | 
 | 
|  |     52 | fun neg_term (cplexNeg t) = t
 | 
|  |     53 |   | neg_term (cplexSum ts) = cplexSum (map neg_term ts)
 | 
|  |     54 |   | neg_term t = cplexNeg t 
 | 
|  |     55 | 	      
 | 
|  |     56 | fun convert_prog (cplexProg (s, goal, constrs, bounds)) = 
 | 
|  |     57 |     let	
 | 
|  |     58 | 	fun build_naming index i2s s2i [] = (index, i2s, s2i)
 | 
|  |     59 | 	  | build_naming index i2s s2i (cplexBounds (cplexNeg cplexInf, cplexLeq, cplexVar v, cplexLeq, cplexInf)::bounds)
 | 
| 17412 |     60 | 	    = build_naming (index+1) (Inttab.update (index, v) i2s) (Symtab.update_new (v, index) s2i) bounds
 | 
| 16784 |     61 | 	  | build_naming _ _ _ _ = raise (Converter "nonfree bound")
 | 
|  |     62 | 
 | 
|  |     63 | 	val (varcount, i2s_tab, s2i_tab) = build_naming 0 Inttab.empty Symtab.empty bounds
 | 
|  |     64 | 
 | 
| 17412 |     65 | 	fun i2s i = case Inttab.lookup i2s_tab i of NONE => raise (Converter "index not found")
 | 
| 16784 |     66 | 						     | SOME n => n
 | 
| 17412 |     67 | 	fun s2i s = case Symtab.lookup s2i_tab s of NONE => raise (Converter ("name not found: "^s))
 | 
| 16784 |     68 | 						     | SOME i => i
 | 
|  |     69 | 	fun num2str positive (cplexNeg t) = num2str (not positive) t
 | 
|  |     70 | 	  | num2str positive (cplexNum num) = if positive then num else "-"^num			
 | 
|  |     71 | 	  | num2str _ _ = raise (Converter "term is not a (possibly signed) number")
 | 
|  |     72 | 
 | 
|  |     73 | 	fun setprod vec positive (cplexNeg t) = setprod vec (not positive) t  
 | 
|  |     74 | 	  | setprod vec positive (cplexVar v) = set_elem vec (s2i v) (if positive then "1" else "-1")
 | 
|  |     75 | 	  | setprod vec positive (cplexProd (cplexNum num, cplexVar v)) = 
 | 
|  |     76 | 	    set_elem vec (s2i v) (if positive then num else "-"^num)
 | 
|  |     77 | 	  | setprod _ _ _ = raise (Converter "term is not a normed product")	
 | 
|  |     78 | 
 | 
|  |     79 | 	fun sum2vec (cplexSum ts) = Library.foldl (fn (vec, t) => setprod vec true t) (empty_vector, ts)
 | 
|  |     80 | 	  | sum2vec t = setprod empty_vector true t						
 | 
|  |     81 | 
 | 
|  |     82 | 	fun constrs2Ab j A b [] = (A, b)
 | 
|  |     83 | 	  | constrs2Ab j A b ((_, cplexConstr (cplexLeq, (t1,t2)))::cs) = 
 | 
|  |     84 | 	    constrs2Ab (j+1) (set_vector A j (sum2vec t1)) (set_elem b j (num2str true t2)) cs
 | 
|  |     85 | 	  | constrs2Ab j A b ((_, cplexConstr (cplexGeq, (t1,t2)))::cs) = 
 | 
|  |     86 | 	    constrs2Ab (j+1) (set_vector A j (sum2vec (neg_term t1))) (set_elem b j (num2str true (neg_term t2))) cs
 | 
|  |     87 | 	  | constrs2Ab j A b ((_, cplexConstr (cplexEq, (t1,t2)))::cs) =
 | 
|  |     88 | 	    constrs2Ab j A b ((NONE, cplexConstr (cplexLeq, (t1,t2)))::
 | 
|  |     89 | 			      (NONE, cplexConstr (cplexGeq, (t1, t2)))::cs)
 | 
|  |     90 | 	  | constrs2Ab _ _ _ _ = raise (Converter "no strict constraints allowed")
 | 
|  |     91 | 
 | 
|  |     92 | 	val (A, b) = constrs2Ab 0 empty_matrix empty_vector constrs
 | 
|  |     93 | 								 
 | 
|  |     94 | 	val (goal_maximize, goal_term) = 
 | 
|  |     95 | 	    case goal of
 | 
|  |     96 | 		(cplexMaximize t) => (true, t)
 | 
|  |     97 | 	      | (cplexMinimize t) => (false, t)				     
 | 
|  |     98 |     in	  
 | 
|  |     99 | 	(goal_maximize, sum2vec goal_term, A, b, (varcount, i2s, s2i))
 | 
|  |    100 |     end
 | 
|  |    101 | 
 | 
|  |    102 | fun convert_results (cplex.Optimal (opt, entries)) name2index =
 | 
|  |    103 |     let
 | 
|  |    104 | 	fun setv (v, (name, value)) = (matrix_builder.set_elem v (name2index name) value) 
 | 
|  |    105 |     in
 | 
|  |    106 | 	(opt, Library.foldl setv (matrix_builder.empty_vector, entries))
 | 
|  |    107 |     end
 | 
|  |    108 |   | convert_results _ _ = raise (Converter "No optimal result")
 | 
|  |    109 |     
 | 
|  |    110 | 
 | 
|  |    111 | end;
 | 
|  |    112 | 
 | 
|  |    113 | structure SimpleMatrixBuilder : MATRIX_BUILDER = 
 | 
|  |    114 | struct
 | 
|  |    115 | type vector = (int * string) list
 | 
|  |    116 | type matrix = (int * vector) list
 | 
|  |    117 | 
 | 
|  |    118 | val empty_matrix = []
 | 
|  |    119 | val empty_vector = []
 | 
|  |    120 | 
 | 
|  |    121 | exception Nat_expected of int;
 | 
|  |    122 | 
 | 
|  |    123 | fun set_elem v i s = v @ [(i, s)] 
 | 
|  |    124 | 
 | 
|  |    125 | fun set_vector m i v = m @ [(i, v)]
 | 
|  |    126 |     
 | 
|  |    127 | end;	      
 | 
|  |    128 | 
 | 
|  |    129 | 
 | 
|  |    130 | 
 | 
|  |    131 | structure SimpleCplexMatrixConverter = MAKE_CPLEX_MATRIX_CONVERTER(structure cplex = Cplex and matrix_builder = SimpleMatrixBuilder);
 | 
|  |    132 | 
 | 
|  |    133 | 
 | 
|  |    134 | 
 | 
|  |    135 | 
 |