Skip to content

Commit

Permalink
Fix OpamSystem.install for Windows
Browse files Browse the repository at this point in the history
The install command doesn't make sense for Windows. OpamSystem.install
altered to use copying instead and also various checks added to guard
against package errors. In particular, .exe is automatically added to
executables (with a warning) if exec is true and warnings are displayed
if Cygwin-linked files or Unix shell-scripts are installed.

Signed-off-by: David Allsopp <david.allsopp@metastack.com>
  • Loading branch information
dra27 committed May 17, 2016
1 parent d4eb2cb commit 8cc885a
Showing 1 changed file with 50 additions and 6 deletions.
56 changes: 50 additions & 6 deletions src/core/opamSystem.ml
Original file line number Diff line number Diff line change
Expand Up @@ -510,7 +510,13 @@ let read_command_output ?verbose ?env ?metadata ?allow_stdin cmd =
let verbose_for_base_commands () =
OpamCoreConfig.(!r.verbose_level) >= 3

let copy_file src dst =
let cygify f =
if Sys.win32 then
List.map (Lazy.force f)
else
fun x -> x

let copy_file_aux f src dst =
if (try Sys.is_directory src
with Sys_error _ -> raise (File_not_found src))
then internal_error "Cannot copy %s: it is a directory." src;
Expand All @@ -519,7 +525,9 @@ let copy_file src dst =
if file_or_symlink_exists dst
then remove_file dst;
mkdir (Filename.dirname dst);
command ~verbose:(verbose_for_base_commands ()) ["cp"; src; dst ]
command ~verbose:(verbose_for_base_commands ()) ("cp"::(cygify f [src; dst]))

let copy_file = copy_file_aux (get_cygpath_function ~command:"cp")

let copy_dir src dst =
if Sys.file_exists dst then
Expand All @@ -536,10 +544,12 @@ let copy_dir src dst =
command ~verbose:(verbose_for_base_commands ())
[ "cp"; "-PRp"; src; dst ])

let mv src dst =
let mv_aux f src dst =
if file_or_symlink_exists dst then remove_file dst;
mkdir (Filename.dirname dst);
command ~verbose:(verbose_for_base_commands ()) ["mv"; src; dst ]
command ~verbose:(verbose_for_base_commands ()) ("mv"::(cygify f [src; dst]))

let mv = mv_aux (get_cygpath_function ~command:"mv")

let is_exec file =
let stat = Unix.stat file in
Expand Down Expand Up @@ -623,8 +633,42 @@ let install ?exec src dst =
let exec = match exec with
| Some e -> e
| None -> is_exec src in
command ("install" :: "-m" :: (if exec then "0755" else "0644") ::
[ src; dst ])
begin
if Sys.win32 then
if exec then begin
let (dst, cygcheck) =
match classify_executable src with
`Exe _ ->
if not (Filename.check_suffix dst ".exe") && not (Filename.check_suffix dst ".dll") then begin
OpamConsole.warning "Automatically adding .exe to %s" dst;
(dst ^ ".exe", true)
end else
(dst, true)
| `Dll _ ->
(* TODO Installation of .dll to bin is unfortunate, but not sure if it should be a warning *)
(dst, true)
| `Script ->
(* TODO Generate a .cmd wrapper (and warn about it - they're not perfect) *)
OpamConsole.warning "%s is a script; the command won't be available" dst;
(dst, false)
| `Unknown ->
(* TODO Installation of a non-executable file is unexpected, but not sure if it should be a warning/error *)
(dst, false) in
copy_file src dst;
if cygcheck then
match OpamStd.Sys.is_cygwin_variant dst with
`Native ->
()
| `Cygwin ->
OpamConsole.warning "%s is a Cygwin-linked executable" dst
| `CygLinked ->
OpamConsole.warning "%s links with a Cygwin-compiled DLL (almost certainly a packaging or environment error)" dst
end else
copy_file src dst
else
command ("install" :: "-m" :: (if exec then "0755" else "0644") ::
[ src; dst ])
end

let cpu_count () =
try
Expand Down

0 comments on commit 8cc885a

Please sign in to comment.