pkgcfg_get_libs Function

public function pkgcfg_get_libs(package, error) result(libraries)

Get package libraries from pkg-config

Arguments

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

Package name

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

Error handler

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

A list of libraries


Source Code

function pkgcfg_get_libs(package,error) result(libraries)

    !> Package name
    character(*), intent(in) :: package
    
    !> Error handler
    type(error_t), allocatable, intent(out) :: error
    
    !> A list of libraries
    type(string_t), allocatable :: libraries(:)

    integer :: exitcode,nlib,i
    logical :: success
    character(len=:), allocatable :: tokens(:)
    type(string_t) :: log    
        
    call run_wrapper(wrapper=string_t('pkg-config'), &
                     args=[string_t(package),string_t('--libs')], &
                     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(libraries(nlib))
        do i=1,nlib
            libraries(i) = string_t(trim(adjustl(tokens(i))))
        end do
        
    else
        
        allocate(libraries(0))
        call fatal_error(error,'cannot get <'//package//'> libraries from pkg-config')
        
    end if   

end function pkgcfg_get_libs