Skip to content

Commit e6108d1

Browse files
committed
add test
1 parent d71a3ff commit e6108d1

File tree

2 files changed

+81
-3
lines changed

2 files changed

+81
-3
lines changed

src/fpm_filesystem.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -517,7 +517,7 @@ recursive subroutine list_files(dir, files, recurse)
517517
call fpm_stop(2,'*list_files*:directory listing failed')
518518
end if
519519

520-
files = read_lines_expanded(temp_file)
520+
files = read_lines(temp_file)
521521
call delete_file(temp_file)
522522

523523
do i=1,size(files)

test/fpm_test/test_filesystem.f90

Lines changed: 80 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,8 @@
11
module test_filesystem
22
use testsuite, only: new_unittest, unittest_t, error_t, test_failed
33
use fpm_filesystem, only: canon_path, is_dir, mkdir, os_delete_dir, &
4-
join_path, is_absolute_path, get_home
4+
join_path, is_absolute_path, get_home, &
5+
delete_file, read_lines, get_temp_filename
56
use fpm_environment, only: OS_WINDOWS, get_os_type, os_is_unix
67
implicit none
78
private
@@ -20,7 +21,8 @@ subroutine collect_filesystem(tests)
2021
& new_unittest("canon-path", test_canon_path), &
2122
& new_unittest("create-delete-directory", test_mkdir_rmdir), &
2223
& new_unittest("test-is-absolute-path", test_is_absolute_path), &
23-
& new_unittest("test-get-home", test_get_home) &
24+
& new_unittest("test-get-home", test_get_home), &
25+
& new_unittest("test-crlf-lines", test_dir_with_crlf) &
2426
]
2527

2628
end subroutine collect_filesystem
@@ -289,5 +291,81 @@ subroutine test_get_home(error)
289291
end if
290292

291293
end subroutine test_get_home
294+
295+
! On MS windows,
296+
subroutine test_dir_with_crlf(error)
297+
type(error_t), allocatable, intent(out) :: error
298+
299+
character, parameter :: CR = achar(13)
300+
character, parameter :: LF = new_line('A')
301+
character(*), parameter :: CRLF = CR//LF
302+
303+
character(*), parameter :: test_lines = 'build.f90'//CRLF//&
304+
'dependency.f90'//CRLF//&
305+
'example.f90'//CRLF//&
306+
'executable.f90'//CRLF//&
307+
'fortran.f90'//CRLF
308+
309+
type(string_t), allocatable :: lines(:)
310+
character(len=:), allocatable :: temp_file
311+
integer :: unit, i, ios
312+
313+
temp_file = get_temp_filename()
314+
315+
open(newunit=unit,file=temp_file,access='stream',action='write',iostat=ios)
316+
if (ios/=0) then
317+
call test_failed(error, "cannot create temporary file")
318+
return
319+
end if
320+
321+
write(unit,iostat=ios) test_lines
322+
if (ios/=0) then
323+
call test_failed(error, "cannot write to temporary file")
324+
return
325+
end if
326+
327+
close(unit,iostat=ios)
328+
if (ios/=0) then
329+
call test_failed(error, "cannot close temporary file")
330+
return
331+
end if
332+
333+
lines = read_lines(temp_file)
334+
335+
if (.not.allocated(lines)) then
336+
call test_failed(error, "Failed reading file with CRLF: no output")
337+
return
338+
end if
339+
340+
if (size(lines)/=5) then
341+
call test_failed(error, "Failed reading file with CRLF: wrong number of lines")
342+
return
343+
end if
344+
345+
if (lines(1)/='build.f90') then
346+
call test_failed(error, "Failed reading file with CRLF: at build.f90")
347+
return
348+
end if
349+
if (lines(2)/='dependency.f90') then
350+
call test_failed(error, "Failed reading file with CRLF: at dependency.f90")
351+
return
352+
end if
353+
if (lines(3)/='example.f90') then
354+
call test_failed(error, "Failed reading file with CRLF: at example.f90")
355+
return
356+
end if
357+
if (lines(4)/='executable.f90') then
358+
call test_failed(error, "Failed reading file with CRLF: at executable.f90")
359+
return
360+
end if
361+
if (lines(5)/='fortran.f90') then
362+
call test_failed(error, "Failed reading file with CRLF: at fortran.f90")
363+
return
364+
end if
365+
366+
call delete_dile(temp_file)
367+
368+
end subroutine test_dir_with_crlf
369+
292370

293371
end module test_filesystem

0 commit comments

Comments
 (0)