Skip to content

Commit

Permalink
Merge pull request #5985 from rjbou/fix-formula-mapfold
Browse files Browse the repository at this point in the history
Fix OpamFilter map/fold functions
  • Loading branch information
rjbou authored Jun 4, 2024
2 parents 6cf6ff3 + de20159 commit 936cf1e
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 3 deletions.
2 changes: 2 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -166,6 +166,8 @@ users)

## opam-format
* `OpamPath`: remove `OpamPath.Switch.last_env` function in favor to `OpamPath.last_env` as the files are no more stored in switch directory [#5962 @moyodiallo - fix #5823]
* `OpamFilter.map_up`: correct handling of FDefined [#5983 @dra27]
* `OpamFilter.fold_down_left`: correct handling of FDefined and FUndef [#5983 @dra27]

## opam-core
* `OpamStd.String`: add `split_quoted` that preserves quoted separator [#5935 @dra27]
Expand Down
13 changes: 10 additions & 3 deletions src/format/opamFilter.ml
Original file line number Diff line number Diff line change
Expand Up @@ -74,16 +74,23 @@ let to_string ?custom t =
let rec fold_down_left f acc filter = match filter with
| FOp(l,_,r) | FAnd(l,r) | FOr(l,r) ->
fold_down_left f (fold_down_left f (f acc filter) l) r
| FNot(x) -> fold_down_left f (f acc filter) x
| x -> f acc x
| FNot x
| FUndef x
| FDefined x ->
fold_down_left f (f acc filter) x
| FBool _
| FString _
| FIdent _ ->
f acc filter

let rec map_up f = function
| FOp (l, op, r) -> f (FOp (map_up f l, op, map_up f r))
| FAnd (l, r) -> f (FAnd (map_up f l, map_up f r))
| FOr (l, r) -> f (FOr (map_up f l, map_up f r))
| FNot x -> f (FNot (map_up f x))
| FUndef x -> f (FUndef (map_up f x))
| (FBool _ | FString _ | FIdent _ | FDefined _) as flt -> f flt
| FDefined x -> f (FDefined (map_up f x))
| (FBool _ | FString _ | FIdent _) as flt -> f flt

(* ["%%"], ["%{xxx}%"], or ["%{xxx"] if unclosed *)
let string_interp_regex =
Expand Down

0 comments on commit 936cf1e

Please sign in to comment.