init_openmp Subroutine

public subroutine init_openmp(this, compiler, error)

Initialize OpenMP metapackage for the current system Cleanup

OpenMP has compiler flags OpenMP flags should be added to

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_openmp(this,compiler,error)
        class(metapackage_t), intent(inout) :: this
        type(compiler_t), intent(in) :: compiler
        type(error_t), allocatable, intent(out) :: error

        !> Cleanup
        call destroy(this)

        !> OpenMP has compiler flags
        this%has_build_flags = .true.
        this%has_link_flags  = .true.

        !> OpenMP flags should be added to
        which_compiler: select case (compiler%id)
           case (id_gcc,id_f95)
                this%flags      = string_t(flag_gnu_openmp)
                this%link_flags = string_t(flag_gnu_openmp)

           case (id_intel_classic_windows,id_intel_llvm_windows)
                this%flags      = string_t(flag_intel_openmp_win)
                this%link_flags = string_t(flag_intel_openmp_win)

           case (id_intel_classic_nix,id_intel_classic_mac,&
                 id_intel_llvm_nix)
                this%flags      = string_t(flag_intel_openmp)
                this%link_flags = string_t(flag_intel_openmp)

           case (id_pgi,id_nvhpc)
                this%flags      = string_t(flag_pgi_openmp)
                this%link_flags = string_t(flag_pgi_openmp)

           case (id_ibmxl)
                this%flags      = string_t(" -qsmp=omp")
                this%link_flags = string_t(" -qsmp=omp")

           case (id_nag)
                this%flags      = string_t(flag_nag_openmp)
                this%link_flags = string_t(flag_nag_openmp)

           case (id_lfortran)
                this%flags      = string_t(flag_lfortran_openmp)
                this%link_flags = string_t(flag_lfortran_openmp)

           case (id_flang, id_flang_new)
                this%flags      = string_t(flag_flang_new_openmp)
                this%link_flags = string_t(flag_flang_new_openmp)

           case default

              call fatal_error(error,'openmp not supported on compiler '//compiler%name()//' yet')

        end select which_compiler


    end subroutine init_openmp