]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql_interpreter/mqint.ml
new MathQL syntax
[helm.git] / helm / ocaml / mathql_interpreter / mqint.ml
index 2bf4d144ed18994658ff0ec012d8d7c7e7aa986b..dce67f86494d9fc3f95006622eae5af340626a51 100644 (file)
@@ -26,7 +26,7 @@
 (*
  * implementazione del'interprete MathQL
  *)
-open Mathql;;
+open MathQL;;
 open Eval;;
 open Utility;;
 open Dbconn;;
@@ -74,7 +74,7 @@ let rec execute_ex env =
  |  MQUse (alist, asvar) ->
      use_ex (execute_ex env alist) asvar "B" (*"backPointer"*)
  |  MQPattern (apreamble, apattern, afragid) ->
-     pattern_ex apreamble apattern afragid
+     pattern_ex (apreamble, apattern, afragid)
  |  MQUnion (l1, l2) ->
      union_ex (execute_ex env l1) (execute_ex env l2)
 (*
@@ -122,6 +122,8 @@ Select.execute := execute_ex;;
  * la uri puo' far parte del risultato.
  *)
 let xres_to_res l =
+ MQRefs (List.map (function {Mathql_semantics.uri = uri} -> uri) l)
+(*
  let tmp = List.map (function {Mathql_semantics.uri = uri} -> uri) l in
   MQRefs
    (List.map
@@ -131,48 +133,49 @@ let xres_to_res l =
           match List.rev tl with
              ")"::n::"xpointer(1"::tail    ->
               (
-               hd,
+               Some hd,
                List.fold_left
                 (fun par t ->
                  match par with
-                    [] -> [MQString t] 
-                 |  _  -> (MQString t) :: MQSlash :: par
+                    [] -> [MQBC t] 
+                 |  _  -> (MQBC t) :: MQBD :: par
                 )
                 []
                 tail, 
-               (Some (int_of_string n), None)
+               [MQFC (int_of_string n)]
               )
           |  ")"::n::m::"xpointer(1"::tail ->
               (
-               hd,
+               Some hd,
                List.fold_left
                 (fun par t ->
                  match par with
-                    [] -> [MQString t] 
-                 |  _  -> (MQString t) :: MQSlash :: par
+                    [] -> [MQBC t] 
+                 |  _  -> (MQBC t) :: MQBD :: par
                 )
                 []
                 tail,
-               (Some (int_of_string m), Some (int_of_string n))
+               [MQFC (int_of_string m); MQFC (int_of_string n)]
               )
           |  tail                          ->
               (
-               hd,
+               Some hd,
                List.fold_left
                 (fun par t ->
                  match par with
-                    [] -> [MQString t] 
-                 |  _  -> (MQString t) :: MQSlash :: par
+                    [] -> [MQBC t] 
+                 |  _  -> (MQBC t) :: MQBD :: par
                 )
                 []
                 tail, 
-               (None, None)
+               []
               )
       )  
       |  [] -> assert false
     )
     tmp
    )
+*)
 ;;