(* Copyright (C) 2004-2005, HELM Team. * * This file is part of HELM, an Hypertextual, Electronic * Library of Mathematics, developed at the Computer Science * Department, University of Bologna, Italy. * * HELM is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License * as published by the Free Software Foundation; either version 2 * of the License, or (at your option) any later version. * * HELM is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU General Public License for more details. * * You should have received a copy of the GNU General Public License * along with HELM; if not, write to the Free Software * Foundation, Inc., 59 Temple Place - Suite 330, Boston, * MA 02111-1307, USA. * * For details, see the HELM World-Wide-Web page, * http://helm.cs.unibo.it/ *) open CicNotationPt (* let meta_names_of term = *) (* let rec names = ref [] in *) (* let add_name n = *) (* if List.mem n !names then () *) (* else names := n :: !names *) (* in *) (* let rec aux = function *) (* | AttributedTerm (_, term) -> aux term *) (* | Appl terms -> List.iter aux terms *) (* | Binder (_, _, body) -> aux body *) (* | Case (term, indty, outty_opt, patterns) -> *) (* aux term ; *) (* aux_opt outty_opt ; *) (* List.iter aux_branch patterns *) (* | LetIn (_, t1, t2) -> *) (* aux t1 ; *) (* aux t2 *) (* | LetRec (_, definitions, body) -> *) (* List.iter aux_definition definitions ; *) (* aux body *) (* | Uri (_, Some substs) -> aux_substs substs *) (* | Ident (_, Some substs) -> aux_substs substs *) (* | Meta (_, substs) -> aux_meta_substs substs *) (* | Implicit *) (* | Ident _ *) (* | Num _ *) (* | Sort _ *) (* | Symbol _ *) (* | Uri _ *) (* | UserInput -> () *) (* | Magic magic -> aux_magic magic *) (* | Variable var -> aux_variable var *) (* | _ -> assert false *) (* and aux_opt = function *) (* | Some term -> aux term *) (* | None -> () *) (* and aux_capture_var (_, ty_opt) = aux_opt ty_opt *) (* and aux_branch (pattern, term) = *) (* aux_pattern pattern ; *) (* aux term *) (* and aux_pattern (head, vars) = *) (* List.iter aux_capture_var vars *) (* and aux_definition (var, term, i) = *) (* aux_capture_var var ; *) (* aux term *) (* and aux_substs substs = List.iter (fun (_, term) -> aux term) substs *) (* and aux_meta_substs meta_substs = List.iter aux_opt meta_substs *) (* and aux_variable = function *) (* | NumVar name -> add_name name *) (* | IdentVar name -> add_name name *) (* | TermVar name -> add_name name *) (* | FreshVar _ -> () *) (* | Ascription _ -> assert false *) (* and aux_magic = function *) (* | Default (t1, t2) *) (* | Fold (_, t1, _, t2) -> *) (* aux t1 ; *) (* aux t2 *) (* | _ -> assert false *) (* in *) (* aux term ; *) (* !names *) let visit_ast ?(special_k = fun _ -> assert false) k = let rec aux = function | Appl terms -> Appl (List.map k terms) | Binder (kind, var, body) -> Binder (kind, aux_capture_variable var, k body) | Case (term, indtype, typ, patterns) -> Case (k term, indtype, aux_opt typ, aux_patterns patterns) | Cast (t1, t2) -> Cast (k t1, k t2) | LetIn (var, t1, t2) -> LetIn (aux_capture_variable var, k t1, k t2) | LetRec (kind, definitions, term) -> let definitions = List.map (fun (var, ty, n) -> aux_capture_variable var, k ty, n) definitions in LetRec (kind, definitions, k term) | Ident (name, Some substs) -> Ident (name, Some (aux_substs substs)) | Uri (name, Some substs) -> Uri (name, Some (aux_substs substs)) | Meta (index, substs) -> Meta (index, List.map aux_opt substs) | (AttributedTerm _ | Layout _ | Literal _ | Magic _ | Variable _) as t -> special_k t | (Ident _ | Implicit | Num _ | Sort _ | Symbol _ | Uri _ | UserInput) as t -> t and aux_opt = function | None -> None | Some term -> Some (k term) and aux_capture_variable (term, typ_opt) = k term, aux_opt typ_opt and aux_patterns patterns = List.map aux_pattern patterns and aux_pattern ((head, vars), term) = ((head, List.map aux_capture_variable vars), k term) and aux_subst (name, term) = (name, k term) and aux_substs substs = List.map aux_subst substs in aux let visit_layout k = function | Sub (t1, t2) -> Sub (k t1, k t2) | Sup (t1, t2) -> Sup (k t1, k t2) | Below (t1, t2) -> Below (k t1, k t2) | Above (t1, t2) -> Above (k t1, k t2) | Over (t1, t2) -> Over (k t1, k t2) | Atop (t1, t2) -> Atop (k t1, k t2) | Frac (t1, t2) -> Frac (k t1, k t2) | Sqrt t -> Sqrt (k t) | Root (arg, index) -> Root (k arg, k index) | Break -> Break | Box (kind, terms) -> Box (kind, List.map k terms) | Group terms -> Group (List.map k terms) let visit_magic k = function | List0 (t, l) -> List0 (k t, l) | List1 (t, l) -> List1 (k t, l) | Opt t -> Opt (k t) | Fold (kind, t1, names, t2) -> Fold (kind, k t1, names, k t2) | Default (t1, t2) -> Default (k t1, k t2) | If (t1, t2, t3) -> If (k t1, k t2, k t3) | Fail -> Fail let variables_of_term t = let rec vars = ref [] in let add_variable v = if List.mem v !vars then () else vars := v :: !vars in let rec aux = function | Magic m -> Magic (visit_magic aux m) | Layout l -> Layout (visit_layout aux l) | Variable v -> Variable (aux_variable v) | Literal _ as t -> t | AttributedTerm (_, t) -> aux t | t -> visit_ast aux t and aux_variable = function | (NumVar _ | IdentVar _ | TermVar _) as t -> add_variable t ; t | FreshVar _ as t -> t | Ascription _ -> assert false in ignore (aux t) ; !vars let names_of_term t = let aux = function | NumVar s | IdentVar s | TermVar s -> s | _ -> assert false in List.map aux (variables_of_term t) let keywords_of_term t = let rec keywords = ref [] in let add_keyword k = keywords := k :: !keywords in let rec aux = function | AttributedTerm (_, t) -> aux t | Layout l -> Layout (visit_layout aux l) | Literal (`Keyword k) as t -> add_keyword k; t | Literal _ as t -> t | Magic m -> Magic (visit_magic aux m) | Variable _ as v -> v | t -> visit_ast aux t in ignore (aux t) ; !keywords let rec strip_attributes t = let special_k = function | AttributedTerm (_, term) -> strip_attributes term | Magic m -> Magic (visit_magic strip_attributes m) | Variable _ as t -> t | t -> assert false in visit_ast ~special_k strip_attributes t let meta_names_of_term term = let rec names = ref [] in let add_name n = if List.mem n !names then () else names := n :: !names in let rec aux = function | AttributedTerm (_, term) -> aux term | Appl terms -> List.iter aux terms | Binder (_, _, body) -> aux body | Case (term, indty, outty_opt, patterns) -> aux term ; aux_opt outty_opt ; List.iter aux_branch patterns | LetIn (_, t1, t2) -> aux t1 ; aux t2 | LetRec (_, definitions, body) -> List.iter aux_definition definitions ; aux body | Uri (_, Some substs) -> aux_substs substs | Ident (_, Some substs) -> aux_substs substs | Meta (_, substs) -> aux_meta_substs substs | Implicit | Ident _ | Num _ | Sort _ | Symbol _ | Uri _ | UserInput -> () | Magic magic -> aux_magic magic | Variable var -> aux_variable var | _ -> assert false and aux_opt = function | Some term -> aux term | None -> () and aux_capture_var (_, ty_opt) = aux_opt ty_opt and aux_branch (pattern, term) = aux_pattern pattern ; aux term and aux_pattern (head, vars) = List.iter aux_capture_var vars and aux_definition (var, term, i) = aux_capture_var var ; aux term and aux_substs substs = List.iter (fun (_, term) -> aux term) substs and aux_meta_substs meta_substs = List.iter aux_opt meta_substs and aux_variable = function | NumVar name -> add_name name | IdentVar name -> add_name name | TermVar name -> add_name name | FreshVar _ -> () | Ascription _ -> assert false and aux_magic = function | Default (t1, t2) | Fold (_, t1, _, t2) -> aux t1 ; aux t2 | If (t1, t2, t3) -> aux t1 ; aux t2 ; aux t3 | Fail -> () | _ -> assert false in aux term ; !names let rectangular matrix = let columns = Array.length matrix.(0) in try Array.iter (fun a -> if Array.length a <> columns then raise Exit) matrix; true with Exit -> false let ncombine ll = let matrix = Array.of_list (List.map Array.of_list ll) in assert (rectangular matrix); let rows = Array.length matrix in let columns = Array.length matrix.(0) in let lists = ref [] in for j = 0 to columns - 1 do let l = ref [] in for i = 0 to rows - 1 do l := matrix.(i).(j) :: !l done; lists := List.rev !l :: !lists done; List.rev !lists let string_of_literal = function | `Symbol s | `Keyword s | `Number s -> s let boxify = function | [ a ] -> a | l -> Layout (Box ((H, false, false), l)) let unboxify = function | Layout (Box ((H, false, false), [ a ])) -> a | l -> l let group = function | [ a ] -> a | l -> Layout (Group l) let ungroup = let rec aux acc = function [] -> List.rev acc | Layout (Group terms) :: terms' -> aux acc (terms @ terms') | term :: terms -> aux (term :: acc) terms in aux [] let dress sauce = let rec aux = function | [] -> [] | [hd] -> [hd] | hd :: tl -> hd :: sauce :: aux tl in aux let find_appl_pattern_uris ap = let rec aux acc = function | UriPattern uri -> (try ignore (List.find (fun uri' -> UriManager.eq uri uri') acc); acc with Not_found -> uri :: acc) | ImplicitPattern | VarPattern _ -> acc | ApplPattern apl -> List.fold_left aux acc apl in aux [] ap let rec find_branch = function Magic (If (_, Magic Fail, t)) -> find_branch t | Magic (If (_, t, _)) -> find_branch t | t -> t let cic_name_of_name = function | CicNotationPt.Ident ("_", None) -> Cic.Anonymous | CicNotationPt.Ident (name, None) -> Cic.Name name | _ -> assert false let name_of_cic_name = function | Cic.Name s -> CicNotationPt.Ident (s, None) | Cic.Anonymous -> CicNotationPt.Ident ("_", None) let fresh_index = ref ~-1 type notation_id = int let fresh_id () = incr fresh_index; !fresh_index (* TODO ensure that names generated by fresh_var do not clash with user's *) let fresh_name () = "fresh" ^ string_of_int (fresh_id ())