summaryrefslogtreecommitdiffstats
path: root/stdlib/filename.mli
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/filename.mli')
-rw-r--r--stdlib/filename.mli12
1 files changed, 8 insertions, 4 deletions
diff --git a/stdlib/filename.mli b/stdlib/filename.mli
index c2cc6a486..9e8a527da 100644
--- a/stdlib/filename.mli
+++ b/stdlib/filename.mli
@@ -87,8 +87,8 @@ val temp_file : ?temp_dir: string -> string -> string -> string
*)
val open_temp_file :
- ?mode: open_flag list -> ?temp_dir: string -> string -> string ->
- string * out_channel
+ ?mode: open_flag list -> ?perms: int -> ?temp_dir: string -> string ->
+ string -> string * out_channel
(** Same as {!Filename.temp_file}, but returns both the name of a fresh
temporary file, and an output channel opened (atomically) on
this file. This function is more secure than [temp_file]: there
@@ -96,8 +96,12 @@ val open_temp_file :
by a symbolic link) before the program opens it. The optional argument
[mode] is a list of additional flags to control the opening of the file.
It can contain one or several of [Open_append], [Open_binary],
- and [Open_text]. The default is [[Open_text]] (open in text mode).
- Raise [Sys_error] if the file could not be opened.
+ and [Open_text]. The default is [[Open_text]] (open in text mode). The
+ file is created with permissions [perms] (defaults to readable and
+ writable only by the file owner).
+
+ @raise Sys_error if the file could not be opened.
+ @before 4.03.0 no ?perms optional argument
@before 3.11.2 no ?temp_dir optional argument
*)