Skip to content

Commit

Permalink
Start copying commands from opam files (#8336)
Browse files Browse the repository at this point in the history
Very early implementation of copying build and install commands from
opam files into lockfiles meant to invite feedback on the general design
of this feature before going deeper.

Not yet supported:

- filters on commands or arguments
- string interpolation in commands
- package-scoped variables other than `_` (the current package)
- executing the actions

Not all opam variables are supported yet.

Signed-off-by: Stephen Sherratt <stephen@sherra.tt>
  • Loading branch information
gridbugs authored Aug 9, 2023
1 parent 788d41e commit 758e370
Show file tree
Hide file tree
Showing 4 changed files with 198 additions and 8 deletions.
46 changes: 45 additions & 1 deletion src/dune_lang/pform.ml
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,9 @@ module Var = struct
| Jobs
| Arch
| Section_dir of Section.t
| Name
| Version
| Make

let compare = Poly.compare

Expand All @@ -72,6 +75,47 @@ module Var = struct
| Arch -> variant "Arch" []
| Section_dir section ->
variant "Section_dir" [ string (Section.to_string section) ]
| Name -> variant "Name" []
| Version -> variant "Version" []
| Make -> variant "Make" []
;;

let of_opam_variable_name_opt name =
match Section.of_string name with
| Some section_dir -> Some (Section_dir section_dir)
| None ->
(match name with
| "switch" -> Some Switch
| "os-version" -> Some Os_version
| "os-distribution" -> Some Os_distribution
| "os-family" -> Some Os_family
| "build" -> Some Build
| "prefix" -> Some Prefix
| "user" -> Some User
| "group" -> Some Group
| "jobs" -> Some Jobs
| "arch" -> Some Arch
| "name" -> Some Name
| "version" -> Some Version
| "make" -> Some Make
| _ -> None)
;;

let encode_to_latest_dune_lang_version = function
| Switch -> "switch"
| Os_version -> "os_version"
| Os_distribution -> "os_distribution"
| Os_family -> "os_family"
| Build -> "build"
| Prefix -> "prefix"
| User -> "user"
| Group -> "group"
| Jobs -> "jobs"
| Arch -> "arch"
| Section_dir section -> Section.to_string section
| Name -> "name"
| Version -> "version"
| Make -> "make"
;;
end

Expand Down Expand Up @@ -393,7 +437,7 @@ let encode_to_latest_dune_lang_version t =
| Corrected_suffix -> Some "corrected-suffix"
| Inline_tests -> Some "inline_tests"
| Toolchain -> Some "toolchain"
| Pkg _ -> assert false (* TODO *)
| Pkg pkg -> Some (Var.Pkg.encode_to_latest_dune_lang_version pkg)
with
| None -> Pform_was_deleted
| Some name -> Success { name; payload = None })
Expand Down
4 changes: 4 additions & 0 deletions src/dune_lang/pform.mli
Original file line number Diff line number Diff line change
Expand Up @@ -32,9 +32,13 @@ module Var : sig
| Jobs
| Arch
| Section_dir of Section.t
| Name
| Version
| Make

val compare : t -> t -> Ordering.t
val to_dyn : t -> Dyn.t
val of_opam_variable_name_opt : string -> t option
end

type t =
Expand Down
87 changes: 80 additions & 7 deletions src/dune_pkg/opam_solver.ml
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
open Stdune
module Package_name = Dune_lang.Package_name
open Dune_lang

module type CONTEXT = Opam_0install.S.CONTEXT

Expand Down Expand Up @@ -230,6 +230,78 @@ module Summary = struct
;;
end

let opam_command_to_string_debug (args, _filter_opt) =
List.map args ~f:(fun (simple_arg, _filter_opt) ->
match simple_arg with
| OpamTypes.CString s -> String.quoted s
| CIdent ident -> ident)
|> String.concat ~sep:" "
;;

let opam_commands_to_actions package (commands : OpamTypes.command list) =
let pform_of_ident_opt ident =
let `Self, variable =
match String.split ident ~on:':' with
| [ variable ] | [ "_"; variable ] -> `Self, variable
| _ ->
(* TODO *)
Code_error.raise
"Evaluating package variables for non-self packages not yet implemented"
[ "While processing package:", Dyn.string (OpamPackage.to_string package)
; "Variable:", Dyn.string ident
]
in
match Pform.Var.Pkg.of_opam_variable_name_opt variable with
| Some pkg_var -> Ok Pform.(Var (Var.Pkg pkg_var))
| None -> Error (`Unknown_variable variable)
in
List.filter_map commands ~f:(fun ((args, _filter_opt) as command) ->
let terms =
List.map args ~f:(fun (simple_arg, _filter_opt) ->
match simple_arg with
| OpamTypes.CString s ->
(* TODO: apply replace string interpolation variables with pforms *)
String_with_vars.make_text Loc.none s
| CIdent ident ->
(match pform_of_ident_opt ident with
| Ok pform -> String_with_vars.make_pform Loc.none pform
| Error (`Unknown_variable variable) ->
(* Note that the variable name is always quoted to clarify
the error message in cases where the grammar of the
sentence would otherwise be unclear, such as:
- Encountered unknown variable type while processing...
- Encountered unknown variable name while processing...
In these examples, the words "type" and "name" are variable
names but it would be easy for users to misunderstand those
error messages without quotes. *)
User_error.raise
[ Pp.textf
"Encountered unknown variable %S while processing commands for \
package %s."
variable
(OpamPackage.to_string package)
; Pp.text "The full command:"
; Pp.text (opam_command_to_string_debug command)
]))
in
match terms with
| program :: args -> Some (Action.run program args)
| [] -> None)
;;

(* returns:
[None] if the command list is empty
[Some (Action.Run ...)] if there is a single command
[Some (Action.Progn [Action.Run ...; ...])] if there are multiple commands *)
let opam_commands_to_action package (commands : OpamTypes.command list) =
match opam_commands_to_actions package commands with
| [] -> None
| [ action ] -> Some action
| actions -> Some (Action.Progn actions)
;;

let opam_package_to_lock_file_pkg ~repo ~local_packages opam_package =
let name = OpamPackage.name opam_package in
let version = OpamPackage.version opam_package |> OpamPackage.Version.to_string in
Expand All @@ -256,12 +328,13 @@ let opam_package_to_lock_file_pkg ~repo ~local_packages opam_package =
|> List.map ~f:(fun name ->
Loc.none, Package_name.of_string (OpamPackage.Name.to_string name))
in
{ Lock_dir.Pkg.build_command = None
; install_command = None
; deps
; info
; exported_env = []
}
let build_command =
opam_commands_to_action opam_package (OpamFile.OPAM.build opam_file)
in
let install_command =
opam_commands_to_action opam_package (OpamFile.OPAM.install opam_file)
in
{ Lock_dir.Pkg.build_command; install_command; deps; info; exported_env = [] }
;;

let solve_package_list local_packages context =
Expand Down
69 changes: 69 additions & 0 deletions test/blackbox-tests/test-cases/pkg/convert-opam-commands.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,69 @@
Helper shell function that generates an opam file for a package:
$ mkpkg() {
> name=$1
> mkdir -p mock-opam-repository/packages/$name/$name.0.0.1
> cat >mock-opam-repository/packages/$name/$name.0.0.1/opam
> }

Helper shell function to generate a dune-project file and generate lockdir:
$ solve_project() {
> cat >dune-project
> dune pkg lock --opam-repository-path=mock-opam-repository
> }

Generate a mock opam repository
$ mkdir -p mock-opam-repository
$ cat >mock-opam-repository/repo <<EOF
> opam-version: "2.0"
> EOF

$ mkpkg standard-dune <<EOF
> opam-version: "2.0"
> build: [
> ["dune" "subst"] {dev}
> [
> "dune"
> "build"
> "-p"
> name
> "-j"
> jobs
> "@install"
> "@runtest" {with-test}
> "@doc" {with-doc}
> ]
> ]
> install: [ make "install" ]
> EOF

$ mkpkg with-unknown-variable <<EOF
> opam-version: "2.0"
> build: [ fake "install" ]
> EOF

$ solve_project <<EOF
> (lang dune 3.8)
> (package
> (name x)
> (depends standard-dune))
> EOF
Solution for dune.lock:
standard-dune.0.0.1


$ cat dune.lock/standard-dune.pkg
(version 0.0.1)
(install (run %{make} install))
(build (progn (run dune subst) (run dune build -p %{name} -j %{jobs} @install @runtest @doc)))

$ solve_project <<EOF
> (lang dune 3.8)
> (package
> (name x)
> (depends with-unknown-variable))
> EOF
Error: Encountered unknown variable "fake" while processing commands for
package with-unknown-variable.0.0.1.
The full command:
fake "install"
[1]

0 comments on commit 758e370

Please sign in to comment.