Skip to content

Commit 4ef107f

Browse files
committed
Added OpenBLAS
1 parent 880abe6 commit 4ef107f

File tree

3 files changed

+61
-1
lines changed

3 files changed

+61
-1
lines changed

src/fpm/manifest/meta.f90

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,9 @@ module fpm_manifest_metapackages
5656
!> NetCDF
5757
type(metapackage_request_t) :: netcdf
5858

59+
!> BLAS
60+
type(metapackage_request_t) :: blas
61+
5962
end type metapackage_config_t
6063

6164

@@ -210,6 +213,9 @@ subroutine new_meta_config(self, table, meta_allowed, error)
210213
call new_meta_request(self%netcdf, "netcdf", table, meta_allowed, error)
211214
if (allocated(error)) return
212215

216+
call new_meta_request(self%blas, "blas", table, meta_allowed, error)
217+
if (allocated(error)) return
218+
213219
end subroutine new_meta_config
214220

215221
!> Check local schema for allowed entries
@@ -221,7 +227,7 @@ logical function is_meta_package(key)
221227
select case (key)
222228

223229
!> Supported metapackages
224-
case ("openmp","stdlib","mpi","minpack","hdf5","netcdf")
230+
case ("openmp","stdlib","mpi","minpack","hdf5","netcdf","blas")
225231
is_meta_package = .true.
226232

227233
case default

src/fpm_meta.f90

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,7 @@ module fpm_meta
3131
use fpm_meta_mpi, only: init_mpi
3232
use fpm_meta_hdf5, only: init_hdf5
3333
use fpm_meta_netcdf, only: init_netcdf
34+
use fpm_meta_blas, only: init_blas
3435

3536
use shlex_module, only: shlex_split => split
3637
use regex_module, only: regex
@@ -63,6 +64,7 @@ subroutine init_from_name(this,name,compiler,error)
6364
case("mpi"); call init_mpi (this,compiler,error)
6465
case("hdf5"); call init_hdf5 (this,compiler,error)
6566
case("netcdf"); call init_netcdf (this,compiler,error)
67+
case("blas"); call init_blas (this,compiler,error)
6668
case default
6769
call syntax_error(error, "Package "//name//" is not supported in [metapackages]")
6870
return
@@ -161,6 +163,12 @@ subroutine resolve_metapackage_model(model,package,settings,error)
161163
if (allocated(error)) return
162164
endif
163165

166+
! blas
167+
if (package%meta%blas%on) then
168+
call add_metapackage_model(model,package,settings,"blas",error)
169+
if (allocated(error)) return
170+
endif
171+
164172
end subroutine resolve_metapackage_model
165173

166174
end module fpm_meta

src/metapackage/fpm_meta_blas.f90

Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,46 @@
1+
module fpm_meta_blas
2+
use fpm_compiler, only: compiler_t, get_include_flag
3+
use fpm_meta_base, only: metapackage_t, destroy
4+
use fpm_meta_util, only: add_pkg_config_compile_options
5+
use fpm_pkg_config, only: assert_pkg_config, pkgcfg_has_package
6+
use fpm_strings, only: string_t
7+
use fpm_error, only: error_t, fatal_error
8+
9+
implicit none
10+
11+
private
12+
13+
public :: init_blas
14+
15+
contains
16+
17+
!> Initialize blas metapackage for the current system
18+
subroutine init_blas(this, compiler, error)
19+
class(metapackage_t), intent(inout) :: this
20+
type(compiler_t), intent(in) :: compiler
21+
type(error_t), allocatable, intent(out) :: error
22+
23+
logical :: s
24+
character(len=:), allocatable :: include_flag, libdir
25+
26+
include_flag = get_include_flag(compiler, "")
27+
28+
!> Cleanup
29+
call destroy(this)
30+
allocate (this % link_libs(0), this % incl_dirs(0), this % external_modules(0))
31+
this % link_flags = string_t("")
32+
this % flags = string_t("")
33+
this % has_external_modules = .false.
34+
35+
!> Assert pkg-config is installed
36+
if (.not. assert_pkg_config()) then
37+
call fatal_error(error, 'blas metapackage requires pkg-config')
38+
return
39+
end if
40+
41+
if (pkgcfg_has_package('openblas')) then
42+
call add_pkg_config_compile_options(this, 'openblas', include_flag, libdir, error)
43+
return
44+
end if
45+
end subroutine init_blas
46+
end module fpm_meta_blas

0 commit comments

Comments
 (0)