Skip to content

Commit

Permalink
Merge pull request #3096 from OCamlPro/fixes
Browse files Browse the repository at this point in the history
A couple bug and UI fixes
  • Loading branch information
AltGr authored Nov 15, 2017
2 parents eca7e83 + ae97f76 commit 23f895f
Show file tree
Hide file tree
Showing 6 changed files with 19 additions and 12 deletions.
4 changes: 2 additions & 2 deletions .travis-ci.sh
Original file line number Diff line number Diff line change
Expand Up @@ -28,10 +28,10 @@ case "$TARGET" in
wget -q -O ~/local/bin/opam \
"https://github.com/ocaml/opam/releases/download/$OPAMBSVERSION/opam-$OPAMBSVERSION-$(uname -m)-$(uname -s)"
chmod a+x ~/local/bin/opam
if [ "$TRAVIS_OS_NAME" = "osx" ]; then
if [ "$TRAVIS_OS_NAME" = "osx" ] && [ -n "$EXTERNAL_SOLVER" ]; then
rvm install ruby-2.3.3
rvm --default use 2.3.3
if [ "$OPAM_TEST" != "1" ]; then brew install aspcud; fi
brew install "$EXTERNAL_SOLVER"
fi
exit 0
;;
Expand Down
2 changes: 1 addition & 1 deletion .travis.yml
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ matrix:
- os: osx
env: OCAML_VERSION=4.03.0 OPAM_TEST=1 EXTERNAL_SOLVER=
- os: osx
env: OCAML_VERSION=4.03.0 OPAM_TEST= EXTERNAL_SOLVER=aspcud
env: OCAML_VERSION=4.03.0 OPAM_TEST=
notifications:
email:
- opam-commits@lists.ocaml.org
Expand Down
1 change: 1 addition & 0 deletions src/client/opamAction.ml
Original file line number Diff line number Diff line change
Expand Up @@ -412,6 +412,7 @@ let make_command st opam ?dir ?text_command (cmd, args) =
]
in
OpamSystem.make_command ~env ~name ?dir ~text
~resolve_path:OpamStateConfig.(not !r.dryrun)
~metadata:["context", context]
~verbose:(OpamConsole.verbose ())
cmd args
Expand Down
16 changes: 8 additions & 8 deletions src/client/opamAuxCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -152,7 +152,7 @@ let resolve_locals_pinned st atom_or_local_list =
in
List.rev atoms

let resolve_locals atom_or_local_list =
let resolve_locals ?(quiet=false) atom_or_local_list =
let target_dir dir =
let d = OpamFilename.Dir.to_string dir in
let backend = OpamUrl.guess_version_control d in
Expand All @@ -164,7 +164,7 @@ let resolve_locals atom_or_local_list =
| `Atom a -> to_pin, a :: atoms
| `Dirname d ->
let names_files = opams_of_dir d in
if names_files = [] then
if names_files = [] && not quiet then
OpamConsole.warning "No package definitions found at %s"
(OpamFilename.Dir.to_string d);
let target = target_dir d in
Expand Down Expand Up @@ -205,8 +205,8 @@ let resolve_locals atom_or_local_list =
(OpamUrl.to_string t))
duplicates)

let autopin_aux st atom_or_local_list =
let to_pin, atoms = resolve_locals atom_or_local_list in
let autopin_aux st ?quiet atom_or_local_list =
let to_pin, atoms = resolve_locals ?quiet atom_or_local_list in
if to_pin = [] then
atoms, to_pin, OpamPackage.Set.empty, OpamPackage.Set.empty
else
Expand Down Expand Up @@ -304,9 +304,9 @@ let fix_atom_versions_in_set set atoms =
(OpamPackage.package_of_name_opt set name))
atoms

let simulate_autopin st atom_or_local_list =
let simulate_autopin st ?quiet atom_or_local_list =
let atoms, to_pin, obsolete_pins, already_pinned_set =
autopin_aux st atom_or_local_list
autopin_aux st ?quiet atom_or_local_list
in
if to_pin = [] then st, atoms else
let st =
Expand All @@ -318,12 +318,12 @@ let simulate_autopin st atom_or_local_list =
let atoms = fix_atom_versions_in_set pins atoms in
st, atoms

let autopin st ?(simulate=false) atom_or_local_list =
let autopin st ?(simulate=false) ?quiet atom_or_local_list =
if OpamStateConfig.(!r.dryrun) || OpamClientConfig.(!r.show) then
simulate_autopin st atom_or_local_list
else
let atoms, to_pin, obsolete_pins, already_pinned_set =
autopin_aux st atom_or_local_list
autopin_aux st ?quiet atom_or_local_list
in
if to_pin = [] && OpamPackage.Set.is_empty obsolete_pins &&
OpamPackage.Set.is_empty already_pinned_set
Expand Down
3 changes: 3 additions & 0 deletions src/client/opamAuxCommands.mli
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,7 @@ val name_and_dir_of_opam_file: filename -> name option * dirname
exit if package names for provided [`Filename] could not be inferred, or if
the same package name appears multiple times *)
val resolve_locals:
?quiet:bool ->
[ `Atom of atom | `Filename of filename | `Dirname of dirname ] list ->
(name * OpamUrl.t * OpamFile.OPAM.t OpamFile.t) list * atom list

Expand All @@ -63,13 +64,15 @@ val resolve_locals_pinned:
val autopin:
rw switch_state ->
?simulate:bool ->
?quiet:bool ->
[ `Atom of atom | `Filename of filename | `Dirname of dirname ] list ->
rw switch_state * atom list

(** The read-only version of [autopin ~simulate:true]: this doesn't require a
write-locked switch, and doesn't update the local packages *)
val simulate_autopin:
'a switch_state ->
?quiet:bool ->
[ `Atom of atom | `Filename of filename | `Dirname of dirname ] list ->
'a switch_state * atom list

Expand Down
5 changes: 4 additions & 1 deletion src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -896,6 +896,9 @@ let config =
);
print "current-switch" "%s"
(OpamSwitch.to_string state.switch);
if List.mem "." (OpamStd.Sys.split_path_variable (Sys.getenv "PATH"))
then OpamConsole.warning
"PATH contains '.' : this is a likely cause of trouble.";
`Ok ()
with e -> print "read-state" "%s" (Printexc.to_string e); `Ok ())
| command, params -> bad_subcommand commands ("config", command, params)
Expand Down Expand Up @@ -1953,7 +1956,7 @@ let switch =
let st =
if not no_install && not empty && OpamSwitch.is_external switch then
let st, atoms =
OpamAuxCommands.autopin st ~simulate:deps_only
OpamAuxCommands.autopin st ~simulate:deps_only ~quiet:true
[`Dirname (OpamFilename.Dir.of_string switch_arg)]
in
OpamClient.install st atoms
Expand Down

0 comments on commit 23f895f

Please sign in to comment.