(* let tactic = Grammar.Entry.create grammar "tactic" *)
 (* let tactical = Grammar.Entry.create grammar "tactical" *)
 
-let return_term loc term = CicTextualParser2Ast.LocatedTerm (loc, term)
+let return_term loc term =
+  CicTextualParser2Ast.AttributedTerm (`Loc loc, term)
 (* let return_term loc term = term *)
 
 let fail (x, y) msg =
 
 type induction_kind = [ `Inductive | `CoInductive ]
 type sort_kind = [ `Prop | `Set | `Type | `CProp ]
 
+type term_attribute =
+  [ `Loc of location  (* source file location *)
+  | `IdRef of string  (* ACic pointer *)
+  ]
+
 type term =
-  | LocatedTerm of location * term
+  | AttributedTerm of term_attribute * term
 
   | Appl of term list
   | Appl_symbol of string * int * term list (* literal, instance, args *)
 
   | name, None -> pp_name name
   | name, Some typ -> "(" ^ pp_name name ^ ": " ^ pp_term typ ^ ")"
 and pp_term = function
-  | LocatedTerm ((p_begin, p_end), term) ->
-(*       sprintf "[%d,%d]%s" p_begin p_end (pp_term term) *)
-      pp_term term
+  | AttributedTerm (_, term) -> pp_term term
 
   | Appl terms -> sprintf "(%s)" (String.concat " " (List.map pp_term terms))
   | Appl_symbol (symbol, _, terms) ->
 
 
 let interpretate ~context ~env ast =
   let rec aux loc context = function
-    | CicTextualParser2Ast.LocatedTerm (loc, term) -> aux loc context term
+    | CicTextualParser2Ast.AttributedTerm (`Loc loc, term) ->
+        aux loc context term
+    | CicTextualParser2Ast.AttributedTerm (_, term) -> aux loc context term
     | CicTextualParser2Ast.Appl terms ->
         Cic.Appl (List.map (aux loc context) terms)
     | CicTextualParser2Ast.Appl_symbol (symb, i, args) ->
     | Some term -> aux loc context term
   in
   match ast with
-  | CicTextualParser2Ast.LocatedTerm (loc, term) -> aux loc context term
+  | CicTextualParser2Ast.AttributedTerm (`Loc loc, term) -> aux loc context term
   | _ -> assert false
 
 let domain_of_term ~context ast =
   let rec aux loc context = function
-    | CicTextualParser2Ast.LocatedTerm (_, term) -> aux loc context term
+    | CicTextualParser2Ast.AttributedTerm (`Loc loc, term) ->
+        aux loc context term
+    | CicTextualParser2Ast.AttributedTerm (_, term) -> aux loc context term
     | CicTextualParser2Ast.Appl terms ->
         List.fold_left (fun dom term -> Domain.union dom (aux loc context term))
           Domain.empty terms
     | Some t -> aux loc context t
   in
   match ast with
-  | CicTextualParser2Ast.LocatedTerm (loc, term) -> aux loc context term
+  | CicTextualParser2Ast.AttributedTerm (`Loc loc, term) -> aux loc context term
   | _ -> assert false
 
 module Make (C: Callbacks) =