pkgcfg_get_build_flags Function

public function pkgcfg_get_build_flags(name, allow_system, error) result(flags)

Get build flags (option to include flags from system directories, that gfortran does not look into by default)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: name

Package name

logical, intent(in) :: allow_system

Should pkg-config look in system paths? This is necessary for gfortran that doesn’t otherwise look into them

type(error_t), intent(out), allocatable :: error

Error flag

Return Value type(string_t), allocatable, (:)

List of compile flags


Source Code

function pkgcfg_get_build_flags(name,allow_system,error) result(flags)
    
    !> Package name
    character(*), intent(in) :: name
    
    !> Should pkg-config look in system paths? This is necessary for gfortran 
    !> that doesn't otherwise look into them
    logical, intent(in) :: allow_system 
    
    !> Error flag 
    type(error_t), allocatable, intent(out) :: error
    
    !> List of compile flags
    type(string_t), allocatable :: flags(:)
    
    integer :: exitcode,i,nlib
    logical :: old_had,success,old_allow
    character(:), allocatable :: old,tokens(:)
    type(string_t) :: log    
    
    ! Check if the current environment includes system flags
    old = get_env('PKG_CONFIG_ALLOW_SYSTEM_CFLAGS',default='ERROR')
    old_had = old/='ERROR'
    old_allow = merge(old=='1',.false.,old_had)
    
    ! Set system flags
    success = set_env('PKG_CONFIG_ALLOW_SYSTEM_CFLAGS',value=merge('1','0',allow_system))
    if (.not.success) then 
        call fatal_error(error,'Cannot get pkg-config build flags: environment variable error.')
        return
    end if
    
    ! Now run wrapper
    call run_wrapper(wrapper=string_t('pkg-config'), &
                     args=[string_t(name),string_t('--cflags')], &
                     exitcode=exitcode,cmd_success=success,screen_output=log) 
                     
    if (success .and. exitcode==0) then 
        
        call remove_newline_characters(log)
        
        ! Split all arguments
        tokens = shlex_split(log%s)
        
        nlib = size(tokens)
        allocate(flags(nlib))
        do i=1,nlib
            flags(i) = string_t(trim(adjustl(tokens(i))))
        end do
        
    else
        
        allocate(flags(0))
        call fatal_error(error,'cannot get <'//name//'> build flags from pkg-config')
        
    end if   

    ! Restore environment variable
    if (old_had) then 
        success = set_env('PKG_CONFIG_ALLOW_SYSTEM_CFLAGS',value=old)
    else
        success = delete_env('PKG_CONFIG_ALLOW_SYSTEM_CFLAGS')
    end if
    if (.not.success) then 
        call fatal_error(error,'Cannot get pkg-config build flags: environment variable error.')
        return
    end if    
    
    
end function pkgcfg_get_build_flags