Skip to content

Commit

Permalink
test(x-compilation): show case of ppx_runtime_libraries not being r…
Browse files Browse the repository at this point in the history
…esolved
  • Loading branch information
anmonteiro committed Jun 5, 2023
1 parent 6282041 commit f99973b
Show file tree
Hide file tree
Showing 11 changed files with 191 additions and 0 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
(lang dune 1.0)

(package
(name other-ppx))
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
(library
(name ppx_deriving_eq)
(public_name other-ppx.eq)
(synopsis "[@@deriving eq]")
(libraries other-ppx.api)
(ppx.driver
(main Ppx_deriving_eq.main))
(kind ppx_deriver))
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
let deriver = "eq"

let main () =
let out = ref "" in
let args =
[ ("-o", Arg.Set_string out, "")
; ("--impl", Arg.Set_string (ref ""), "")
; ("--as-ppx", Arg.Set (ref false), "")
; ("--cookie", Arg.Set (ref false), "")
]
in
let anon _ = () in
Arg.parse (Arg.align args) anon "";
let out = open_out !out in
close_out out;
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
(library
(name ppx_deriving_std)
(public_name other-ppx.std)
(libraries ppx_deriving_eq)
(kind ppx_deriver))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(* dummy module to appease dune and older version of OCaml *)
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
(library
(name ppx_deriving_api)
(public_name other-ppx.api)
(wrapped false)
(ppx_runtime_libraries ppx_deriving_runtime)
(libraries compiler-libs.common))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let () = ()
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
(library
(name ppx_deriving_runtime)
(public_name other-ppx.runtime)
(wrapped false))
Original file line number Diff line number Diff line change
@@ -0,0 +1,34 @@
type nonrec int = int
type nonrec char = char
type nonrec string = string
type nonrec float = float
type nonrec bool = bool
type nonrec unit = unit
type nonrec exn = exn
type nonrec 'a array = 'a array
type nonrec 'a list = 'a list
type nonrec 'a option = 'a option
type nonrec nativeint = nativeint
type nonrec int32 = int32
type nonrec int64 = int64
type nonrec 'a lazy_t = 'a lazy_t
type nonrec bytes = bytes

(* We require 4.08 while 4.07 already has a Stdlib module.
In 4.07, the type equalities on Stdlib.Pervasives
are not strong enough for the 'include Stdlib'
below to satisfy the signature constraints on
Ppx_deriving_runtime.Pervasives. *)
module Stdlib = Stdlib

include Stdlib

module Result = struct
type ('a, 'b) t = ('a, 'b) result =
| Ok of 'a
| Error of 'b

type ('a, 'b) result = ('a, 'b) t =
| Ok of 'a
| Error of 'b
end
Original file line number Diff line number Diff line change
@@ -0,0 +1,41 @@
(** A module collecting all predefined OCaml types, exceptions and
modules operating on them, so that ppx_deriving plugins operate
in a well-defined environment. *)

(** {2 Predefined types} *)
type nonrec int = int
type nonrec char = char
type nonrec string = string
type nonrec float = float
type nonrec bool = bool
type nonrec unit = unit
type nonrec exn = exn
type nonrec 'a array = 'a array
type nonrec 'a list = 'a list
type nonrec 'a option = 'a option
type nonrec nativeint = nativeint
type nonrec int32 = int32
type nonrec int64 = int64
type nonrec 'a lazy_t = 'a lazy_t
type nonrec bytes = bytes

(** {2 Predefined modules}
{3 Operations on predefined types} *)

include module type of struct
include Stdlib
end

module Stdlib = Stdlib

module Result : sig
type ('a, 'b) t = ('a, 'b) result =
| Ok of 'a
| Error of 'b

(* we also expose Result.result for backward-compatibility
with the Result package! *)
type ('a, 'b) result = ('a, 'b) t =
| Ok of 'a
| Error of 'b
end
Original file line number Diff line number Diff line change
@@ -0,0 +1,72 @@
Demonstrate a bad interaction between cross-compilation and
ppx_runtime_libraries

$ mkdir -p etc/findlib.conf.d
$ export OCAMLFIND_CONF=$PWD/etc/findlib.conf
$ touch etc/findlib.conf etc/findlib.conf.d/foo.conf

Create lib1, ppx and lib2:
- lib1 is a regular library
- lib2 is a regular library, declares `ppx_runtime_libraries` for lib
- ppx has a runtime dep on lib1 (via `ppx_runtime_libraries`)

$ mkdir lib1 ppx lib2
$ cat > dune-project <<EOF
> (lang dune 3.8)
> (package (name ppx-cross))
> EOF

$ cat > lib1/dune <<EOF
> (library
> (name lib1)
> (public_name ppx-cross.lib1))
> EOF

$ cat > lib2/dune <<EOF
> (library
> (name lib2)
> (public_name ppx-cross.lib2)
> (ppx_runtime_libraries lib1))
> EOF
$ touch lib2/lib2.ml

$ dune build @install -x foo

$ cat > ppx/dune <<EOF
> (library
> (name ppx)
> (public_name ppx-cross.ppx)
> (kind ppx_rewriter)
> (ppx.driver (main Ppx.main)))
> EOF
$ cat > ppx/ppx.ml <<EOF
> let main () =
> let out = ref "" in
> let args =
> [ ("-o", Arg.Set_string out, "")
> ; ("--impl", Arg.Set_string (ref ""), "")
> ; ("--as-ppx", Arg.Set (ref false), "")
> ; ("--cookie", Arg.Set (ref false), "")
> ]
> in
> let anon _ = () in
> Arg.parse (Arg.align args) anon "";
> let out = open_out !out in
> close_out out;
> EOF

$ mkdir lib3
$ cat > lib3/dune <<EOF
> (library
> (name lib3)
> (public_name ppx-cross.lib3)
> (preprocess (pps other-ppx.std)))
> EOF
$ touch lib3/lib3.ml

$ cat > dune <<EOF
> (vendored_dirs ppx_deriving)
> EOF

$ dune build @install -x foo

0 comments on commit f99973b

Please sign in to comment.