]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic/deannotate.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / cic / deannotate.ml
index 2bee18d6f161e3c82c88c0e1d64fcd7f64df5204..21e591d4e20cbe4e39b1726296cb55769e57e0f6 100644 (file)
@@ -43,7 +43,7 @@ let rec deannotate_term =
       in
        C.Meta (n, l')
    | C.ASort (_,s) -> C.Sort s
-   | C.AImplicit _ -> C.Implicit
+   | C.AImplicit (_, annotation) -> C.Implicit annotation
    | C.ACast (_,va,ty) -> C.Cast (deannotate_term va, deannotate_term ty)
    | C.AProd (_,name,so,ta) ->
       C.Prod (name, deannotate_term so, deannotate_term ta)
@@ -90,15 +90,15 @@ let deannotate_inductiveType (_, name, isinductive, arity, cons) =
 let deannotate_obj =
  let module C = Cic in
   function
-     C.AConstant (_, _, id, bo, ty, params) ->
+     C.AConstant (_, _, id, bo, ty, params, attrs) ->
       C.Constant (id,
        (match bo with None -> None | Some bo -> Some (deannotate_term bo)),
-       deannotate_term ty, params)
-   | C.AVariable (_, name, bo, ty, params) ->
+       deannotate_term ty, params, attrs)
+   | C.AVariable (_, name, bo, ty, params, attrs) ->
       C.Variable (name,
        (match bo with None -> None | Some bo -> Some (deannotate_term bo)),
-       deannotate_term ty, params)
-   | C.ACurrentProof (_, _, name, conjs, bo, ty, params) ->
+       deannotate_term ty, params, attrs)
+   | C.ACurrentProof (_, _, name, conjs, bo, ty, params, attrs) ->
       C.CurrentProof (
        name,
         List.map
@@ -116,9 +116,9 @@ let deannotate_obj =
             in
             (id,context,deannotate_term con) 
          ) conjs,
-       deannotate_term bo,deannotate_term ty,params
+       deannotate_term bo,deannotate_term ty, params, attrs
       )
-   | C.AInductiveDefinition (_, tys, params, parno) ->
+   | C.AInductiveDefinition (_, tys, params, parno, attrs) ->
       C.InductiveDefinition (List.map deannotate_inductiveType tys,
-       params, parno)
+       params, parno, attrs)
 ;;