]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_notation/cicNotationMatcher.mli
ocaml 3.09 transition
[helm.git] / helm / ocaml / cic_notation / cicNotationMatcher.mli
index 4abb5b8bc9b37127e77243f74172f025f38e8459..f8daca79894216ebcb75cc24bba525d3adc5e9a9 100644 (file)
@@ -30,30 +30,50 @@ module type PATTERN =
 sig
   type pattern_t
   type term_t
+
   val classify : pattern_t -> pattern_kind
   val tag_of_pattern : pattern_t -> tag_t * pattern_t list
   val tag_of_term : term_t -> tag_t * term_t list
+
+  (** {3 Debugging} *)
+  val string_of_term: term_t -> string
+  val string_of_pattern: pattern_t -> string
 end
 
 module Matcher (P: PATTERN) :
 sig
+  (** @param patterns pattern matrix (pairs <pattern, pattern_id>)
+   * @param success_cb callback invoked in case of matching.
+   *  Its argument are the list of pattern who matches the input term, the list
+   *  of terms bound in them, the list of terms which matched constructors.
+   *  Its return value is Some _ if the matching is valid, None otherwise; the
+   *  latter kind of return value will trigger backtracking in the pattern
+   *  matching algorithm
+   * @param failure_cb callback invoked in case of matching failure
+   * @param term term on which pattern match on *)
   val compiler:
     (P.pattern_t * int) list ->
-    ((P.pattern_t list * int) list -> P.term_t list -> 'a option) ->
+    ((P.pattern_t list * int) list -> P.term_t list -> P.term_t list ->
+      'a option) ->                   (* terms *)    (* constructors *)
     (unit -> 'a option) ->
       (P.term_t -> 'a option)
 end
 
 module Matcher21:
 sig
+  (** @param l2_patterns level 2 (AST) patterns *)
   val compiler :
     (CicNotationPt.term * int) list ->
-      (CicNotationPt.term -> (CicNotationEnv.t * int) option)
+      (CicNotationPt.term ->
+        (CicNotationEnv.t * CicNotationPt.term list * int) option)
 end
 
 module Matcher32:
 sig
+  (** @param l3_patterns level 3 (CIC) patterns (AKA cic_appl_pattern) *)
   val compiler :
     (CicNotationPt.cic_appl_pattern * int) list ->
-      (Cic.annterm -> ((string * Cic.annterm) list * int) option)
+      (Cic.annterm ->
+        ((string * Cic.annterm) list * Cic.annterm list * int) option)
 end
+