]> matita.cs.unibo.it Git - helm.git/blob - helm/software/matita/library/didactic/support/natural_deduction.ma
fixed or-in-left
[helm.git] / helm / software / matita / library / didactic / support / natural_deduction.ma
1 (* Logic system *)
2
3 inductive Imply (A,B:CProp) : CProp ≝
4 | Imply_intro: (A → B) → Imply A B.
5  
6 definition Imply_elim ≝ λA,B.λf:Imply A B. λa:A.
7   match f with [ Imply_intro g ⇒ g a].
8
9 inductive And (A,B:CProp) : CProp ≝
10 | And_intro: A → B → And A B.
11
12 definition And_elim_l ≝ λA,B.λc:And A B.
13   match c with [ And_intro a b ⇒ a ].
14
15 definition And_elim_r ≝ λA,B.λc:And A B.
16   match c with [ And_intro a b ⇒ b ].
17
18 inductive Or (A,B:CProp) : CProp ≝
19 | Or_intro_l: A → Or A B
20 | Or_intro_r: B → Or A B. 
21  
22 definition Or_elim ≝ λA,B,C:CProp.λc:Or A B.λfa: A → C.λfb: B → C.
23   match c with 
24   [ Or_intro_l a ⇒ fa a 
25   | Or_intro_r b ⇒ fb b].
26
27 inductive Top : CProp := 
28 | Top_intro : Top.
29
30 inductive Bot : CProp := .
31
32 definition Bot_elim ≝ λP:CProp.λx:Bot.
33   match x in Bot return λx.P with []. 
34
35 definition Not := λA:CProp.Imply A Bot.
36
37 definition Not_intro : ∀A.(A → Bot) → Not A ≝  λA. 
38   Imply_intro A Bot.
39
40 definition Not_elim : ∀A.Not A → A → Bot ≝ λA. 
41   Imply_elim ? Bot.  
42
43 definition Discharge := λA:CProp.λa:A.
44   a.
45
46 axiom Raa : ∀A.(Not A → Bot) → A.
47
48 (* Dummy proposition *)
49 axiom unit : CProp.
50
51 (* Notations *)
52 notation "hbox(a break ⇒ b)" right associative with precedence 20 
53 for @{ 'Imply $a $b }.
54 interpretation "Imply" 'Imply a b = (Imply a b).
55 interpretation "constructive or" 'or x y = (Or x y).
56 interpretation "constructive and" 'and x y = (And x y).
57 notation "⊤" non associative with precedence 90 for @{'Top}.
58 interpretation "Top" 'Top = Top.
59 notation "⊥" non associative with precedence 90 for @{'Bot}.
60 interpretation "Bot" 'Bot = Bot.
61 interpretation "Not" 'not a = (Not a).
62 notation "✶" non associative with precedence 90 for @{'unit}.
63 interpretation "dummy prop" 'unit = unit.
64
65 (* Variables *)
66 axiom A : CProp.
67 axiom B : CProp.
68 axiom C : CProp.
69 axiom D : CProp.
70 axiom E : CProp.
71 axiom F : CProp.
72 axiom G : CProp.
73 axiom H : CProp.
74 axiom I : CProp.
75 axiom J : CProp.
76 axiom K : CProp.
77 axiom L : CProp.
78 axiom M : CProp.
79 axiom N : CProp.
80 axiom O : CProp.
81 axiom P : CProp.
82 axiom Q : CProp.
83 axiom R : CProp.
84 axiom S : CProp.
85 axiom T : CProp.
86 axiom U : CProp.
87 axiom V : CProp.
88 axiom W : CProp.
89 axiom X : CProp.
90 axiom Y : CProp.
91 axiom Z : CProp.
92
93 (* Every formula user provided annotates its proof:
94    `A` becomes `(show A ?)` *)
95 definition show : ∀A.A→A ≝ λA:CProp.λa:A.a.
96
97 (* When something does not fit, this daemon is used *)
98 axiom cast: ∀A,B:CProp.B → A.
99
100 (* begin a proof: draws the root *)
101 notation > "'prove' p" non associative with precedence 19 
102 for @{ 'prove $p }.
103 interpretation "prove KO" 'prove p = (cast _ _ (show p _)).
104 interpretation "prove OK" 'prove p = (show p _).
105
106 (* Leaves *)
107 notation < "\infrule (t\atop ⋮) a ?" with precedence 19
108 for @{ 'leaf_ok $a $t }.
109 interpretation "leaf OK" 'leaf_ok a t = (show a t).
110 notation < "\infrule (t\atop ⋮) mstyle color #ff0000 (a) ?" with precedence 19 
111 for @{ 'leaf_ko $a $t }.
112 interpretation "leaf KO" 'leaf_ko a t = (cast _ _ (show a t)).
113
114 (* discharging *)
115 notation < "[ a ] \sup mstyle color #ff0000 (H)" with precedence 19 
116 for @{ 'discharge_ko_1 $a $H }.
117 interpretation "discharge_ko_1" 'discharge_ko_1 a H = 
118   (show a (cast _ _ (Discharge _ H))).
119 notation < "[ mstyle color #ff0000 (a) ] \sup mstyle color #ff0000 (H)" with precedence 19 
120 for @{ 'discharge_ko_2 $a $H }.
121 interpretation "discharge_ko_2" 'discharge_ko_2 a H = 
122   (cast _ _ (show a (cast _ _ (Discharge _ H)))).
123
124 notation < "[ a ] \sup H" with precedence 19 
125 for @{ 'discharge_ok_1 $a $H }.
126 interpretation "discharge_ok_1" 'discharge_ok_1 a H = 
127   (show a (Discharge _ H)).
128 notation < "[ mstyle color #ff0000 (a) ] \sup H" with precedence 19 
129 for @{ 'discharge_ok_2 $a $H }.
130 interpretation "discharge_ok_2" 'discharge_ok_2 a H = 
131   (cast _ _ (show a (Discharge _ H))).
132
133 notation > "'discharge' [H]" with precedence 19 
134 for @{ 'discharge $H }.
135 interpretation "discharge KO" 'discharge H = (cast _ _ (Discharge _ H)).
136 interpretation "discharge OK" 'discharge H = (Discharge _ H).
137
138 (* ⇒ introduction *)
139 notation < "\infrule hbox(\emsp b \emsp) ab (mstyle color #ff0000 (⇒\sub\i \emsp) ident H) " with precedence 19
140 for @{ 'Imply_intro_ko_1 $ab (λ${ident H}:$p.$b) }.
141 interpretation "Imply_intro_ko_1" 'Imply_intro_ko_1 ab \eta.b = 
142   (show ab (cast _ _ (Imply_intro _ _ b))).
143
144 notation < "\infrule hbox(\emsp b \emsp) mstyle color #ff0000 (ab) (mstyle color #ff0000 (⇒\sub\i \emsp) ident H) " with precedence 19
145 for @{ 'Imply_intro_ko_2 $ab (λ${ident H}:$p.$b) }.
146 interpretation "Imply_intro_ko_2" 'Imply_intro_ko_2 ab \eta.b = 
147   (cast _ _ (show ab (cast _ _ (Imply_intro _ _ b)))).
148
149 notation < "\infrule hbox(\emsp b \emsp) ab (⇒\sub\i \emsp ident H) " with precedence 19
150 for @{ 'Imply_intro_ok_1 $ab (λ${ident H}:$p.$b) }.
151 interpretation "Imply_intro_ok_1" 'Imply_intro_ok_1 ab \eta.b = 
152   (show ab (Imply_intro _ _ b)).
153
154 notation < "\infrule hbox(\emsp b \emsp) mstyle color #ff0000 (ab) (⇒\sub\i \emsp ident H) " with precedence 19
155 for @{ 'Imply_intro_ok_2 $ab (λ${ident H}:$p.$b) }.
156 interpretation "Imply_intro_ok_2" 'Imply_intro_ok_2 ab \eta.b = 
157   (cast _ _ (show ab (Imply_intro _ _ b))).
158
159 notation > "⇒_'i' [ident H] term 90 b" with precedence 19
160 for @{ 'Imply_intro $b (λ${ident H}.show $b ?) }.
161 interpretation "Imply_intro KO" 'Imply_intro b pb = 
162   (cast _ (Imply unit b) (Imply_intro _ b pb)).
163 interpretation "Imply_intro OK" 'Imply_intro b pb = 
164   (Imply_intro _ b pb).
165
166 (* ⇒ elimination *)
167 notation < "\infrule hbox(\emsp ab \emsp\emsp\emsp a\emsp) b mstyle color #ff0000 (⇒\sub\e) " with precedence 19
168 for @{ 'Imply_elim_ko_1 $ab $a $b }.
169 interpretation "Imply_elim_ko_1" 'Imply_elim_ko_1 ab a b = 
170   (show b (cast _ _ (Imply_elim _ _ (cast _ _ ab) (cast _ _ a)))).
171
172 notation < "\infrule hbox(\emsp ab \emsp\emsp\emsp a\emsp) mstyle color #ff0000 (b) mstyle color #ff0000 (⇒\sub\e) " with precedence 19 
173 for @{ 'Imply_elim_ko_2 $ab $a $b }.
174 interpretation "Imply_elim_ko_2" 'Imply_elim_ko_2 ab a b = 
175   (cast _ _ (show b (cast _ _ (Imply_elim _ _ (cast _ _ ab) (cast _ _ a))))).
176
177 notation < "\infrule hbox(\emsp ab \emsp\emsp\emsp a\emsp) b (⇒\sub\e) " with precedence 19 
178 for @{ 'Imply_elim_ok_1 $ab $a $b }.
179 interpretation "Imply_elim_ok_1" 'Imply_elim_ok_1 ab a b = 
180   (show b (Imply_elim _ _ ab a)).
181
182 notation < "\infrule hbox(\emsp ab \emsp\emsp\emsp a\emsp) mstyle color #ff0000 (b) (⇒\sub\e) " with precedence 19 
183 for @{ 'Imply_elim_ok_2 $ab $a $b }.
184 interpretation "Imply_elim_ok_2" 'Imply_elim_ok_2 ab a b = 
185   (cast _ _ (show b (Imply_elim _ _ ab a))).
186
187 notation > "⇒_'e' term 90 ab term 90 a" with precedence 19 
188 for @{ 'Imply_elim (show $ab ?) (show $a ?) }.
189 interpretation "Imply_elim KO" 'Imply_elim ab a = 
190   (cast _ _ (Imply_elim _ _ (cast (Imply unit unit) _ ab) (cast unit _ a))).
191 interpretation "Imply_elim OK" 'Imply_elim ab a = 
192   (Imply_elim _ _ ab a). 
193
194 (* ∧ introduction *)
195 notation < "\infrule hbox(\emsp a \emsp\emsp\emsp b \emsp) ab mstyle color #ff0000 (∧\sub\i)" with precedence 19 
196 for @{ 'And_intro_ko_1 $a $b $ab }.
197 interpretation "And_intro_ko_1" 'And_intro_ko_1 a b ab = 
198   (show ab (cast _ _ (And_intro _ _ a b))).
199
200 notation < "\infrule hbox(\emsp a \emsp\emsp\emsp b \emsp) mstyle color #ff0000 (ab) mstyle color #ff0000 (∧\sub\i)" with precedence 19 
201 for @{ 'And_intro_ko_2 $a $b $ab }.
202 interpretation "And_intro_ko_2" 'And_intro_ko_2 a b ab = 
203   (cast _ _ (show ab (cast _ _ (And_intro _ _ a b)))).
204
205 notation < "\infrule hbox(\emsp a \emsp\emsp\emsp b \emsp) ab (∧\sub\i)" with precedence 19 
206 for @{ 'And_intro_ok_1 $a $b $ab }.
207 interpretation "And_intro_ok_1" 'And_intro_ok_1 a b ab = 
208   (show ab (And_intro _ _ a b)).
209
210 notation < "\infrule hbox(\emsp a \emsp\emsp\emsp b \emsp) mstyle color #ff0000 (ab) (∧\sub\i)" with precedence 19 
211 for @{ 'And_intro_ok_2 $a $b $ab }.
212 interpretation "And_intro_ok_2" 'And_intro_ok_2 a b ab = 
213   (cast _ _ (show ab (And_intro _ _ a b))).
214
215 notation > "∧_'i' term 90 a term 90 b" with precedence 19 
216 for @{ 'And_intro (show $a ?) (show $b ?) }.
217 interpretation "And_intro KO" 'And_intro a b = (cast _ _ (And_intro _ _ a b)).
218 interpretation "And_intro OK" 'And_intro a b = (And_intro _ _ a b).
219
220 (* ∧ elimination *)
221 notation < "\infrule hbox(\emsp ab \emsp) a mstyle color #ff0000 (∧\sub(\e_\l))" with precedence 19 
222 for @{ 'And_elim_l_ko_1 $ab $a }.
223 interpretation "And_elim_l_ko_1" 'And_elim_l_ko_1 ab a = 
224   (show a (cast _ _ (And_elim_l _ _ (cast _ _ ab)))).
225
226 notation < "\infrule hbox(\emsp ab \emsp) mstyle color #ff0000 (a) mstyle color #ff0000 (∧\sub(\e_\l))" with precedence 19 
227 for @{ 'And_elim_l_ko_2 $ab $a }.
228 interpretation "And_elim_l_ko_2" 'And_elim_l_ko_2 ab a = 
229   (cast _ _ (show a (cast _ _ (And_elim_l _ _ (cast _ _ ab))))).
230
231 notation < "\infrule hbox(\emsp ab \emsp) a (∧\sub(\e_\l))" with precedence 19 
232 for @{ 'And_elim_l_ok_1 $ab $a }.
233 interpretation "And_elim_l_ok_1" 'And_elim_l_ok_1 ab a = 
234   (show a (And_elim_l _ _ ab)).
235
236 notation < "\infrule hbox(\emsp ab \emsp) mstyle color #ff0000 (a) (∧\sub(\e_\l))" with precedence 19 
237 for @{ 'And_elim_l_ok_2 $ab $a }.
238 interpretation "And_elim_l_ok_2" 'And_elim_l_ok_2 ab a = 
239   (cast _ _ (show a (And_elim_l _ _ ab))).
240
241 notation > "∧_'e_l' term 90 ab" with precedence 19
242 for @{ 'And_elim_l (show $ab ?) }.
243 interpretation "And_elim_l KO" 'And_elim_l a = (cast _ _ (And_elim_l _ _ (cast (And unit unit) _ a))).
244 interpretation "And_elim_l OK" 'And_elim_l a = (And_elim_l _ _ a).
245
246 notation < "\infrule hbox(\emsp ab \emsp) a mstyle color #ff0000 (∧\sub(\e_\r))" with precedence 19 
247 for @{ 'And_elim_r_ko_1 $ab $a }.
248 interpretation "And_elim_r_ko_1" 'And_elim_r_ko_1 ab a = 
249   (show a (cast _ _ (And_elim_r _ _ (cast _ _ ab)))).
250
251 notation < "\infrule hbox(\emsp ab \emsp) mstyle color #ff0000 (a) mstyle color #ff0000 (∧\sub(\e_\r))" with precedence 19 
252 for @{ 'And_elim_r_ko_2 $ab $a }.
253 interpretation "And_elim_r_ko_2" 'And_elim_r_ko_2 ab a = 
254   (cast _ _ (show a (cast _ _ (And_elim_r _ _ (cast _ _ ab))))).
255
256 notation < "\infrule hbox(\emsp ab \emsp) a (∧\sub(\e_\r))" with precedence 19 
257 for @{ 'And_elim_r_ok_1 $ab $a }.
258 interpretation "And_elim_r_ok_1" 'And_elim_r_ok_1 ab a = 
259   (show a (And_elim_r _ _ ab)).
260
261 notation < "\infrule hbox(\emsp ab \emsp) mstyle color #ff0000 (a) (∧\sub(\e_\r))" with precedence 19 
262 for @{ 'And_elim_r_ok_2 $ab $a }.
263 interpretation "And_elim_r_ok_2" 'And_elim_r_ok_2 ab a = 
264   (cast _ _ (show a (And_elim_r _ _ ab))).
265
266 notation > "∧_'e_r' term 90 ab" with precedence 19
267 for @{ 'And_elim_r (show $ab ?) }.
268 interpretation "And_elim_r KO" 'And_elim_r a = (cast _ _ (And_elim_r _ _ (cast (And unit unit) _ a))).
269 interpretation "And_elim_r OK" 'And_elim_r a = (And_elim_r _ _ a).
270
271 (* ∨ introduction *)
272 notation < "\infrule hbox(\emsp a \emsp) ab mstyle color #ff0000 (∨\sub(\i_\l))" with precedence 19 
273 for @{ 'Or_intro_l_ko_1 $a $ab }.
274 interpretation "Or_intro_l_ko_1" 'Or_intro_l_ko_1 a ab = 
275   (show ab (cast _ _ (Or_intro_l _ _ a))).
276
277 notation < "\infrule hbox(\emsp a \emsp) mstyle color #ff0000 (ab) mstyle color #ff0000 (∨\sub(\i_\l))" with precedence 19 
278 for @{ 'Or_intro_l_ko_2 $a $ab }.
279 interpretation "Or_intro_l_ko_2" 'Or_intro_l_ko_2 a ab = 
280   (cast _ _ (show ab (cast _ _ (Or_intro_l _ _ a)))).
281
282 notation < "\infrule hbox(\emsp a \emsp) ab (∨\sub(\i_\l))" with precedence 19 
283 for @{ 'Or_intro_l_ok_1 $a $ab }.
284 interpretation "Or_intro_l_ok_1" 'Or_intro_l_ok_1 a ab = 
285   (show ab (Or_intro_l _ _ a)).
286
287 notation < "\infrule hbox(\emsp a \emsp) mstyle color #ff0000 (ab) (∨\sub(\i_\l))" with precedence 19 
288 for @{ 'Or_intro_l_ok_2 $a $ab }.
289 interpretation "Or_intro_l_ok_2" 'Or_intro_l_ok_2 a ab = 
290   (cast _ _ (show ab (Or_intro_l _ _ a))).
291
292 notation > "∨_'i_l' term 90 a" with precedence 19
293 for @{ 'Or_intro_l (show $a ?) }.
294 interpretation "Or_intro_l KO" 'Or_intro_l a = (cast _ (Or _ unit) (Or_intro_l _ _ a)).
295 interpretation "Or_intro_l OK" 'Or_intro_l a = (Or_intro_l _ _ a). 
296   
297 notation < "\infrule hbox(\emsp a \emsp) ab mstyle color #ff0000 (∨\sub(\i_\r))" with precedence 19 
298 for @{ 'Or_intro_r_ko_1 $a $ab }.
299 interpretation "Or_intro_r_ko_1" 'Or_intro_r_ko_1 a ab = 
300   (show ab (cast _ _ (Or_intro_r _ _ a))).
301
302 notation < "\infrule hbox(\emsp a \emsp) mstyle color #ff0000 (ab) mstyle color #ff0000 (∨\sub(\i_\r))" with precedence 19 
303 for @{ 'Or_intro_r_ko_2 $a $ab }.
304 interpretation "Or_intro_r_ko_2" 'Or_intro_r_ko_2 a ab = 
305   (cast _ _ (show ab (cast _ _ (Or_intro_r _ _ a)))).
306
307 notation < "\infrule hbox(\emsp a \emsp) ab (∨\sub(\i_\r))" with precedence 19 
308 for @{ 'Or_intro_r_ok_1 $a $ab }.
309 interpretation "Or_intro_r_ok_1" 'Or_intro_r_ok_1 a ab = 
310   (show ab (Or_intro_r _ _ a)).
311
312 notation < "\infrule hbox(\emsp a \emsp) mstyle color #ff0000 (ab) (∨\sub(\i_\r))" with precedence 19 
313 for @{ 'Or_intro_r_ok_1 $a $ab }.
314 interpretation "Or_intro_r_ok_2" 'Or_intro_r_ok_2 a ab = 
315   (cast _ _ (show ab (Or_intro_r _ _ a))).
316
317 notation > "∨_'i_r' term 90 a" with precedence 19
318 for @{ 'Or_intro_r (show $a ?) }.
319 interpretation "Or_intro_r KO" 'Or_intro_r a = (cast _ (Or unit _) (Or_intro_r _ _ a)).
320 interpretation "Or_intro_r OK" 'Or_intro_r a = (Or_intro_r _ _ a). 
321
322 (* ∨ elimination *)
323 notation < "\infrule hbox(\emsp ab \emsp\emsp\emsp ac \emsp\emsp\emsp bc \emsp) c (mstyle color #ff0000 (∨\sub\e \emsp) ident Ha \emsp ident Hb)" with precedence 19
324 for @{ 'Or_elim_ko_1 $ab $c (λ${ident Ha}:$ta.$ac) (λ${ident Hb}:$tb.$bc) }.
325 interpretation "Or_elim_ko_1" 'Or_elim_ko_1 ab c \eta.ac \eta.bc = 
326   (show c (cast _ _ (Or_elim _ _ _ (cast _ _ ab) (cast _ _ ac) (cast _ _ bc)))).
327
328 notation < "\infrule hbox(\emsp ab \emsp\emsp\emsp ac \emsp\emsp\emsp bc \emsp) mstyle color #ff0000 (c) (mstyle color #ff0000 (∨\sub\e) \emsp ident Ha \emsp ident Hb)" with precedence 19
329 for @{ 'Or_elim_ko_2 $ab (λ${ident Ha}:$ta.$ac) (λ${ident Hb}:$tb.$bc) $c }.
330 interpretation "Or_elim_ko_2" 'Or_elim_ko_2 ab \eta.ac \eta.bc c = 
331   (cast _ _ (show c (cast _ _ (Or_elim _ _ _ (cast _ _ ab) (cast _ _ ac) (cast _ _ bc))))).
332
333 notation < "\infrule hbox(\emsp ab \emsp\emsp\emsp ac \emsp\emsp\emsp bc \emsp) c (∨\sub\e \emsp ident Ha \emsp ident Hb)" with precedence 19
334 for @{ 'Or_elim_ok_1 $ab (λ${ident Ha}:$ta.$ac) (λ${ident Hb}:$tb.$bc) $c }.
335 interpretation "Or_elim_ok_1" 'Or_elim_ok_1 ab \eta.ac \eta.bc c = 
336   (show c (Or_elim _ _ _ ab ac bc)).
337
338 notation < "\infrule hbox(\emsp ab \emsp\emsp\emsp ac \emsp\emsp\emsp bc \emsp) mstyle color #ff0000 (c) (∨\sub\e \emsp ident Ha \emsp ident Hb)" with precedence 19
339 for @{ 'Or_elim_ok_2 $ab (λ${ident Ha}:$ta.$ac) (λ${ident Hb}:$tb.$bc) $c }.
340 interpretation "Or_elim_ok_2" 'Or_elim_ok_2 ab \eta.ac \eta.bc c = 
341   (cast _ _ (show c (Or_elim _ _ _ ab ac bc))).
342
343 definition unit_to ≝ λx:CProp.unit → x.
344
345 notation > "∨_'e' term 90 ab [ident Ha] term 90 cl [ident Hb] term 90 cr" with precedence 19
346 for @{ 'Or_elim (show $ab ?) (λ${ident Ha}.show $cl ?) (λ${ident Hb}.show $cr ?) }.
347 interpretation "Or_elim KO" 'Or_elim ab ac bc = 
348   (cast _ _ (Or_elim _ _ _ 
349     (cast (Or unit unit) _ ab) 
350     (cast (unit_to unit) (unit_to _) ac) 
351     (cast (unit_to unit) (unit_to _) bc))).
352 interpretation "Or_elim OK" 'Or_elim ab ac bc = (Or_elim _ _ _ ab ac bc).
353
354 (* ⊤ introduction *)
355 notation < "\infrule \nbsp ⊤ mstyle color #ff0000 (⊤\sub\i)" with precedence 19 
356 for @{'Top_intro_ko_1}.
357 interpretation "Top_intro_ko_1" 'Top_intro_ko_1 = 
358   (show _ (cast _ _ Top_intro)).
359
360 notation < "\infrule \nbsp mstyle color #ff0000 (⊤) mstyle color #ff0000 (⊤\sub\i)" with precedence 19 
361 for @{'Top_intro_ko_2}.
362 interpretation "Top_intro_ko_2" 'Top_intro_ko_2 = 
363   (cast _ _ (show _ (cast _ _ Top_intro))).
364
365 notation < "\infrule \nbsp ⊤ (⊤\sub\i)" with precedence 19 
366 for @{'Top_intro_ok_1}.
367 interpretation "Top_intro_ok_1" 'Top_intro_ok_1 = (show _ Top_intro).
368
369 notation < "\infrule \nbsp ⊤ (⊤\sub\i)" with precedence 19 
370 for @{'Top_intro_ok_2 }.
371 interpretation "Top_intro_ok_2" 'Top_intro_ok_2 = (cast _ _ (show _ Top_intro)).
372
373 notation > "⊤_'i'" with precedence 19 for @{ 'Top_intro }.
374 interpretation "Top_intro KO" 'Top_intro = (cast _ _ Top_intro).
375 interpretation "Top_intro OK" 'Top_intro = Top_intro.
376
377 (* ⊥ introduction *)
378 notation < "\infrule b a mstyle color #ff0000 (⊥\sub\e)" with precedence 19 
379 for @{'Bot_elim_ko_1 $a $b}.
380 interpretation "Bot_elim_ko_1" 'Bot_elim_ko_1 a b = 
381   (show a (Bot_elim _ (cast _ _ b))).
382
383 notation < "\infrule b mstyle color #ff0000 (a) mstyle color #ff0000 (⊥\sub\e)" with precedence 19 
384 for @{'Bot_elim_ko_2 $a $b}.
385 interpretation "Bot_elim_ko_2" 'Bot_elim_ko_2 a b = 
386   (cast _ _ (show a (Bot_elim _ (cast _ _ b)))).
387
388 notation < "\infrule b a (⊥\sub\e)" with precedence 19 
389 for @{'Bot_elim_ok_1 $a $b}.
390 interpretation "Bot_elim_ok_1" 'Bot_elim_ok_1 a b = 
391   (show a (Bot_elim _ b)).
392
393 notation < "\infrule b mstyle color #ff0000 (a) (⊥\sub\e)" with precedence 19 
394 for @{'Bot_elim_ok_2 $a $b}.
395 interpretation "Bot_elim_ok_2" 'Bot_elim_ok_2 a b = 
396   (cast _ _ (show a (Bot_elim _ b))).
397
398 notation > "⊥_'e' term 90 b" with precedence 19 
399 for @{ 'Bot_elim (show $b ?) }.
400 interpretation "Bot_elim KO" 'Bot_elim a = (Bot_elim _ (cast _ _ a)).  
401 interpretation "Bot_elim OK" 'Bot_elim a = (Bot_elim _ a).
402
403 (* ¬ introduction *)
404 notation < "\infrule hbox(\emsp b \emsp) ab (mstyle color #ff0000 (\lnot\sub\i) \emsp ident H)" with precedence 19
405 for @{ 'Not_intro_ko_1 $ab (λ${ident H}:$p.$b) }.
406 interpretation "Not_intro_ko_1" 'Not_intro_ko_1 ab \eta.b = 
407   (show ab (cast _ _ (Not_intro _ (cast _ _ b)))).
408
409 notation < "\infrule hbox(\emsp b \emsp) mstyle color #ff0000 (ab) (mstyle color #ff0000 (\lnot\sub\i) \emsp ident H)" with precedence 19
410 for @{ 'Not_intro_ko_2 $ab (λ${ident H}:$p.$b) }.
411 interpretation "Not_intro_ko_2" 'Not_intro_ko_2 ab \eta.b = 
412   (cast _ _ (show ab (cast _ _ (Not_intro _ (cast _ _ b))))).
413
414 notation < "\infrule hbox(\emsp b \emsp) ab (\lnot\sub\i \emsp ident H) " with precedence 19
415 for @{ 'Not_intro_ok_1 $ab (λ${ident H}:$p.$b) }.
416 interpretation "Not_intro_ok_1" 'Not_intro_ok_1 ab \eta.b = 
417   (show ab (Not_intro _ b)).
418
419 notation < "\infrule hbox(\emsp b \emsp) mstyle color #ff0000 (ab) (\lnot\sub\i \emsp ident H) " with precedence 19
420 for @{ 'Not_intro_ok_2 $ab (λ${ident H}:$p.$b) }.
421 interpretation "Not_intro_ok_2" 'Not_intro_ok_2 ab \eta.b = 
422   (cast _ _ (show ab (Not_intro _ b))).
423
424 notation > "¬_'i' [ident H] term 90 b" with precedence 19
425 for @{ 'Not_intro (λ${ident H}.show $b ?) }.
426 interpretation "Not_intro KO" 'Not_intro a = (cast _ _ (Not_intro _ (cast _ _ a))).
427 interpretation "Not_intro OK" 'Not_intro a = (Not_intro _ a).
428
429 (* ¬ elimination *)
430 notation < "\infrule hbox(\emsp ab \emsp\emsp\emsp a\emsp) b mstyle color #ff0000 (\lnot\sub\e) " with precedence 19 
431 for @{ 'Not_elim_ko_1 $ab $a $b }.
432 interpretation "Not_elim_ko_1" 'Not_elim_ko_1 ab a b = 
433   (show b (cast _ _ (Not_elim _ (cast _ _ ab) (cast _ _ a)))).
434
435 notation < "\infrule hbox(\emsp ab \emsp\emsp\emsp a\emsp) mstyle color #ff0000 (b) mstyle color #ff0000 (\lnot\sub\e) " with precedence 19 
436 for @{ 'Not_elim_ko_2 $ab $a $b }.
437 interpretation "Not_elim_ko_2" 'Not_elim_ko_2 ab a b = 
438   (cast _ _ (show b (cast _ _ (Not_elim _ (cast _ _ ab) (cast _ _ a))))).
439
440 notation < "\infrule hbox(\emsp ab \emsp\emsp\emsp a\emsp) b (\lnot\sub\e) " with precedence 19 
441 for @{ 'Not_elim_ok_1 $ab $a $b }.
442 interpretation "Not_elim_ok_1" 'Not_elim_ok_1 ab a b = 
443   (show b (Not_elim _ ab a)).
444
445 notation < "\infrule hbox(\emsp ab \emsp\emsp\emsp a\emsp) mstyle color #ff0000 (b) (\lnot\sub\e) " with precedence 19 
446 for @{ 'Not_elim_ok_2 $ab $a $b }.
447 interpretation "Not_elim_ok_2" 'Not_elim_ok_2 ab a b = 
448   (cast _ _ (show b (Not_elim _ ab a))).
449
450 notation > "¬_'e' term 90 ab term 90 a" with precedence 19
451 for @{ 'Not_elim (show $ab ?) (show $a ?) }.
452 interpretation "Not_elim KO" 'Not_elim ab a = 
453   (cast _ _ (Not_elim unit (cast _ _ ab) (cast _ _ a))).
454 interpretation "Not_elim OK" 'Not_elim ab a = 
455   (Not_elim _ ab a).
456
457 (* RAA *)
458 notation < "\infrule hbox(\emsp Px \emsp) Pn (mstyle color #ff0000 (\RAA) \emsp ident x)" with precedence 19
459 for @{ 'RAA_ko_1 (λ${ident x}:$tx.$Px) $Pn }.
460 interpretation "RAA_ko_1" 'RAA_ko_1 Px Pn = 
461   (show Pn (cast _ _ (Raa _ (cast _ _ Px)))).
462
463 notation < "\infrule hbox(\emsp Px \emsp) mstyle color #ff0000 (Pn) (mstyle color #ff0000 (\RAA) \emsp ident x)" with precedence 19
464 for @{ 'RAA_ko_2 (λ${ident x}:$tx.$Px) $Pn }.
465 interpretation "RAA_ko_2" 'RAA_ko_2 Px Pn = 
466   (cast _ _ (show Pn (cast _ _ (Raa _ (cast _ _ Px))))).
467
468 notation < "\infrule hbox(\emsp Px \emsp) Pn (\RAA \emsp ident x)" with precedence 19
469 for @{ 'RAA_ok_1 (λ${ident x}:$tx.$Px) $Pn }.
470 interpretation "RAA_ok_1" 'RAA_ok_1 Px Pn = 
471   (show Pn (Raa _ Px)).
472
473 notation < "\infrule hbox(\emsp Px \emsp) mstyle color #ff0000 (Pn) (\RAA \emsp ident x)" with precedence 19
474 for @{ 'RAA_ok_2 (λ${ident x}:$tx.$Px) $Pn }.
475 interpretation "RAA_ok_2" 'RAA_ok_2 Px Pn = 
476   (cast _ _ (show Pn (Raa _ Px))).
477
478 notation > "'RAA' [ident H] term 90 b" with precedence 19 
479 for @{ 'Raa (λ${ident H}.show $b ?) }. 
480 interpretation "RAA KO" 'Raa p = (cast _ unit (Raa _ (cast _ (unit_to _) p))).
481 interpretation "RAA OK" 'Raa p = (Raa _ p).
482
483 (*DOCBEGIN
484 Templates for rules:
485
486         apply rule (⇒_i […] (…)).
487
488         apply rule (∧_i (…) (…));
489                 [
490                 |
491                 ]
492
493         apply rule (∨_i_l (…)).
494
495         apply rule (∨_i_r (…)).
496
497         apply rule (¬_i […] (…)).
498
499         apply rule (⊤_i).
500
501         apply rule (⇒_e (…) (…));
502                 [
503                 |
504                 ]
505
506         apply rule (∧_e_l (…)).
507
508         apply rule (∧_e_r (…)).
509
510         apply rule (∨_e (…) […] (…) […] (…));
511                 [
512                 |
513                 |
514                 ]
515
516         apply rule (¬_e (…) (…));
517                 [
518                 |
519                 ]
520
521         apply rule (⊥_e (…)).
522
523         apply rule (prove (…)).
524
525         apply rule (RAA […] (…)).
526
527         apply rule (discharge […]).
528
529 DOCEND*)
530
531
532
533