File: kernel_file.txt

package info (click to toggle)
erlang 1%3A25.2.3%2Bdfsg-1%2Bdeb12u3
  • links: PTS, VCS
  • area: main
  • in suites: bookworm-proposed-updates
  • size: 219,972 kB
  • sloc: erlang: 1,440,803; xml: 473,412; ansic: 392,382; cpp: 164,287; makefile: 17,392; sh: 13,842; lisp: 9,675; java: 8,578; asm: 6,426; perl: 5,527; python: 5,469; javascript: 610; pascal: 126; sed: 72; php: 3
file content (199 lines) | stat: -rw-r--r-- 7,207 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199

	file

  This module provides an interface to the file system.

  Warning:
    File operations are only guaranteed to appear atomic when
    going through the same file server. A NIF or other OS process
    may observe intermediate steps on certain operations on some
    operating systems, eg. renaming an existing file on Windows,
    or write_file_info/2 on any OS at the time of writing.

  Regarding filename encoding, the Erlang VM can operate in two
  modes. The current mode can be queried using function 
  native_name_encoding/0. It returns latin1 or utf8.

  In latin1 mode, the Erlang VM does not change the encoding of
  filenames. In utf8 mode, filenames can contain Unicode
  characters greater than 255 and the VM converts filenames back and
  forth to the native filename encoding (usually UTF-8, but UTF-16
  on Windows).

  The default mode depends on the operating system. Windows, MacOS X
  and Android enforce consistent filename encoding and therefore the
  VM uses utf8 mode.

  On operating systems with transparent naming (for example, all
  Unix systems except MacOS X), default is utf8 if the terminal
  supports UTF-8, otherwise latin1. The default can be overridden
  using +fnl (to force latin1 mode) or +fnu (to force utf8
  mode) when starting erl.

  On operating systems with transparent naming, files can be
  inconsistently named, for example, some files are encoded in UTF-8
  while others are encoded in ISO Latin-1. The concept of raw
  filenames is introduced to handle file systems with inconsistent
  naming when running in utf8 mode.

  A raw filename is a filename specified as a binary. The Erlang
  VM does not translate a filename specified as a binary on systems
  with transparent naming.

  When running in utf8 mode, functions list_dir/1 and 
  read_link/1 never return raw filenames. To return all filenames
  including raw filenames, use functions list_dir_all/1 and 
  read_link_all/1.

  See also section Notes About Raw Filenames in the STDLIB User's
  Guide.

  Note:
    File operations used to accept filenames containing null
    characters (integer value zero). This caused the name to be
    truncated and in some cases arguments to primitive operations
    to be mixed up. Filenames containing null characters inside
    the filename are now rejected and will cause primitive file
    operations fail.

POSIX Error Codes

   • eacces - Permission denied

   • eagain - Resource temporarily unavailable

   • ebadf - Bad file number

   • ebusy - File busy

   • edquot - Disk quota exceeded

   • eexist - File already exists

   • efault - Bad address in system call argument

   • efbig - File too large

   • eintr - Interrupted system call

   • einval - Invalid argument

   • eio - I/O error

   • eisdir - Illegal operation on a directory

   • eloop - Too many levels of symbolic links

   • emfile - Too many open files

   • emlink - Too many links

   • enametoolong - Filename too long

   • enfile - File table overflow

   • enodev - No such device

   • enoent - No such file or directory

   • enomem - Not enough memory

   • enospc - No space left on device

   • enotblk - Block device required

   • enotdir - Not a directory

   • enotsup - Operation not supported

   • enxio - No such device or address

   • eperm - Not owner

   • epipe - Broken pipe

   • erofs - Read-only file system

   • espipe - Invalid seek

   • esrch - No such process

   • estale - Stale remote file handle

   • exdev - Cross-domain link

Performance

  For increased performance, raw files are recommended.

  A normal file is really a process so it can be used as an I/O
  device (see io). Therefore, when data is written to a normal
  file, the sending of the data to the file process, copies all data
  that are not binaries. Opening the file in binary mode and writing
  binaries is therefore recommended. If the file is opened on
  another node, or if the file server runs as slave to the file
  server of another node, also binaries are copied.

  Note:
    Raw files use the file system of the host machine of the node.
    For normal files (non-raw), the file server is used to find
    the files, and if the node is running its file server as slave
    to the file server of another node, and the other node runs on
    some other host machine, they can have different file systems.
    However, this is seldom a problem.

  open/2 can be given the options delayed_write and read_ahead
  to turn on caching, which will reduce the number of operating
  system calls and greatly improve performance for small reads and
  writes. However, the overhead won't disappear completely and it's
  best to keep the number of file operations to a minimum. As a
  contrived example, the following function writes 4MB in 2.5
  seconds when tested:

    create_file_slow(Name) ->
        {ok, Fd} = file:open(Name, [raw, write, delayed_write, binary]),
        create_file_slow_1(Fd, 4 bsl 20),
        file:close(Fd).
    
    create_file_slow_1(_Fd, 0) ->
        ok;
    create_file_slow_1(Fd, M) ->
        ok = file:write(Fd, <<0>>),
        create_file_slow_1(Fd, M - 1).

  The following functionally equivalent code writes 128 bytes per
  call to write/2 and so does the same work in 0.08 seconds, which
  is roughly 30 times faster:

    create_file(Name) ->
        {ok, Fd} = file:open(Name, [raw, write, delayed_write, binary]),
        create_file_1(Fd, 4 bsl 20),
        file:close(Fd),
        ok.
    
    create_file_1(_Fd, 0) ->
        ok;
    create_file_1(Fd, M) when M >= 128 ->
        ok = file:write(Fd, <<0:(128)/unit:8>>),
        create_file_1(Fd, M - 128);
    create_file_1(Fd, M) ->
        ok = file:write(Fd, <<0:(M)/unit:8>>),
        create_file_1(Fd, M - 1).

  When writing data it's generally more efficient to write a list of
  binaries rather than a list of integers. It is not needed to
  flatten a deep list before writing. On Unix hosts, scatter output,
  which writes a set of buffers in one operation, is used when
  possible. In this way write(FD, [Bin1, Bin2 | Bin3]) writes the
  contents of the binaries without copying the data at all, except
  for perhaps deep down in the operating system kernel.

  Warning:
    If an error occurs when accessing an open file with module io,
    the process handling the file exits. The dead file process can
    hang if a process tries to access it later. This will be fixed
    in a future release.

See Also

  filename(3)