]> matita.cs.unibo.it Git - helm.git/blob - helm/software/components/ng_kernel/nCicEnvironment.ml
...
[helm.git] / helm / software / components / ng_kernel / nCicEnvironment.ml
1 (*
2     ||M||  This file is part of HELM, an Hypertextual, Electronic        
3     ||A||  Library of Mathematics, developed at the Computer Science     
4     ||T||  Department, University of Bologna, Italy.                     
5     ||I||                                                                
6     ||T||  HELM is free software; you can redistribute it and/or         
7     ||A||  modify it under the terms of the GNU General Public License   
8     \   /  version 2 or (at your option) any later version.      
9      \ /   This software is distributed as is, NO WARRANTY.     
10       V_______________________________________________________________ *)
11
12 (* $Id$ *)
13
14 module C = NCic
15 module Ref = NReference
16
17 exception CircularDependency of string Lazy.t;;
18 exception ObjectNotFound of string Lazy.t;;
19 exception BadDependency of string Lazy.t;;
20 exception BadConstraint of string Lazy.t;;
21
22 let type0 = []
23
24 let le_constraints = ref [] (* strict,a,b *)
25
26 let rec le_path_uri avoid strict a b =
27  (not strict && NUri.eq a b) ||
28  List.exists
29   (fun (strict',x,y) ->
30      NUri.eq y b && not (List.exists (NUri.eq x) avoid) &&
31        le_path_uri (x::avoid) (strict && not strict') a x
32   ) !le_constraints
33 ;;
34
35 let leq_path a b = le_path_uri [b] (fst a) (snd a) b;;
36
37 let universe_leq a b = 
38   match a, b with
39   | a,[(false,b)] -> List.for_all (fun a -> leq_path a b) a
40   | _,_ ->
41      raise (BadConstraint
42       (lazy "trying to check if a universe is less or equal than an inferred universe"))
43
44 let universe_eq a b = universe_leq b a && universe_leq a b
45
46 let pp_constraint b x y =  
47   NUri.name_of_uri x ^ (if b then " < " else " <= ") ^ NUri.name_of_uri y
48 ;;
49
50 let pp_constraints () =
51   String.concat "\n" (List.map (fun (b,x,y) -> pp_constraint b x y) !le_constraints)
52 ;;
53
54 let universes = ref [];;
55
56 let add_constraint strict a b = 
57   match a,b with
58   | [false,a2],[false,b2] -> 
59       if not (le_path_uri [] strict a2 b2) then (
60         if le_path_uri [] (not strict) b2 a2 then
61          (raise(BadConstraint(lazy("universe inconsistency adding "^pp_constraint strict a2 b2
62            ^ " to:\n" ^ pp_constraints ()))));
63         universes := a2 :: b2 :: 
64           List.filter (fun x -> not (NUri.eq x a2 || NUri.eq x b2)) !universes;
65         le_constraints := (strict,a2,b2) :: !le_constraints)
66   | _ -> raise (BadConstraint
67           (lazy "trying to add a constraint on an inferred universe"))
68 ;;
69
70 let sup l =
71   match l with
72   | [false,_] -> Some l
73   | l ->
74    let bigger_than acc (s1,n1) = List.filter (le_path_uri [] s1 n1) acc in
75    let solutions = List.fold_left bigger_than !universes l in
76    let rec aux = function
77      | [] -> None
78      | u :: tl ->
79          if List.exists (fun x -> le_path_uri [] true x u) solutions then aux tl
80          else Some [false,u]
81    in
82     aux solutions
83 ;;
84
85
86
87 let typecheck_obj,already_set = ref (fun _ -> assert false), ref false;;
88 let set_typecheck_obj f =
89  if !already_set then
90   assert false
91  else
92   begin
93    typecheck_obj := f;
94    already_set := true
95   end
96 ;;
97
98 let cache = NUri.UriHash.create 313;;
99 let frozen_list = ref [];;
100
101 exception Propagate of NUri.uri * exn;;
102
103 let get_checked_obj u =
104  if List.exists (fun (k,_) -> NUri.eq u k) !frozen_list
105  then
106   raise (CircularDependency (lazy (NUri.string_of_uri u)))
107  else
108   let obj =
109    try NUri.UriHash.find cache u
110    with
111     Not_found ->
112      let saved_frozen_list = !frozen_list in
113      try
114       let obj =
115        try NCicLibrary.get_obj u
116        with
117         NCicLibrary.ObjectNotFound m -> raise (ObjectNotFound m)
118       in
119         frozen_list := (u,obj)::saved_frozen_list;
120         !typecheck_obj obj;
121         frozen_list := saved_frozen_list;
122         let obj = `WellTyped obj in
123         NUri.UriHash.add cache u obj;
124         obj
125      with
126         Sys.Break as e ->
127          frozen_list := saved_frozen_list;
128          raise e
129       | Propagate (u',_) as e' ->
130          frozen_list := saved_frozen_list;
131          let exn = `Exn (BadDependency (lazy (NUri.string_of_uri u ^
132            " depends (recursively) on " ^ NUri.string_of_uri u' ^
133            " which is not well-typed"))) in
134          NUri.UriHash.add cache u exn;
135          if saved_frozen_list = [] then
136           exn
137          else
138           raise e'
139       | e ->
140          frozen_list := saved_frozen_list;
141          let exn = `Exn e in
142          NUri.UriHash.add cache u exn;
143          if saved_frozen_list = [] then
144           exn
145          else
146           raise (Propagate (u,e))
147   in
148    match obj with
149       `WellTyped o -> o
150     | `Exn e -> raise e
151 ;;
152
153 let get_checked_decl = function
154   | Ref.Ref (uri, Ref.Decl) ->
155       (match get_checked_obj uri with
156       | _,height,_,_, C.Constant (rlv,name,None,ty,att) ->
157           rlv,name,ty,att,height
158       | _,_,_,_, C.Constant (_,_,Some _,_,_) ->
159           prerr_endline "get_checked_decl on a definition"; assert false
160       | _ -> prerr_endline "get_checked_decl on a non decl 2"; assert false)
161   | _ -> prerr_endline "get_checked_decl on a non decl"; assert false
162 ;;
163
164 let get_checked_def = function
165   | Ref.Ref (uri, Ref.Def _) ->
166       (match get_checked_obj uri with
167       | _,height,_,_, C.Constant (rlv,name,Some bo,ty,att) ->
168           rlv,name,bo,ty,att,height
169       | _,_,_,_, C.Constant (_,_,None,_,_) ->
170           prerr_endline "get_checked_def on an axiom"; assert false
171       | _ -> prerr_endline "get_checked_def on a non def 2"; assert false)
172   | _ -> prerr_endline "get_checked_def on a non def"; assert false
173 ;;
174
175 let get_checked_indtys = function
176   | Ref.Ref (uri, (Ref.Ind (_,n,_)|Ref.Con (n,_,_))) ->
177       (match get_checked_obj uri with
178       | _,_,_,_, C.Inductive (inductive,leftno,tys,att) ->
179         inductive,leftno,tys,att,n
180       | _ -> prerr_endline "get_checked_indtys on a non ind 2"; assert false)
181   | _ -> prerr_endline "get_checked_indtys on a non ind"; assert false
182 ;;
183
184 let get_checked_fixes_or_cofixes = function
185   | Ref.Ref (uri, (Ref.Fix _|Ref.CoFix _))->
186       (match get_checked_obj uri with
187       | _,height,_,_, C.Fixpoint (_,funcs,att) ->
188          funcs, att, height
189       | _ ->prerr_endline "get_checked_(co)fix on a non (co)fix 2";assert false)
190   | _ -> prerr_endline "get_checked_(co)fix on a non (co)fix"; assert false
191 ;;
192
193 let get_relevance (Ref.Ref (_, infos) as r) =
194   match infos with
195      Ref.Def _ -> let res,_,_,_,_,_ = get_checked_def r in res
196    | Ref.Decl -> let res,_,_,_,_ = get_checked_decl r in res
197    | Ref.Ind _ ->
198        let _,_,tl,_,n = get_checked_indtys r in
199        let res,_,_,_ = List.nth tl n in
200          res
201     | Ref.Con (_,i,_) ->
202        let _,_,tl,_,n = get_checked_indtys r in
203        let _,_,_,cl = List.nth tl n in
204        let res,_,_ = List.nth cl (i - 1) in
205          res
206     | Ref.Fix (fixno,_,_)
207     | Ref.CoFix fixno ->
208         let fl,_,_ = get_checked_fixes_or_cofixes r in
209         let res,_,_,_,_ = List.nth fl fixno in
210           res
211 ;;
212
213
214 let invalidate _ = 
215   assert (!frozen_list = []);
216   NUri.UriHash.clear cache
217 ;;