Merge branch 'cleaning_again_example_sin_cos' into 'master'
[why3.git] / stdlib / relations.mlw
blob74739cdfdc2f6a7fc865c57aaa2b7c5f2ef5fd8d
2 (** {1 Relations} *)
4 (** {2 Relations and orders} *)
6 module EndoRelation
7   type t
8   predicate rel t t
9 end
11 module Reflexive
12   clone export EndoRelation
13   axiom Refl : forall x:t. rel x x
14 end
16 module Irreflexive
17   clone export EndoRelation
18   axiom Strict : forall x:t. not rel x x
19 end
21 module Transitive
22   clone export EndoRelation
23   axiom Trans : forall x y z:t. rel x y -> rel y z -> rel x z
24 end
26 module Symmetric
27   clone export EndoRelation
28   axiom Symm : forall x y:t. rel x y -> rel y x
29 end
31 module Asymmetric
32   clone export EndoRelation
33   axiom Asymm : forall x y:t. rel x y -> not rel y x
34 end
36 module Antisymmetric
37   clone export EndoRelation
38   axiom Antisymm : forall x y:t. rel x y -> rel y x -> x = y
39 end
41 module Total
42   clone export EndoRelation
43   axiom Total : forall x y:t. rel x y \/ rel y x
44 end
46 module PreOrder
47   clone export Reflexive with axiom Refl
48   clone export Transitive with type t = t, predicate rel = rel, axiom Trans
49 end
51 module Equivalence
52   clone export PreOrder with axiom Refl, axiom Trans
53   clone export Symmetric with type t = t, predicate rel = rel, axiom Symm
54 end
56 module TotalPreOrder
57   clone export PreOrder with axiom Refl, axiom Trans
58   clone export Total with type t = t, predicate rel = rel, axiom Total
59 end
61 module PartialOrder
62   clone export PreOrder with axiom Refl, axiom Trans
63   clone export Antisymmetric with
64     type t = t, predicate rel = rel, axiom Antisymm
65 end
67 module TotalOrder
68   clone export PartialOrder with axiom .
69   clone export Total with type t = t, predicate rel = rel, axiom Total
70 end
72 module PartialStrictOrder
73   clone export Transitive with axiom Trans
74   clone export Asymmetric with type t = t, predicate rel = rel, axiom Asymm
75 end
77 module TotalStrictOrder
78   clone export PartialStrictOrder with axiom Trans, axiom Asymm
79   axiom Trichotomy : forall x y:t. rel x y \/ rel y x \/ x = y
80 end
82 module Inverse
83   clone export EndoRelation
85   predicate inv_rel (x y : t) = rel y x
86 end
88 (** {2 Closures} *)
90 module ReflClosure
91   clone export EndoRelation
93   inductive relR t t =
94   | BaseRefl : forall x:t. relR x x
95   | StepRefl : forall x y:t. rel x y -> relR x y
96 end
98 module TransClosure
99   clone export EndoRelation
101   inductive relT t t =
102   | BaseTrans : forall x y:t. rel x y -> relT x y
103   | StepTrans : forall x y z:t. relT x y -> rel y z -> relT x z
105   lemma relT_transitive:
106     forall x y z: t. relT x y -> relT y z -> relT x z
109 module ReflTransClosure
110   clone export EndoRelation
112   inductive relTR t t =
113   | BaseTransRefl : forall x:t. relTR x x
114   | StepTransRefl : forall x y z:t. relTR x y -> rel y z -> relTR x z
116   lemma relTR_transitive:
117     forall x y z: t. relTR x y -> relTR y z -> relTR x z
120 (** {2 Lexicographic ordering} *)
122 module Lex
124   type t1
125   type t2
127   predicate rel1 t1 t1
128   predicate rel2 t2 t2
130   inductive lex (t1, t2) (t1, t2) =
131   | Lex_1: forall x1 x2 : t1, y1 y2 : t2.
132        rel1 x1 x2 -> lex (x1,y1) (x2,y2)
133   | Lex_2: forall x : t1, y1 y2 : t2.
134        rel2 y1 y2 -> lex (x,y1) (x,y2)
138 (** {2 Minimum and maximum for total orders} *)
140 module MinMax
142   type t
143   predicate le t t
145   clone TotalOrder as TO with type t = t, predicate rel = le, axiom .
147   function min (x y : t) : t = if le x y then x else y
148   function max (x y : t) : t = if le x y then y else x
150   lemma Min_r : forall x y:t. le y x -> min x y = y
151   lemma Max_l : forall x y:t. le y x -> max x y = x
153   lemma Min_comm : forall x y:t. min x y = min y x
154   lemma Max_comm : forall x y:t. max x y = max y x
156   lemma Min_assoc : forall x y z:t. min (min x y) z = min x (min y z)
157   lemma Max_assoc : forall x y z:t. max (max x y) z = max x (max y z)
161 (** {2 Well-founded relation} *)
163 module WellFounded
165 use export why3.WellFounded.WellFounded
167 (** This is now part of the built-in theories. The contents is reproduced here for information
168 {h <pre>
170   inductive acc (r: 'a -> 'a -> bool) (x: 'a) =
171   | acc_x: forall r, x: 'a. (forall y. r y x -> acc r y) -> acc r x
173   predicate well_founded (r: 'a -> 'a -> bool) =
174     forall x. acc r x
177 </pre>}