let rec aux context term =
match (context, term) with
| Cic.Implicit (Some `Hole), t -> [t]
+ | Cic.Implicit None,_ -> []
| Cic.Meta (_, ctxt1), Cic.Meta (_, ctxt2) ->
List.concat
(List.map2
let regexp blank = [ ' ' '\t' '\n' ]
let regexp paren = [ '(' '[' '{' ')' ']' '}' ]
let regexp implicit = '?'
+let regexp placeholder = '%'
let regexp symbol_char =
[^ 'a' - 'z' 'A' - 'Z' '0' - '9'
' ' '\t' '\n'
| paren -> return lexbuf ("PAREN", Ulexing.utf8_lexeme lexbuf)
| meta -> return lexbuf ("META", Ulexing.utf8_lexeme lexbuf)
| implicit -> return lexbuf ("IMPLICIT", Ulexing.utf8_lexeme lexbuf)
+ | placeholder -> return lexbuf ("PLACEHOLDER", Ulexing.utf8_lexeme lexbuf)
| qstring ->
return lexbuf ("QSTRING", remove_quotes (Ulexing.utf8_lexeme lexbuf))
| symbol -> return lexbuf ("SYMBOL", Ulexing.utf8_lexeme lexbuf)
| n = substituted_name -> return_term loc n
| i = NUM -> return_term loc (CicAst.Num (i, (fresh_num_instance ())))
| IMPLICIT -> return_term loc CicAst.Implicit
+ | PLACEHOLDER -> return_term loc CicAst.UserInput
| m = META;
substs = [
PAREN "["; substs = LIST0 meta_subst SEP SYMBOL ";" ; PAREN "]" ->
reduction_kind: [
[ [ IDENT "reduce" ] -> `Reduce
| [ IDENT "simplify" ] -> `Simpl
- | [ IDENT "whd" ] -> `Whd ]
+ | [ IDENT "whd" ] -> `Whd
+ | [ IDENT "normalize" ] -> `Normalize ]
];
tactic: [
[ [ IDENT "absurd" ]; t = tactic_term ->
| None, terms -> TacticAst.Reduce (loc, kind, Some (terms, `Goal))
| Some pat, [] -> fail loc "Missing term [list]"
| Some pat, terms -> TacticAst.Reduce (loc, kind, Some (terms, pat)))
+ | kind = reduction_kind; where = IDENT ; IDENT "at" ; pat = term ->
+ TacticAst.ReduceAt (loc, kind, where, pat)
| [ IDENT "reflexivity" ] ->
TacticAst.Reflexivity loc
| [ IDENT "replace" ];
CicEnvironment.CircularDependency _ ->
raise DisambiguateChoices.Invalid_choice))
| CicAst.Implicit -> Cic.Implicit None
+ | CicAst.UserInput -> Cic.Implicit (Some `Hole)
+(* | CicAst.UserInput -> assert false*)
| CicAst.Num (num, i) -> resolve env (Num i) ~num ()
| CicAst.Meta (index, subst) ->
let cic_subst =
| CicAst.Sort `CProp -> Cic.Sort Cic.CProp
| CicAst.Symbol (symbol, instance) ->
resolve env (Symbol (symbol, instance)) ()
- | CicAst.UserInput -> assert false
and aux_option loc context = function
| None -> Cic.Implicit (Some `Type)
| Some term -> aux loc context term
exception NoWellTypedInterpretation
+val interpretate:
+ context:Cic.name list ->
+ env:DisambiguateTypes.environment ->
+ CicAst.term -> Cic.term
+
module type Disambiguator =
sig
val disambiguate_term :
type term =
| AttributedTerm of term_attribute * term
-
| Appl of term list
| Binder of binder_kind * capture_variable * term (* kind, name, body *)
| Case of term * string option * term option * (case_pattern * term) list
*)
type direction = [ `Left | `Right ]
-type reduction_kind = [ `Reduce | `Simpl | `Whd ]
+type reduction_kind = [ `Reduce | `Simpl | `Whd | `Normalize ]
(* type 'term pattern = Pattern of 'term *)
(* everywhere includes goal and hypotheses *)
| LetIn of loc * 'term * 'ident
(* | Named_intros of loc * 'ident list (* joined with Intros above *) *)
(* | Reduce of loc * reduction_kind * 'term pattern * 'ident option (* what, where *) *)
+ | ReduceAt of loc * reduction_kind * 'ident * 'term
| Reduce of loc * reduction_kind * ('term list * 'term pattern) option
(* kind, (what, where)
* if second argument is None, reduction is applied to the current goal,
| `Reduce -> "reduce"
| `Simpl -> "simplify"
| `Whd -> "whd"
+ | `Normalize -> "normalize"
let dummy_tbl = Hashtbl.create 0
| `Reduce -> "reduce"
| `Simpl -> "simplify"
| `Whd -> "whd"
+ | `Normalize -> "normalize"
let rec pp_tactic = function
| Absurd (_, term) -> "absurd" ^ pp_term_ast term
mk_tactic ( reduction_tac ~reduction:CicReduction.whd
~also_in_hypotheses ~terms);;
+let normalize_tac ~also_in_hypotheses ~terms =
+ mk_tactic ( reduction_tac ~reduction:CicReduction.normalize
+ ~also_in_hypotheses ~terms);;
+
let fold_tac ~reduction ~also_in_hypotheses ~term =
let fold_tac ~reduction ~also_in_hypotheses ~term (proof,goal) =
let curi,metasenv,pbo,pty = proof in
val whd_tac:
also_in_hypotheses:bool -> terms:(Cic.term list option) ->
ProofEngineTypes.tactic
+val normalize_tac:
+ also_in_hypotheses:bool -> terms:(Cic.term list option) ->
+ ProofEngineTypes.tactic
val fold_tac:
reduction:(Cic.context -> Cic.term -> Cic.term) ->
let symmetry = EqualityTactics.symmetry_tac
let transitivity = EqualityTactics.transitivity_tac
let whd = ReductionTactics.whd_tac
-
+let normalize = ReductionTactics.normalize_tac
val whd :
also_in_hypotheses:bool ->
terms:Cic.term list option -> ProofEngineTypes.tactic
+val normalize :
+ also_in_hypotheses:bool ->
+ terms:Cic.term list option -> ProofEngineTypes.tactic