Skip to content

Commit fb9153f

Browse files
committed
add several tests
1 parent 6f14446 commit fb9153f

File tree

1 file changed

+366
-2
lines changed

1 file changed

+366
-2
lines changed

test/fpm_test/test_features.f90

Lines changed: 366 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ module test_features
66
use fpm_manifest_feature_collection, only: feature_collection_t
77
use fpm_manifest_platform, only: platform_config_t
88
use fpm_environment, only: OS_ALL, OS_LINUX, OS_MACOS, OS_WINDOWS
9-
use fpm_compiler, only: id_all, id_gcc, id_intel_classic_nix, id_intel_classic_windows, match_compiler_type
9+
use fpm_compiler, only: id_all, id_gcc, id_intel_classic_nix, id_intel_classic_windows, id_intel_llvm_nix, match_compiler_type
1010
use fpm_strings, only: string_t
1111
use fpm_filesystem, only: get_temp_filename
1212
implicit none
@@ -33,7 +33,11 @@ subroutine collect_features(testsuite)
3333
& new_unittest("feature-flag-addition", test_feature_flag_addition), &
3434
& new_unittest("feature-metapackage-addition", test_feature_metapackage_addition), &
3535
& new_unittest("feature-extract-gfortran-linux", test_feature_extract_gfortran_linux), &
36-
& new_unittest("feature-extract-ifort-windows", test_feature_extract_ifort_windows) &
36+
& new_unittest("feature-extract-ifort-windows", test_feature_extract_ifort_windows), &
37+
& new_unittest("feature-extract-dependencies-examples", test_feature_extract_dependencies_examples), &
38+
& new_unittest("feature-extract-build-configs", test_feature_extract_build_configs), &
39+
& new_unittest("feature-extract-test-configs", test_feature_extract_test_configs), &
40+
& new_unittest("feature-extract-example-configs", test_feature_extract_example_configs) &
3741
& ]
3842

3943
end subroutine collect_features
@@ -728,4 +732,364 @@ subroutine test_feature_extract_ifort_windows(error)
728732

729733
end subroutine test_feature_extract_ifort_windows
730734

735+
!> Test feature extraction with dependencies and examples for gfortran+macOS target
736+
subroutine test_feature_extract_dependencies_examples(error)
737+
!> Error handling
738+
type(error_t), allocatable, intent(out) :: error
739+
740+
type(package_config_t) :: package
741+
character(:), allocatable :: temp_file
742+
integer :: unit
743+
type(feature_config_t) :: extracted_feature
744+
type(platform_config_t) :: target_platform
745+
integer :: i, j
746+
logical :: has_gfortran_dep, has_macos_dep
747+
748+
allocate(temp_file, source=get_temp_filename())
749+
750+
open(file=temp_file, newunit=unit)
751+
write(unit, '(a)') &
752+
& 'name = "deps-test"', &
753+
& 'version = "0.1.0"', &
754+
& '[features]', &
755+
& '[features.testing.dependencies]', &
756+
& 'base_dep.git = "https://github.com/example/base"', &
757+
& '[features.testing.gfortran.dependencies]', &
758+
& 'gfortran_dep.git = "https://github.com/example/gfortran"', &
759+
& '[features.testing.macos.dependencies]', &
760+
& 'macos_dep.git = "https://github.com/example/macos"', &
761+
& '[[features.testing.example]]', &
762+
& 'name = "base_example"', &
763+
& 'source-dir = "example"', &
764+
& '[[features.testing.gfortran.example]]', &
765+
& 'name = "gfortran_example"', &
766+
& 'source-dir = "example/gfortran"', &
767+
& '[[features.testing.macos.example]]', &
768+
& 'name = "macos_example"', &
769+
& 'source-dir = "example/macos"', &
770+
& '[features.testing.macos.fortran]', &
771+
& 'implicit-typing = false'
772+
close(unit)
773+
774+
call get_package_data(package, temp_file, error)
775+
if (allocated(error)) return
776+
777+
! Find testing collection and extract for gfortran+macOS
778+
do i = 1, size(package%features)
779+
if (package%features(i)%base%name == "testing") then
780+
target_platform = platform_config_t(id_gcc, OS_MACOS)
781+
extracted_feature = package%features(i)%extract_for_target(target_platform)
782+
783+
! Check that all dependencies are combined (base + gfortran + macos)
784+
if (.not. allocated(extracted_feature%dependency)) then
785+
call test_failed(error, "Missing dependencies in gfortran+macOS extraction")
786+
return
787+
end if
788+
789+
! Verify that specific dependencies are present by checking names
790+
has_gfortran_dep = .false.
791+
has_macos_dep = .false.
792+
793+
do j = 1, size(extracted_feature%dependency)
794+
if (extracted_feature%dependency(j)%name == "gfortran_dep") then
795+
has_gfortran_dep = .true.
796+
end if
797+
if (extracted_feature%dependency(j)%name == "macos_dep") then
798+
has_macos_dep = .true.
799+
end if
800+
end do
801+
802+
if (.not. has_gfortran_dep) then
803+
call test_failed(error, "Missing gfortran_dep dependency in gfortran+macOS extraction")
804+
return
805+
end if
806+
if (.not. has_macos_dep) then
807+
call test_failed(error, "Missing macos_dep dependency in gfortran+macOS extraction")
808+
return
809+
end if
810+
811+
! Check that all examples are combined (base + gfortran + macos)
812+
if (.not. allocated(extracted_feature%example) .or. size(extracted_feature%example) < 3) then
813+
call test_failed(error, "Wrong number of examples in gfortran+macOS (expected 3)")
814+
return
815+
end if
816+
817+
! Check that fortran config is set (only macOS variant has it)
818+
if (.not. allocated(extracted_feature%fortran)) then
819+
call test_failed(error, "Missing fortran config in gfortran+macOS extraction")
820+
return
821+
end if
822+
823+
if (extracted_feature%fortran%implicit_typing) then
824+
call test_failed(error, "Fortran config not applied correctly - implicit typing should be false")
825+
return
826+
end if
827+
828+
return ! Test passed
829+
end if
830+
end do
831+
832+
call test_failed(error, "testing collection not found")
833+
834+
end subroutine test_feature_extract_dependencies_examples
835+
836+
!> Test feature extraction with build configurations for ifort+Linux target
837+
subroutine test_feature_extract_build_configs(error)
838+
!> Error handling
839+
type(error_t), allocatable, intent(out) :: error
840+
841+
type(package_config_t) :: package
842+
character(:), allocatable :: temp_file
843+
integer :: unit
844+
type(feature_config_t) :: extracted_feature
845+
type(platform_config_t) :: target_platform
846+
integer :: i
847+
848+
allocate(temp_file, source=get_temp_filename())
849+
850+
open(file=temp_file, newunit=unit)
851+
write(unit, '(a)') &
852+
& 'name = "build-test"', &
853+
& 'version = "0.1.0"', &
854+
& '[features]', &
855+
& '[features.optimization.ifort.linux.build]', &
856+
& 'auto-executables = false', &
857+
& 'auto-tests = false', &
858+
& 'link = ["mylib"]', &
859+
& 'external-modules = ["external_mod"]'
860+
close(unit)
861+
862+
call get_package_data(package, temp_file, error)
863+
if (allocated(error)) return
864+
865+
! Find optimization collection and extract for ifort+Linux
866+
do i = 1, size(package%features)
867+
if (package%features(i)%base%name == "optimization") then
868+
target_platform = platform_config_t(id_intel_classic_nix, OS_LINUX)
869+
extracted_feature = package%features(i)%extract_for_target(target_platform)
870+
871+
! Check that build config is present
872+
if (.not. allocated(extracted_feature%build)) then
873+
call test_failed(error, "Missing build config in ifort+Linux extraction")
874+
return
875+
end if
876+
877+
! Check that auto-executables is set correctly
878+
if (extracted_feature%build%auto_executables) then
879+
call test_failed(error, "Build config auto-executables should be false")
880+
return
881+
end if
882+
883+
! Check that auto-tests is set correctly
884+
if (extracted_feature%build%auto_tests) then
885+
call test_failed(error, "Build config auto-tests should be false")
886+
return
887+
end if
888+
889+
! Check that link libraries are present
890+
if (.not. allocated(extracted_feature%build%link) .or. size(extracted_feature%build%link) < 1) then
891+
call test_failed(error, "Missing link libraries in ifort+Linux build config")
892+
return
893+
end if
894+
895+
! Check that external modules are present
896+
if (.not. allocated(extracted_feature%build%external_modules) .or. size(extracted_feature%build%external_modules) < 1) then
897+
call test_failed(error, "Missing external modules in ifort+Linux build config")
898+
return
899+
end if
900+
901+
return ! Test passed
902+
end if
903+
end do
904+
905+
call test_failed(error, "optimization collection not found")
906+
907+
end subroutine test_feature_extract_build_configs
908+
909+
!> Test feature extraction with test configurations for gfortran+Windows target
910+
subroutine test_feature_extract_test_configs(error)
911+
!> Error handling
912+
type(error_t), allocatable, intent(out) :: error
913+
914+
type(package_config_t) :: package
915+
character(:), allocatable :: temp_file
916+
integer :: unit
917+
type(feature_config_t) :: extracted_feature
918+
type(platform_config_t) :: target_platform
919+
integer :: i, j
920+
logical :: has_base, has_gfortran, has_windows, has_specific
921+
922+
allocate(temp_file, source=get_temp_filename())
923+
924+
open(file=temp_file, newunit=unit)
925+
write(unit, '(a)') &
926+
& 'name = "test-configs"', &
927+
& 'version = "0.1.0"', &
928+
& '[features]', &
929+
& '[[features.testing.test]]', &
930+
& 'name = "base_test"', &
931+
& 'source-dir = "test"', &
932+
& '[[features.testing.gfortran.test]]', &
933+
& 'name = "gfortran_test"', &
934+
& 'source-dir = "test/gfortran"', &
935+
& '[[features.testing.windows.test]]', &
936+
& 'name = "windows_test"', &
937+
& 'source-dir = "test/windows"', &
938+
& '[[features.testing.gfortran.windows.test]]', &
939+
& 'name = "gfortran_windows_test"', &
940+
& 'source-dir = "test/gfortran_windows"'
941+
close(unit)
942+
943+
call get_package_data(package, temp_file, error)
944+
if (allocated(error)) return
945+
946+
! Find testing collection and extract for gfortran+Windows
947+
do i = 1, size(package%features)
948+
if (package%features(i)%base%name == "testing") then
949+
target_platform = platform_config_t(id_gcc, OS_WINDOWS)
950+
extracted_feature = package%features(i)%extract_for_target(target_platform)
951+
952+
! Check that all test configs are combined (base + gfortran + windows + gfortran.windows)
953+
if (.not. allocated(extracted_feature%test) .or. size(extracted_feature%test) < 4) then
954+
call test_failed(error, "Wrong number of test configs in gfortran+Windows (expected 4)")
955+
return
956+
end if
957+
958+
! Verify that specific test configs are present by checking names
959+
has_base = .false.
960+
has_gfortran = .false.
961+
has_windows = .false.
962+
has_specific = .false.
963+
964+
do j = 1, size(extracted_feature%test)
965+
select case (extracted_feature%test(j)%name)
966+
case ("base_test")
967+
has_base = .true.
968+
case ("gfortran_test")
969+
has_gfortran = .true.
970+
case ("windows_test")
971+
has_windows = .true.
972+
case ("gfortran_windows_test")
973+
has_specific = .true.
974+
end select
975+
end do
976+
977+
if (.not. has_base) then
978+
call test_failed(error, "Missing base_test in gfortran+Windows extraction")
979+
return
980+
end if
981+
if (.not. has_gfortran) then
982+
call test_failed(error, "Missing gfortran_test in gfortran+Windows extraction")
983+
return
984+
end if
985+
if (.not. has_windows) then
986+
call test_failed(error, "Missing windows_test in gfortran+Windows extraction")
987+
return
988+
end if
989+
if (.not. has_specific) then
990+
call test_failed(error, "Missing gfortran_windows_test in gfortran+Windows extraction")
991+
return
992+
end if
993+
994+
return ! Test passed
995+
end if
996+
end do
997+
998+
call test_failed(error, "testing collection not found")
999+
1000+
end subroutine test_feature_extract_test_configs
1001+
1002+
!> Test feature extraction with example configurations for ifx+macOS target
1003+
subroutine test_feature_extract_example_configs(error)
1004+
!> Error handling
1005+
type(error_t), allocatable, intent(out) :: error
1006+
1007+
type(package_config_t) :: package
1008+
character(:), allocatable :: temp_file
1009+
integer :: unit
1010+
type(feature_config_t) :: extracted_feature
1011+
type(platform_config_t) :: target_platform
1012+
integer :: i, j
1013+
logical :: has_base, has_ifx, has_macos, has_specific
1014+
1015+
allocate(temp_file, source=get_temp_filename())
1016+
1017+
open(file=temp_file, newunit=unit)
1018+
write(unit, '(a)') &
1019+
& 'name = "example-configs"', &
1020+
& 'version = "0.1.0"', &
1021+
& '[features]', &
1022+
& '[[features.showcase.example]]', &
1023+
& 'name = "base_example"', &
1024+
& 'source-dir = "examples"', &
1025+
& '[[features.showcase.ifx.example]]', &
1026+
& 'name = "ifx_example"', &
1027+
& 'source-dir = "examples/ifx"', &
1028+
& '[[features.showcase.macos.example]]', &
1029+
& 'name = "macos_example"', &
1030+
& 'source-dir = "examples/macos"', &
1031+
& '[[features.showcase.ifx.macos.example]]', &
1032+
& 'name = "ifx_macos_example"', &
1033+
& 'source-dir = "examples/ifx_macos"'
1034+
close(unit)
1035+
1036+
call get_package_data(package, temp_file, error)
1037+
if (allocated(error)) return
1038+
1039+
! Find showcase collection and extract for ifx+macOS
1040+
do i = 1, size(package%features)
1041+
if (package%features(i)%base%name == "showcase") then
1042+
target_platform = platform_config_t(id_intel_llvm_nix, OS_MACOS)
1043+
extracted_feature = package%features(i)%extract_for_target(target_platform)
1044+
1045+
! Check that all example configs are combined (base + ifx + macos + ifx.macos)
1046+
if (.not. allocated(extracted_feature%example) .or. size(extracted_feature%example) < 4) then
1047+
call test_failed(error, "Wrong number of example configs in ifx+macOS (expected 4)")
1048+
return
1049+
end if
1050+
1051+
! Verify that specific example configs are present by checking names
1052+
has_base = .false.
1053+
has_ifx = .false.
1054+
has_macos = .false.
1055+
has_specific = .false.
1056+
1057+
do j = 1, size(extracted_feature%example)
1058+
select case (extracted_feature%example(j)%name)
1059+
case ("base_example")
1060+
has_base = .true.
1061+
case ("ifx_example")
1062+
has_ifx = .true.
1063+
case ("macos_example")
1064+
has_macos = .true.
1065+
case ("ifx_macos_example")
1066+
has_specific = .true.
1067+
end select
1068+
end do
1069+
1070+
if (.not. has_base) then
1071+
call test_failed(error, "Missing base_example in ifx+macOS extraction")
1072+
return
1073+
end if
1074+
if (.not. has_ifx) then
1075+
call test_failed(error, "Missing ifx_example in ifx+macOS extraction")
1076+
return
1077+
end if
1078+
if (.not. has_macos) then
1079+
call test_failed(error, "Missing macos_example in ifx+macOS extraction")
1080+
return
1081+
end if
1082+
if (.not. has_specific) then
1083+
call test_failed(error, "Missing ifx_macos_example in ifx+macOS extraction")
1084+
return
1085+
end if
1086+
1087+
return ! Test passed
1088+
end if
1089+
end do
1090+
1091+
call test_failed(error, "showcase collection not found")
1092+
1093+
end subroutine test_feature_extract_example_configs
1094+
7311095
end module test_features

0 commit comments

Comments
 (0)