]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql_generator/mQGUtil.ml
This commit was manufactured by cvs2svn to create branch 'moogle'.
[helm.git] / helm / ocaml / mathql_generator / mQGUtil.ml
diff --git a/helm/ocaml/mathql_generator/mQGUtil.ml b/helm/ocaml/mathql_generator/mQGUtil.ml
deleted file mode 100644 (file)
index e307426..0000000
+++ /dev/null
@@ -1,148 +0,0 @@
-(* Copyright (C) 2000, 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://cs.unibo.it/helm/.
- *)
-
-(*  AUTOR: Ferruccio Guidi <fguidi@cs.unibo.it>
- *)
-
-module T = MQGTypes
-
-(* low level functions  *****************************************************)
-
-let string_of_position p = 
-   let ns = "http://www.cs.unibo.it/helm/schemas/schema-helm#" in
-   match p with
-      | T.MainHypothesis -> ns ^ "MainHypothesis"
-      | T.InHypothesis   -> ns ^ "InHypothesis"
-      | T.MainConclusion -> ns ^ "MainConclusion"
-      | T.InConclusion   -> ns ^ "InConclusion"
-      | T.InBody         -> ns ^ "InBody"
-      
-let string_of_sort = function
-   | T.Set   -> "Set"
-   | T.Prop  -> "Prop"
-   | T.Type  -> "Type"
-   | T.CProp -> "CProp"
-
-let string_of_depth = string_of_int
-
-let mathql_of_position = function
-   | T.MainHypothesis -> "$MH"
-   | T.InHypothesis   -> "$IH"
-   | T.MainConclusion -> "$MC"
-   | T.InConclusion   -> "$IC"
-   | T.InBody         -> "$IB"
-      
-let mathql_of_sort = function
-   | T.Set   -> "$SET"
-   | T.Prop  -> "$PROP"
-   | T.Type  -> "$TYPE"
-   | T.CProp -> "$CPROP"
-
-let mathql_of_depth = string_of_int
-
-let mathql_of_uri u = u
-
-let mathql_of_specs out l =
-   let rec iter f = function 
-      | []        -> ()
-      | [s]       -> out "\""; out (f s); out "\""
-      | s :: tail -> out "\""; out (f s); out "\", "; iter f tail
-   in
-   let txt_uri l = out "{"; iter mathql_of_uri l; out "} " in
-   let txt_pos l = out "{"; iter mathql_of_position l; out "} " in
-   let txt_sort l = out "{"; iter mathql_of_sort l; out "} " in
-   let txt_depth l = out "{"; iter mathql_of_depth l; out "} " in
-   let txt_spec = function
-      | T.MustObj  (u, p, d) -> out "mustobj  "; txt_uri u; txt_pos p; txt_depth d; out "\n" 
-      | T.MustSort (s, p, d) -> out "mustsort "; txt_sort s; txt_pos p; txt_depth d; out "\n" 
-      | T.MustRel  (   p, d) -> out "mustrel  "; txt_pos p; txt_depth d; out "\n" 
-      | T.OnlyObj  (u, p, d) -> out "onlyobj  "; txt_uri u; txt_pos p; txt_depth d; out "\n" 
-      | T.OnlySort (s, p, d) -> out "onlysort "; txt_sort s; txt_pos p; txt_depth d; out "\n" 
-      | T.OnlyRel  (   p, d) -> out "onlyrel  "; txt_pos p; txt_depth d; out "\n" 
-      | T.Universe (   p   ) -> out "universe "; txt_pos p; out "\n" 
-   in   
-   List.iter txt_spec l  
-
-let position_of_mathql = function
-   | "$MH" -> T.MainHypothesis 
-   | "$IH" -> T.InHypothesis
-   | "$MC" -> T.MainConclusion
-   | "$IC" -> T.InConclusion
-   | "$IB" -> T.InBody
-   | _     -> raise Parsing.Parse_error 
-
-let sort_of_mathql = function
-   | "$SET"   -> T.Set 
-   | "$PROP"  -> T.Prop
-   | "$TYPE"  -> T.Type
-   | "$CPROP" -> T.CProp
-   | _       -> raise Parsing.Parse_error 
-
-let depth_of_mathql s =
-   try 
-      let d = int_of_string s in
-      if d < 0 then raise (Failure "") else d
-   with Failure _ -> raise Parsing.Parse_error
-
-let uri_of_mathql s = s
-
-(* high level functions  ****************************************************)
-
-let text_of_position = function
-   | `MainHypothesis _ -> "MainHypothesis"
-   | `MainConclusion _ -> "MainConclusion"
-   | `InHypothesis     -> "InHypothesis" 
-   | `InConclusion     -> "InConclusion" 
-   | `InBody           -> "InBody" 
-
-let text_of_depth pos no_depth_text = match pos with
-   | `MainHypothesis (Some d)
-   | `MainConclusion (Some d) -> string_of_int d
-   | _                        -> no_depth_text
-
-let text_of_sort = function
-   | T.Set   -> "Set"
-   | T.Prop  -> "Prop"
-   | T.Type  -> "Type"
-   | T.CProp -> "CProp"
-
-let is_main_position = function
-   | `MainHypothesis _
-   | `MainConclusion _ -> true
-   | _                 -> false
-
-let is_conclusion = function
-   | `MainConclusion _ 
-   | `InConclusion     -> true
-   | _                 -> false
-
-let set_full_position pos depth = match pos with
-   | `MainHypothesis _ -> `MainHypothesis depth
-   | `MainConclusion _ -> `MainConclusion depth
-   | _                 -> pos
-
-let set_main_position pos depth = match pos with
-   | `MainHypothesis _ -> `MainHypothesis depth
-   | `MainConclusion _ -> `MainConclusion depth