]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_annotations/cicXPath.ml
Initial revision
[helm.git] / helm / ocaml / cic_annotations / cicXPath.ml
index 1eaf31f4e97611319a3e8759c7297a51e014104f..f2cb0ed409e4316155ab5036b0f868bbde9eea32 100644 (file)
@@ -42,6 +42,8 @@ let get_annotation ids_to_annotations xpath =
 
 exception MoreThanOneTargetFor of Cic.id;;
 
+(* creates a hashtable mapping each unique id to a node of the annotated 
+object *)
 let get_ids_to_targets annobj =
  let module C = Cic in
   let ids_to_targets = Hashtbl.create 503 in
@@ -56,7 +58,7 @@ let get_ids_to_targets annobj =
      match t with
         C.ARel (id,_,_)
       | C.AVar (id,_)
-      | C.AMeta (id,_)
+      | C.AMeta (id,_,_)
       | C.ASort (id,_)
       | C.AImplicit id ->
          set_target id (C.Term t)
@@ -74,7 +76,6 @@ let get_ids_to_targets annobj =
          set_target id (C.Term t) ;
          List.iter add_target_term l
       | C.AConst (id,_,_)
-      | C.AAbst (id,_)
       | C.AMutInd (id,_,_,_)
       | C.AMutConstruct (id,_,_,_,_) ->
          set_target id (C.Term t)
@@ -114,7 +115,17 @@ let get_ids_to_targets annobj =
          add_target_term ty
       | C.ACurrentProof (id,_,cl,bo,ty) ->
          set_target id (C.Object annobj) ;
-         List.iter (function (_,t) -> add_target_term t) cl ;
+         List.iter (function (cid,_,context, t) as annconj ->
+           set_target cid (C.Conjecture annconj) ;
+          List.iter 
+            (function ((hid,h) as annhyp) ->
+               set_target hid (C.Hypothesis annhyp) ;
+               match h with
+                 Some (_,C.ADecl at) -> add_target_term at
+               | Some (_,C.ADef at) -> add_target_term at
+               | None -> ()
+            ) context;
+          add_target_term t) cl ;
          add_target_term bo ;
          add_target_term ty
       | C.AInductiveDefinition (id,itl,_,_) ->