1- require Record
2-
3- defmodule File.Stat do
4- @ moduledoc """
5- A struct responsible to hold file information.
6-
7- In Erlang, this struct is represented by a `:file_info` record.
8- Therefore this module also provides functions for converting
9- in between the Erlang record and the Elixir struct.
10-
11- Its fields are:
12-
13- * `size` - size of file in bytes.
14-
15- * `type` - `:device | :directory | :regular | :other`; the type of the
16- file.
17-
18- * `access` - `:read | :write | :read_write | :none`; the current system
19- access to the file.
20-
21- * `atime` - the last time the file was read.
22-
23- * `mtime` - the last time the file was written.
24-
25- * `ctime` - the interpretation of this time field depends on the operating
26- system. On Unix, it is the last time the file or the inode was changed.
27- In Windows, it is the time of creation.
28-
29- * `mode` - the file permissions.
30-
31- * `links` - the number of links to this file. This is always 1 for file
32- systems which have no concept of links.
33-
34- * `major_device` - identifies the file system where the file is located.
35- In windows, the number indicates a drive as follows: 0 means A:, 1 means
36- B:, and so on.
37-
38- * `minor_device` - only valid for character devices on Unix. In all other
39- cases, this field is zero.
40-
41- * `inode` - gives the inode number. On non-Unix file systems, this field
42- will be zero.
43-
44- * `uid` - indicates the owner of the file.
45-
46- * `gid` - gives the group that the owner of the file belongs to. Will be
47- zero for non-Unix file systems.
48-
49- The time type returned in `atime`, `mtime`, and `ctime` is dependent on the
50- time type set in options. `{:time, type}` where type can be `:local`,
51- `:universal`, or `:posix`. Default is `:local`.
52- """
53-
54- record = Record . extract ( :file_info , from_lib: "kernel/include/file.hrl" )
55- keys = :lists . map ( & elem ( & 1 , 0 ) , record )
56- vals = :lists . map ( & { & 1 , [ ] , nil } , keys )
57- pairs = :lists . zip ( keys , vals )
58-
59- defstruct keys
60-
61- @ doc """
62- Converts a `File.Stat` struct to a `:file_info` record.
63- """
64- def to_record ( % File.Stat { unquote_splicing ( pairs ) } ) do
65- { :file_info , unquote_splicing ( vals ) }
66- end
67-
68- @ doc """
69- Converts a `:file_info` record into a `File.Stat`.
70- """
71- def from_record ( { :file_info , unquote_splicing ( vals ) } ) do
72- % File.Stat { unquote_splicing ( pairs ) }
73- end
74- end
75-
76- defmodule File.Stream do
77- @ moduledoc """
78- Defines a `File.Stream` struct returned by `File.stream!/3`.
79-
80- The following fields are public:
81-
82- * `path` - the file path
83- * `modes` - the file modes
84- * `raw` - a boolean indicating if bin functions should be used
85- * `line_or_bytes` - if reading should read lines or a given amount of bytes
86-
87- """
88-
89- defstruct path: nil , modes: [ ] , line_or_bytes: :line , raw: true
90-
91- defimpl Collectable do
92- def empty ( stream ) do
93- stream
94- end
95-
96- def into ( % { path: path , modes: modes , raw: raw } = stream ) do
97- modes = for mode <- modes , not mode in [ :read ] , do: mode
98-
99- case :file . open ( path , [ :write | modes ] ) do
100- { :ok , device } ->
101- { :ok , into ( device , stream , raw ) }
102- { :error , reason } ->
103- raise File.Error , reason: reason , action: "stream" , path: path
104- end
105- end
106-
107- defp into ( device , stream , raw ) do
108- fn
109- :ok , { :cont , x } ->
110- case raw do
111- true -> IO . binwrite ( device , x )
112- false -> IO . write ( device , x )
113- end
114- :ok , :done ->
115- :file . close ( device )
116- stream
117- :ok , :halt ->
118- :file . close ( device )
119- end
120- end
121- end
122-
123- defimpl Enumerable do
124- def reduce ( % { path: path , modes: modes , line_or_bytes: line_or_bytes , raw: raw } , acc , fun ) do
125- modes = for mode <- modes , not mode in [ :write , :append ] , do: mode
126-
127- start_fun =
128- fn ->
129- case :file . open ( path , modes ) do
130- { :ok , device } -> device
131- { :error , reason } ->
132- raise File.Error , reason: reason , action: "stream" , path: path
133- end
134- end
135-
136- next_fun =
137- case raw do
138- true -> & IO . each_binstream ( & 1 , line_or_bytes )
139- false -> & IO . each_stream ( & 1 , line_or_bytes )
140- end
141-
142- Stream . resource ( start_fun , next_fun , & :file . close / 1 ) . ( acc , fun )
143- end
144-
145- def count ( _stream ) do
146- { :error , __MODULE__ }
147- end
148-
149- def member? ( _stream , _term ) do
150- { :error , __MODULE__ }
151- end
152- end
153- end
154-
1551defmodule File do
1562 @ moduledoc ~S"""
1573 This module contains functions to manipulate files.
@@ -224,8 +70,7 @@ defmodule File do
22470 about such options and other performance considerations.
22571 """
22672
227- alias :file , as: F
228- alias :filelib , as: FL
73+ alias :file , as: F
22974
23075 @ type posix :: :file . posix ( )
23176 @ type io_device :: :file . io_device ( )
@@ -241,15 +86,15 @@ defmodule File do
24186 """
24287 @ spec regular? ( Path . t ) :: boolean
24388 def regular? ( path ) do
244- FL . is_regular ( IO . chardata_to_string ( path ) )
89+ :elixir_utils . read_file_type ( IO . chardata_to_string ( path ) ) == { :ok , :regular }
24590 end
24691
24792 @ doc """
24893 Returns `true` if the path is a directory.
24994 """
25095 @ spec dir? ( Path . t ) :: boolean
25196 def dir? ( path ) do
252- FL . is_dir ( IO . chardata_to_string ( path ) )
97+ :elixir_utils . read_file_type ( IO . chardata_to_string ( path ) ) == { :ok , :directory }
25398 end
25499
255100 @ doc """
@@ -319,7 +164,31 @@ defmodule File do
319164 """
320165 @ spec mkdir_p ( Path . t ) :: :ok | { :error , posix }
321166 def mkdir_p ( path ) do
322- FL . ensure_dir ( Path . join ( path , "." ) )
167+ do_mkdir_p ( IO . chardata_to_string ( path ) )
168+ end
169+
170+ defp do_mkdir_p ( "/" ) do
171+ :ok
172+ end
173+
174+ defp do_mkdir_p ( path ) do
175+ if dir? ( path ) do
176+ :ok
177+ else
178+ parent = Path . dirname ( path )
179+ if parent == path do
180+ # Protect against infinite loop
181+ { :error , :einval }
182+ else
183+ _ = do_mkdir_p ( parent )
184+ case :file . make_dir ( path ) do
185+ { :error , :eexist } = error ->
186+ if dir? ( path ) , do: :ok , else: error
187+ other ->
188+ other
189+ end
190+ end
191+ end
323192 end
324193
325194 @ doc """
@@ -636,7 +505,7 @@ defmodule File do
636505 # src may be a file or a directory, dest is definitely
637506 # a directory. Returns nil unless an error is found.
638507 defp do_cp_r ( src , dest , callback , acc ) when is_list ( acc ) do
639- case :elixir_utils . file_type ( src ) do
508+ case :elixir_utils . read_link_type ( src ) do
640509 { :ok , :regular } ->
641510 do_cp_file ( src , dest , callback , acc )
642511 { :ok , :symlink } ->
@@ -922,9 +791,9 @@ defmodule File do
922791 end
923792
924793 defp safe_list_dir ( path ) do
925- case :elixir_utils . file_type ( path ) do
794+ case :elixir_utils . read_link_type ( path ) do
926795 { :ok , :symlink } ->
927- case :elixir_utils . file_type ( path , :read_file_info ) do
796+ case :elixir_utils . read_file_type ( path ) do
928797 { :ok , :directory } -> { :ok , :directory }
929798 _ -> { :ok , :regular }
930799 end
@@ -1235,21 +1104,7 @@ defmodule File do
12351104 """
12361105 def stream! ( path , modes \\ [ ] , line_or_bytes \\ :line ) do
12371106 modes = open_defaults ( modes , true )
1238- raw = :lists . keyfind ( :encoding , 1 , modes ) == false
1239-
1240- modes =
1241- if raw do
1242- if :lists . keyfind ( :read_ahead , 1 , modes ) == { :read_ahead , false } do
1243- [ :raw | modes ]
1244- else
1245- [ :raw , :read_ahead | modes ]
1246- end
1247- else
1248- modes
1249- end
1250-
1251- % File.Stream { path: IO . chardata_to_string ( path ) , modes: modes ,
1252- raw: raw , line_or_bytes: line_or_bytes }
1107+ File.Stream . __build__ ( IO . chardata_to_string ( path ) , modes , line_or_bytes )
12531108 end
12541109
12551110 @ doc """
0 commit comments