]> 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 82ab6f9da3bec59495864f787ecdf15928d37ed4..7e82fe5474a1919e49bfa08e25fa00c45dda5b69 100644 (file)
  * http://www.cs.unibo.it/helm/.
  *)
 
-(******************************************************************************)
-(*                                                                            *)
-(*                               PROJECT HELM                                 *)
-(*                                                                            *)
-(*                     Ferruccio Guidi <fguidi@cs.unibo.it>                   *)
-(*                     Domenico Lordi  <lordi@cs.unibo.it>                    *)
-(*                                 30/04/2002                                 *)
-(*                                                                            *)
-(*                                                                            *)
-(******************************************************************************)
-
-exception MQInvalidURI of string
-exception MQConnectionFailed of string
-exception MQInvalidConnection of string
-
-(* Input types **************************************************************)
-(* main type is mquery                                                      *)
-
-type mqrvar = string (* name *)
-
-type mqsvar = string (* name *)
-
-type mqlvar = string (* name *)
-
-type mqpt = string option (* PROTOCOL TOKENS *)
-                          (* Some = constant string *)
-                          (* None = single star: '*' *)
-
-type mqbt =               (* BODY TOKENS *)
-   | MQBC of string       (* a constant string *)
-   | MQBD                 (* a slash: '/' *)
-   | MQBQ                 (* a question mark: '?' *)
-   | MQBS                 (* a single star: '*' *)
-   | MQBSS                (* a double star: '**' *)
-
-type mqft =               (* FRAGMENT TOKENS *)
-   | MQFC of int          (* a constant integer *)
-   | MQFS                 (* a single star: '*' *)
-   | MQFSS                (* a double star: '**' *)
-
-type mquref = UriManager.uri * (int list) (* uri, fragment identifier *)
-
-type mqtref = mqpt * (mqbt list) * (mqft list) (* tokenized pattern reference *)
-
-type mqref = string (* format for references (helper) *)
-
-type mqfunc =
-   | MQName         (* Name *)
-   | MQTheory       (* theory *)
-   | MQTitle        (* DC properties *)
-   | MQContributor
-   | MQCreator
-   | MQPublisher
-   | MQSubject
-   | MQDescription
-   | MQDate
-   | MQType
-   | MQFormat
-   | MQIdentifier
-   | MQLanguage
-   | MQRelation
-   | MQSource
-   | MQCoverage
-   | MQRights
-   | MQInstitution
-   | MQContact
-   | MQFirstVersion 
-   | MQModified
-
-type mqstring =
-   | MQCons of string          (* constant *)
-   | MQFunc of mqfunc * mqrvar (* function, rvar *)
-   | MQStringRVar of mqrvar    (* rvar *)
-   | MQStringSVar of mqsvar    (* svar *)
-   | MQMConclusion             (* main conclusion *)
-   | MQConclusion              (* inner conclusion *)
-
-type mqorder =
-   | MQAsc     (* ascending order *)
-   | MQDesc    (* descending order *)
-
-type mqbool =
-   | MQTrue                        (* true *)
-   | MQFalse                       (* false *)
-   | MQAnd of mqbool * mqbool      (* conjunction *)
-   | MQOr of mqbool * mqbool       (* disjunction *)
-   | MQNot of mqbool               (* negation *)
-   | MQIs of mqstring * mqstring   (* case-sensitive comparison  *)
-   | MQSetEqual of mqlist * mqlist (* the two lists denote the same set *)
-   | MQSubset of mqlist * mqlist   (* the two lists denote two sets, the 1st subset of the 2nd *)
-
-and mqlist =
-   | MQReference of mqref list               (* reference list *)
-   | MQPattern of mqtref list                (* pattern list *)
-   | MQListLVar of mqlvar                    (* lvar *)
-   | MQListRVar of mqrvar                    (* rvar *)
-   | MQSelect of mqrvar * mqlist * mqbool    (* rvar, list, boolean *) 
-   | MQUse of mqlist * mqsvar                (* list, Position attribute *)
-   | MQUsedBy of mqlist * mqsvar             (* list, Position attribute *)
-   | MQUnion of mqlist * mqlist              (* operands *)
-   | MQIntersect of mqlist * mqlist          (* operands *)
-   | MQSortedBy of mqlist * mqorder * mqfunc (* ordering *)
-   | MQDiff of mqlist * mqlist               (* set difference  *)
-   | MQLetIn of mqlvar * mqlist * mqlist     (* explicit lvar assignment *)
-   | MQMinimize of mqlist                    (* list minimization *)
-   
-type mquery =
-   | MQList of mqlist
-   
-(* Output types *************************************************************)
-(* main type is mqresult                                                    *)
-
-type mqresult =
-   | MQRefs of mqref list
+(*  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       = path * value           (* an attribute *)
+
+type attribute_group = attribute list         (* a group of attributes *)
+
+type attribute_set   = attribute_group list   (* the attributes of an URI *)
+
+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