Skip to content

Commit

Permalink
Merge pull request #380 from rgrinberg/yy
Browse files Browse the repository at this point in the history
Cross Compilation
  • Loading branch information
rgrinberg authored Jan 1, 2018
2 parents 1de1ced + f68c1dd commit 5cb909b
Show file tree
Hide file tree
Showing 38 changed files with 867 additions and 368 deletions.
7 changes: 6 additions & 1 deletion CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ next
absolute path but with the context's environment set appropriately. Lastly,
`jbuilder exec` will change the root as to which paths are relative using the
`-root` option. (#286)

- Fix `jbuilder rules` printing rules when some binaries are missing (#292)

- Build documentation for non public libraries (#306)
Expand All @@ -28,6 +28,11 @@ next

- Fix copy# for C/C++ with Microsoft C compiler (#353)

- Add support for cross-compilation. Currently we are supporting the
opam-cross-x repositories such as
[opam-cross-windows](https://github.com/whitequark/opam-cross-windows)
(#355)

1.0+beta16 (05/11/2017)
-----------------------

Expand Down
17 changes: 15 additions & 2 deletions bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ type common =
; target_prefix : string
; only_packages : String_set.t option
; capture_outputs : bool
; x : string option
; (* Original arguments for the external-lib-deps hint *)
orig_args : string list
}
Expand Down Expand Up @@ -74,7 +75,9 @@ module Main = struct
?unlink_aliases
?workspace_file:common.workspace_file
?only_packages:common.only_packages
?filter_out_optional_stanzas_with_missing_deps ()
?filter_out_optional_stanzas_with_missing_deps
?x:common.x
()
end

type target =
Expand Down Expand Up @@ -154,6 +157,7 @@ let common =
no_buffer
workspace_file
(root, only_packages, orig)
x
=
let root, to_cwd =
match root with
Expand Down Expand Up @@ -181,6 +185,7 @@ let common =
; only_packages =
Option.map only_packages
~f:(fun s -> String_set.of_list (String.split s ~on:','))
; x
}
in
let docs = copts_sect in
Expand Down Expand Up @@ -304,6 +309,12 @@ let common =
$ only_packages
$ frop))
in
let x =
Arg.(value
& opt (some string) None
& info ["x"] ~docs
~doc:{|Cross-compile using this toolchain.|})
in
Term.(const make
$ concurrency
$ ddep_path
Expand All @@ -314,14 +325,16 @@ let common =
$ no_buffer
$ workspace_file
$ root_and_only_packages
$ x
)

let installed_libraries =
let doc = "Print out libraries installed on the system." in
let go common na =
set_common common ~targets:[];
Future.Scheduler.go ~log:(Log.create ())
(Context.default () >>= fun ctx ->
(Context.create (Default [Native]) >>= fun ctxs ->
let ctx = List.hd ctxs in
let findlib = ctx.findlib in
if na then begin
let pkgs = Findlib.all_unavailable_packages findlib in
Expand Down
93 changes: 93 additions & 0 deletions doc/advanced-topics.rst
Original file line number Diff line number Diff line change
Expand Up @@ -102,6 +102,99 @@ set of predicates:
it is linked as part of a driver or meant to add a ``-ppx`` argument
to the compiler, choose the former behavior

Cross Compilation
=================

Jbuilder allows for cross compilation by defining build contexts with
multiple targets. Targets are specified by adding a ``targets`` field
to the definition of a build context.

``targets`` takes a list of target name. It can be either:

- ``native`` which means using the native tools that can build
binaries that run on the machine doing the build

- the name of an alternative toolchain

Note that at the moment, there is no official support for
cross-compilation in OCaml. Jbuilder supports the two following
opam-cross-x repositories:

- `opam-cross-windows <https://github.com/whitequark/opam-cross-windows>`_
- `opam-cross-android <https://github.com/whitequark/opam-cross-android>`_

To build Windows binaries using opam-cross-windows, write ``windows``
in the list of targets. To build Android binaries using
opam-cross-android, write ``android`` in the list of targets.

For example, the following workspace file defines three different
targets for the ``default`` build context:

.. code:: scheme
(context (default (targets (native windows android))))
This configuration defines three build contexts:

- ``default``
- ``default.windows``
- ``default.android``

Note that the ``native`` target is always implicitly added when not
present. However, when implicitly added ``jbuilder build @install``
will skip this context, i.e. ``default`` will only be used for
building executables needed by the other contexts.

With such a setup, calling ``jbuilder build @install`` will build all
the packages three times.

Note that instead of writing a ``jbuild-workspace`` file, you can also
use the ``-x`` command line option. Passing ``-x foo`` to ``jbuilder``
without having a ``jbuild-workspace`` file is the same as writing the
following ``jbuild-workspace`` file:

.. code:: scheme
(context (default (targets (foo))))
If you have a ``jbuild-workspace`` and pass a ``-x foo`` option,
``foo`` will be added as target of all context stanzas.

How does it work?
-----------------

In such a setup, binaries that need to be built and executed in the
``default.windows`` or ``default.android`` contexts as part of the
build, will no longer be executed. Instead, all the binaries that will
be executed will come from the ``default`` context. One consequence of
this is that all preprocessing (ppx or otherwise) will be done using
binaries built in the ``default`` context.

To clarify this with an example, let's assume that you have the
following ``src/jbuild`` file:

.. code:: scheme
(executable ((name foo)))
(rule (with-stdout-to blah (run ./foo.exe)))
When building ``_build/default/src/blah``, jbuilder will resolve ``./foo.exe`` to
``_build/default/src/foo.exe`` as expected. However, for
``_build/default.windows/src/blah`` jbuilder will resolve ``./foo.exe`` to
``_build/default/src/foo.exe``

Assuming that the right packages are installed or that your workspace
has no external dependencies, jbuilder will be able to cross-compile a
given package without doing anything special.

Some packages might still have to be updated to support cross-compilation. For
instance if the ``foo.exe`` program in the previous example was using
``Sys.os_type``, it should instead take it as a command line argument:

.. code:: scheme
(rule (with-stdout-to blah (run ./foo.exe -os-type ${os_type})))
Classical ppx
=============

Expand Down
27 changes: 20 additions & 7 deletions doc/usage.rst
Original file line number Diff line number Diff line change
Expand Up @@ -334,9 +334,9 @@ a typical ``jbuild-workspace`` file looks like:

.. code:: scheme
(context ((switch 4.02.3)))
(context ((switch 4.03.0)))
(context ((switch 4.04.0)))
(context (opam (switch 4.02.3)))
(context (opam (switch 4.03.0)))
(context (opam (switch 4.04.0)))
The rest of this section describe the stanzas available.

Expand All @@ -354,13 +354,13 @@ context
~~~~~~~

The ``(context ...)`` stanza declares a build context. The argument
can be either ``default`` for the default build context or can be the
description of an opam switch, as follows:
can be either ``default`` or ``(default)`` for the default build
context or can be the description of an opam switch, as follows:

.. code:: scheme
(context ((switch <opam-switch-name>)
<optional-fields>))
(context (opam (switch <opam-switch-name>)
<optional-fields>))
``<optional-fields>`` are:

Expand All @@ -374,6 +374,10 @@ description of an opam switch, as follows:
- ``(merlin)`` instructs Jbuilder to use this build context for
merlin

Both ``(default ...)`` and ``(opam ...)`` accept a ``targets`` field
in order to setup cross compilation. See `Cross Compilation`_ for more
information.

Merlin reads compilation artifacts and it can only read the
compilation artifacts of a single context. Usually, you should use
the artifacts from the ``default`` context, and if you have the
Expand All @@ -384,6 +388,15 @@ For rare cases where this is not what you want, you can force Jbuilder
to use a different build contexts for merlin by adding the field
``(merlin)`` to this context.

Note that the following syntax is still accepted but is deprecated:

.. code:: scheme
(context ((switch <opam-switch-name>)
<optional-fields>))
it is interpreted the same as ``(context (opam (switch ...) ...))``.

Building JavaScript with js_of_ocaml
====================================

Expand Down
12 changes: 6 additions & 6 deletions jbuild-workspace.dev
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
;; This file is used by `make all-supported-ocaml-versions`
(context ((switch 4.02.3)))
(context ((switch 4.03.0)))
(context ((switch 4.04.2)))
(context ((switch 4.05.0)))
(context ((switch 4.06.0)))
(context ((switch 4.07.0+trunk)))
(context (opam (switch 4.02.3)))
(context (opam (switch 4.03.0)))
(context (opam (switch 4.04.2)))
(context (opam (switch 4.05.0)))
(context (opam (switch 4.06.0)))
(context (opam (switch 4.07.0+trunk)))
48 changes: 36 additions & 12 deletions src/action.ml
Original file line number Diff line number Diff line change
Expand Up @@ -327,23 +327,28 @@ module Unexpanded = struct
~map:(fun x -> (x, []))
end

let rec expand dir t ~f : Unresolved.t =
let rec expand t ~dir ~map_exe ~f : Unresolved.t =
match t with
| Run (prog, args) ->
let args = List.concat_map args ~f:(E.strings ~dir ~f) in
let prog, more_args = E.prog_and_args ~dir ~f prog in
let prog =
match prog with
| Search _ -> prog
| This path -> This (map_exe path)
in
Run (prog, more_args @ args)
| Chdir (fn, t) ->
let fn = E.path ~dir ~f fn in
Chdir (fn, expand fn t ~f)
Chdir (fn, expand t ~dir:fn ~map_exe ~f)
| Setenv (var, value, t) ->
Setenv (E.string ~dir ~f var, E.string ~dir ~f value,
expand dir t ~f)
expand t ~dir ~map_exe ~f)
| Redirect (outputs, fn, t) ->
Redirect (outputs, E.path ~dir ~f fn, expand dir t ~f)
Redirect (outputs, E.path ~dir ~f fn, expand t ~dir ~map_exe ~f)
| Ignore (outputs, t) ->
Ignore (outputs, expand dir t ~f)
| Progn l -> Progn (List.map l ~f:(fun t -> expand dir t ~f))
Ignore (outputs, expand t ~dir ~map_exe ~f)
| Progn l -> Progn (List.map l ~f:(fun t -> expand t ~dir ~map_exe ~f))
| Echo x -> Echo (E.string ~dir ~f x)
| Cat x -> Cat (E.path ~dir ~f x)
| Copy (x, y) ->
Expand Down Expand Up @@ -406,7 +411,7 @@ module Unexpanded = struct
~special:VE.to_prog_and_args
end

let rec partial_expand dir t ~f : Partial.t =
let rec partial_expand t ~dir ~map_exe ~f : Partial.t =
match t with
| Run (prog, args) ->
let args =
Expand All @@ -419,6 +424,11 @@ module Unexpanded = struct
match E.prog_and_args ~dir ~f prog with
| Inl (prog, more_args) ->
let more_args = List.map more_args ~f:(fun x -> Inl x) in
let prog =
match prog with
| Search _ -> prog
| This path -> This (map_exe path)
in
Run (Inl prog, more_args @ args)
| Inr _ as prog ->
Run (prog, args)
Expand All @@ -427,7 +437,7 @@ module Unexpanded = struct
let res = E.path ~dir ~f fn in
match res with
| Inl dir ->
Chdir (res, partial_expand dir t ~f)
Chdir (res, partial_expand t ~dir ~map_exe ~f)
| Inr fn ->
let loc = SW.loc fn in
Loc.fail loc
Expand All @@ -436,12 +446,12 @@ module Unexpanded = struct
end
| Setenv (var, value, t) ->
Setenv (E.string ~dir ~f var, E.string ~dir ~f value,
partial_expand dir t ~f)
partial_expand t ~dir ~map_exe ~f)
| Redirect (outputs, fn, t) ->
Redirect (outputs, E.path ~dir ~f fn, partial_expand dir t ~f)
Redirect (outputs, E.path ~dir ~f fn, partial_expand t ~dir ~map_exe ~f)
| Ignore (outputs, t) ->
Ignore (outputs, partial_expand dir t ~f)
| Progn l -> Progn (List.map l ~f:(fun t -> partial_expand dir t ~f))
Ignore (outputs, partial_expand t ~dir ~map_exe ~f)
| Progn l -> Progn (List.map l ~f:(fun t -> partial_expand t ~dir ~map_exe ~f))
| Echo x -> Echo (E.string ~dir ~f x)
| Cat x -> Cat (E.path ~dir ~f x)
| Copy (x, y) ->
Expand Down Expand Up @@ -525,6 +535,20 @@ type exec_context =
}

let run ~ectx ~dir ~env_extra ~stdout_to ~stderr_to prog args =
begin match ectx.context with
| None
| Some { Context.for_host = None; _ } -> ()
| Some ({ Context.for_host = Some host; _ } as target) ->
let invalid_prefix prefix =
match Path.descendant prog ~of_:(Path.of_string prefix) with
| None -> ()
| Some _ ->
die "Context %s has a host %[email protected]'s not possible to execute binary %a \
in it.@[email protected] is a bug and should be reported upstream."
target.name host.name Path.pp prog in
invalid_prefix ("_build/" ^ target.name);
invalid_prefix ("_build/install/" ^ target.name);
end;
let stdout_to = get_std_output stdout_to in
let stderr_to = get_std_output stderr_to in
let env = Context.extend_env ~vars:env_extra ~env:ectx.env in
Expand Down
10 changes: 6 additions & 4 deletions src/action.mli
Original file line number Diff line number Diff line change
Expand Up @@ -78,15 +78,17 @@ module Unexpanded : sig
with type string = (string , String_with_vars.t) either

val expand
: Path.t
-> t
: t
-> dir:Path.t
-> map_exe:(Path.t -> Path.t)
-> f:(Loc.t -> String.t -> Var_expansion.t option)
-> Unresolved.t
end

val partial_expand
: Path.t
-> t
: t
-> dir:Path.t
-> map_exe:(Path.t -> Path.t)
-> f:(Loc.t -> string -> Var_expansion.t option)
-> Partial.t
end
Expand Down
Loading

0 comments on commit 5cb909b

Please sign in to comment.