(* Copyright (C) 2004, 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/ *) let fresh_binder = let counter = ref ~-1 in fun () -> incr counter; "elim" ^ string_of_int !counter (** verifies if a given uri occurs in a term in target position *) let rec recursive uri = function | Cic.Prod (_, _, target) -> recursive uri target | Cic.MutInd (uri', _, _) | Cic.Appl [ Cic.MutInd (uri', _, _); _ ] -> UriManager.eq uri uri' | _ -> false let unfold_appl = function | Cic.Appl ((Cic.Appl args) :: tl) -> Cic.Appl (args @ tl) | t -> t (** build elimination principle part related to a single constructor * @param strip number of Prod to ignore in this constructor (i.e. number of * inductive parameters) *) let rec delta (uri, typeno, subst) strip consno t p args = assert (subst = []); match t with | Cic.MutInd (uri', typeno', subst') | Cic.Appl (Cic.MutInd (uri', typeno', subst') :: _) when UriManager.eq uri uri' && typeno = typeno' && subst = subst' -> (match args with | [] -> assert false | [arg] -> unfold_appl (Cic.Appl [p; arg]) | _ -> unfold_appl (Cic.Appl [p; unfold_appl (Cic.Appl args)])) (* | Cic.Appl (Cic.MutInd (uri', typeno', subst') :: _) when UriManager.eq uri uri' && typeno = typeno' && subst = subst' -> Cic.Appl (Cic.Rel p_rel :: args) *) | Cic.Prod (binder, src, tgt) when strip = 0 -> if recursive uri src then let args = List.map (CicSubstitution.lift 2) args in let phi = (delta (uri, typeno, subst) strip consno src (CicSubstitution.lift 1 p) [Cic.Rel 1]) in Cic.Prod (Cic.Name (fresh_binder ()), src, Cic.Prod (Cic.Anonymous, phi, delta (uri, typeno, subst) strip consno tgt (CicSubstitution.lift 2 p) (args @ [Cic.Rel 2]))) else (* non recursive *) let args = List.map (CicSubstitution.lift 1) args in Cic.Prod (Cic.Name (fresh_binder ()), src, delta (uri, typeno, subst) strip consno tgt (CicSubstitution.lift 1 p) (args @ [Cic.Rel 1])) | Cic.Prod (_, _, tgt) (* when strip > 0 *) -> (* after stripping the parameters we lift of 1 since P has been inserted * in the way *) let tgt = if strip = 1 then CicSubstitution.lift consno tgt else tgt in delta (uri, typeno, subst) (strip - 1) consno tgt p args | _ -> assert false let rec add_params indno ty eliminator = if indno = 0 then eliminator else match ty with | Cic.Prod (binder, src, tgt) -> Cic.Prod (binder, src, add_params (indno - 1) tgt eliminator) | _ -> assert false let rec mk_rels consno = function | 0 -> [] | n -> Cic.Rel (n+consno) :: mk_rels consno (n-1) let elim_of uri typeno = let (obj, univ) = (CicEnvironment.get_obj uri CicUniv.empty_ugraph) in let subst = [] in match obj with | Cic.InductiveDefinition (indTypes, params, indno) -> let (name, inductive, ty, constructors) = try List.nth indTypes typeno with Failure _ -> assert false in let conslen = List.length constructors in let consno = ref (conslen + 1) in let indty = let indty = Cic.MutInd (uri, typeno, subst) in if indno = 0 then indty else Cic.Appl (indty :: mk_rels 0 indno) in let mk_constructor consno = let constructor = Cic.MutConstruct (uri, typeno, consno, subst) in if indno = 0 then constructor else Cic.Appl (constructor :: mk_rels consno indno) in let eliminator = Cic.Prod (Cic.Name "P", (Cic.Prod (Cic.Anonymous, indty, (* Cic.MutInd (uri, typeno, subst), *) Cic.Sort (Cic.Type (CicUniv.fresh ())))), (List.fold_right (fun (_, constructor) acc -> decr consno; let p = Cic.Rel !consno in Cic.Prod (Cic.Anonymous, (delta (uri, typeno, subst) indno !consno constructor p [mk_constructor !consno]), acc)) (* lift acc? see assumption above on delta *) constructors (Cic.Prod (Cic.Name (fresh_binder ()), CicSubstitution.lift (conslen + 1) indty (* Cic.MutInd (uri, typeno, subst) *), Cic.Appl [Cic.Rel (2 + conslen); Cic.Rel 1])))) in add_params indno ty eliminator | _ -> assert false