summaryrefslogtreecommitdiffstats
path: root/ocamlbuild/shell.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocamlbuild/shell.ml')
-rw-r--r--ocamlbuild/shell.ml71
1 files changed, 71 insertions, 0 deletions
diff --git a/ocamlbuild/shell.ml b/ocamlbuild/shell.ml
new file mode 100644
index 000000000..9c056ff39
--- /dev/null
+++ b/ocamlbuild/shell.ml
@@ -0,0 +1,71 @@
+(***********************************************************************)
+(* ocamlbuild *)
+(* *)
+(* Nicolas Pouillard, Berke Durak, projet Gallium, INRIA Rocquencourt *)
+(* *)
+(* Copyright 2007 Institut National de Recherche en Informatique et *)
+(* en Automatique. All rights reserved. This file is distributed *)
+(* under the terms of the Q Public License version 1.0. *)
+(* *)
+(***********************************************************************)
+
+(* $Id$ *)
+(* Original author: Nicolas Pouillard *)
+open My_std
+
+let is_simple_filename s =
+ let ls = String.length s in
+ ls <> 0 &&
+ let rec loop pos =
+ if pos >= ls then true else
+ match s.[pos] with
+ | 'a'..'z' | 'A'..'Z' | '0'..'9' | '.' | '-' | '/' | '_' | ':' | '@' | '+' | ',' -> loop (pos + 1)
+ | _ -> false in
+ loop 0
+let quote_filename_if_needed s =
+ if is_simple_filename s then s else Filename.quote s
+let chdir dir =
+ reset_filesys_cache ();
+ Sys.chdir dir
+let run args =
+ reset_readdir_cache ();
+ let cmd = String.concat " " (List.map quote_filename_if_needed args) in
+ if !*My_unix.is_degraded || Sys.os_type = "Win32" then
+ begin
+ let st = sys_command cmd in
+ if st <> 0 then
+ failwith (Printf.sprintf "Error during command `%s'.\nExit code %d.\n" cmd st)
+ else
+ ()
+ end
+ else
+ match My_unix.execute_many ~ticker:Log.update ~display:Log.display [[(cmd, ignore)]] with
+ | None -> ()
+ | Some(_, x) ->
+ failwith (Printf.sprintf "Error during command %S: %s" cmd (Printexc.to_string x))
+let rm = sys_remove
+let rm_f x =
+ if sys_file_exists x then rm x
+let mkdir dir =
+ reset_filesys_cache_for_file dir;
+ (*Sys.mkdir dir (* MISSING in ocaml *) *)
+ run ["mkdir"; dir]
+let try_mkdir dir = if not (sys_file_exists dir) then mkdir dir
+let rec mkdir_p dir =
+ if sys_file_exists dir then ()
+ else (mkdir_p (Filename.dirname dir); mkdir dir)
+let cp = copy_file (* Décret du 2007-02-01 *)
+(*
+ let cp src dest =
+ reset_filesys_cache_for_file dest;
+ run["cp";"-pf";src;dest]*)
+let readlink = My_unix.readlink
+let is_link = My_unix.is_link
+let rm_rf x =
+ reset_filesys_cache ();
+ run["rm";"-Rf";x]
+let mv src dest =
+ reset_filesys_cache_for_file src;
+ reset_filesys_cache_for_file dest;
+ run["mv"; src; dest]
+ (*Sys.rename src dest*)