Skip to content

Commit

Permalink
Merge pull request #5840 from kit-ty-kate/pkg-name-plusplus
Browse files Browse the repository at this point in the history
Hijack the %{?val_if_true:val_if_false}% syntax to support extending the variables of packages with + in their name
  • Loading branch information
kit-ty-kate authored Apr 4, 2024
2 parents f4e0c45 + 3e318fd commit a98e122
Show file tree
Hide file tree
Showing 10 changed files with 331 additions and 14 deletions.
11 changes: 9 additions & 2 deletions doc/pages/Manual.md
Original file line number Diff line number Diff line change
Expand Up @@ -247,7 +247,7 @@ and _options_:
<section> ::= <ident> [ <string> ] "{" <file-contents> "}"
<ident> ::= { <identchar> }* <letter> { <identchar> }*
<varident> ::= [ ( <ident> | "_" ) { "+" ( <ident> | "_" ) }* : ] <ident>
<identchar> ::= <letter> | <digit> | "_" | "-"
<identchar> ::= <letter> | <digit> | "_" | "-" | "+"
<letter> ::= "a".."z" | "A".."Z"
<digit> ::= "0".."9"
<value> ::= <bool> | <int> | <string> | <ident> | <varident> | <operator> | <list> | <option> | "(" <value> ")"
Expand Down Expand Up @@ -383,7 +383,14 @@ insert different strings depending on the boolean value of a variable.
Additionally, boolean package variables may be combined using the following
form: `name1+name2+name3:var` is the conjunction of `var` for each of `name1`,
`name2` and `name3`, _i.e_ it is equivalent to `name1:var & name2:var &
name3:var`
name3:var`.

**Warning**: if the package name contains a `+` character (e.g. `conf-g++`),
their variables may only be accessed using opam 2.2 via string interpolation,
with the following syntax:
```
"%{?conf-g++:your-variable:}%"
```

#### Scopes

Expand Down
10 changes: 10 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,7 @@ users)
## Source

## Lint
* Add warning 69: Warn for new syntax when package name in variable in string interpolation contains several '+' [#5840 @rjbou]

## Repository

Expand All @@ -76,6 +77,7 @@ users)
* Unixify Windows paths in init shells scripts (sh, bash, zsh, fish & tsh) [#5797 @rjbou]

## Opamfile
* Hijack the `%{?val_if_true:val_if_false}%` syntax to support extending the variables of packages with + in their name [#5840 @kit-ty-kate]

## External dependencies
* Add support for Wolfi OS, treat it like Apline family as it uses apk too [#5878 @xnox]
Expand Down Expand Up @@ -140,6 +142,10 @@ users)
### Tests
* Add init scripts tests [#5864 @rjbou]
* Add test for init OCaml predefined eval variables and their format upgrade [#5829 @rjbou]
+ Add a test showing the current behaviour of opam with variable expansion, in particular when the package contains pluses [#5840 @kit-ty-kate]
+ Add a test testing showing the current behaviour of opam with variable expansion, in particular when the package contains pluses [#5840 @kit-ty-kate]
* Update lint test: W41 [#5840 @rjbou]
* Update lint test: W41 and W69 [#5840 @rjbou]

### Engine

Expand All @@ -155,6 +161,7 @@ users)
* Fix missing spaces in `opam --help` [#5850 @sorawee].
* Manual: add missing 'since opam 2.2' annotation when mentionning with-dev-setup [#5885 @kit-ty-kate]
* Installation: update badges for Ubuntu and Fedora to newer versions [#5905 @AldanTanneo]
* Manual: update regarding `pkg+` variables new syntax [#5840 @kit-ty-kate]

## Security fixes

Expand All @@ -177,6 +184,9 @@ users)

## opam-format
* `OpamFile.InitConfig`: add `sys-pkg-manager-cmd` field [#5847 @rjbou]
* `OpamTypesBase`: add `filter_ident_of_string_interp` that is used for parsing variables in string interpolation like `filter_ident_of_string` but permits the parsing of '%{?pkg+:var:}%' syntax [#5840 @rjbou]
* `OpamTypesBase.filter_ident_of_string_interp`: add `accept` optional argument to be able to raise an error when several pluses are in the package name without using the new syntax, like `%{pkg+++:var}%`
* `OpamFilter`: add `extract_variables_from_string` to retrieve string of variables, and exposes it [#5840 @rjbou]

## opam-core
* `OpamStd.Sys`: add `is_cygwin_variant_cygcheck` that returns true if in path `cygcheck` is from a Cygwin or MSYS2 installation [#5843 @rjbou]
Expand Down
17 changes: 9 additions & 8 deletions src/format/opamFilter.ml
Original file line number Diff line number Diff line change
Expand Up @@ -117,9 +117,7 @@ let fident_variables = function
| Some n -> OpamVariable.Full.create n var
| None -> OpamVariable.Full.self var) pkgs

(* extracts variables appearing in interpolations in a string*)
let string_variables s =
let matches =
let extract_variables_from_string s =
let rec aux acc pos =
try
let ss = Re.exec ~pos string_interp_regex s in
Expand All @@ -131,11 +129,13 @@ let string_variables s =
with Not_found -> acc
in
aux [] 0
in

(* extracts variables appearing in interpolations in a string *)
let string_variables s =
List.fold_left (fun acc s ->
try fident_variables (filter_ident_of_string s) @ acc
try fident_variables (filter_ident_of_string_interp s) @ acc
with Failure _ -> acc)
[] matches
[] (extract_variables_from_string s)

let variables filter =
fold_down_left (fun acc -> function
Expand Down Expand Up @@ -255,7 +255,8 @@ let expand_string_aux ?(partial=false) ?(escape_value=fun x -> x) ?default env t
str)
else
let fident = String.sub str 2 (String.length str - 4) in
resolve_ident ~no_undef_expand:partial env (filter_ident_of_string fident)
resolve_ident ~no_undef_expand:partial env
(filter_ident_of_string_interp fident)
|> value_string ?default:(default fident) |> escape_value
in
Re.replace string_interp_regex ~f text
Expand Down Expand Up @@ -307,7 +308,7 @@ let map_variables_in_string f =
~default:(fun fid_string ->
try
fid_string |>
filter_ident_of_string |>
filter_ident_of_string_interp |>
map_variables_in_fident f |>
string_of_filter_ident
with Failure _ -> fid_string)
Expand Down
3 changes: 3 additions & 0 deletions src/format/opamFilter.mli
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,9 @@ val map_up: (filter -> filter) -> filter -> filter
["%{xxx"] if unclosed) *)
val string_interp_regex : Re.re

(* Extract string of variables appearing in interpolation in a string *)
val extract_variables_from_string : string -> string list

(** Returns all the variables appearing in a filter (including the ones within
string interpolations *)
val variables: filter -> full_variable list
Expand Down
31 changes: 27 additions & 4 deletions src/format/opamTypesBase.ml
Original file line number Diff line number Diff line change
Expand Up @@ -122,18 +122,35 @@ let string_of_filter_ident (pkgs,var,converter) =
| Some (it,ifu) -> "?"^it^":"^ifu
| None -> "")

let filter_ident_of_string s =
exception Parse_variable of string * string

let filter_ident_of_string_t ~interpolation ?(accept=true) s =
match OpamStd.String.rcut_at s ':' with
| None -> [], OpamVariable.of_string s, None
| Some (p,last) ->
let get_names s =
List.map
(function "_" -> None | s -> Some (OpamPackage.Name.of_string s))
(OpamStd.String.split s '+')
List.filter_map
(function
| "_" -> Some None
| "" -> if accept then None else raise (Parse_variable (s, last))
| s -> Some ( Some (OpamPackage.Name.of_string s)))
(OpamStd.String.split_delim s '+')
in
match OpamStd.String.rcut_at p '?' with
| None ->
get_names p, OpamVariable.of_string last, None
| Some ("",val_if_true) when interpolation ->
(* TODO: Remove in opam 3.0.
Hack added in opam 2.2. This is a compatible syntax with opam 2.0 and
2.1 but supports + in the package name. See
https://github.com/ocaml/opam-file-format/issues/59 *)
(match OpamStd.String.rcut_at val_if_true ':' with
| None ->
(* behaviour from opam 2.0 and 2.1 *)
[], OpamVariable.of_string last, None
| Some (p, var) ->
[Some (OpamPackage.Name.of_string p)],
OpamVariable.of_string var, None)
| Some (p,val_if_true) ->
let converter = Some (val_if_true, last) in
match OpamStd.String.rcut_at p ':' with
Expand All @@ -142,6 +159,12 @@ let filter_ident_of_string s =
| Some (packages,var) ->
get_names packages, OpamVariable.of_string var, converter

let filter_ident_of_string s =
filter_ident_of_string_t ~interpolation:false ~accept:true s

let filter_ident_of_string_interp ?accept s =
filter_ident_of_string_t ~interpolation:true ?accept s

let all_package_flags = [
Pkgflag_LightUninstall;
(* Pkgflag_AllSwitches; This has no "official" existence yet and does
Expand Down
10 changes: 10 additions & 0 deletions src/format/opamTypesBase.mli
Original file line number Diff line number Diff line change
Expand Up @@ -59,11 +59,21 @@ val string_of_user_action: user_action -> string
preserve order *)
val env_array: env -> string array

exception Parse_variable of string * string

(** Parses the data suitable for a filter.FIdent from a string. May raise
[Failure msg] on bad package names. A self-reference [_] parses to [None] *)
val filter_ident_of_string:
string -> name option list * variable * (string * string) option

(** Like [Filter_ident_of_string] but parses also '%{?pkg+:var:}% syntax for
variables with package name that contains a '+'. if [accept] is [false],
[Parse_variable (pkg,var)] is raised when several '+' are encountered in
package name, i.e. 'pkg++:var'. *)
val filter_ident_of_string_interp:
?accept:bool -> string
-> name option list * variable * (string * string) option

val string_of_filter_ident:
name option list * variable * (string * string) option -> string

Expand Down
25 changes: 25 additions & 0 deletions src/state/opamFileTools.ml
Original file line number Diff line number Diff line change
Expand Up @@ -875,6 +875,31 @@ let t_lint ?check_extra_files ?(check_upstream=false) ?(all=false) t =
cond 68 `Warning
"Missing field 'license'"
(t.license = []);
(let vars =
List.flatten @@
List.map (fun s ->
List.filter_map
(fun f ->
try
let _ =
OpamTypesBase.filter_ident_of_string_interp
~accept:false f
in
None
with OpamTypesBase.Parse_variable (p,v) ->
Some (p,v)
)
(OpamFilter.extract_variables_from_string s))
all_expanded_strings
in
cond 69 `Warning
"Package name in variable in string interpolation contains several \
'+', use"
~detail:(List.map (fun (p,v) ->
Printf.sprintf "'?%s:%s:' instead of '%s:%s'"
p v p v)
vars)
(vars <> []));
]
in
format_errors @
Expand Down
18 changes: 18 additions & 0 deletions tests/reftests/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -926,6 +926,24 @@
%{targets}
(run ./run.exe %{exe:../../src/client/opamMain.exe.exe} %{dep:lock.test} %{read-lines:testing-env}))))

(rule
(alias reftest-opam-pkgvar-with-plus)
(action
(diff opam-pkgvar-with-plus.test opam-pkgvar-with-plus.out)))

(alias
(name reftest)
(deps (alias reftest-opam-pkgvar-with-plus)))

(rule
(targets opam-pkgvar-with-plus.out)
(deps root-N0REP0)
(package opam)
(action
(with-stdout-to
%{targets}
(run ./run.exe %{exe:../../src/client/opamMain.exe.exe} %{dep:opam-pkgvar-with-plus.test} %{read-lines:testing-env}))))

(rule
(alias reftest-opamroot-versions)
(action
Expand Down
33 changes: 33 additions & 0 deletions tests/reftests/lint.test
Original file line number Diff line number Diff line change
Expand Up @@ -387,6 +387,19 @@ messages: "foo" { bar:innerenv }
### opam lint ./lint.opam
${BASEDIR}/lint.opam: Warnings.
warning 41: Some packages are mentioned in package scripts or features, but there is no dependency or depopt toward them: "bar"
### <lint.opam>
opam-version: "2.0"
synopsis: "A word"
description: "Two words."
authors: "the testing team"
homepage: "egapemoh"
maintainer: "[email protected]"
license: "ISC"
dev-repo: "hg+https://[email protected]"
bug-reports: "https://nobug"
messages: "foo" { bar:installed }
### opam lint ./lint.opam
${BASEDIR}/lint.opam: Passed.
### : E42: The 'dev-repo:' field doesn't use version control. You should use URLs of the form "git://", "git+https://", "hg+https://"...
### <lint.opam>
opam-version: "2.0"
Expand Down Expand Up @@ -929,3 +942,23 @@ bug-reports: "https://nobug"
### opam lint ./lint.opam
${BASEDIR}/lint.opam: Warnings.
warning 68: Missing field 'license'
### : W69: Package name in variable in string interpolation contains several '+'
### <lint.opam>
opam-version: "2.0"
name: "conf-g++"
synopsis: "A word"
description: "Two words."
authors: "the testing team"
homepage: "egapemoh"
maintainer: "[email protected]"
license: "ISC"
dev-repo: "hg+https://[email protected]"
bug-reports: "https://nobug"
messages: [
"foo" { "%{?conf-c++:installed:}%" }
"bar" { "%{conf-g++:installed}%" }
"baz" { "%{abc+xyz+jkl:installed}%" }
]
### opam lint ./lint.opam
${BASEDIR}/lint.opam: Warnings.
warning 69: Package name in variable in string interpolation contains several '+', use: "'?conf-g++:installed:' instead of 'conf-g++:installed'"
Loading

0 comments on commit a98e122

Please sign in to comment.