Skip to content

Commit

Permalink
Nullify positions of the extensions fields in OpamFile.OPAM.effective…
Browse files Browse the repository at this point in the history
…_part
  • Loading branch information
kit-ty-kate committed Jun 18, 2024
1 parent 5331467 commit 872015f
Show file tree
Hide file tree
Showing 5 changed files with 26 additions and 4 deletions.
1 change: 1 addition & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@ users)
## Var/Option

## Update / Upgrade
* Fix `opam upgrade` wanting to recompile opam files containing the `x-env-path-rewrite` field [#6029 @kit-ty-kate - fix #6028]

## Tree

Expand Down
5 changes: 4 additions & 1 deletion src/format/opamFile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3629,7 +3629,10 @@ module OPAM = struct

(* We keep only `x-env-path-rewrite` as it affects build/install *)
extensions =
OpamStd.String.Map.filter (fun x _ -> String.equal rewrite_xfield x)
OpamStd.String.Map.filter_map (fun k v ->
if String.equal rewrite_xfield k
then Some (OpamTypesBase.nullify_pos_value v)
else None)
t.extensions;

url = OpamStd.Option.map effective_url t.url;
Expand Down
17 changes: 17 additions & 0 deletions src/format/opamTypesBase.ml
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,23 @@ let pos_null =
stop = -1, -1;
}
let nullify_pos pelem = {pelem; pos = pos_null}
let nullify_pos_map f {pelem; pos = _} = nullify_pos (f pelem)

let rec nullify_pos_value {pelem; pos = _} =
nullify_pos @@
match pelem with
| Bool b -> Bool (b : bool)
| Int i -> Int (i : int)
| String s -> String (s : string)
| Relop (relop, v1, v2) -> Relop (nullify_pos_map (fun (x : OpamParserTypes.FullPos.relop_kind) -> x) relop, nullify_pos_value v1, nullify_pos_value v2)
| Prefix_relop (relop, v) -> Prefix_relop (nullify_pos_map (fun (x : OpamParserTypes.FullPos.relop_kind) -> x) relop, nullify_pos_value v)
| Logop (logop, v1, v2) -> Logop (nullify_pos_map (fun (x : OpamParserTypes.FullPos.logop_kind) -> x) logop, nullify_pos_value v1, nullify_pos_value v2)
| Pfxop (pfxop, v) -> Pfxop (nullify_pos_map (fun (x : OpamParserTypes.FullPos.pfxop_kind) -> x) pfxop, nullify_pos_value v)
| Ident s -> Ident (s : string)
| List {pelem = l; pos = _} -> List (nullify_pos (List.map nullify_pos_value l))
| Group {pelem = l; pos = _} -> Group (nullify_pos (List.map nullify_pos_value l))
| Option (v, {pelem = filter; pos = _}) -> Option (nullify_pos_value v, nullify_pos (List.map nullify_pos_value filter))
| Env_binding (v1, env_update_op, v2) -> Env_binding (nullify_pos_value v1, nullify_pos_map (fun (x : OpamParserTypes.FullPos.env_update_op_kind) -> x) env_update_op, nullify_pos_value v2)

(* XXX update *)
let pos_best pos1 pos2 =
Expand Down
2 changes: 2 additions & 0 deletions src/format/opamTypesBase.mli
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,8 @@ val string_of_shell: shell -> string
(** The empty file position *)
val pos_null: pos
val nullify_pos : 'a -> 'a with_pos
val nullify_pos_map : ('a -> 'b) -> 'a with_pos -> 'b with_pos
val nullify_pos_value : value -> value

(** [pos_best pos1 pos2] returns the most detailed position between [pos1] and
[pos2] (defaulting to [pos1]) *)
Expand Down
5 changes: 2 additions & 3 deletions tests/reftests/effectively-equal.test
Original file line number Diff line number Diff line change
Expand Up @@ -222,6 +222,5 @@ Already up-to-date.
Nothing to do.
### rm OPAM/eff-eq/.opam-switch/packages/cache
### opam upgrade --show
The following actions would be performed:
=== recompile 1 package
- recompile test-all-fields 1 [upstream or system changes]
Already up-to-date.
Nothing to do.

0 comments on commit 872015f

Please sign in to comment.