Skip to content

Commit

Permalink
Fix splitting of quoted variables
Browse files Browse the repository at this point in the history
Function before was incorrect on Windows and probably incorrect on Unix
- instead generalise OpamStd.Sys.split_path_variable to support
splitting with a colon-separator (and quoting).
  • Loading branch information
dra27 committed Apr 24, 2024
1 parent 1872569 commit d7ba7d8
Show file tree
Hide file tree
Showing 3 changed files with 8 additions and 37 deletions.
8 changes: 4 additions & 4 deletions src/core/opamStd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -877,15 +877,15 @@ module OpamSys = struct
let path_sep = if Sys.win32 then ';' else ':'

let split_path_variable ?(clean=true) =
if Sys.win32 then fun path ->
if Sys.win32 then fun ?(sep=path_sep) path ->
let length = String.length path in
let rec f acc index current last normal =
if index = length then
let current = current ^ String.sub path last (index - last) in
List.rev (if current <> "" then current::acc else acc)
else let c = path.[index]
and next = succ index in
if c = ';' && normal || c = '"' then
if c = sep && normal || c = '"' then
let current = current ^ String.sub path last (index - last) in
if c = '"' then
f acc next current next (not normal)
Expand All @@ -895,9 +895,9 @@ module OpamSys = struct
else
f acc next current last normal in
f [] 0 "" 0 true
else fun path ->
else fun ?(sep=path_sep) path ->
let split = if clean then OpamString.split else OpamString.split_delim in
split path path_sep
split path sep

let with_process_in cmd args f =
if Sys.win32 then
Expand Down
2 changes: 1 addition & 1 deletion src/core/opamStd.mli
Original file line number Diff line number Diff line change
Expand Up @@ -536,7 +536,7 @@ module Sys : sig
it seems, because there may be quoting on Windows. By default, it returns
the path cleaned (remove trailing, leading, contiguous delimiters).
Optional argument [clean] permits to keep those empty strings. *)
val split_path_variable: ?clean:bool -> string -> string list
val split_path_variable: ?clean:bool -> ?sep:char -> string -> string list

(** For native Windows builds, returns [`Cygwin] if the command is a Cygwin-
compiled executable, [`Msys2] if the command is a MSYS2-compiled
Expand Down
35 changes: 3 additions & 32 deletions src/state/opamEnv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -150,39 +150,10 @@ let split_var ~(sepfmt:sep_path_format) var value =
in
let sep = OpamTypesBase.char_of_separator separator in
match format with
| Target_quoted | Host_quoted ->
OpamStd.String.split value sep
| Target | Host ->
(* we suppose that it is in the form:
- "quoted":unquoted
- unquoted:"quoted"
- "quoted":unquoted:"quoted"
- unquoted:"quoted":unquoted
- "quoted"
- unquoted
*)
let rec aux remaining acc =
match String.get remaining 0 with
| '"' ->
(let remaining =
String.sub remaining 1 (String.length remaining - 1)
in
match OpamStd.String.cut_at remaining '"' with
| Some (quoted, rest) ->
aux rest (("\""^quoted^"\"")::acc)
| None -> remaining::acc)
| _ ->
let remaining =
if Char.equal (String.get remaining 0) sep then
String.sub remaining 1 (String.length remaining - 1)
else remaining in
(match OpamStd.String.cut_at remaining sep with
| Some (unquoted, rest) ->
aux rest (unquoted::acc)
| None -> remaining::acc)
| exception Invalid_argument _ -> acc
in
List.rev @@ aux value []
OpamStd.String.split value sep
| Target_quoted | Host_quoted ->
OpamStd.Sys.split_path_variable ~sep value

let join_var ~(sepfmt:sep_path_format) var values =
let separator =
Expand Down

0 comments on commit d7ba7d8

Please sign in to comment.