init_feature_components Subroutine

public subroutine init_feature_components(self, table, platform, root, error)

Initialize the feature components (shared between new_feature and new_package)

Arguments

Type IntentOptional Attributes Name
type(feature_config_t), intent(inout) :: self
type(toml_table), intent(inout) :: table
type(platform_config_t), intent(in), optional :: platform
character(len=*), intent(in), optional :: root
type(error_t), intent(out), allocatable :: error

Source Code

      subroutine init_feature_components(self, table, platform, root, error)
          type(feature_config_t), intent(inout) :: self
          type(toml_table), intent(inout) :: table
          type(platform_config_t), optional, intent(in) :: platform
          character(len=*), intent(in), optional :: root
          type(error_t), allocatable, intent(out) :: error

          type(toml_table), pointer :: child, node
          type(toml_array), pointer :: children
          integer :: ii, nn, stat

          ! Initialize platform with defaults 
          if (present(platform)) then 
              self%platform = platform
          else
              self%platform = platform_config_t(id_all,OS_ALL)  
          end if

          ! Get description and default flag
          call get_value(table, "description", self%description)
          call get_value(table, "default", self%default, .false.)

          ! Get compiler flags
          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)

          ! Get feature dependencies
          call get_list(table, "requires", self%requires_features, error)
          if (allocated(error)) return

          ! Get build configuration
          call get_value(table, "build", child, requested=.false., stat=stat)
          if (stat == toml_stat%success .and. associated(child)) then
              allocate(self%build)
              call new_build_config(self%build, child, self%name, error)
              if (allocated(error)) return
          end if

          ! Get install configuration
          call get_value(table, "install", child, requested=.false., stat=stat)
          if (stat == toml_stat%success .and. associated(child)) then
              allocate(self%install)
              call new_install_config(self%install, child, error)
              if (allocated(error)) return
          end if

          ! Get Fortran configuration
          call get_value(table, "fortran", child, requested=.false., stat=stat)
          if (stat == toml_stat%success .and. associated(child)) then
              allocate(self%fortran)
              call new_fortran_config(self%fortran, child, error)          
              if (allocated(error)) return
          end if
     
          ! Get library configuration
          call get_value(table, "library", child, requested=.false.)
          if (associated(child)) then
              allocate(self%library)
              call new_library(self%library, child, error)
              if (allocated(error)) return
          end if

          ! Get dependencies and metapackage dependencies
          call get_value(table, "dependencies", child, requested=.false.)
          if (associated(child)) then
              call new_dependencies(self%dependency, child, root, self%meta, error=error)
              if (allocated(error)) return
          end if

          ! Get development dependencies
          call get_value(table, "dev-dependencies", child, requested=.false.)
          if (associated(child)) then
              call new_dependencies(self%dev_dependency, child, root, error=error)
              if (allocated(error)) return
          end if

          ! Get executables
          call get_value(table, "executable", children, requested=.false.)
          if (associated(children)) then
              nn = len(children)
              allocate(self%executable(nn))
              do ii = 1, nn
                  call get_value(children, ii, node, stat=stat)
                  if (stat /= toml_stat%success) then
                      call fatal_error(error, "Could not retrieve executable from array entry")
                      exit
                  end if
                  call new_executable(self%executable(ii), node, error)
                  if (allocated(error)) exit
              end do
              if (allocated(error)) return
          end if

          ! Get examples
          call get_value(table, "example", children, requested=.false.)
          if (associated(children)) then
              nn = len(children)
              allocate(self%example(nn))
              do ii = 1, nn
                  call get_value(children, ii, node, stat=stat)
                  if (stat /= toml_stat%success) then
                      call fatal_error(error, "Could not retrieve example from array entry")
                      exit
                  end if
                  call new_example(self%example(ii), node, error)
                  if (allocated(error)) exit
              end do
              if (allocated(error)) return
          end if

          ! Get tests
          call get_value(table, "test", children, requested=.false.)
          if (associated(children)) then
              nn = len(children)
              allocate(self%test(nn))
              do ii = 1, nn
                  call get_value(children, ii, node, stat=stat)
                  if (stat /= toml_stat%success) then
                      call fatal_error(error, "Could not retrieve test from array entry")
                      exit
                  end if
                  call new_test(self%test(ii), node, error)
                  if (allocated(error)) exit
              end do
              if (allocated(error)) return
          end if

          ! Get preprocessors
          call get_value(table, "preprocess", child, requested=.false.)
          if (associated(child)) then
              call new_preprocessors(self%preprocess, child, error)
              if (allocated(error)) return
          end if

          ! Validate unique program names
          if (allocated(self%executable)) then
              call unique_programs(self%executable, error)
              if (allocated(error)) return
          end if

          if (allocated(self%example)) then
              call unique_programs(self%example, error)
              if (allocated(error)) return

              if (allocated(self%executable)) then
                  call unique_programs(self%executable, self%example, error)
                  if (allocated(error)) return
              end if
          end if

          if (allocated(self%test)) then
              call unique_programs(self%test, error)
              if (allocated(error)) return
          end if

      end subroutine init_feature_components