Skip to content

Commit

Permalink
flambda-backend: Evaluate signature substitutions lazily (upstream PR…
Browse files Browse the repository at this point in the history
… 10599) (ocaml#280)

(cherry picked from commit fa43873)
  • Loading branch information
stedolan committed Sep 20, 2021
1 parent a1a07de commit 57231d2
Show file tree
Hide file tree
Showing 14 changed files with 626 additions and 256 deletions.
2 changes: 2 additions & 0 deletions .depend
Expand Up @@ -1106,6 +1106,8 @@ typing/subst.cmx : \
typing/subst.cmi : \
typing/types.cmi \
typing/path.cmi \
parsing/parsetree.cmi \
parsing/location.cmi \
typing/ident.cmi
typing/tast_iterator.cmo : \
typing/typedtree.cmi \
Expand Down
Binary file modified boot/ocamlc
Binary file not shown.
Binary file modified boot/ocamllex
Binary file not shown.
18 changes: 9 additions & 9 deletions testsuite/tests/shadow_include/shadow_all.ml
Expand Up @@ -304,7 +304,7 @@ module NN :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = N.T
exception E
type ext = N.ext = ..
type ext += C
Expand All @@ -329,7 +329,7 @@ module Type :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = N.T
exception E
type ext = N.ext = ..
type ext += C
Expand All @@ -352,7 +352,7 @@ module Module :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = N.T
exception E
type ext = N.ext = ..
type ext += C
Expand All @@ -370,12 +370,12 @@ end
[%%expect{|
module Module_type :
sig
module type U = sig end
module type U = N.T
type t = N.t
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = N.T
exception E
type ext = N.ext = ..
type ext += C
Expand All @@ -398,7 +398,7 @@ module Exception :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = N.T
exception E
type ext = N.ext = ..
type ext += C
Expand All @@ -421,7 +421,7 @@ module Extension :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = N.T
exception E
type ext = N.ext = ..
type ext += C
Expand All @@ -444,7 +444,7 @@ module Class :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = N.T
exception E
type ext = N.ext = ..
type ext += C
Expand All @@ -467,7 +467,7 @@ module Class_type :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = N.T
exception E
type ext = N.ext = ..
type ext += C
Expand Down

0 comments on commit 57231d2

Please sign in to comment.