Skip to content

Commit

Permalink
dummy for recursive modules
Browse files Browse the repository at this point in the history
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/fastclass@5971 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
Jacques Garrigue committed Nov 22, 2003
1 parent b87ab0d commit 8e0d1a9
Show file tree
Hide file tree
Showing 2 changed files with 1 addition and 5 deletions.
5 changes: 1 addition & 4 deletions bytecomp/translclass.ml
Original file line number Diff line number Diff line change
Expand Up @@ -723,11 +723,8 @@ module F(X:sig end) = struct
end;;
*)

let class_stub =
Lprim(Pmakeblock(0, Mutable), [lambda_unit; lambda_unit; lambda_unit])

let dummy_class undef_fn =
Lprim(Pmakeblock(0, Mutable), [undef_fn; undef_fn; oo_prim "dummy_table"])
Lprim(Pmakeblock(0, Mutable), [undef_fn; undef_fn; undef_fn; lambda_unit])

(* Wrapper for class compilation *)

Expand Down
1 change: 0 additions & 1 deletion bytecomp/translclass.mli
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,6 @@
open Typedtree
open Lambda

val class_stub : lambda
val dummy_class : lambda -> lambda
val transl_class :
Ident.t list -> Ident.t -> int -> string list -> class_expr -> lambda;;
Expand Down

0 comments on commit 8e0d1a9

Please sign in to comment.