(**************************************************************************) (* *) (* OCaml *) (* *) (* David Allsopp, University of Cambridge & Tarides *) (* *) (* Copyright 2025 David Allsopp Ltd. *) (* *) (* All rights reserved. This file is distributed under the terms of *) (* the GNU Lesser General Public License version 2.1, with the *) (* special exception on linking described in the file LICENSE. *) (* *) (**************************************************************************) (* This script is called from the root of the repository at the end of `make INSTALL_MODE= install` and is responsible for converting the various files generated by the installation backend into final output. Parameters are the following Makefile variables: $1 = $(INSTALL_MODE) (opam or clone) $2 = $(OPAM_PACKAGE_NAME) $3 = $(LN) *) let exit_because fmt = Printf.ksprintf (fun s -> prerr_endline s; exit 1) fmt let () = if Array.length Sys.argv <> 4 || Sys.argv.(1) <> "clone" && Sys.argv.(1) <> "opam" then begin exit_because "Invalid command line arguments" end let mode = Sys.argv.(1) let package = Sys.argv.(2) let ln_command = Sys.argv.(3) let output_endline oc = Printf.kfprintf (fun oc -> output_char oc '\n') oc (* [generate_file file] processes then erases opam-bin, opam-lib opam-libexec and opam-man to produce [file] *) let write_install_lines oc file = In_channel.with_open_text file @@ In_channel.fold_lines (fun _ -> output_endline oc " %s") () let output_section oc section = let file = "opam-" ^ section in if Sys.file_exists file then begin let section = if section = "lib" || section = "libexec" then section ^ "_root" else section in output_endline oc {|%s: [ %a]|} section write_install_lines file; Sys.remove file end let generate_install file = Out_channel.with_open_text file @@ fun oc -> List.iter (output_section oc) ["bin"; "lib"; "libexec"; "man"]; output_endline oc {|share_root: [ "config.cache" {"ocaml/config.cache"} "config.status" {"ocaml/config.status"} ]|} (* [process_clone oc process] processes clone-* in the current directory, emitting mkdir commands to [oc] and passing the directory name and a channel set to the start of each clone file to [process]. The clone files are erased after processing. *) let process_clone oc process = let process_file file = if String.starts_with ~prefix:"clone-" file then begin let dir = String.map (function '@' -> '/' | c -> c) (String.sub file 6 (String.length file - 6)) in output_endline oc {|mkdir -p "$1/%s"|} dir; In_channel.with_open_text file @@ process oc dir; Sys.remove file end in Array.iter process_file (Sys.readdir Filename.current_dir_name) (* [process_symlinks oc ~mkdir] processes create-symlinks, if it exists, writing any required mkdir commands to [oc] if [~mkdir = true] and also the appropriate ln / mklink commands. create-symlinks is erased after processing. *) let process_symlinks oc ~mkdir = let module StringSet = Set.Make(String) in let file = "create-symlinks" in if Sys.file_exists file then let lines = let parse acc line = match String.split_on_char ' ' line with | [dir; target; source] -> (dir, target, source)::acc | _ -> exit_because "Invalid line encountered in create-symlinks" in In_channel.with_open_text file @@ fun ic -> List.rev (In_channel.fold_lines parse [] ic) in output_endline oc {|cd "$1"|}; let _ = let create_dir seen (dir, _, _) = if not (StringSet.mem dir seen) && String.contains dir '/' then output_endline oc {|mkdir -p '%s'|} dir; StringSet.add dir seen in List.fold_left create_dir StringSet.empty (if mkdir then lines else []) in if not Sys.win32 then let ln (dir, target, source) = let target = Filename.quote target in let source = Filename.quote (Filename.concat dir source) in output_endline oc {|%s %s %s|} ln_command target source in List.iter ln lines else begin let mklink (dir, target, source) = (* Convert all slashes to _two_ backslashes *) let to_backslashes oc s = output_string oc (String.concat {|\\|} (String.split_on_char '/' s)) in output_endline oc {| cmd /c "mklink %a\\%s %s"|} to_backslashes dir source target and cp (dir, target, source) = let target = Filename.quote (Filename.concat dir target) in let source = Filename.quote (Filename.concat dir source) in output_endline oc {| $CP %s %s|} target source in output_endline oc {|cmd /c "mklink __ln_test mklink-test"|}; output_endline oc {|if test -L "$1/__ln_test"; then|}; List.iter mklink lines; output_endline oc {|else|}; List.iter cp lines; output_endline oc {|fi|}; output_endline oc {|rm -f __ln_test|} end; Sys.remove file let copy_files oc dir = In_channel.fold_lines (fun _ line -> match String.split_on_char ' ' line with | [source; dest] -> output_endline oc {|cp '%s' "$1/%s/%s"|} source dir dest | _ -> exit_because "Invalid line encountered in clone files") () let clone_files oc dir ic = output_endline oc {|dest="$1/%s" xargs sh "$1/clone-files" <<'EOF'|} dir; In_channel.fold_lines (fun _ -> output_endline oc "%s") () ic; output_endline oc {|EOF|} let () = if mode = "opam" then begin generate_install (package ^ ".install"); (* The script must be written with Unix line-endings on Windows *) Out_channel.with_open_bin (package ^ "-fixup.sh") @@ fun oc -> output_endline oc {|#!/bin/sh set -e|}; process_clone oc copy_files; process_symlinks oc ~mkdir:true end else begin (* Don't pass -p to cp on Windows - it's never going to be relevant (no execute bit which needs preserving) and there are scenarios in which it's more likely to fail than add anytning useful (especially if copying from a Cygwin-managed build directory to /cygdrive) *) let preserve = if Sys.win32 then "" else "p" in (* The script must be written with Unix line-endings on Windows *) Out_channel.with_open_bin (package ^ "-clone.sh") @@ fun oc -> output_endline oc {|#!/bin/sh set -e mkdir -p "$1" rm -f "$1/__cp_test" "$1/__ln_test" if cp --reflink=always doc/ocaml/LICENSE "$1/__cp_test" 2>/dev/null; then rm -f "$1/__cp_test" CP='cp --reflink=always -%sf' if ! test -e "$1/clone-files"; then echo "$CP"' "$@" "$dest/"' > "$1/clone-files" fi else CP='cp -%sf' if ! test -e "$1/clone-files"; then if ln -f doc/ocaml/LICENSE "$1/__ln_test" 2>/dev/null; then rm -f "$1/__ln_test" echo 'ln -f "$@" "$dest/"' > "$1/clone-files" else echo "$CP"' "$@" "$dest/"' > "$1/clone-files" fi fi fi|} preserve preserve; let has_config_cache = Sys.file_exists "config.cache" in Out_channel.with_open_text "clone-share@ocaml" (fun oc -> output_endline oc "share/ocaml/clone"; if has_config_cache then output_endline oc "share/ocaml/config.cache"); process_clone oc clone_files; if not has_config_cache then output_endline oc {|mkdir -p "$1/share/ocaml"|}; (* ld.conf is a configuration file, so is always copied. Makefile.config and config.status will both contain the original prefix, which must be updated. *) output_endline oc {|cp lib/ocaml/ld.conf "$1/lib/ocaml/ld.conf" cat > "$1/prefix.awk" <<"ENDAWK" { rest = $0 while ((p = index(rest, ENVIRON["O"]))) { printf "%%s%%s", substr(rest, 1, p-1), ENVIRON["N"] rest = substr(rest, p + length(ENVIRON["O"])) } print rest } ENDAWK prefix="$(sed -ne 's/^prefix *= *//p' lib/ocaml/Makefile.config)" for file in lib/ocaml/Makefile.config share/ocaml/config.status; do O="$prefix" N="$1" awk -f "$1/prefix.awk" "$file" > "$1/$file" done rm -f "$1/clone-files" "$1/prefix.awk"|}; process_symlinks oc ~mkdir:false end