Read from toml table (no checks made at this stage)
Read all packages
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(profile_config_t), | intent(inout) | :: | self |
Instance of the serializable object |
||
type(toml_table), | intent(inout) | :: | table |
Data structure |
||
type(error_t), | intent(out), | allocatable | :: | error |
Error handling |
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
type(toml_key), | public, | allocatable | :: | dep_keys(:) | |||
character(len=:), | public, | allocatable | :: | flag |
Local variables |
||
integer, | public | :: | ii | ||||
integer, | public | :: | jj | ||||
type(toml_key), | public, | allocatable | :: | keys(:) | |||
type(toml_table), | public, | pointer | :: | ptr | |||
type(toml_table), | public, | pointer | :: | ptr_dep |
subroutine profile_load(self, table, error) !> Instance of the serializable object class(profile_config_t), intent(inout) :: self !> Data structure type(toml_table), intent(inout) :: table !> Error handling type(error_t), allocatable, intent(out) :: error !> Local variables character(len=:), allocatable :: flag integer :: ii, jj type(toml_table), pointer :: ptr_dep, ptr type(toml_key), allocatable :: keys(:),dep_keys(:) call table%get_keys(keys) call get_value(table, "profile-name", self%profile_name) call get_value(table, "compiler", self%compiler) call get_value(table,"os-type",flag) call match_os_type(flag, self%os_type) call get_value(table, "flags", self%flags) call get_value(table, "c-flags", self%c_flags) call get_value(table, "cxx-flags", self%cxx_flags) call get_value(table, "link-time-flags", self%link_time_flags) call get_value(table, "is-built-in", self%is_built_in, error, 'profile_config_t') if (allocated(error)) return if (allocated(self%file_scope_flags)) deallocate(self%file_scope_flags) sub_deps: do ii = 1, size(keys) select case (keys(ii)%key) case ("file-scope-flags") call get_value(table, keys(ii), ptr) if (.not.associated(ptr)) then call fatal_error(error,'profile_config_t: error retrieving file_scope_flags table') return end if !> Read all packages call ptr%get_keys(dep_keys) allocate(self%file_scope_flags(size(dep_keys))) do jj = 1, size(dep_keys) call get_value(ptr, dep_keys(jj), ptr_dep) call self%file_scope_flags(jj)%load_from_toml(ptr_dep, error) if (allocated(error)) return end do end select end do sub_deps end subroutine profile_load