]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic/cicParser2.ml
New experimental commit: metavariables representation is changed again,
[helm.git] / helm / ocaml / cic / cicParser2.ml
index 0dbf9f41075c9075847247d01d2fe89f9d55d66e..4865c6e4a584fcb82bf05e2bb300cd549353e9e6 100644 (file)
@@ -118,6 +118,15 @@ let bool_of_attr a =
  bool_of_string (string_of_attr a)
 ;;
 
+let name_of_attr a =
+ let module T = Pxp_types in
+ let module C = Cic in
+  match a with
+     T.Value s -> C.Name s
+   | T.Implied_value -> C.Anonimous
+   | _ -> raise (IllFormedXml 0)
+;;
+
 (* Other utility functions *)
 
 let get_content n =
@@ -142,9 +151,28 @@ let get_conjs_value_type l =
    match l with
       [] -> (c, v, t)
     | conj::tl when conj#node_type = D.T_element "Conjecture" ->
-       let no = int_of_attr (conj#attribute "no")
-       and typ = (get_content conj)#extension#to_cic_term in
-        rget ((no, typ)::c, v, t) tl
+       let no = int_of_attr (conj#attribute "no") in
+       let typ,canonical_context =
+        match List.rev (conj#sub_nodes) with
+           [] -> raise (IllFormedXml 13)
+         | typ::canonical_context ->
+            (get_content typ)#extension#to_cic_term,
+            List.map
+             (function n ->
+               match n#node_type with
+                  D.T_element "Decl" ->
+                   let name = name_of_attr (n#attribute "name") in
+                   let term = (get_content n)#extension#to_cic_term in
+                    Some (name,Cic.ADecl term)
+                | D.T_element "Def" ->
+                   let name = name_of_attr (n#attribute "name") in
+                   let term = (get_content n)#extension#to_cic_term in
+                    Some (name,Cic.ADef term)
+                | D.T_element "Hidden" -> None
+                | _ -> raise (IllFormedXml 14)
+             ) canonical_context
+       in
+        rget ((no, canonical_context, typ)::c, v, t) tl
     | value::tl when value#node_type = D.T_element "body" ->
        let v' = (get_content value)#extension#to_cic_term in
         (match v with
@@ -160,7 +188,7 @@ let get_conjs_value_type l =
     | _ -> raise (IllFormedXml 4)
  in
   match rget ([], None, None) l with
-     (c, Some v, Some t) -> (c, v, t)
+     (revc, Some v, Some t) -> (List.rev revc, v, t)
    | _ -> raise (IllFormedXml 5)
 ;;