find_profile Subroutine

public subroutine find_profile(profiles, profile_name, target, found_matching, chosen_profile)

Look for profile with given configuration in array profiles

Arguments

Type IntentOptional Attributes Name
type(profile_config_t), intent(in), allocatable :: profiles(:)

Array of profiles

character(len=:), intent(in), allocatable :: profile_name

Name of profile

type(platform_config_t), intent(in) :: target
logical, intent(out) :: found_matching

Boolean value containing true if matching profile was found

type(profile_config_t), intent(out) :: chosen_profile

Last matching profile in the profiles array


Variables

Type Visibility Attributes Name Initial
integer, public :: i

Source Code

      subroutine find_profile(profiles, profile_name, target, found_matching, chosen_profile)

        !> Array of profiles
        type(profile_config_t), allocatable, intent(in) :: profiles(:)

        !> Name of profile
        character(:), allocatable, intent(in) :: profile_name

        ! Target platform
        type(platform_config_t), intent(in) :: target

        !> Boolean value containing true if matching profile was found
        logical, intent(out) :: found_matching

        !> Last matching profile in the profiles array
        type(profile_config_t), intent(out) :: chosen_profile

        integer :: i

        found_matching = .false.
        if (size(profiles) < 1) return
        
       
        ! Try to find profile with matching OS type
        do i=1,size(profiles)
            
          associate (feat => profiles(i)%profile_feature)  
            
          if (profiles(i)%profile_feature%name == profile_name) then
            if (profiles(i)%profile_feature%platform%matches(target)) then
                chosen_profile = profiles(i)
                found_matching = .true.
                return
            end if
          end if
          
          endassociate
          
        end do
        
      end subroutine find_profile