]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql/mathQL.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / mathql / mathQL.ml
index 6d112c85b0adea087cc7e0b7b20ec77f6317e24e..7e82fe5474a1919e49bfa08e25fa00c45dda5b69 100644 (file)
  * http://www.cs.unibo.it/helm/.
  *)
 
-(******************************************************************************)
-(*                                                                            *)
-(*                               PROJECT HELM                                 *)
-(*                                                                            *)
-(*                     Ferruccio Guidi <fguidi@cs.unibo.it>                   *)
-(*                     Irene Schena  <schena@cs.unibo.it>                     *)
-(*                                 10/09/2002                                 *)
-(*                                                                            *)
-(*                                                                            *)
-(******************************************************************************)
-
-
-(* input data structures ****************************************************)
-
-type svar = string (* the name of a variable for a resource set *)
-
-type rvar = string (* the name of a variable for a resource *)
-
-type vvar = string (* the name of a variable for an attribute value *)
-
-type refine_op = ExactOp
-               | SubOp
-              | SuperOp
-
-type path = string list
-
-type vvar_list = vvar list
-
-type set_exp = SVar of svar
-            | RVar of rvar
-             | Ref of val_exp
-             | Pattern of val_exp
-            | Relation of refine_op * path * set_exp * vvar_list
-             | Select of rvar * set_exp * boole_exp
-            | Union of set_exp * set_exp
-            | Intersect of set_exp * set_exp
-            | Diff of set_exp * set_exp
-            | LetSVar of svar * set_exp * set_exp
-            | LetVVar of vvar * val_exp * set_exp
-            
-and boole_exp = False
-              | True
-             | Not of boole_exp
-             | Ex of rvar list * boole_exp   
-             | And of boole_exp * boole_exp
-             | Or of boole_exp * boole_exp
-             | Sub of val_exp * val_exp
-             | Meet of val_exp * val_exp
-             | Eq of val_exp * val_exp
-              
-and val_exp = Const of string list 
-            | RefOf of set_exp 
-           | Record of rvar * vvar
-           | VVar of vvar
-           | Fun of string * val_exp
-           | Attribute of refine_op * path * bool * val_exp
-
-type query = set_exp
-
+(*  AUTOR: Ferruccio Guidi <fguidi@cs.unibo.it>
+ *)
 
 (* output data structures ***************************************************)
 
+type path            = string list            (* the name of an attribute *)
+
 type value           = string list            (* the value of an attribute *)
 
-type attribute       = string * value         (* an attribute *)
+type attribute       = path * value           (* an attribute *)
 
 type attribute_group = attribute list         (* a group of attributes *)
 
@@ -98,3 +43,89 @@ type resource        = string * attribute_set (* an attributed URI *)
 type resource_set    = resource list          (* the query result *)
 
 type result = resource_set
+
+
+(* input data structures ****************************************************)
+
+type svar = string (* the name of a variable for a resource set *)
+
+type avar = string (* the name of a variable for a resource *)
+
+type vvar = string (* the name of a variable for an attribute value *)
+
+type inverse = bool 
+
+type refine = RefineExact
+            | RefineSub
+           | RefineSuper
+
+type main = path
+
+type pattern = bool
+
+type exp = path * (path option) 
+
+type exp_list = exp list
+
+type allbut = bool
+
+type xml = bool
+
+type source = bool
+
+type bin = BinFJoin (* full union - with attr handling *)
+         | BinFMeet (* full intersection - with attr handling *)
+         | BinFDiff (* full difference - with attr handling *)
+
+type gen = GenFJoin (* full union - with attr handling *)
+         | GenFMeet (* full intersection - with attr handling *)
+
+type test = Xor
+          | Or
+         | And
+          | Sub
+         | Meet
+         | Eq
+         | Le
+         | Lt
+
+type query = Empty
+           | SVar of svar
+          | AVar of avar
+           | Subj of msval
+          | Property of inverse * refine * path * 
+                        main * istrue * isfalse list * exp_list *
+                        pattern * msval
+           | Select of avar * query * msval
+          | Bin of bin * query * query
+          | LetSVar of svar * query * query
+          | LetVVar of vvar * msval * query
+          | For of gen * avar * query * query 
+          | Add of bool * groups * query
+          | If of msval * query * query
+          | Log of xml * source * query
+          | StatQuery of query
+          | Keep of allbut * path list * query
+          
+and msval = False
+          | True
+          | Not of msval
+         | Ex of avar list * msval
+         | Test of test * msval * msval
+         | Const of string
+         | Set of msval list
+          | Proj of path option * query 
+         | Dot of avar * path
+         | VVar of vvar
+         | StatVal of msval
+         | Count of msval
+         | Align of string * msval
+
+and groups = Attr of (path * msval) list list
+           | From of avar
+
+and con = pattern * path * msval
+
+and istrue = con list
+
+and isfalse = con list