summaryrefslogtreecommitdiffstats
path: root/stdlib/sys.mli
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2003-03-03 17:16:15 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2003-03-03 17:16:15 +0000
commit859efb84a8160e694b35a90fd60fcb3606ca8ef9 (patch)
treed09e19f7742c3914e33e92e56451a5021ba1740a /stdlib/sys.mli
parentdc64ea8cc7ed73b7b67f8554f29b95575883b81b (diff)
Ajout de Sys.readdir
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5415 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/sys.mli')
-rw-r--r--stdlib/sys.mli17
1 files changed, 13 insertions, 4 deletions
diff --git a/stdlib/sys.mli b/stdlib/sys.mli
index ff5c43502..551e958a6 100644
--- a/stdlib/sys.mli
+++ b/stdlib/sys.mli
@@ -51,6 +51,15 @@ external chdir : string -> unit = "sys_chdir"
external getcwd : unit -> string = "sys_getcwd"
(** Return the current working directory of the process. *)
+external readdir : string -> string array = "sys_read_directory"
+(** Return the names of all files present in the given directory.
+ Names denoting the current directory and the parent directory
+ (["."] and [".."] in Unix) are not returned. Each string in the
+ result is a file name rather than a complete path. There is no
+ guarantee that the name strings in the resulting array will appear
+ in any specific order; they are not, in particular, guaranteed to
+ appear in alphabetical order. *)
+
val interactive : bool ref
(** This reference is initially set to [false] in standalone
programs and to [true] if the code is being executed under
@@ -58,10 +67,10 @@ val interactive : bool ref
val os_type : string
(** Operating system currently executing the Caml program. One of
- ["Unix"] (for all Unix versions, including Linux and Mac OS X),
- ["Win32"] (for MS-Windows, OCaml compiled with MSVC++),
- ["Cygwin"] (for MS-Windows, OCaml compiled with Cygwin),
- ["MacOS"] (for MacOS 9). *)
+- ["Unix"] (for all Unix versions, including Linux and Mac OS X),
+- ["Win32"] (for MS-Windows, OCaml compiled with MSVC++ or Mingw),
+- ["Cygwin"] (for MS-Windows, OCaml compiled with Cygwin),
+- ["MacOS"] (for MacOS 9). *)
val word_size : int
(** Size of one word on the machine currently executing the Caml