Skip to content

Commit 0ae912b

Browse files
committed
tests for non_intrinsic parsing
1 parent 1bae477 commit 0ae912b

File tree

1 file changed

+137
-4
lines changed

1 file changed

+137
-4
lines changed

test/fpm_test/test_source_parsing.f90

Lines changed: 137 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,19 +2,19 @@
22
module test_source_parsing
33
use testsuite, only : new_unittest, unittest_t, error_t, test_failed
44
use fpm_filesystem, only: get_temp_filename
5-
use fpm_source_parsing, only: parse_f_source, parse_c_source
5+
use fpm_source_parsing, only: parse_f_source, parse_c_source, parse_use_statement
66
use fpm_model, only: srcfile_t, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
77
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
88
FPM_UNIT_CPPSOURCE
9-
use fpm_strings, only: operator(.in.)
9+
use fpm_strings, only: operator(.in.), lower
10+
use fpm_error, only: file_parse_error, fatal_error
1011
implicit none
1112
private
1213

1314
public :: collect_source_parsing
1415

1516
contains
1617

17-
1818
!> Collect all exported unit tests
1919
subroutine collect_source_parsing(testsuite)
2020

@@ -24,6 +24,7 @@ subroutine collect_source_parsing(testsuite)
2424
testsuite = [ &
2525
& new_unittest("modules-used", test_modules_used), &
2626
& new_unittest("intrinsic-modules-used", test_intrinsic_modules_used), &
27+
& new_unittest("nonintrinsic-modules-used", test_nonintrinsic_modules_used), &
2728
& new_unittest("include-stmt", test_include_stmt), &
2829
& new_unittest("program", test_program), &
2930
& new_unittest("module", test_module), &
@@ -42,7 +43,8 @@ subroutine collect_source_parsing(testsuite)
4243
& new_unittest("invalid-module", &
4344
test_invalid_module, should_fail=.true.), &
4445
& new_unittest("invalid-submodule", &
45-
test_invalid_submodule, should_fail=.true.) &
46+
test_invalid_submodule, should_fail=.true.), &
47+
& new_unittest("use-statement",test_use_statement) &
4648
]
4749

4850
end subroutine collect_source_parsing
@@ -187,6 +189,78 @@ subroutine test_intrinsic_modules_used(error)
187189
end subroutine test_intrinsic_modules_used
188190

189191

192+
!> Check that intrinsic module names are not ignored if declared non_intrinsic
193+
subroutine test_nonintrinsic_modules_used(error)
194+
195+
!> Error handling
196+
type(error_t), allocatable, intent(out) :: error
197+
198+
integer :: unit
199+
character(:), allocatable :: temp_file
200+
type(srcfile_t), allocatable :: f_source
201+
202+
allocate(temp_file, source=get_temp_filename())
203+
204+
open(file=temp_file, newunit=unit)
205+
write(unit, '(a)') &
206+
& 'program test', &
207+
& ' use, non_intrinsic :: iso_c_binding', &
208+
& ' use, intrinsic :: iso_fortran_env', &
209+
& ' use, non_intrinsic :: ieee_arithmetic', &
210+
& ' use, non_intrinsic :: ieee_exceptions', &
211+
& ' use, non_intrinsic :: ieee_features', &
212+
& ' use, non_intrinsic :: my_module', &
213+
& ' implicit none', &
214+
& 'end program test'
215+
close(unit)
216+
217+
f_source = parse_f_source(temp_file,error)
218+
if (allocated(error)) then
219+
return
220+
end if
221+
222+
if (size(f_source%modules_provided) /= 0) then
223+
call test_failed(error,'Unexpected modules_provided - expecting zero')
224+
return
225+
end if
226+
227+
if (size(f_source%modules_used) /= 5) then
228+
call test_failed(error,'Incorrect number of modules_used - expecting five')
229+
return
230+
end if
231+
232+
if (.not. ('iso_c_binding' .in. f_source%modules_used)) then
233+
call test_failed(error,'Non-Intrinsic module found in modules_used')
234+
return
235+
end if
236+
237+
if ('iso_fortran_env' .in. f_source%modules_used) then
238+
call test_failed(error,'Intrinsic module found in modules_used')
239+
return
240+
end if
241+
242+
if (.not. ('ieee_arithmetic' .in. f_source%modules_used)) then
243+
call test_failed(error,'Non-Intrinsic module found in modules_used')
244+
return
245+
end if
246+
247+
if (.not. ('ieee_exceptions' .in. f_source%modules_used)) then
248+
call test_failed(error,'Non-Intrinsic module found in modules_used')
249+
return
250+
end if
251+
252+
if (.not. ('ieee_features' .in. f_source%modules_used)) then
253+
call test_failed(error,'Non-Intrinsic module found in modules_used')
254+
return
255+
end if
256+
257+
if (.not. ('my_module' .in. f_source%modules_used)) then
258+
call test_failed(error,'Non-Intrinsic module found in modules_used')
259+
return
260+
end if
261+
262+
end subroutine test_nonintrinsic_modules_used
263+
190264
!> Check parsing of include statements
191265
subroutine test_include_stmt(error)
192266

@@ -945,6 +1019,65 @@ subroutine test_invalid_submodule(error)
9451019

9461020
end subroutine test_invalid_submodule
9471021

1022+
!> Parse several USE statements
1023+
subroutine test_use_statement(error)
1024+
1025+
!> Error handling
1026+
type(error_t), allocatable, intent(out) :: error
1027+
1028+
character(*), parameter :: filename='test_use_statement'
1029+
character(:), allocatable :: line,module_name
1030+
1031+
logical :: used,is_intrinsic
1032+
1033+
line = 'use, intrinsic:: iso_fortran_env'
1034+
call parse_use_statement(filename,0,line,used,is_intrinsic,module_name,error)
1035+
if (allocated(error)) return
1036+
1037+
if (.not. (used .and. &
1038+
is_intrinsic .and. &
1039+
module_name=='iso_fortran_env' .and. &
1040+
used)) then
1041+
call fatal_error(error,'USE statement failed parsing <'//line//'>')
1042+
return
1043+
endif
1044+
1045+
line = 'use, non_intrinsic :: iso_fortran_env'
1046+
call parse_use_statement(filename,0,line,used,is_intrinsic,module_name,error)
1047+
if (allocated(error)) return
1048+
1049+
if (.not. (used .and. &
1050+
(.not.is_intrinsic) .and. &
1051+
module_name=='iso_fortran_env' .and. &
1052+
used)) then
1053+
call fatal_error(error,'USE statement failed parsing <'//line//'>')
1054+
return
1055+
endif
1056+
1057+
line = 'use, non_intrinsic :: my_fortran_module'
1058+
call parse_use_statement(filename,0,line,used,is_intrinsic,module_name,error)
1059+
if (allocated(error)) return
1060+
1061+
if (.not. (used .and. &
1062+
(.not.is_intrinsic) .and. &
1063+
module_name=='my_fortran_module' .and. &
1064+
used)) then
1065+
call fatal_error(error,'USE statement failed parsing <'//line//'>')
1066+
return
1067+
endif
1068+
1069+
line = 'use, intrinsic :: my_fortran_module'
1070+
call parse_use_statement(filename,0,line,used,is_intrinsic,module_name,error)
1071+
1072+
! This is not an intrinsic module: should detect an error
1073+
if (.not. allocated(error)) then
1074+
call fatal_error(error,'Did not catch invalid intrinsic module in <'//line//'>')
1075+
return
1076+
else
1077+
deallocate(error)
1078+
endif
1079+
1080+
end subroutine test_use_statement
9481081

9491082

9501083
end module test_source_parsing

0 commit comments

Comments
 (0)