Skip to content

Commit

Permalink
Merge pull request #786 from fortran-lang/feat/cpp-profiles
Browse files Browse the repository at this point in the history
feat(manifest): add C++ flags in profiles
  • Loading branch information
gnikit authored Oct 31, 2022
2 parents 77cc356 + fb19001 commit 440272a
Showing 1 changed file with 28 additions and 5 deletions.
33 changes: 28 additions & 5 deletions src/fpm/manifest/profiles.f90
Original file line number Diff line number Diff line change
Expand Up @@ -33,9 +33,10 @@
!>
!> Each of the subtables currently supports the following fields:
!>```toml
!>[profile.debug.gfortran.linux]
!>[profiles.debug.gfortran.linux]
!> flags="-Wall -g -Og"
!> c-flags="-g O1"
!> cxx-flags="-g O1"
!> link-time-flags="-xlinkopt"
!> files={"hello_world.f90"="-Wall -O3"}
!>```
Expand Down Expand Up @@ -84,6 +85,9 @@ module fpm_manifest_profile
!> C compiler flags
character(len=:), allocatable :: c_flags

!> C++ compiler flags
character(len=:), allocatable :: cxx_flags

!> Link time compiler flags
character(len=:), allocatable :: link_time_flags

Expand All @@ -103,7 +107,8 @@ module fpm_manifest_profile
contains

!> Construct a new profile configuration from a TOML data structure
function new_profile(profile_name, compiler, os_type, flags, c_flags, link_time_flags, file_scope_flags, is_built_in) &
function new_profile(profile_name, compiler, os_type, flags, c_flags, cxx_flags, &
link_time_flags, file_scope_flags, is_built_in) &
& result(profile)

!> Name of the profile
Expand All @@ -121,6 +126,9 @@ function new_profile(profile_name, compiler, os_type, flags, c_flags, link_time_
!> C compiler flags
character(len=*), optional, intent(in) :: c_flags

!> C++ compiler flags
character(len=*), optional, intent(in) :: cxx_flags

!> Link time compiler flags
character(len=*), optional, intent(in) :: link_time_flags

Expand All @@ -145,6 +153,11 @@ function new_profile(profile_name, compiler, os_type, flags, c_flags, link_time_
else
profile%c_flags = ""
end if
if (present(cxx_flags)) then
profile%cxx_flags = cxx_flags
else
profile%cxx_flags = ""
end if
if (present(link_time_flags)) then
profile%link_time_flags = link_time_flags
else
Expand Down Expand Up @@ -239,7 +252,7 @@ subroutine validate_profile_table(profile_name, compiler_name, key_list, table,
!> Was called with valid operating system
logical, intent(in) :: os_valid

character(len=:), allocatable :: flags, c_flags, link_time_flags, key_name, file_name, file_flags, err_message
character(len=:), allocatable :: flags, c_flags, cxx_flags, link_time_flags, key_name, file_name, file_flags, err_message
type(toml_table), pointer :: files
type(toml_key), allocatable :: file_list(:)
integer :: ikey, ifile, stat
Expand All @@ -260,6 +273,12 @@ subroutine validate_profile_table(profile_name, compiler_name, key_list, table,
call syntax_error(error, "c-flags has to be a key-value pair")
return
end if
else if (key_name.eq.'cxx-flags') then
call get_value(table, 'cxx-flags', cxx_flags, stat=stat)
if (stat /= toml_stat%success) then
call syntax_error(error, "cxx-flags has to be a key-value pair")
return
end if
else if (key_name.eq.'link-time-flags') then
call get_value(table, 'link-time-flags', link_time_flags, stat=stat)
if (stat /= toml_stat%success) then
Expand Down Expand Up @@ -324,7 +343,7 @@ subroutine get_flags(profile_name, compiler_name, os_type, key_list, table, prof
!> Was called with valid operating system
logical, intent(in) :: os_valid

character(len=:), allocatable :: flags, c_flags, link_time_flags, key_name, file_name, file_flags, err_message
character(len=:), allocatable :: flags, c_flags, cxx_flags, link_time_flags, key_name, file_name, file_flags, err_message
type(toml_table), pointer :: files
type(toml_key), allocatable :: file_list(:)
type(file_scope_flag), allocatable :: file_scope_flags(:)
Expand All @@ -333,6 +352,7 @@ subroutine get_flags(profile_name, compiler_name, os_type, key_list, table, prof

call get_value(table, 'flags', flags)
call get_value(table, 'c-flags', c_flags)
call get_value(table, 'cxx-flags', cxx_flags)
call get_value(table, 'link-time-flags', link_time_flags)
call get_value(table, 'files', files)
if (associated(files)) then
Expand All @@ -350,7 +370,7 @@ subroutine get_flags(profile_name, compiler_name, os_type, key_list, table, prof
end if

profiles(profindex) = new_profile(profile_name, compiler_name, os_type, &
& flags, c_flags, link_time_flags, file_scope_flags)
& flags, c_flags, cxx_flags, link_time_flags, file_scope_flags)
profindex = profindex + 1
end subroutine get_flags

Expand Down Expand Up @@ -656,6 +676,8 @@ subroutine new_profiles(profiles, table, error)
& " "//profiles(iprof)%flags
profiles(profindex)%c_flags=profiles(profindex)%c_flags// &
& " "//profiles(iprof)%c_flags
profiles(profindex)%cxx_flags=profiles(profindex)%cxx_flags// &
& " "//profiles(iprof)%cxx_flags
profiles(profindex)%link_time_flags=profiles(profindex)%link_time_flags// &
& " "//profiles(iprof)%link_time_flags
end if
Expand Down Expand Up @@ -861,6 +883,7 @@ function info_profile(profile) result(s)
end select
if (allocated(profile%flags)) s = s // ', flags="' // profile%flags // '"'
if (allocated(profile%c_flags)) s = s // ', c_flags="' // profile%c_flags // '"'
if (allocated(profile%cxx_flags)) s = s // ', cxx_flags="' // profile%cxx_flags // '"'
if (allocated(profile%link_time_flags)) s = s // ', link_time_flags="' // profile%link_time_flags // '"'
if (allocated(profile%file_scope_flags)) then
do i=1,size(profile%file_scope_flags)
Expand Down

0 comments on commit 440272a

Please sign in to comment.