init_blas Subroutine

public subroutine init_blas(this, compiler, error)

Initialize blas metapackage for the current system Cleanup Assert pkg-config is installed

Arguments

Type IntentOptional Attributes Name
class(metapackage_t), intent(inout) :: this
type(compiler_t), intent(in) :: compiler
type(error_t), intent(out), allocatable :: error

Source Code

    subroutine init_blas(this, compiler, error)
        class(metapackage_t), intent(inout) :: this
        type(compiler_t), intent(in) :: compiler
        type(error_t), allocatable, intent(out) :: error

        integer :: i
        character(len=:), allocatable :: include_flag, libdir
        character(*), parameter :: candidates(*) = &
                                   [character(20) :: 'mkl-dynamic-lp64-tbb', 'openblas', 'blas']

        include_flag = get_include_flag(compiler, "")

        !> Cleanup
        call destroy(this)
        allocate (this%link_libs(0), this%incl_dirs(0), this%external_modules(0))
        this%link_flags = string_t("")
        this%flags = string_t("")
        this%has_external_modules = .false.

        if (get_os_type() == OS_MACOS) then
            if (compile_and_link_flags_supported(compiler, "-framework Accelerate")) then
                call set_compile_and_link_flags(this, compiler, "-framework Accelerate")
                return
            end if
        end if

        if (compiler%is_intel()) then
            if (get_os_type() == OS_WINDOWS) then
                if (compile_and_link_flags_supported(compiler, "/Qmkl")) then
                    call set_compile_and_link_flags(this, compiler, "/Qmkl")
                    return
                end if
            else if (compile_and_link_flags_supported(compiler, "-qmkl")) then
                call set_compile_and_link_flags(this, compiler, "-qmkl")
                return
            endif
        end if

        !> Assert pkg-config is installed
        if (.not. assert_pkg_config()) then
            call fatal_error(error, 'blas metapackage requires pkg-config to continue lookup')
            return
        end if

        do i = 1, size(candidates)
            if (pkgcfg_has_package(trim(candidates(i)))) then
                call add_pkg_config_compile_options( &
                    this, trim(candidates(i)), include_flag, libdir, error)
                print *, 'found blas package: ', trim(candidates(i))
                return
            end if
        end do

        call fatal_error(error, 'pkg-config could not find a suitable blas package.')
    end subroutine init_blas