Skip to content

Commit 1d0c99e

Browse files
committed
Add: tests for new [build] table in manifest
1 parent 99da449 commit 1d0c99e

File tree

1 file changed

+146
-1
lines changed

1 file changed

+146
-1
lines changed

fpm/test/fpm_test/test_manifest.f90

Lines changed: 146 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
!> Define tests for the `fpm_manifest` modules
22
module test_manifest
3+
use fpm_filesystem, only: get_temp_filename
34
use testsuite, only : new_unittest, unittest_t, error_t, test_failed, &
45
& check_string
56
use fpm_manifest
@@ -17,10 +18,11 @@ subroutine collect_manifest(testsuite)
1718

1819
!> Collection of tests
1920
type(unittest_t), allocatable, intent(out) :: testsuite(:)
20-
21+
2122
testsuite = [ &
2223
& new_unittest("valid-manifest", test_valid_manifest), &
2324
& new_unittest("invalid-manifest", test_invalid_manifest, should_fail=.true.), &
25+
& new_unittest("default-build-configuration", test_default_build_config), &
2426
& new_unittest("default-library", test_default_library), &
2527
& new_unittest("default-executable", test_default_executable), &
2628
& new_unittest("dependency-empty", test_dependency_empty, should_fail=.true.), &
@@ -35,6 +37,9 @@ subroutine collect_manifest(testsuite)
3537
& new_unittest("executable-typeerror", test_executable_typeerror, should_fail=.true.), &
3638
& new_unittest("executable-noname", test_executable_noname, should_fail=.true.), &
3739
& new_unittest("executable-wrongkey", test_executable_wrongkey, should_fail=.true.), &
40+
& new_unittest("build-config-valid", test_build_config_valid), &
41+
& new_unittest("build-config-empty", test_build_config_empty), &
42+
& new_unittest("build-config-invalid-values", test_build_config_invalid_values, should_fail=.true.), &
3843
& new_unittest("library-empty", test_library_empty), &
3944
& new_unittest("library-wrongkey", test_library_wrongkey, should_fail=.true.), &
4045
& new_unittest("package-simple", test_package_simple), &
@@ -65,6 +70,9 @@ subroutine test_valid_manifest(error)
6570
open(file=manifest, newunit=unit)
6671
write(unit, '(a)') &
6772
& 'name = "example"', &
73+
& '[build]', &
74+
& 'auto-executables = false', &
75+
& 'auto-tests = false', &
6876
& '[dependencies.fpm]', &
6977
& 'git = "https://github.com/fortran-lang/fpm"', &
7078
& '[[executable]]', &
@@ -94,6 +102,11 @@ subroutine test_valid_manifest(error)
94102
return
95103
end if
96104

105+
if (.not.allocated(package%build_config)) then
106+
call test_failed(error, "build is not present in package data")
107+
return
108+
end if
109+
97110
if (.not.allocated(package%library)) then
98111
call test_failed(error, "library is not present in package data")
99112
return
@@ -152,6 +165,31 @@ subroutine test_invalid_manifest(error)
152165
end subroutine test_invalid_manifest
153166

154167

168+
!> Create a default build configuration
169+
subroutine test_default_build_config(error)
170+
171+
!> Error handling
172+
type(error_t), allocatable, intent(out) :: error
173+
174+
type(package_t) :: package
175+
176+
allocate(package%build_config)
177+
call default_build_config(package%build_config)
178+
179+
if (.not. package%build_config%auto_executables) then
180+
call test_failed(error,'Incorrect value for auto_executables in default build configuration, expecting .true.')
181+
return
182+
end if
183+
184+
if (.not. package%build_config%auto_tests) then
185+
call test_failed(error,'Incorrect value for auto_tests in default build configuration, expecting .true.')
186+
return
187+
end if
188+
189+
190+
end subroutine test_default_build_config
191+
192+
155193
!> Create a default library
156194
subroutine test_default_library(error)
157195

@@ -446,6 +484,113 @@ subroutine test_executable_wrongkey(error)
446484
end subroutine test_executable_wrongkey
447485

448486

487+
!> Try to read values from the [build] table
488+
subroutine test_build_config_valid(error)
489+
490+
!> Error handling
491+
type(error_t), allocatable, intent(out) :: error
492+
493+
type(package_t) :: package
494+
character(:), allocatable :: temp_file
495+
integer :: unit
496+
497+
allocate(temp_file, source=get_temp_filename())
498+
499+
open(file=temp_file, newunit=unit)
500+
write(unit, '(a)') &
501+
& 'name = "example"', &
502+
& '[build]', &
503+
& 'auto-executables = false', &
504+
& 'auto-tests = false'
505+
close(unit)
506+
507+
call get_package_data(package, temp_file, error)
508+
509+
if (allocated(error)) return
510+
511+
if (.not.allocated(package%build_config)) then
512+
call test_failed(error, "build is not present in package data")
513+
return
514+
end if
515+
516+
if (package%build_config%auto_executables) then
517+
call test_failed(error, "Wong value of 'auto-executables' read, expecting .false.")
518+
return
519+
end if
520+
521+
if (package%build_config%auto_tests) then
522+
call test_failed(error, "Wong value of 'auto-tests' read, expecting .false.")
523+
return
524+
end if
525+
526+
end subroutine test_build_config_valid
527+
528+
529+
!> Try to read values from an empty [build] table
530+
subroutine test_build_config_empty(error)
531+
532+
!> Error handling
533+
type(error_t), allocatable, intent(out) :: error
534+
535+
type(package_t) :: package
536+
character(:), allocatable :: temp_file
537+
integer :: unit
538+
539+
allocate(temp_file, source=get_temp_filename())
540+
541+
open(file=temp_file, newunit=unit)
542+
write(unit, '(a)') &
543+
& 'name = "example"', &
544+
& '[build]', &
545+
& '[library]'
546+
close(unit)
547+
548+
call get_package_data(package, temp_file, error)
549+
550+
if (allocated(error)) return
551+
552+
if (.not.allocated(package%build_config)) then
553+
call test_failed(error, "build is not present in package data")
554+
return
555+
end if
556+
557+
if (.not.package%build_config%auto_executables) then
558+
call test_failed(error, "Wong default value of 'auto-executables' read, expecting .true.")
559+
return
560+
end if
561+
562+
if (.not.package%build_config%auto_tests) then
563+
call test_failed(error, "Wong default value of 'auto-tests' read, expecting .true.")
564+
return
565+
end if
566+
567+
end subroutine test_build_config_empty
568+
569+
570+
!> Try to read values from a [build] table with invalid values
571+
subroutine test_build_config_invalid_values(error)
572+
573+
!> Error handling
574+
type(error_t), allocatable, intent(out) :: error
575+
576+
type(package_t) :: package
577+
character(:), allocatable :: temp_file
578+
integer :: unit
579+
580+
allocate(temp_file, source=get_temp_filename())
581+
582+
open(file=temp_file, newunit=unit)
583+
write(unit, '(a)') &
584+
& 'name = "example"', &
585+
& '[build]', &
586+
& 'auto-executables = "false"'
587+
close(unit)
588+
589+
call get_package_data(package, temp_file, error)
590+
591+
end subroutine test_build_config_invalid_values
592+
593+
449594
!> Libraries can be created from empty tables
450595
subroutine test_library_empty(error)
451596
use fpm_manifest_library

0 commit comments

Comments
 (0)