Skip to content

Commit

Permalink
Merge pull request #4237 from rjbou/swname-check
Browse files Browse the repository at this point in the history
Switch name check
  • Loading branch information
rjbou authored Jul 9, 2020
2 parents 1b645db + aabc6b0 commit 7f0ac18
Show file tree
Hide file tree
Showing 4 changed files with 41 additions and 11 deletions.
10 changes: 9 additions & 1 deletion master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ Possibly scripts breaking changes are prefixed with ✘
## Switch
* Fix Not_found with `opam switch create . --deps` [#4151 @AltGr]
* Package Var: resolve self `name` variable for orphan packages [#4228 @rjbou - fix #4224]
* ✘ Reject (shell) character on switch names [#4237 @rjbou - fix #4231]

## Pin
* Don't keep unpinned package version if it exists in repo [#4073 @rjbou - fix #3630]
Expand All @@ -44,16 +45,23 @@ Possibly scripts breaking changes are prefixed with ✘
* Fix install command dryrun [#4200 @rjbou]


## Env
* Fix `OPAMSWITCH` empty string setting, consider as unset [#4237 @rjbou]

## Remove
* Fix autoremove env var handling [#4219 @rjbou - fix #4217]

## Repository management
* Fix temp files repository cleaning [#4197 @rjbou]

## Opam installer
* For paths, remove use of empty switch in favor of a context-less module [#4237 @rjbou]

## Internal
* Disable chrono when timestamps are disables [#4206 @rjbou]
* Expose some functionality in the `OpamAction`, `OpamPath` and `OpamSwitchState`
modules for use without a `switch` value [#4147]
modules for use without a `switch` value [#4147 @timberston]
*Path: introduce a functor to permit replicating switch layout in different contexts

## Test
* Add show cram test [#4206 @rjbou]
Expand Down
2 changes: 1 addition & 1 deletion src/client/opamConfigCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -182,7 +182,7 @@ let env gt switch ?(set_opamroot=false) ?(set_opamswitch=false)
(OpamFile.Config.switch gt.config)
in
match OpamStd.Config.env_string "SWITCH" with
| None ->
| None | Some "" ->
Some (OpamStateConfig.resolve_local_switch gt.root switch) <> default
| Some s ->
OpamStateConfig.resolve_local_switch gt.root (OpamSwitch.of_string s) <>
Expand Down
17 changes: 17 additions & 0 deletions src/format/opamSwitch.ml
Original file line number Diff line number Diff line change
Expand Up @@ -19,12 +19,29 @@ let is_external s =

let external_dirname = "_opam"

let check s =
if String.compare s "" = 0 &&
let re =
Re.(compile @@
seq [
bol;
opt @@ seq [ wordc ; char ':'; set "/\\" ];
rep @@ diff any @@ set "<>!`$():";
eol
])
in
(try ignore @@ Re.exec re s; true with Not_found -> false) then
failwith (Printf.sprintf "Invalid character in switch name %S" s);
s

let of_string s =
check @@
if is_external s then OpamFilename.Dir.(to_string (of_string s))
else s

let of_dirname d =
let s = OpamFilename.Dir.to_string d in
check @@
try
let swdir = Unix.readlink (Filename.concat s external_dirname) in
let swdir =
Expand Down
23 changes: 14 additions & 9 deletions src/tools/opam_installer.ml
Original file line number Diff line number Diff line change
Expand Up @@ -156,26 +156,31 @@ let script_commands project_root ochan =
where [dest src dst] returns the destination of a file with a
["src" {"dst"}] line in the .install *)
let iter_install f instfile o =
let module D = OpamPath.Switch.Default in
let open OpamFilename.Op in
let module D =
struct
include OpamPath.Switch.DefaultF (struct
type ctx = unit
let root d _ = d
let lib_dir t a = root t a / "lib"
end)
end
in
let module S = OpamFile.Dot_install in
let dest ?fix dir =
let dir = OpamStd.Option.default dir fix in
fun src dst ->
OpamFilename.create dir
(OpamStd.Option.default (OpamFilename.basename src) dst)
in
let dest_global ?fix instdir_f =
dest ?fix (instdir_f o.prefix (OpamSwitch.of_string ""))
in
let dest_global ?fix instdir_f = dest ?fix (instdir_f o.prefix ()) in
let dest_pkg ?fix instdir_f =
let fix =
OpamStd.Option.map
OpamFilename.Op.(fun d ->
d / OpamPackage.Name.to_string o.pkgname)
OpamStd.Option.map (fun d ->
d / OpamPackage.Name.to_string o.pkgname)
fix
in
dest ?fix
(instdir_f o.prefix (OpamSwitch.of_string "") o.pkgname)
dest ?fix (instdir_f o.prefix () o.pkgname)
in
List.iter f
[ dest_global D.bin, S.bin instfile, true;
Expand Down

0 comments on commit 7f0ac18

Please sign in to comment.