11module file_utilities
2- use file_utils_consolidated, only: find_files, find_files_with_glob, &
3- read_binary_file, read_binary_file_safe, write_text_file, &
4- write_text_file_safe, read_file_content, read_file_content_enhanced, &
5- ensure_directory, ensure_directory_safe, resolve_path, file_exists, &
6- basename
2+ ! ! Consolidated file utilities module
3+ ! ! Owns file ops APIs previously in file_utils_consolidated.
4+
5+ use iso_fortran_env, only: int64
6+ use error_handling_core
7+ use iostat_utilities
8+ use input_validation_core
9+ use directory_operations
10+ use file_ops_secure, only: safe_find_files
11+ use file_search_secure, only: safe_find_files_with_glob
12+ use path_utils_consolidated, only: resolve_path, file_exists, basename
713 implicit none
814 private
915
10- ! Re-export all procedures for backward compatibility
16+ ! File finding procedures
1117 public :: find_files
1218 public :: find_files_with_glob
13- public :: resolve_path
19+
20+ ! Binary I/O procedures
1421 public :: read_binary_file
15- public :: write_text_file
16- public :: ensure_directory
1722 public :: read_binary_file_safe
23+
24+ ! Text I/O procedures
25+ public :: write_text_file
1826 public :: write_text_file_safe
19- public :: ensure_directory_safe
20- public :: file_exists
2127 public :: read_file_content
2228 public :: read_file_content_enhanced
29+
30+ ! Directory operations
31+ public :: ensure_directory
32+ public :: ensure_directory_safe
33+
34+ ! Path operations
35+ public :: resolve_path
36+ public :: file_exists
2337 public :: basename
38+
39+ contains
40+
41+ ! ========================================================================
42+ ! File Finding Operations
43+ ! ========================================================================
44+
45+ function find_files (pattern ) result(files)
46+ character (len=* ), intent (in ) :: pattern
47+ character (len= :), allocatable :: files(:)
48+ type (error_context_t) :: error_ctx
49+ integer :: stat
50+ character (len= 512 ) :: errmsg
51+
52+ call safe_find_files(pattern, files, error_ctx)
53+
54+ if (error_ctx% error_code /= ERROR_SUCCESS) then
55+ if (allocated (files)) deallocate (files, stat= stat)
56+ allocate (character (len= 256 ) :: files(0 ), stat= stat, errmsg= errmsg)
57+ if (stat /= 0 ) then
58+ write (* , ' (A)' ) " Error: Failed to allocate empty files array: " // trim (errmsg)
59+ return
60+ end if
61+ end if
62+ end function find_files
63+
64+ function find_files_with_glob (directory , pattern ) result(files)
65+ character (len=* ), intent (in ) :: directory
66+ character (len=* ), intent (in ) :: pattern
67+ character (len= :), allocatable :: files(:)
68+
69+ type (error_context_t) :: error_ctx
70+ integer :: stat
71+ character (len= 512 ) :: errmsg
72+
73+ call safe_find_files_with_glob(directory, pattern, files, error_ctx)
74+
75+ if (error_ctx% error_code /= ERROR_SUCCESS) then
76+ if (allocated (files)) deallocate (files, stat= stat)
77+ allocate (character (len= 256 ) :: files(0 ), stat= stat, errmsg= errmsg)
78+ if (stat /= 0 ) then
79+ write (* , ' (A)' ) " Error: Failed to allocate empty files array: " // trim (errmsg)
80+ return
81+ end if
82+ end if
83+ end function find_files_with_glob
84+
85+ ! ========================================================================
86+ ! Binary File I/O Operations
87+ ! ========================================================================
88+
89+ subroutine read_binary_file (filename , data , error_flag )
90+ character (len=* ), intent (in ) :: filename
91+ integer (kind= 1 ), allocatable , intent (out ) :: data (:)
92+ logical , intent (out ) :: error_flag
93+ integer :: unit, stat, file_size, i
94+ integer (kind= 1 ) :: byte
95+ character (len= 512 ) :: errmsg
96+
97+ error_flag = .false.
98+
99+ inquire (file= filename, exist= error_flag, size= file_size)
100+ if (.not. error_flag) then
101+ error_flag = .true.
102+ allocate (data (0 ), stat= stat, errmsg= errmsg)
103+ if (stat /= 0 ) then
104+ write (* , ' (A)' ) " Error: Failed to allocate empty data array: " // trim (errmsg)
105+ end if
106+ return
107+ end if
108+
109+ error_flag = .false.
110+
111+ open (newunit= unit, file= filename, access= ' stream' , &
112+ status= ' old' , iostat= stat)
113+ if (stat /= 0 ) then
114+ error_flag = .true.
115+ allocate (data (0 ), stat= stat, errmsg= errmsg)
116+ if (stat /= 0 ) then
117+ write (* , ' (A)' ) " Error: Failed to allocate empty data array: " // trim (errmsg)
118+ end if
119+ return
120+ end if
121+
122+ allocate (data (file_size), stat= stat, errmsg= errmsg)
123+ if (stat /= 0 ) then
124+ write (* , ' (A)' ) " Error: Failed to allocate data array: " // trim (errmsg)
125+ error_flag = .true.
126+ close (unit)
127+ return
128+ end if
129+
130+ do i = 1 , file_size
131+ read (unit, iostat= stat) byte
132+ if (stat /= 0 ) then
133+ error_flag = .true.
134+ close (unit)
135+ return
136+ end if
137+ data (i) = byte
138+ end do
139+
140+ close (unit)
141+ end subroutine read_binary_file
142+
143+ subroutine read_binary_file_safe (filename , data , error_ctx )
144+ character (len=* ), intent (in ) :: filename
145+ integer (kind= 1 ), allocatable , intent (out ) :: data (:)
146+ type (error_context_t), intent (out ) :: error_ctx
147+
148+ logical :: file_exists, error_flag
149+ integer :: file_size
150+ integer :: stat
151+ character (len= 512 ) :: errmsg
152+
153+ call clear_error_context(error_ctx)
154+
155+ inquire (file= filename, exist= file_exists, size= file_size)
156+ if (.not. file_exists) then
157+ call handle_missing_source(filename, error_ctx)
158+ allocate (data (0 ), stat= stat, errmsg= errmsg)
159+ if (stat /= 0 ) then
160+ write (* , ' (A)' ) " Error: Failed to allocate empty data array: " // trim (errmsg)
161+ end if
162+ return
163+ end if
164+
165+ call read_binary_file(filename, data , error_flag)
166+
167+ if (error_flag) then
168+ if (file_size == 0 ) then
169+ error_ctx% error_code = ERROR_INVALID_CONFIG
170+ write (error_ctx% message, ' (A,A)' ) &
171+ " Empty file: " , trim (filename)
172+ write (error_ctx% suggestion, ' (A)' ) &
173+ " Check if file was properly generated."
174+ else
175+ call handle_permission_denied(filename, error_ctx)
176+ end if
177+ end if
178+ end subroutine read_binary_file_safe
179+
180+ ! ========================================================================
181+ ! Text File I/O Operations
182+ ! ========================================================================
183+
184+ subroutine write_text_file (filename , content , error_flag )
185+ character (len=* ), intent (in ) :: filename
186+ character (len=* ), intent (in ) :: content
187+ logical , intent (out ) :: error_flag
188+ integer :: unit, stat
189+
190+ error_flag = .false.
191+
192+ open (newunit= unit, file= filename, status= ' replace' , iostat= stat)
193+ if (stat /= 0 ) then
194+ error_flag = .true.
195+ return
196+ end if
197+
198+ write (unit, ' (A)' , iostat= stat) content
199+ if (stat /= 0 ) then
200+ error_flag = .true.
201+ close (unit)
202+ return
203+ end if
204+
205+ close (unit)
206+ end subroutine write_text_file
207+
208+ subroutine write_text_file_safe (filename , content , error_ctx )
209+ character (len=* ), intent (in ) :: filename, content
210+ type (error_context_t), intent (out ) :: error_ctx
211+
212+ logical :: error_flag
213+ character (len= :), allocatable :: dir_path
214+ integer :: last_slash
215+
216+ call clear_error_context(error_ctx)
217+
218+ last_slash = index (filename, " /" , back= .true. )
219+ if (last_slash > 0 ) then
220+ dir_path = filename(1 :last_slash-1 )
221+ call ensure_directory_safe(dir_path, error_ctx)
222+ if (error_ctx% error_code /= ERROR_SUCCESS) return
223+ end if
224+
225+ call write_text_file(filename, content, error_flag)
226+
227+ if (error_flag) then
228+ call handle_permission_denied(filename, error_ctx)
229+ end if
230+ end subroutine write_text_file_safe
231+
232+ subroutine read_file_content (filename , content , error_flag )
233+ character (len=* ), intent (in ) :: filename
234+ character (len= :), allocatable , intent (out ) :: content
235+ logical , intent (out ) :: error_flag
236+
237+ integer :: unit, iostat, i
238+ integer (int64) :: file_size
239+ character (len= 1 ), allocatable :: buffer(:)
240+ type (validation_result_t) :: validation_result
241+ integer :: stat
242+ character (len= 512 ) :: errmsg
243+
244+ error_flag = .false.
245+
246+ call validate_file_constraints(filename, validation_result)
247+ if (.not. validation_result% is_valid) then
248+ error_flag = .true.
249+ return
250+ end if
251+
252+ open (newunit= unit, file= filename, status= ' old' , action= ' read' , &
253+ access= ' stream' , iostat= iostat)
254+ if (iostat /= 0 ) then
255+ error_flag = .true.
256+ content = " "
257+ return
258+ end if
259+
260+ inquire (unit= unit, size= file_size)
261+ if (file_size <= 0 ) then
262+ close (unit)
263+ content = " "
264+ return
265+ end if
266+
267+ allocate (buffer(file_size), stat= stat, errmsg= errmsg)
268+ if (stat /= 0 ) then
269+ write (* , ' (A)' ) " Error: Failed to allocate buffer: " // trim (errmsg)
270+ error_flag = .true.
271+ close (unit)
272+ content = " "
273+ return
274+ end if
275+
276+ read (unit, iostat= iostat) buffer
277+ if (iostat /= 0 ) then
278+ error_flag = .true.
279+ deallocate (buffer, stat= stat)
280+ close (unit)
281+ content = " "
282+ return
283+ end if
284+
285+ close (unit)
286+
287+ allocate (character (len= file_size) :: content, stat= stat, errmsg= errmsg)
288+ if (stat /= 0 ) then
289+ write (* , ' (A)' ) " Error: Failed to allocate content string: " // trim (errmsg)
290+ error_flag = .true.
291+ deallocate (buffer, stat= stat)
292+ return
293+ end if
294+ do i = 1 , int (file_size)
295+ content(i:i) = buffer(i)
296+ end do
297+ deallocate (buffer, stat= stat)
298+ end subroutine read_file_content
299+
300+ subroutine read_file_content_enhanced (filename , content , error_ctx )
301+ character (len=* ), intent (in ) :: filename
302+ character (len= :), allocatable , intent (out ) :: content
303+ type (error_context_t), intent (out ) :: error_ctx
304+
305+ logical :: error_flag
306+
307+ call clear_error_context(error_ctx)
308+
309+ call read_file_content(filename, content, error_flag)
310+
311+ if (error_flag) then
312+ call handle_permission_denied(filename, error_ctx)
313+ content = " "
314+ end if
315+ end subroutine read_file_content_enhanced
24316
25- end module file_utilities
317+ end module file_utilities
0 commit comments