Skip to content

Commit

Permalink
fix: properly escape block string for string with vars
Browse files Browse the repository at this point in the history
Signed-off-by: Max Große <[email protected]>
  • Loading branch information
maxRN committed Jul 31, 2024
1 parent 857fc84 commit 5fefd7f
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 1 deletion.
13 changes: 12 additions & 1 deletion src/dune_lang/string_with_vars.ml
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,7 @@ let make ?(quoted = false) loc parts =
{ quoted; loc; parts }
;;

(* TODO(maxrn): escape Block_string here *)
let literal ~quoted ~loc s = { parts = [ Text s ]; quoted; loc }

let decoding_env_key =
Expand All @@ -84,6 +85,16 @@ let add_user_vars_to_decoding_env vars =
| Some env -> Some (Pform.Env.add_user_vars env vars))
;;

(* TODO(maxrn): remove duplicated code *)
let plain_string_of_block_string bs =
String.split bs ~on:'\n'
|> List.map ~f:(fun line ->
match String.length line with
| 0 -> line
| _ as length -> String.sub line ~pos:4 ~len:(length - 4))
|> String.concat ~sep:"\n"
;;

let decode_manually f =
let open Decoder in
let+ env = get decoding_env_key
Expand All @@ -97,7 +108,7 @@ let decode_manually f =
| Atom (loc, A s) -> literal ~quoted:false ~loc s
| Quoted_string (loc, s) -> literal ~quoted:true ~loc s
(* TODO(maxrn) *)
| Block_string (loc, s) -> literal ~quoted:true ~loc s
| Block_string (loc, s) -> literal ~quoted:true ~loc (plain_string_of_block_string s)
| List (loc, _) -> User_error.raise ~loc [ Pp.text "Unexpected list" ]
| Template { quoted; loc; parts } ->
{ quoted
Expand Down
1 change: 1 addition & 0 deletions src/dune_pkg/lock_dir.ml
Original file line number Diff line number Diff line change
Expand Up @@ -191,6 +191,7 @@ module Pkg = struct
;;

let encode_extra_source (local, source) : Dune_sexp.t =
(* TODO(maxrn): LOOK AT THIS *)
List
[ Dune_sexp.atom_or_quoted_string (Path.Local.to_string local)
; Source.encode source
Expand Down

0 comments on commit 5fefd7f

Please sign in to comment.