Skip to content

Commit 54f1231

Browse files
committed
serialize profile_config_t, test, bugfix OS check
1 parent a7cb2a0 commit 54f1231

File tree

2 files changed

+96
-7
lines changed

2 files changed

+96
-7
lines changed

src/fpm/manifest/profiles.f90

Lines changed: 80 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -85,7 +85,7 @@ module fpm_manifest_profile
8585
character(len=:), allocatable :: compiler
8686

8787
!> Value repesenting OS
88-
integer :: os_type
88+
integer :: os_type = OS_ALL
8989

9090
!> Fortran compiler flags
9191
character(len=:), allocatable :: flags
@@ -103,7 +103,7 @@ module fpm_manifest_profile
103103
type(file_scope_flag), allocatable :: file_scope_flags(:)
104104

105105
!> Is this profile one of the built-in ones?
106-
logical :: is_built_in
106+
logical :: is_built_in = .false.
107107

108108
contains
109109

@@ -234,7 +234,8 @@ subroutine match_os_type(os_name, os_type)
234234

235235
select case (os_name)
236236
case ("linux"); os_type = OS_LINUX
237-
case ("macos"); os_type = OS_WINDOWS
237+
case ("macos"); os_type = OS_MACOS
238+
case ("windows"); os_type = OS_WINDOWS
238239
case ("cygwin"); os_type = OS_CYGWIN
239240
case ("solaris"); os_type = OS_SOLARIS
240241
case ("freebsd"); os_type = OS_FREEBSD
@@ -245,6 +246,22 @@ subroutine match_os_type(os_name, os_type)
245246

246247
end subroutine match_os_type
247248

249+
!> Match lowercase string with name of OS to os_type enum
250+
function os_type_name(os_type)
251+
252+
!> Name of operating system
253+
character(len=:), allocatable :: os_type_name
254+
255+
!> Enum representing type of OS
256+
integer, intent(in) :: os_type
257+
258+
select case (os_type)
259+
case (OS_ALL); os_type_name = "all"
260+
case default; os_type_name = lower(OS_NAME(os_type))
261+
end select
262+
263+
end function os_type_name
264+
248265
subroutine validate_profile_table(profile_name, compiler_name, key_list, table, error, os_valid)
249266

250267
!> Name of profile
@@ -849,7 +866,7 @@ subroutine info(self, unit, verbosity)
849866
write(unit, fmt) "- compiler", self%compiler
850867
end if
851868

852-
write(unit, fmt) "- os", self%os_type
869+
write(unit, fmt) "- os", os_type_name(self%os_type)
853870

854871
if (allocated(self%flags)) then
855872
write(unit, fmt) "- compiler flags", self%flags
@@ -1042,40 +1059,51 @@ logical function profile_same(this,that)
10421059

10431060
select type (other=>that)
10441061
type is (profile_config_t)
1062+
print *, 'check name'
10451063
if (allocated(this%profile_name).neqv.allocated(other%profile_name)) return
10461064
if (allocated(this%profile_name)) then
10471065
if (.not.(this%profile_name==other%profile_name)) return
10481066
endif
1067+
print *, 'check compiler'
10491068
if (allocated(this%compiler).neqv.allocated(other%compiler)) return
10501069
if (allocated(this%compiler)) then
10511070
if (.not.(this%compiler==other%compiler)) return
10521071
endif
1072+
print *, 'check os'
10531073
if (this%os_type/=other%os_type) return
1074+
print *, 'check flags'
10541075
if (allocated(this%flags).neqv.allocated(other%flags)) return
10551076
if (allocated(this%flags)) then
10561077
if (.not.(this%flags==other%flags)) return
10571078
endif
1079+
print *, 'check cflags'
10581080
if (allocated(this%c_flags).neqv.allocated(other%c_flags)) return
10591081
if (allocated(this%c_flags)) then
10601082
if (.not.(this%c_flags==other%c_flags)) return
10611083
endif
1084+
print *, 'check cxxflags'
10621085
if (allocated(this%cxx_flags).neqv.allocated(other%cxx_flags)) return
10631086
if (allocated(this%cxx_flags)) then
10641087
if (.not.(this%cxx_flags==other%cxx_flags)) return
10651088
endif
1089+
print *, 'check link'
10661090
if (allocated(this%link_time_flags).neqv.allocated(other%link_time_flags)) return
10671091
if (allocated(this%link_time_flags)) then
10681092
if (.not.(this%link_time_flags==other%link_time_flags)) return
10691093
endif
10701094

1095+
print *, 'check file scope'
1096+
10711097
if (allocated(this%file_scope_flags).neqv.allocated(other%file_scope_flags)) return
10721098
if (allocated(this%file_scope_flags)) then
10731099
if (.not.size(this%file_scope_flags)==size(other%file_scope_flags)) return
10741100
do ii=1,size(this%file_scope_flags)
1101+
print *, 'check ii-th file scope: ',ii
10751102
if (.not.this%file_scope_flags(ii)==other%file_scope_flags(ii)) return
10761103
end do
10771104
endif
10781105

1106+
print *, 'check builtin'
10791107
if (this%is_built_in.neqv.other%is_built_in) return
10801108

10811109
class default
@@ -1109,7 +1137,8 @@ subroutine profile_dump(self, table, error)
11091137
if (allocated(error)) return
11101138
call set_string(table, "compiler", self%compiler, error)
11111139
if (allocated(error)) return
1112-
call set_string(table,"os-type",OS_NAME(self%os_type), error, 'profile_config_t')
1140+
print *, 'save os-type = ',os_type_name(self%os_type)
1141+
call set_string(table,"os-type",os_type_name(self%os_type), error, 'profile_config_t')
11131142
if (allocated(error)) return
11141143
call set_string(table, "flags", self%flags, error)
11151144
if (allocated(error)) return
@@ -1169,8 +1198,52 @@ subroutine profile_load(self, table, error)
11691198
!> Error handling
11701199
type(error_t), allocatable, intent(out) :: error
11711200

1172-
! call get_value(table, "file-name", self%profile_name)
1173-
! call get_value(table, "flags", self%flags)
1201+
!> Local variables
1202+
character(len=:), allocatable :: flag
1203+
integer :: ii, jj
1204+
type(toml_table), pointer :: ptr_dep, ptr
1205+
type(toml_key), allocatable :: keys(:),dep_keys(:)
1206+
1207+
call table%get_keys(keys)
1208+
1209+
call get_value(table, "profile-name", self%profile_name)
1210+
call get_value(table, "compiler", self%compiler)
1211+
call get_value(table,"os-type",flag)
1212+
print *, 'OS flag = ',flag
1213+
call match_os_type(flag, self%os_type)
1214+
call get_value(table, "flags", self%flags)
1215+
call get_value(table, "c-flags", self%c_flags)
1216+
call get_value(table, "cxx-flags", self%cxx_flags)
1217+
call get_value(table, "link-time-flags", self%link_time_flags)
1218+
call get_value(table, "is-built-in", self%is_built_in, error, 'profile_config_t')
1219+
if (allocated(error)) return
1220+
1221+
if (allocated(self%file_scope_flags)) deallocate(self%file_scope_flags)
1222+
sub_deps: do ii = 1, size(keys)
1223+
1224+
select case (keys(ii)%key)
1225+
case ("file-scope-flags")
1226+
1227+
call get_value(table, keys(ii), ptr)
1228+
if (.not.associated(ptr)) then
1229+
call fatal_error(error,'profile_config_t: error retrieving file_scope_flags table')
1230+
return
1231+
end if
1232+
1233+
!> Read all packages
1234+
call ptr%get_keys(dep_keys)
1235+
allocate(self%file_scope_flags(size(dep_keys)))
1236+
1237+
do jj = 1, size(dep_keys)
1238+
1239+
call get_value(ptr, dep_keys(jj), ptr_dep)
1240+
call self%file_scope_flags(jj)%load_from_toml(ptr_dep, error)
1241+
if (allocated(error)) return
1242+
1243+
end do
1244+
1245+
end select
1246+
end do sub_deps
11741247

11751248
end subroutine profile_load
11761249

test/fpm_test/test_manifest.f90

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -517,6 +517,9 @@ subroutine test_profiles(error)
517517
return
518518
end if
519519

520+
call chosen_profile%test_serialization('profile serialization: '//profile_name//' '//compiler,error)
521+
if (allocated(error)) return
522+
520523
profile_name = 'release'
521524
compiler = 'gfortran'
522525
call find_profile(package%profiles, profile_name, compiler, 3, profile_found, chosen_profile)
@@ -525,6 +528,9 @@ subroutine test_profiles(error)
525528
return
526529
end if
527530

531+
call chosen_profile%test_serialization('profile serialization: '//profile_name//' '//compiler,error)
532+
if (allocated(error)) return
533+
528534
profile_name = 'publish'
529535
compiler = 'gfortran'
530536
call find_profile(package%profiles, profile_name, compiler, 1, profile_found, chosen_profile)
@@ -533,6 +539,9 @@ subroutine test_profiles(error)
533539
return
534540
end if
535541

542+
call chosen_profile%test_serialization('profile serialization: '//profile_name//' '//compiler,error)
543+
if (allocated(error)) return
544+
536545
profile_name = 'debug'
537546
compiler = 'ifort'
538547
call find_profile(package%profiles, profile_name, compiler, 3, profile_found, chosen_profile)
@@ -541,13 +550,20 @@ subroutine test_profiles(error)
541550
return
542551
end if
543552

553+
call chosen_profile%test_serialization('profile serialization: '//profile_name//' '//compiler,error)
554+
if (allocated(error)) return
555+
544556
profile_name = 'release'
545557
compiler = 'ifort'
546558
call find_profile(package%profiles, profile_name, compiler, 1, profile_found, chosen_profile)
547559
if (.not.(chosen_profile%flags.eq.'5')) then
548560
call test_failed(error, "Failed to overwrite built-in profile")
549561
return
550562
end if
563+
564+
call chosen_profile%test_serialization('profile serialization: '//profile_name//' '//compiler,error)
565+
if (allocated(error)) return
566+
551567
end subroutine test_profiles
552568

553569
!> 'flags' is a key-value entry, test should fail as it is defined as a table

0 commit comments

Comments
 (0)