Skip to content

Commit

Permalink
boot: add a --static option to build a static dune (#10528)
Browse files Browse the repository at this point in the history
This options adds `-ccopt -static` to the link flags (this requires a
libc that supports static linking).

The motivation is `nix build .#dune-static`, which otherwise requires
patching sources.

Signed-off-by: Etienne Millon <me@emillon.org>
  • Loading branch information
emillon committed May 15, 2024
1 parent 5904a00 commit cd9595a
Show file tree
Hide file tree
Showing 3 changed files with 8 additions and 9 deletions.
1 change: 1 addition & 0 deletions boot/bootstrap.ml
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ let keep_generated_files =
; ( "--force-byte-compilation"
, Arg.Unit ignore
, " Force bytecode compilation even if ocamlopt is available" )
; "--static", Arg.Unit ignore, " Build a static binary"
]
anon
"Usage: ocaml bootstrap.ml <options>\nOptions are:";
Expand Down
8 changes: 6 additions & 2 deletions boot/duneboot.ml
Original file line number Diff line number Diff line change
@@ -1,13 +1,14 @@
(** {2 Command line} *)

let concurrency, verbose, debug, secondary, force_byte_compilation =
let concurrency, verbose, debug, secondary, force_byte_compilation, static =
let anon s = raise (Arg.Bad (Printf.sprintf "don't know what to do with %s\n" s)) in
let concurrency = ref None in
let verbose = ref false in
let prog = Filename.basename Sys.argv.(0) in
let debug = ref false in
let secondary = ref false in
let force_byte_compilation = ref false in
let static = ref false in
Arg.parse
[ "-j", Int (fun n -> concurrency := Some n), "JOBS Concurrency"
; "--verbose", Set verbose, " Set the display mode"
Expand All @@ -17,10 +18,11 @@ let concurrency, verbose, debug, secondary, force_byte_compilation =
; ( "--force-byte-compilation"
, Set force_byte_compilation
, " Force bytecode compilation even if ocamlopt is available" )
; "--static", Set static, " Build a static binary"
]
anon
(Printf.sprintf "Usage: %s <options>\nOptions are:" prog);
!concurrency, !verbose, !debug, !secondary, !force_byte_compilation
!concurrency, !verbose, !debug, !secondary, !force_byte_compilation, !static
;;

(** {2 General configuration} *)
Expand Down Expand Up @@ -1123,6 +1125,7 @@ let build
| ".ml" -> Some (Filename.remove_extension fn ^ compiled_ml_ext)
| _ -> None)
in
let static_flags = if static then [ "-ccopt"; "-static" ] else [] in
write_args "compiled_ml_files" compiled_ml_files;
Process.run
~cwd:build_dir
Expand All @@ -1132,6 +1135,7 @@ let build
; obj_files
; [ "-args"; "compiled_ml_files" ]
; link_flags
; static_flags
; allow_unstable_sources
])
;;
Expand Down
8 changes: 1 addition & 7 deletions flake.nix
Original file line number Diff line number Diff line change
Expand Up @@ -47,13 +47,7 @@
ocamlPackages = super.ocaml-ng.ocamlPackages_4_14.overrideScope (oself: osuper: {
dune_3 = osuper.dune_3.overrideAttrs (a: {
src = ./.;
postPatch = ''
substituteInPlace \
boot/duneboot.ml \
--replace-fail \
'; link_flags' \
'; link_flags; ["-ccopt"; "-static"]'
'';
preBuild = "ocaml boot/bootstrap.ml --static";
});
});
};
Expand Down

0 comments on commit cd9595a

Please sign in to comment.