Skip to content

Commit 313fe32

Browse files
authored
Merge pull request #178 from LKedward/more_examples
Add more example packages
2 parents db21f13 + db67194 commit 313fe32

File tree

16 files changed

+303
-25
lines changed

16 files changed

+303
-25
lines changed

ci/run_tests.bat

Lines changed: 27 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,4 +41,31 @@ if errorlevel 1 exit 1
4141
if errorlevel 1 exit 1
4242

4343
.\build\gfortran_debug\test\farewell_test
44+
if errorlevel 1 exit 1
45+
46+
47+
cd ..\with_c
48+
if errorlevel 1 exit 1
49+
50+
..\..\..\fpm\build\gfortran_debug\app\fpm build
51+
if errorlevel 1 exit 1
52+
53+
.\build\gfortran_debug\app\with_c
54+
if errorlevel 1 exit 1
55+
56+
57+
cd ..\submodules
58+
if errorlevel 1 exit 1
59+
60+
..\..\..\fpm\build\gfortran_debug\app\fpm build
61+
if errorlevel 1 exit 1
62+
63+
64+
cd ..\program_with_module
65+
if errorlevel 1 exit 1
66+
67+
..\..\..\fpm\build\gfortran_debug\app\fpm build
68+
if errorlevel 1 exit 1
69+
70+
.\build\gfortran_debug\app\Program_with_module
4471
if errorlevel 1 exit 1

ci/run_tests.sh

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,4 +17,15 @@ cd ../hello_complex
1717
./build/gfortran_debug/app/say_Hello
1818
./build/gfortran_debug/app/say_goodbye
1919
./build/gfortran_debug/test/greet_test
20-
./build/gfortran_debug/test/farewell_test
20+
./build/gfortran_debug/test/farewell_test
21+
22+
cd ../with_c
23+
../../../fpm/build/gfortran_debug/app/fpm build
24+
./build/gfortran_debug/app/with_c
25+
26+
cd ../submodules
27+
../../../fpm/build/gfortran_debug/app/fpm build
28+
29+
cd ../program_with_module
30+
../../../fpm/build/gfortran_debug/app/fpm build
31+
./build/gfortran_debug/app/Program_with_module

fpm/src/fpm_sources.f90

Lines changed: 54 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -309,7 +309,7 @@ function parse_f_source(f_filename,error) result(f_source)
309309
if (.not.validate_name(mod_name)) then
310310
call file_parse_error(error,f_filename, &
311311
'empty or invalid name for module',i, &
312-
file_lines(i)%s)
312+
file_lines(i)%s, index(file_lines(i)%s,mod_name))
313313
return
314314
end if
315315

@@ -326,6 +326,22 @@ function parse_f_source(f_filename,error) result(f_source)
326326
! Extract name of submodule if is submodule
327327
if (index(adjustl(lower(file_lines(i)%s)),'submodule') == 1) then
328328

329+
mod_name = split_n(file_lines(i)%s,n=3,delims='()',stat=stat)
330+
if (stat /= 0) then
331+
call file_parse_error(error,f_filename, &
332+
'unable to get submodule name',i, &
333+
file_lines(i)%s)
334+
return
335+
end if
336+
if (.not.validate_name(mod_name)) then
337+
call file_parse_error(error,f_filename, &
338+
'empty or invalid name for submodule',i, &
339+
file_lines(i)%s, index(file_lines(i)%s,mod_name))
340+
return
341+
end if
342+
343+
n_mod = n_mod + 1
344+
329345
temp_string = split_n(file_lines(i)%s,n=2,delims='()',stat=stat)
330346
if (stat /= 0) then
331347
call file_parse_error(error,f_filename, &
@@ -346,22 +362,24 @@ function parse_f_source(f_filename,error) result(f_source)
346362

347363
end if
348364

349-
f_source%modules_used(n_use)%s = lower(temp_string)
350-
351365
if (.not.validate_name(temp_string)) then
352366
call file_parse_error(error,f_filename, &
353367
'empty or invalid name for submodule parent',i, &
354368
file_lines(i)%s, index(file_lines(i)%s,temp_string))
355369
return
356370
end if
357371

372+
f_source%modules_used(n_use)%s = lower(temp_string)
373+
374+
f_source%modules_provided(n_mod)%s = lower(mod_name)
375+
358376
end if
359377

360378
end if
361379

362-
! Detect if is program
363-
if (f_source%unit_type == FPM_UNIT_UNKNOWN .and. &
364-
index(adjustl(lower(file_lines(i)%s)),'program') == 1) then
380+
! Detect if contains a program
381+
! (no modules allowed after program def)
382+
if (index(adjustl(lower(file_lines(i)%s)),'program') == 1) then
365383

366384
f_source%unit_type = FPM_UNIT_PROGRAM
367385

@@ -525,7 +543,7 @@ function split_n(string,delims,n,stat) result(substring)
525543
return
526544
end if
527545

528-
substring = trim(string_parts(i))
546+
substring = trim(adjustl(string_parts(i)))
529547
stat = 0
530548

531549
end function split_n
@@ -537,22 +555,42 @@ subroutine resolve_module_dependencies(sources)
537555
!
538556
type(srcfile_t), intent(inout), target :: sources(:)
539557

540-
integer :: n_depend, i, j
558+
type(srcfile_ptr) :: dep
559+
560+
integer :: n_depend, i, pass, j
541561

542562
do i=1,size(sources)
543563

544-
n_depend = size(sources(i)%modules_used)
564+
do pass=1,2
565+
566+
n_depend = 0
567+
568+
do j=1,size(sources(i)%modules_used)
569+
570+
if (sources(i)%modules_used(j)%s .in. sources(i)%modules_provided) then
571+
! Dependency satisfied in same file, skip
572+
cycle
573+
end if
545574

546-
allocate(sources(i)%file_dependencies(n_depend))
575+
dep%ptr => find_module_dependency(sources,sources(i)%modules_used(j)%s)
576+
577+
if (.not.associated(dep%ptr)) then
578+
write(*,*) '(!) Unable to find source for module dependency: ', &
579+
sources(i)%modules_used(j)%s
580+
write(*,*) ' for file ',sources(i)%file_name
581+
! stop
582+
end if
547583

548-
do j=1,n_depend
584+
n_depend = n_depend + 1
585+
586+
if (pass == 2) then
587+
sources(i)%file_dependencies(n_depend) = dep
588+
end if
549589

550-
sources(i)%file_dependencies(j)%ptr => &
551-
find_module_dependency(sources,sources(i)%modules_used(j)%s)
590+
end do
552591

553-
if (.not.associated(sources(i)%file_dependencies(j)%ptr)) then
554-
write(*,*) '(!) Unable to find source for module dependency: ',sources(i)%modules_used(j)%s
555-
! stop
592+
if (pass == 1) then
593+
allocate(sources(i)%file_dependencies(n_depend))
556594
end if
557595

558596
end do

fpm/test/test_source_parsing.f90

Lines changed: 82 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@ subroutine collect_source_parsing(testsuite)
2525
& new_unittest("intrinsic-modules-used", test_intrinsic_modules_used), &
2626
& new_unittest("include-stmt", test_include_stmt), &
2727
& new_unittest("module", test_module), &
28+
& new_unittest("program-with-module", test_program_with_module), &
2829
& new_unittest("submodule", test_submodule), &
2930
& new_unittest("submodule-ancestor", test_submodule_ancestor), &
3031
& new_unittest("subprogram", test_subprogram), &
@@ -258,7 +259,7 @@ subroutine test_module(error)
258259
& 'contains', &
259260
& 'module procedure f()', &
260261
& 'end procedure f', &
261-
& 'end submodule test'
262+
& 'end module test'
262263
close(unit)
263264

264265
f_source = parse_f_source(temp_file,error)
@@ -287,13 +288,76 @@ subroutine test_module(error)
287288
end if
288289

289290
if (.not.('module_one' .in. f_source%modules_used)) then
290-
call test_failed(error,'Missing parent module in modules_used')
291+
call test_failed(error,'Missing module in modules_used')
291292
return
292293
end if
293294

294295
end subroutine test_module
295296

296297

298+
!> Try to parse combined fortran module and program
299+
!> Check that parsed unit type is FPM_UNIT_PROGRAM
300+
subroutine test_program_with_module(error)
301+
302+
!> Error handling
303+
type(error_t), allocatable, intent(out) :: error
304+
305+
integer :: unit
306+
character(:), allocatable :: temp_file
307+
type(srcfile_t), allocatable :: f_source
308+
309+
allocate(temp_file, source=get_temp_filename())
310+
311+
open(file=temp_file, newunit=unit)
312+
write(unit, '(a)') &
313+
& 'module my_mod', &
314+
& 'use module_one', &
315+
& 'interface', &
316+
& ' module subroutine f()', &
317+
& 'end interface', &
318+
& 'contains', &
319+
& 'module procedure f()', &
320+
& 'end procedure f', &
321+
& 'end module test', &
322+
& 'program my_program', &
323+
& 'use my_mod', &
324+
& 'implicit none', &
325+
& 'end my_program'
326+
close(unit)
327+
328+
f_source = parse_f_source(temp_file,error)
329+
if (allocated(error)) then
330+
return
331+
end if
332+
333+
if (f_source%unit_type /= FPM_UNIT_PROGRAM) then
334+
call test_failed(error,'Wrong unit type detected - expecting FPM_UNIT_PROGRAM')
335+
return
336+
end if
337+
338+
if (size(f_source%modules_provided) /= 1) then
339+
call test_failed(error,'Unexpected modules_provided - expecting one')
340+
return
341+
end if
342+
343+
if (.not.('my_mod' .in. f_source%modules_provided)) then
344+
call test_failed(error,'Missing module in modules_provided')
345+
return
346+
end if
347+
348+
if (.not.('module_one' .in. f_source%modules_used)) then
349+
call test_failed(error,'Missing module in modules_used')
350+
return
351+
end if
352+
353+
if (.not.('my_mod' .in. f_source%modules_used)) then
354+
call test_failed(error,'Missing module in modules_used')
355+
return
356+
end if
357+
358+
end subroutine test_program_with_module
359+
360+
297361
!> Try to parse fortran submodule for ancestry
298362
subroutine test_submodule(error)
299363

@@ -308,7 +372,7 @@ subroutine test_submodule(error)
308372

309373
open(file=temp_file, newunit=unit)
310374
write(unit, '(a)') &
311-
& 'submodule (parent) :: child', &
375+
& 'submodule (parent) child', &
312376
& 'use module_one', &
313377
& 'end submodule test'
314378
close(unit)
@@ -323,8 +387,8 @@ subroutine test_submodule(error)
323387
return
324388
end if
325389

326-
if (size(f_source%modules_provided) /= 0) then
327-
call test_failed(error,'Unexpected modules_provided - expecting zero')
390+
if (size(f_source%modules_provided) /= 1) then
391+
call test_failed(error,'Unexpected modules_provided - expecting one')
328392
return
329393
end if
330394

@@ -333,6 +397,11 @@ subroutine test_submodule(error)
333397
return
334398
end if
335399

400+
if (.not.('child' .in. f_source%modules_provided)) then
401+
call test_failed(error,'Missing module in modules_provided')
402+
return
403+
end if
404+
336405
if (.not.('module_one' .in. f_source%modules_used)) then
337406
call test_failed(error,'Missing module in modules_used')
338407
return
@@ -360,7 +429,7 @@ subroutine test_submodule_ancestor(error)
360429

361430
open(file=temp_file, newunit=unit)
362431
write(unit, '(a)') &
363-
& 'submodule (ancestor:parent) :: child', &
432+
& 'submodule (ancestor:parent) child', &
364433
& 'use module_one', &
365434
& 'end submodule test'
366435
close(unit)
@@ -375,8 +444,8 @@ subroutine test_submodule_ancestor(error)
375444
return
376445
end if
377446

378-
if (size(f_source%modules_provided) /= 0) then
379-
call test_failed(error,'Unexpected modules_provided - expecting zero')
447+
if (size(f_source%modules_provided) /= 1) then
448+
call test_failed(error,'Unexpected modules_provided - expecting one')
380449
return
381450
end if
382451

@@ -385,6 +454,11 @@ subroutine test_submodule_ancestor(error)
385454
return
386455
end if
387456

457+
if (.not.('child' .in. f_source%modules_provided)) then
458+
call test_failed(error,'Missing module in modules_provided')
459+
return
460+
end if
461+
388462
if (.not.('module_one' .in. f_source%modules_used)) then
389463
call test_failed(error,'Missing module in modules_used')
390464
return

test/example_packages/README.md

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
# Example packages
2+
3+
See the table below for a list of the example packages provided in this directory including
4+
the features demonstrated in each package and which versions of fpm are supported.
5+
6+
7+
| Name | Features | Bootstrap (Haskell) fpm | fpm |
8+
|---------------------|---------------------------------------------------------------|:-----------------------:|:---:|
9+
| circular_example | Local path dependency; circular dependency | Y | N |
10+
| circular_test | Local path dependency; circular dependency | Y | N |
11+
| hello_complex | Non-standard directory layout; multiple tests and executables | Y | Y |
12+
| hello_fpm | App-only; local path dependency | Y | N |
13+
| hello_world | App-only | Y | Y |
14+
| makefile_complex | External build command (makefile); local path dependency | Y | N |
15+
| program_with_module | App-only; module+program in single source file | Y | Y |
16+
| submodules | Lib-only; submodules (3 levels) | N | Y |
17+
| with_c | Compile with `c` source files | N | Y |
18+
| with_makefile | External build command (makefile) | Y | N |
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
module greet_m
2+
implicit none
3+
character(*), parameter :: greeting = 'Hello, fpm!'
4+
end module greet_m
5+
6+
program program_with_module
7+
use greet_m, only: greeting
8+
implicit none
9+
print *, greeting
10+
end program program_with_module
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
name = "Program_with_module"
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
name = "submodules"
Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
submodule(parent) child1
2+
implicit none
3+
4+
interface
5+
module function my_fun() result (b)
6+
integer :: b
7+
end function my_fun
8+
end interface
9+
10+
contains
11+
12+
module procedure my_sub1
13+
a = 1
14+
end procedure my_sub1
15+
16+
end submodule child1
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
submodule(parent) child2
2+
implicit none
3+
4+
contains
5+
6+
module procedure my_sub2
7+
a = 2
8+
end procedure my_sub2
9+
10+
end submodule child2

0 commit comments

Comments
 (0)