]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_notation/cicNotation.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / cic_notation / cicNotation.ml
index 87eb9980e04ad34de832e01520c72d34dbe3c18f..cbad3391f3e01f8f67acec183780c5a748a58b00 100644 (file)
@@ -32,15 +32,23 @@ type notation_id =
 
 let process_notation st =
   match st with
-  | Notation (loc, l1, associativity, precedence, l2) ->
+  | Notation (loc, dir, l1, associativity, precedence, l2) ->
       let rule_id =
-        CicNotationParser.extend l1 ?precedence ?associativity
-          (fun env loc -> CicNotationFwd.instantiate_level2 env l2)
+        if dir <> Some `RightToLeft then
+          [ RuleId (CicNotationParser.extend l1 ?precedence ?associativity
+              (fun env loc -> CicNotationFwd.instantiate_level2 env l2)) ]
+        else
+          []
       in
       let pp_id =
-        CicNotationRew.add_pretty_printer ?precedence ?associativity l2 l1
+        if dir <> Some `LeftToRight then
+          [ PrettyPrinterId
+              (CicNotationRew.add_pretty_printer ?precedence ?associativity
+                l2 l1) ]
+        else
+          []
       in
-      st, [ RuleId rule_id; PrettyPrinterId pp_id ]
+      st, rule_id @ pp_id
   | Interpretation (loc, dsc, l2, l3) ->
       let interp_id = CicNotationRew.add_interpretation dsc l2 l3 in
       st, [ InterpretationId interp_id ]
@@ -53,12 +61,30 @@ let remove_notation = function
 
 let load_notation fname =
   let ic = open_in fname in
-  let istream = Stream.of_channel ic in
+  let lexbuf = Ulexing.from_utf8_channel ic in
   try
     while true do
-      match GrafiteParser.parse_statement istream with
+      match GrafiteParser.parse_statement lexbuf with
       | Executable (_, Command (_, cmd)) -> ignore (process_notation cmd)
       | _ -> ()
     done
   with End_of_file -> close_in ic
 
+let get_all_notations () =
+  List.map
+    (fun (interp_id, dsc) ->
+      InterpretationId interp_id, "interpretation: " ^ dsc)
+    (CicNotationRew.get_all_interpretations ())
+
+let get_active_notations () =
+  List.map (fun id -> InterpretationId id)
+    (CicNotationRew.get_active_interpretations ())
+
+let set_active_notations ids =
+  let interp_ids =
+    HExtlib.filter_map
+      (function InterpretationId interp_id -> Some interp_id | _ -> None)
+      ids
+  in
+  CicNotationRew.set_active_interpretations interp_ids
+