@@ -24,6 +24,7 @@ subroutine collect_source_parsing(testsuite)
24
24
& new_unittest(" modules-used" , test_modules_used), &
25
25
& new_unittest(" intrinsic-modules-used" , test_intrinsic_modules_used), &
26
26
& new_unittest(" include-stmt" , test_include_stmt), &
27
+ & new_unittest(" program" , test_program), &
27
28
& new_unittest(" module" , test_module), &
28
29
& new_unittest(" program-with-module" , test_program_with_module), &
29
30
& new_unittest(" submodule" , test_submodule), &
@@ -238,6 +239,61 @@ subroutine test_include_stmt(error)
238
239
239
240
end subroutine test_include_stmt
240
241
242
+ ! > Try to parse a simple fortran program
243
+ subroutine test_program (error )
244
+
245
+ ! > Error handling
246
+ type (error_t), allocatable , intent (out ) :: error
247
+
248
+ integer :: unit
249
+ character (:), allocatable :: temp_file
250
+ type (srcfile_t), allocatable :: f_source
251
+
252
+ allocate (temp_file, source= get_temp_filename())
253
+
254
+ open (file= temp_file, newunit= unit)
255
+ write (unit, ' (a)' ) &
256
+ & ' program my_program' , &
257
+ & ' use module_one' , &
258
+ & ' implicit none' , &
259
+ & ' integer :: module' , &
260
+ & ' module = 1' , &
261
+ & ' module= 1' , &
262
+ & ' module =1' , &
263
+ & ' module (i) =1' , &
264
+ & ' contains' , &
265
+ & ' subroutine f()' , &
266
+ & ' end subroutine f' , &
267
+ & ' end program my_program'
268
+ close (unit)
269
+
270
+ f_source = parse_f_source(temp_file,error)
271
+ if (allocated (error)) then
272
+ return
273
+ end if
274
+
275
+ if (f_source% unit_type /= FPM_UNIT_PROGRAM) then
276
+ call test_failed(error,' Wrong unit type detected - expecting FPM_UNIT_PROGRAM' )
277
+ return
278
+ end if
279
+
280
+ if (size (f_source% modules_provided) /= 0 ) then
281
+ call test_failed(error,' Unexpected modules_provided - expecting zero' )
282
+ return
283
+ end if
284
+
285
+ if (size (f_source% modules_used) /= 1 ) then
286
+ call test_failed(error,' Incorrect number of modules_used - expecting one' )
287
+ return
288
+ end if
289
+
290
+ if (.not. (' module_one' .in . f_source% modules_used)) then
291
+ call test_failed(error,' Missing module in modules_used' )
292
+ return
293
+ end if
294
+
295
+ end subroutine test_program
296
+
241
297
242
298
! > Try to parse fortran module
243
299
subroutine test_module (error )
@@ -258,6 +314,11 @@ subroutine test_module(error)
258
314
& ' interface' , &
259
315
& ' module subroutine f()' , &
260
316
& ' end interface' , &
317
+ & ' integer :: program' , &
318
+ & ' program = 1' , &
319
+ & ' program= 1' , &
320
+ & ' program =1' , &
321
+ & ' program (i) =1' , &
261
322
& ' contains' , &
262
323
& ' module procedure f()' , &
263
324
& ' end procedure f' , &
0 commit comments