~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/filename.xml

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
<?xml version="1.0" encoding="latin1" ?>
 
2
<!DOCTYPE erlref SYSTEM "erlref.dtd">
 
3
 
 
4
<erlref>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>1997</year>
 
8
      <year>2007</year>
 
9
      <holder>Ericsson AB, All Rights Reserved</holder>
 
10
    </copyright>
 
11
    <legalnotice>
 
12
  The contents of this file are subject to the Erlang Public License,
 
13
  Version 1.1, (the "License"); you may not use this file except in
 
14
  compliance with the License. You should have received a copy of the
 
15
  Erlang Public License along with this software. If not, it can be
 
16
  retrieved online at http://www.erlang.org/.
 
17
 
 
18
  Software distributed under the License is distributed on an "AS IS"
 
19
  basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
20
  the License for the specific language governing rights and limitations
 
21
  under the License.
 
22
 
 
23
  The Initial Developer of the Original Code is Ericsson AB.
 
24
    </legalnotice>
 
25
 
 
26
    <title>filename</title>
 
27
    <prepared>Kenneth Lundin</prepared>
 
28
    <docno>1</docno>
 
29
    <date>97-11-13</date>
 
30
    <rev>B</rev>
 
31
  </header>
 
32
  <module>filename</module>
 
33
  <modulesummary>Filename Manipulation Functions</modulesummary>
 
34
  <description>
 
35
    <p>The module <c>filename</c> provides a number of useful functions
 
36
      for analyzing and manipulating file names. These functions are
 
37
      designed so that the Erlang code can work on many different
 
38
      platforms with different formats for file names. With file name
 
39
      is meant all strings that can be used to denote a file. They can
 
40
      be short relative names like <c>foo.erl</c>, very long absolute
 
41
      name which include a drive designator and directory names like
 
42
      <c>D:\\usr/local\\bin\\erl/lib\\tools\\foo.erl</c>, or any variations
 
43
      in between.</p>
 
44
    <p>In Windows, all functions return file names with forward slashes
 
45
      only, even if the arguments contain back slashes. Use
 
46
      <c>join/1</c> to normalize a file name by removing redundant
 
47
      directory separators.</p>
 
48
  </description>
 
49
 
 
50
  <section>
 
51
    <title>DATA TYPES</title>
 
52
    <code type="none">
 
53
name() = string() | atom() | DeepList
 
54
  DeepList = [char() | atom() | DeepList]</code>
 
55
  </section>
 
56
  <funcs>
 
57
    <func>
 
58
      <name>absname(Filename) -> string()</name>
 
59
      <fsummary>Convert a filename to an absolute name, relative the working directory</fsummary>
 
60
      <type>
 
61
        <v>Filename = name()</v>
 
62
      </type>
 
63
      <desc>
 
64
        <p>Converts a relative <c>Filename</c> and returns an absolute
 
65
          name. No attempt is made to create the shortest absolute name,
 
66
          because this can give incorrect results on file systems which
 
67
          allow links.</p>
 
68
        <p>Unix examples:</p>
 
69
        <pre>
 
70
1> <input>pwd().</input>
 
71
"/usr/local"
 
72
2> <input>filename:absname("foo").</input>
 
73
"/usr/local/foo"
 
74
3> <input>filename:absname("../x").</input>
 
75
"/usr/local/../x"
 
76
4> <input>filename:absname("/").</input>
 
77
"/"</pre>
 
78
        <p>Windows examples:</p>
 
79
        <pre>
 
80
1> <input>pwd().</input>
 
81
"D:/usr/local"
 
82
2> <input>filename:absname("foo").</input>
 
83
"D:/usr/local/foo"
 
84
3> <input>filename:absname("../x").</input>
 
85
"D:/usr/local/../x"
 
86
4> <input>filename:absname("/").</input>
 
87
"D:/"</pre>
 
88
      </desc>
 
89
    </func>
 
90
    <func>
 
91
      <name>absname(Filename, Dir) -> string()</name>
 
92
      <fsummary>Convert a filename to an absolute name, relative a specified directory</fsummary>
 
93
      <type>
 
94
        <v>Filename = name()</v>
 
95
        <v>Dir = string()</v>
 
96
      </type>
 
97
      <desc>
 
98
        <p>This function works like <c>absname/1</c>, except that
 
99
          the directory to which the file name should be made relative
 
100
          is given explicitly in the <c>Dir</c> argument.</p>
 
101
      </desc>
 
102
    </func>
 
103
    <func>
 
104
      <name>absname_join(Dir, Filename) -> string()</name>
 
105
      <fsummary>Join an absolute directory with a relative filename</fsummary>
 
106
      <type>
 
107
        <v>Dir = string()</v>
 
108
        <v>Filename = name()</v>
 
109
      </type>
 
110
      <desc>
 
111
        <p>Joins an absolute directory with a relative filename.
 
112
          Similar to <c>join/2</c>, but on platforms with tight
 
113
          restrictions on raw filename length and no support for
 
114
          symbolic links (read: VxWorks), leading parent directory
 
115
          components in <c>Filename</c> are matched against trailing
 
116
          directory components in <c>Dir</c> so they can be removed
 
117
          from the result - minimizing its length.</p>
 
118
      </desc>
 
119
    </func>
 
120
    <func>
 
121
      <name>basename(Filename) -> string()</name>
 
122
      <fsummary>Return the last component of a filename</fsummary>
 
123
      <type>
 
124
        <v>Filename = name()</v>
 
125
      </type>
 
126
      <desc>
 
127
        <p>Returns the last component of <c>Filename</c>, or
 
128
          <c>Filename</c> itself if it does not contain any directory
 
129
          separators.</p>
 
130
        <pre>
 
131
5> <input>filename:basename("foo").</input>
 
132
"foo"
 
133
6> <input>filename:basename("/usr/foo").</input>
 
134
"foo"
 
135
7> <input>filename:basename("/").</input>
 
136
[]</pre>
 
137
      </desc>
 
138
    </func>
 
139
    <func>
 
140
      <name>basename(Filename, Ext) -> string()</name>
 
141
      <fsummary>Return the last component of a filename, stripped of the specified extension</fsummary>
 
142
      <type>
 
143
        <v>Filename = Ext = name()</v>
 
144
      </type>
 
145
      <desc>
 
146
        <p>Returns the last component of <c>Filename</c> with the
 
147
          extension <c>Ext</c> stripped. This function should be used
 
148
          to remove a specific extension which might, or might not, be
 
149
          there. Use <c>rootname(basename(Filename))</c> to remove an
 
150
          extension that exists, but you are not sure which one it is.</p>
 
151
        <pre>
 
152
8> <input>filename:basename("~/src/kalle.erl", ".erl").</input>
 
153
"kalle"
 
154
9> <input>filename:basename("~/src/kalle.beam", ".erl").</input>
 
155
"kalle.beam"
 
156
10> <input>filename:basename("~/src/kalle.old.erl", ".erl").</input>
 
157
"kalle.old"
 
158
11> <input>filename:rootname(filename:basename("~/src/kalle.erl")).</input>
 
159
"kalle"
 
160
12> <input>filename:rootname(filename:basename("~/src/kalle.beam")).</input>
 
161
"kalle"</pre>
 
162
      </desc>
 
163
    </func>
 
164
    <func>
 
165
      <name>dirname(Filename) -> string()</name>
 
166
      <fsummary>Return the directory part of a path name</fsummary>
 
167
      <type>
 
168
        <v>Filename = name()</v>
 
169
      </type>
 
170
      <desc>
 
171
        <p>Returns the directory part of <c>Filename</c>.</p>
 
172
        <pre>
 
173
13> <input>filename:dirname("/usr/src/kalle.erl").</input>
 
174
"/usr/src"
 
175
14> <input>filename:dirname("kalle.erl").</input>
 
176
"."
 
177
 
 
178
5> <input>filename:dirname("\\\\usr\\\\src/kalle.erl").</input> % Windows
 
179
"/usr/src"</pre>
 
180
      </desc>
 
181
    </func>
 
182
    <func>
 
183
      <name>extension(Filename) -> string()</name>
 
184
      <fsummary>Return the file extension</fsummary>
 
185
      <type>
 
186
        <v>Filename = name()</v>
 
187
      </type>
 
188
      <desc>
 
189
        <p>Returns the file extension of <c>Filename</c>, including
 
190
          the period. Returns an empty string if there is no extension.</p>
 
191
        <pre>
 
192
15> <input>filename:extension("foo.erl").</input>
 
193
".erl"
 
194
16> <input>filename:extension("beam.src/kalle").</input>
 
195
[]</pre>
 
196
      </desc>
 
197
    </func>
 
198
    <func>
 
199
      <name>flatten(Filename) -> string()</name>
 
200
      <fsummary>Convert a filename to a flat string</fsummary>
 
201
      <type>
 
202
        <v>Filename = name()</v>
 
203
      </type>
 
204
      <desc>
 
205
        <p>Converts a possibly deep list filename consisting of
 
206
          characters and atoms into the corresponding flat string
 
207
          filename.</p>
 
208
      </desc>
 
209
    </func>
 
210
    <func>
 
211
      <name>join(Components) -> string()</name>
 
212
      <fsummary>Join a list of filename components with directory separators</fsummary>
 
213
      <type>
 
214
        <v>Components = [string()]</v>
 
215
      </type>
 
216
      <desc>
 
217
        <p>Joins a list of file name <c>Components</c> with directory
 
218
          separators. If one of the elements of <c>Components</c>
 
219
          includes an absolute path, for example <c>"/xxx"</c>,
 
220
          the preceding elements, if any, are removed from the result.</p>
 
221
        <p>The result is "normalized":</p>
 
222
        <list type="bulleted">
 
223
          <item>Redundant directory separators are removed.</item>
 
224
          <item>In Windows, all directory separators are forward
 
225
           slashes and the drive letter is in lower case.</item>
 
226
        </list>
 
227
        <pre>
 
228
17> <input>filename:join(["/usr", "local", "bin"]).</input>
 
229
"/usr/local/bin"
 
230
18> <input>filename:join(["a/b///c/"]).</input>
 
231
"a/b/c"
 
232
 
 
233
6> <input>filename:join(["B:a\\\\b///c/"]).</input> % Windows
 
234
"b:a/b/c"</pre>
 
235
      </desc>
 
236
    </func>
 
237
    <func>
 
238
      <name>join(Name1, Name2) -> string()</name>
 
239
      <fsummary>Join two filename components with directory separators</fsummary>
 
240
      <type>
 
241
        <v>Name1 = Name2 = string()</v>
 
242
      </type>
 
243
      <desc>
 
244
        <p>Joins two file name components with directory separators. 
 
245
          Equivalent to <c>join([Name1, Name2])</c>.</p>
 
246
      </desc>
 
247
    </func>
 
248
    <func>
 
249
      <name>nativename(Path) -> string()</name>
 
250
      <fsummary>Return the native form of a file path</fsummary>
 
251
      <type>
 
252
        <v>Path = string()</v>
 
253
      </type>
 
254
      <desc>
 
255
        <p>Converts <c>Path</c> to a form accepted by the command shell
 
256
          and native applications on the current platform. On Windows,
 
257
          forward slashes is converted to backward slashes. On all
 
258
          platforms, the name is normalized as done by <c>join/1</c>.</p>
 
259
        <pre>
 
260
19> <input>filename:nativename("/usr/local/bin/").</input> % Unix
 
261
"/usr/local/bin"
 
262
 
 
263
7> <input>filename:nativename("/usr/local/bin/").</input> % Windows
 
264
"\\\\usr\\\\local\\\\bin"</pre>
 
265
      </desc>
 
266
    </func>
 
267
    <func>
 
268
      <name>pathtype(Path) -> absolute | relative | volumerelative</name>
 
269
      <fsummary>Return the type of a path</fsummary>
 
270
      <desc>
 
271
        <p>Returns the type of path, one of <c>absolute</c>,
 
272
          <c>relative</c>, or <c>volumerelative</c>.</p>
 
273
        <taglist>
 
274
          <tag><c>absolute</c></tag>
 
275
          <item>
 
276
            <p>The path name refers to a specific file on a specific
 
277
              volume.</p>
 
278
            <p>Unix example: <c>/usr/local/bin</c></p>
 
279
            <p>Windows example: <c>D:/usr/local/bin</c></p>
 
280
          </item>
 
281
          <tag><c>relative</c></tag>
 
282
          <item>
 
283
            <p>The path name is relative to the current working
 
284
              directory on the current volume.</p>
 
285
            <p>Example: <c>foo/bar, ../src</c></p>
 
286
          </item>
 
287
          <tag><c>volumerelative</c></tag>
 
288
          <item>
 
289
            <p>The path name is relative to the current working
 
290
              directory on a specified volume, or it is a specific file
 
291
              on the current working volume.</p>
 
292
            <p>Windows example: <c>D:bar.erl, /bar/foo.erl</c></p>
 
293
          </item>
 
294
        </taglist>
 
295
      </desc>
 
296
    </func>
 
297
    <func>
 
298
      <name>rootname(Filename) -> string()</name>
 
299
      <name>rootname(Filename, Ext) -> string()</name>
 
300
      <fsummary>Remove a filename extension</fsummary>
 
301
      <type>
 
302
        <v>Filename = Ext = name()</v>
 
303
      </type>
 
304
      <desc>
 
305
        <p>Remove a filename extension. <c>rootname/2</c> works as
 
306
          <c>rootname/1</c>, except that the extension is removed only
 
307
          if it is <c>Ext</c>.</p>
 
308
        <pre>
 
309
20> <input>filename:rootname("/beam.src/kalle").</input>
 
310
/beam.src/kalle"
 
311
21> <input>filename:rootname("/beam.src/foo.erl").</input>
 
312
"/beam.src/foo"
 
313
22> <input>filename:rootname("/beam.src/foo.erl", ".erl").</input>
 
314
"/beam.src/foo"
 
315
23> <input>filename:rootname("/beam.src/foo.beam", ".erl").</input>
 
316
"/beam.src/foo.beam"</pre>
 
317
      </desc>
 
318
    </func>
 
319
    <func>
 
320
      <name>split(Filename) -> Components</name>
 
321
      <fsummary>Split a filename into its path components</fsummary>
 
322
      <type>
 
323
        <v>Filename = name()</v>
 
324
        <v>Components = [string()]</v>
 
325
      </type>
 
326
      <desc>
 
327
        <p>Returns a list whose elements are the path components of
 
328
          <c>Filename</c>.</p>
 
329
        <pre>
 
330
24> <input>filename:split("/usr/local/bin").</input>
 
331
["/","usr","local","bin"]
 
332
25> <input>filename:split("foo/bar").</input>
 
333
["foo","bar"]
 
334
26> <input>filename:split("a:\\\\msdev\\\\include").</input>
 
335
["a:/","msdev","include"]</pre>
 
336
      </desc>
 
337
    </func>
 
338
    <func>
 
339
      <name>find_src(Beam) -> {SourceFile, Options} | {error,{ErrorReason,Module}}</name>
 
340
      <name>find_src(Beam, Rules) -> {SourceFile, Options} | {error,{ErrorReason,Module}}</name>
 
341
      <fsummary>Find the filename and compiler options for a module</fsummary>
 
342
      <type>
 
343
        <v>Beam = Module | Filename</v>
 
344
        <v>&nbsp;Module = atom()</v>
 
345
        <v>&nbsp;Filename = string() | atom()</v>
 
346
        <v>SourceFile = string()</v>
 
347
        <v>Options = [Opt]</v>
 
348
        <v>&nbsp;Opt = {i, string()} | {outdir, string()} | {d, atom()}</v>
 
349
        <v>ErrorReason = non_existing | preloaded | interpreted</v>
 
350
      </type>
 
351
      <desc>
 
352
        <p>Finds the source filename and compiler options for a module.
 
353
          The result can be fed to <c>compile:file/2</c> in order to
 
354
          compile the file again.</p>
 
355
        <p>The <c>Beam</c> argument, which can be a string or an atom,
 
356
          specifies either the module name or the path to the source
 
357
          code, with or without the <c>".erl"</c> extension. In either
 
358
          case, the module must be known by the code server, i.e.
 
359
          <c>code:which(Module)</c> must succeed.</p>
 
360
        <p><c>Rules</c> describes how the source directory can be found,
 
361
          when the object code directory is known. It is a list of
 
362
          tuples <c>{BinSuffix, SourceSuffix}</c> and is interpreted
 
363
          as follows: If the end of the directory name where the object
 
364
          is located matches <c>BinSuffix</c>, then the source code
 
365
          directory has the same name, but with <c>BinSuffix</c>
 
366
          replaced by <c>SourceSuffix</c>. <c>Rules</c> defaults to:</p>
 
367
        <code type="none">
 
368
[{"", ""}, {"ebin", "src"}, {"ebin", "esrc"}]</code>
 
369
        <p>If the source file is found in the resulting directory, then
 
370
          the function returns that location together with
 
371
          <c>Options</c>. Otherwise, the next rule is tried, and so on.</p>
 
372
 
 
373
        <p>The function returns <c>{SourceFile, Options}</c> if it succeeds.
 
374
          <c>SourceFile</c> is the absolute path to the source file
 
375
          without the <c>".erl"</c> extension. <c>Options</c> include
 
376
          the options which are necessary to recompile the file with
 
377
          <c>compile:file/2</c>, but excludes options such as
 
378
          <c>report</c> or <c>verbose</c> which do not change the way
 
379
          code is generated. The paths in the <c>{outdir, Path}</c>
 
380
          and <c>{i, Path}</c> options are guaranteed to be
 
381
          absolute.</p>
 
382
 
 
383
      </desc>
 
384
    </func>
 
385
  </funcs>
 
386
</erlref>
 
387