@@ -480,7 +480,6 @@ subroutine dump_to_toml(self, table, error)
480480 end do
481481 end if
482482
483- 1 format (' UNNAMED_' ,a,' _' ,i0)
484483 2 format (' PROFILE_' ,i0)
485484
486485 end subroutine dump_to_toml
@@ -560,20 +559,23 @@ subroutine load_from_toml(self, table, error)
560559 end subroutine load_from_toml
561560
562561 ! > Export package configuration for a given (OS+compiler) platform
563- type (package_config_t) function export_config(self, platform, features, profile, error) result(cfg)
564-
565- ! > Instance of the package configuration
562+ type (package_config_t) function export_config(self, platform, features, profile, verbose, error) result(cfg)
563+
564+ ! > Instance of the package configuration
566565 class(package_config_t), intent (in ), target :: self
567-
566+
568567 ! > Target platform
569568 type (platform_config_t), intent (in ) :: platform
570-
569+
571570 ! > Optional list of features to apply (cannot be used with profile)
572571 type (string_t), optional , intent (in ), target :: features(:)
573-
572+
574573 ! > Optional profile name to apply (cannot be used with features)
575574 character (len=* ), optional , intent (in ) :: profile
576-
575+
576+ ! > Verbose output flag
577+ logical , optional , intent (in ) :: verbose
578+
577579 ! > Error handling
578580 type (error_t), allocatable , intent (out ) :: error
579581
@@ -604,21 +606,28 @@ type(package_config_t) function export_config(self, platform, features, profile,
604606 nullify(want_features)
605607 endif
606608
607- apply_features: if (associated (want_features)) then
609+ apply_features: if (associated (want_features)) then
608610 do i= 1 ,size (want_features)
609-
611+
610612 ! Find feature
611613 idx = self% find_feature(want_features(i)% s)
612- if (idx<= 0 ) then
614+ if (idx<= 0 ) then
613615 call fatal_error(error, " Cannot find feature " // want_features(i)% s// &
614616 " in package " // self% name)
615617 return
616618 end if
617-
619+
620+ ! Print feature collection info if verbose
621+ if (present (verbose)) then
622+ if (verbose) then
623+ call print_feature_collection(self% features(idx), platform)
624+ end if
625+ end if
626+
618627 ! Add it to the current configuration
619628 call self% features(idx)% merge_into_package(cfg, platform, error)
620629 if (allocated (error)) return
621-
630+
622631 end do
623632 end if apply_features
624633
@@ -752,20 +761,96 @@ subroutine validate_profiles(self, error)
752761 end subroutine validate_profiles
753762
754763 ! > Check if there is a CPP preprocessor configuration
755- elemental logical function has_cpp(self)
764+ elemental logical function has_cpp(self)
756765 class(package_config_t), intent (in ) :: self
757-
766+
758767 integer :: i
759-
768+
760769 has_cpp = self% feature_config_t% has_cpp()
761770 if (has_cpp) return
762771 if (.not. allocated (self% features)) return
763-
772+
764773 do i= 1 ,size (self% features)
765774 has_cpp = self% features(i)% has_cpp()
766775 if (has_cpp) return
767776 end do
768-
777+
769778 end function has_cpp
770779
780+ ! > Print feature collection information in verbose mode
781+ subroutine print_feature_collection (collection , platform )
782+ use , intrinsic :: iso_fortran_env, only: stdout = > output_unit
783+ use fpm_compiler, only: compiler_name
784+ use fpm_environment, only: os_name
785+ use fpm_strings, only: string_cat
786+ type (feature_collection_t), intent (in ) :: collection
787+ type (platform_config_t), intent (in ) :: platform
788+
789+ type (feature_config_t) :: extracted
790+ type (error_t), allocatable :: error_tmp
791+ integer :: i, j, n_macros
792+
793+ ! Extract the feature configuration for the target platform
794+ extracted = collection% extract_for_target(platform, error_tmp)
795+ if (allocated (error_tmp)) return
796+
797+ ! Print header with feature name
798+ if (allocated (extracted% name)) then
799+ print * , ' + feature collection: ' , trim (extracted% name)
800+ end if
801+
802+ ! Print platform information
803+ print * , ' + platform: ' , platform% compiler_name(), ' on ' , platform% os_name()
804+
805+ ! Print flags
806+ if (allocated (extracted% flags)) then
807+ print * , ' + flags: ' , trim (extracted% flags)
808+ end if
809+ if (allocated (extracted% c_flags)) then
810+ print * , ' + c-flags: ' , trim (extracted% c_flags)
811+ end if
812+ if (allocated (extracted% cxx_flags)) then
813+ print * , ' + cxx-flags: ' , trim (extracted% cxx_flags)
814+ end if
815+ if (allocated (extracted% link_time_flags)) then
816+ print * , ' + link-flags: ' , trim (extracted% link_time_flags)
817+ end if
818+
819+ ! Print preprocessor macros
820+ if (allocated (extracted% preprocess)) then
821+ n_macros = 0
822+ do i = 1 , size (extracted% preprocess)
823+ if (allocated (extracted% preprocess(i)% macros)) then
824+ n_macros = n_macros + size (extracted% preprocess(i)% macros)
825+ end if
826+ end do
827+
828+ if (n_macros > 0 ) then
829+ print * , ' + cpp-macros: yes (' , n_macros, ' defined)'
830+ do i = 1 , size (extracted% preprocess)
831+ if (allocated (extracted% preprocess(i)% macros)) then
832+ do j = 1 , size (extracted% preprocess(i)% macros)
833+ print * , ' + - ' , trim (extracted% preprocess(i)% macros(j)% s)
834+ end do
835+ end if
836+ end do
837+ else
838+ print * , ' + cpp-macros: no'
839+ end if
840+ else
841+ print * , ' + cpp-macros: no'
842+ end if
843+
844+ ! Print description if available
845+ if (allocated (extracted% description)) then
846+ print * , ' + description: ' , trim (extracted% description)
847+ end if
848+
849+ ! Print number of variants in collection
850+ if (allocated (collection% variants)) then
851+ print * , ' + variants: ' , size (collection% variants)
852+ end if
853+
854+ end subroutine print_feature_collection
855+
771856end module fpm_manifest_package
0 commit comments