2 ref (fun ~context ~subst ~metasenv ?inside_fix t -> "Please, set a pp callback")
5 let set_ppterm f = ppterm := f;;
7 let ppterm ~context ~subst ~metasenv ?inside_fix t =
8 !ppterm ~context ~subst ~metasenv ?inside_fix t
14 let r2s pp_fix_name r =
17 | R.Ref (_,u,R.Ind i) ->
18 (match snd(NCicEnvironment.get_obj u) with
19 | _,_,_,_, C.Inductive (_,_,itl,_) ->
20 let _,name,_,_ = List.nth itl i in name
22 | R.Ref (_,u,R.Con (i,j)) ->
23 (match snd(NCicEnvironment.get_obj u) with
24 | _,_,_,_, C.Inductive (_,_,itl,_) ->
25 let _,_,_,cl = List.nth itl i in
26 let _,name,_ = List.nth cl (j-1) in name
28 | R.Ref (_,u,(R.Decl | R.Def )) ->
29 (match snd(NCicEnvironment.get_obj u) with
30 | _,_,_,_, C.Constant (_,name,_,_,_) -> name
32 | R.Ref (_,u,(R.Fix (i,_)|R.CoFix i)) ->
33 (match snd(NCicEnvironment.get_obj u) with
34 | _,_,_,_, C.Fixpoint (_,fl,_) ->
36 let _,name,_,_,_ = List.nth fl i in name
38 let name = NUri.string_of_uri u in
39 let name = Filename.basename name in
40 let name = Filename.chop_extension name in
41 name ^"("^ string_of_int i ^ ")"
43 with exn -> R.string_of_reference r
46 let trivial_pp_term ~context ~subst ~metasenv ?(inside_fix=false) t =
47 let buff = Buffer.create 100 in
48 let f = Format.formatter_of_buffer buff in
49 let module F = Format in
50 let rec aux ?(toplevel=false) ctx = function
53 let name = List.nth ctx (m-1) in
54 F.fprintf f "%s" (if name = "_" then "__"^string_of_int m else name)
55 with Failure _ -> F.fprintf f " -%d" (m - List.length context))
56 | C.Const r -> F.fprintf f "%s" (r2s inside_fix r)
58 if not toplevel then F.fprintf f "(";
59 F.fprintf f "@[<hov 1>";
60 aux ~toplevel:true ctx s;
62 aux ~toplevel:true ("_"::ctx) t;
64 if not toplevel then F.fprintf f ")";
65 | C.Prod (name,s,t) ->
66 if not toplevel then F.fprintf f "(";
67 F.fprintf f "@[<hov 1>";
68 F.fprintf f "@[<hov 2>∀%s:@;" name;
69 aux ~toplevel:true ctx s;
71 aux ~toplevel:true (name::ctx) t;
73 if not toplevel then F.fprintf f ")";
74 | C.Lambda (name,s,t) ->
75 if not toplevel then F.fprintf f "(";
76 F.fprintf f "@[<hov 1>";
77 F.fprintf f "λ%s:" name;
78 aux ~toplevel:true ctx s;
80 aux ~toplevel:true (name::ctx) t;
82 if not toplevel then F.fprintf f ")";
83 | C.LetIn (name,ty,t,b) ->
84 if not toplevel then F.fprintf f "(";
85 F.fprintf f "@[<hov 1>";
86 F.fprintf f "let %s:@;" name;
87 aux ~toplevel:true ctx ty;
89 aux ~toplevel:true ctx t;
91 (aux ~toplevel:true (name::ctx) b);
93 if not toplevel then F.fprintf f ")";
94 | C.Match (r,oty,t,pl) ->
95 F.fprintf f "@[<hov>match ";
96 aux ~toplevel:true ctx t;
97 F.fprintf f "@;return ";
98 aux ~toplevel:true ctx oty;
99 F.fprintf f "@; @[<v>[ ";
102 F.fprintf f "@[<hov 2>%s ⇒@;" (r2s inside_fix (R.mk_constructor 1 r));
103 aux ~toplevel:true ctx (List.hd pl);
105 ignore(List.fold_left
107 F.fprintf f "@;| @[<hov 2>%s ⇒@;" (r2s inside_fix (R.mk_constructor i r));
108 aux ~toplevel:true ctx t;
113 F.fprintf f "]@] @]";
115 F.fprintf f "@[<hov 2>";
116 if not toplevel then F.fprintf f "(";
118 List.iter (fun x -> F.fprintf f "@;";aux ctx x) (List.tl l);
119 if not toplevel then F.fprintf f ")";
121 | C.Implicit _ -> F.fprintf f "?"
122 | C.Meta (n,_) -> F.fprintf f "?%d" n
123 | C.Sort C.Prop -> F.fprintf f "Prop"
124 | C.Sort C.CProp -> F.fprintf f "CProp"
125 | C.Sort (C.Type n) -> F.fprintf f "Type%d" n
127 aux ~toplevel:true (List.map fst context) t;
133 | (u,_,metasenv,subst,NCic.Fixpoint (b, fl, _)) ->
134 "{"^NUri.string_of_uri u^"}\n"^
136 String.concat "\nand "
137 (List.map (fun (_,name,n,ty,bo) ->
138 name^ " on " ^ string_of_int n ^ " : " ^
139 ppterm ~metasenv ~subst ~context:[] ty ^ " :=\n"^
140 ppterm ~metasenv ~subst ~context:[] ~inside_fix:true bo) fl)
141 | (u,_,metasenv,subst,NCic.Inductive (b, leftno,tyl, _)) ->
142 "{"^NUri.string_of_uri u^"} with "^string_of_int leftno^" fixed params\n"^
144 String.concat "\nand "
145 (List.map (fun (_,name,ty,cl) ->
146 name^": "^ppterm ~metasenv ~subst ~context:[] ty^ " :=\n"^
148 (List.map (fun (_,name,ty) ->
149 " | "^name^": "^ppterm ~metasenv ~subst ~context:[] ty)
151 | (u,_,metasenv,subst,NCic.Constant (_,name,None,ty, _)) ->
152 "{"^NUri.string_of_uri u^"}\n"^
153 "axiom " ^ name ^ " : " ^
154 ppterm ~metasenv ~subst ~context:[] ty ^ "\n"
155 | (u,_,metasenv,subst,NCic.Constant (_,name,Some bo,ty, _)) ->
156 "{"^NUri.string_of_uri u^"}\n"^
157 "definition " ^ name ^ " : " ^
158 ppterm ~metasenv ~subst ~context:[] ty ^ " := \n"^
159 ppterm ~metasenv ~subst ~context:[] bo ^ "\n"