profile_dump Subroutine

public subroutine profile_dump(self, table, error)

Dump to toml table

Because files need a name, fallback if this has no name

Type Bound

profile_config_t

Arguments

Type IntentOptional 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


Variables

Type Visibility Attributes Name Initial
integer, public :: ierr

Local variables

integer, public :: ii

Local variables

type(toml_table), public, pointer :: ptr
type(toml_table), public, pointer :: ptr_deps
character(len=30), public :: unnamed

Source Code

    subroutine profile_dump(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
       integer :: ierr, ii
       type(toml_table), pointer :: ptr_deps, ptr
       character(len=30) :: unnamed

       call set_string(table, "profile-name", self%profile_name, error)
       if (allocated(error)) return
       call set_string(table, "compiler", self%compiler, error)
       if (allocated(error)) return
       call set_string(table,"os-type",os_type_name(self%os_type), error, 'profile_config_t')
       if (allocated(error)) return
       call set_string(table, "flags", self%flags, error)
       if (allocated(error)) return
       call set_string(table, "c-flags", self%c_flags, error)
       if (allocated(error)) return
       call set_string(table, "cxx-flags", self%cxx_flags, error)
       if (allocated(error)) return
       call set_string(table, "link-time-flags", self%link_time_flags, error)
       if (allocated(error)) return

       if (allocated(self%file_scope_flags)) then

           ! Create dependency table
           call add_table(table, "file-scope-flags", ptr_deps)
           if (.not. associated(ptr_deps)) then
              call fatal_error(error, "profile_config_t cannot create file scope table ")
              return
           end if

           do ii = 1, size(self%file_scope_flags)
              associate (dep => self%file_scope_flags(ii))

                 !> Because files need a name, fallback if this has no name
                 if (len_trim(dep%file_name)==0) then
                    write(unnamed,1) ii
                    call add_table(ptr_deps, trim(unnamed), ptr)
                 else
                    call add_table(ptr_deps, dep%file_name, ptr)
                 end if
                 if (.not. associated(ptr)) then
                    call fatal_error(error, "profile_config_t cannot create entry for file "//dep%file_name)
                    return
                 end if
                 call dep%dump_to_toml(ptr, error)
                 if (allocated(error)) return
              end associate
           end do

       endif

       call set_value(table, "is-built-in", self%is_built_in, error, 'profile_config_t')
       if (allocated(error)) return

       1 format('UNNAMED_FILE_',i0)

     end subroutine profile_dump