File: shape_reduce.mli

package info (click to toggle)
ocaml 5.4.0-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 44,372 kB
  • sloc: ml: 370,196; ansic: 52,820; sh: 27,419; asm: 5,462; makefile: 3,684; python: 974; awk: 278; javascript: 273; perl: 59; fortran: 21; cs: 9
file content (62 lines) | stat: -rw-r--r-- 3,202 bytes parent folder | download | duplicates (9)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
(**************************************************************************)
(*                                                                        *)
(*                                 OCaml                                  *)
(*                                                                        *)
(*                 Ulysse Gérard, Thomas Refis, Tarides                   *)
(*                    Nathanaëlle Courant, OCamlPro                       *)
(*              Gabriel Scherer, projet Picube, INRIA Paris               *)
(*                                                                        *)
(*   Copyright 2021 Institut National de Recherche en Informatique et     *)
(*     en Automatique.                                                    *)
(*                                                                        *)
(*   All rights reserved.  This file is distributed under the terms of    *)
(*   the GNU Lesser General Public License version 2.1, with the          *)
(*   special exception on linking described in the file LICENSE.          *)
(*                                                                        *)
(**************************************************************************)

(** The result of reducing a shape and looking for its uid *)
type result =
  | Resolved of Shape.Uid.t (** Shape reduction succeeded and a uid was found *)
  | Resolved_alias of Shape.Uid.t * result (** Reduction led to an alias *)
  | Unresolved of Shape.t (** Result still contains [Comp_unit] terms *)
  | Approximated of Shape.Uid.t option
    (** Reduction failed: it can arrive with first-class modules for example *)
  | Internal_error_missing_uid
    (** Reduction succeeded but no uid was found, this should never happen *)

val print_result : Format.formatter -> result -> unit

(** The [Make] functor is used to generate a reduction function for
    shapes.

    It is parametrized by:
    - a function to load the shape of an external compilation unit
    - some fuel, which is used to bound recursion when dealing with recursive
      shapes introduced by recursive modules. (FTR: merlin currently uses a
      fuel of 10, which seems to be enough for most practical examples)

    Usage warning: To ensure good performances, every reduction made with the
    same instance of that functor share the same ident-based memoization tables.
    Such an instance should only be used to perform reduction inside a unique
    compilation unit to prevent conflicting entries in these memoization tables.
*)
module Make(_ : sig
    val fuel : int

    val read_unit_shape : unit_name:string -> Shape.t option
  end) : sig
  val reduce : Env.t -> Shape.t -> Shape.t

  (** Perform weak reduction and return the head's uid if any. If reduction was
    incomplete the partially reduced shape is returned. *)
  val reduce_for_uid : Env.t -> Shape.t -> result
end

(** [local_reduce] will not reduce shapes that require loading external
  compilation units. *)
val local_reduce : Env.t -> Shape.t -> Shape.t

(** [local_reduce_for_uid] will not reduce shapes that require loading external
  compilation units. *)
val local_reduce_for_uid : Env.t -> Shape.t -> result