Skip to content

Commit 3f0a304

Browse files
authored
[metapackage] stdlib: enable external BLAS/LAPACK (#1139)
2 parents 0066512 + 8ad8f52 commit 3f0a304

18 files changed

+364
-113
lines changed

ci/meta_tests.sh

+5
Original file line numberDiff line numberDiff line change
@@ -57,5 +57,10 @@ pushd metapackage_blas
5757
"$fpm" run --verbose
5858
popd
5959

60+
pushd metapackage_stdlib_extblas
61+
"$fpm" build --verbose
62+
"$fpm" run --verbose
63+
popd
64+
6065
# Cleanup
6166
rm -rf ./*/build
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
! fortran-lang stdlib + external BLAS test case
2+
! Program will fail if an external BLAS has not been linked against.
3+
program test_stdlib_metapackage
4+
use stdlib_linalg_constants, only: external_blas_ilp32,external_lapack_ilp32, &
5+
external_blas_ilp64,external_lapack_ilp64
6+
implicit none
7+
8+
if (.not.(external_blas_ilp32 .or. external_blas_ilp64)) then
9+
stop 1
10+
elseif (.not.(external_lapack_ilp32 .or. external_lapack_ilp64)) then
11+
stop 2
12+
else
13+
stop 0
14+
end if
15+
16+
end program test_stdlib_metapackage
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
name = "test_stdlib_ext_blas"
2+
dependencies.blas = "*"
3+
dependencies.stdlib = "*"
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
program cpp
2+
use preprocess_cpp
3+
call say_hello()
4+
end program

src/fpm.f90

+37-29
Original file line numberDiff line numberDiff line change
@@ -40,12 +40,13 @@ module fpm
4040
subroutine build_model(model, settings, package, error)
4141
type(fpm_model_t), intent(out) :: model
4242
class(fpm_build_settings), intent(inout) :: settings
43-
type(package_config_t), intent(inout) :: package
43+
type(package_config_t), intent(inout), target :: package
4444
type(error_t), allocatable, intent(out) :: error
4545

4646
integer :: i, j
47-
type(package_config_t) :: dependency
48-
character(len=:), allocatable :: manifest, lib_dir
47+
type(package_config_t), target :: dependency
48+
type(package_config_t), pointer :: manifest
49+
character(len=:), allocatable :: file_name, lib_dir
4950
logical :: has_cpp
5051
logical :: duplicates_found
5152
type(string_t) :: include_dir
@@ -76,7 +77,7 @@ subroutine build_model(model, settings, package, error)
7677
! Resolve meta-dependencies into the package and the model
7778
call resolve_metapackages(model,package,settings,error)
7879
if (allocated(error)) return
79-
80+
8081
! Create dependencies
8182
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"), &
8283
& path_to_config=settings%path_to_config)
@@ -99,25 +100,32 @@ subroutine build_model(model, settings, package, error)
99100
has_cpp = .false.
100101
do i = 1, model%deps%ndep
101102
associate(dep => model%deps%dep(i))
102-
manifest = join_path(dep%proj_dir, "fpm.toml")
103-
104-
call get_package_data(dependency, manifest, error, apply_defaults=.true.)
105-
if (allocated(error)) exit
103+
file_name = join_path(dep%proj_dir, "fpm.toml")
106104

107-
model%packages(i)%name = dependency%name
105+
! The main package manifest should not be reloaded, because it may have been
106+
! affected by model dependencies and metapackages
107+
if (i==1) then
108+
manifest => package
109+
else
110+
111+
call get_package_data(dependency, file_name, error, apply_defaults=.true.)
112+
if (allocated(error)) exit
113+
114+
manifest => dependency
115+
end if
116+
117+
model%packages(i)%name = manifest%name
108118
associate(features => model%packages(i)%features)
109-
features%implicit_typing = dependency%fortran%implicit_typing
110-
features%implicit_external = dependency%fortran%implicit_external
111-
features%source_form = dependency%fortran%source_form
119+
features%implicit_typing = manifest%fortran%implicit_typing
120+
features%implicit_external = manifest%fortran%implicit_external
121+
features%source_form = manifest%fortran%source_form
112122
end associate
113123
model%packages(i)%version = package%version%s()
114124

115125
!> Add this dependency's manifest macros
116-
call model%packages(i)%preprocess%destroy()
117-
118-
if (allocated(dependency%preprocess)) then
119-
do j = 1, size(dependency%preprocess)
120-
call model%packages(i)%preprocess%add_config(dependency%preprocess(j))
126+
if (allocated(manifest%preprocess)) then
127+
do j = 1, size(manifest%preprocess)
128+
call model%packages(i)%preprocess%add_config(manifest%preprocess(j))
121129
end do
122130
end if
123131

@@ -132,20 +140,20 @@ subroutine build_model(model, settings, package, error)
132140

133141
if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))
134142

135-
if (allocated(dependency%library)) then
143+
if (allocated(manifest%library)) then
136144

137-
if (allocated(dependency%library%source_dir)) then
138-
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
145+
if (allocated(manifest%library%source_dir)) then
146+
lib_dir = join_path(dep%proj_dir, manifest%library%source_dir)
139147
if (is_dir(lib_dir)) then
140148
call add_sources_from_dir(model%packages(i)%sources, lib_dir, FPM_SCOPE_LIB, &
141149
with_f_ext=model%packages(i)%preprocess%suffixes, error=error)
142150
if (allocated(error)) exit
143151
end if
144152
end if
145153

146-
if (allocated(dependency%library%include_dir)) then
147-
do j=1,size(dependency%library%include_dir)
148-
include_dir%s = join_path(dep%proj_dir, dependency%library%include_dir(j)%s)
154+
if (allocated(manifest%library%include_dir)) then
155+
do j=1,size(manifest%library%include_dir)
156+
include_dir%s = join_path(dep%proj_dir, manifest%library%include_dir(j)%s)
149157
if (is_dir(include_dir%s)) then
150158
model%include_dirs = [model%include_dirs, include_dir]
151159
end if
@@ -154,17 +162,17 @@ subroutine build_model(model, settings, package, error)
154162

155163
end if
156164

157-
if (allocated(dependency%build%link)) then
158-
model%link_libraries = [model%link_libraries, dependency%build%link]
165+
if (allocated(manifest%build%link)) then
166+
model%link_libraries = [model%link_libraries, manifest%build%link]
159167
end if
160168

161-
if (allocated(dependency%build%external_modules)) then
162-
model%external_modules = [model%external_modules, dependency%build%external_modules]
169+
if (allocated(manifest%build%external_modules)) then
170+
model%external_modules = [model%external_modules, manifest%build%external_modules]
163171
end if
164172

165173
! Copy naming conventions from this dependency's manifest
166-
model%packages(i)%enforce_module_names = dependency%build%module_naming
167-
model%packages(i)%module_prefix = dependency%build%module_prefix
174+
model%packages(i)%enforce_module_names = manifest%build%module_naming
175+
model%packages(i)%module_prefix = manifest%build%module_prefix
168176

169177
end associate
170178
end do

src/fpm/manifest/dependency.f90

+44
Original file line numberDiff line numberDiff line change
@@ -70,6 +70,9 @@ module fpm_manifest_dependency
7070

7171
!> Print information on this instance
7272
procedure :: info
73+
74+
!> Add a preprocessor configuration
75+
procedure :: add_preprocess
7376

7477
!> Serialization interface
7578
procedure :: serializable_is_same => dependency_is_same
@@ -561,6 +564,47 @@ pure subroutine resize_dependency_config(var, n)
561564
end if
562565

563566
end subroutine resize_dependency_config
567+
568+
subroutine add_preprocess(dep, preprocess)
569+
!> Instance of the dependency config
570+
class(dependency_config_t), intent(inout) :: dep
571+
!> Instance of the preprocessor configuration
572+
type(preprocess_config_t), intent(in) :: preprocess
573+
574+
integer :: i,n
575+
type(preprocess_config_t), allocatable :: new_preprocess(:)
576+
577+
if (allocated(dep%preprocess)) then
578+
579+
n = size(dep%preprocess)
580+
581+
if (n<1) then
582+
deallocate(dep%preprocess)
583+
allocate(dep%preprocess(1),source=preprocess)
584+
else
585+
586+
find_similar: do i=1,n
587+
if (dep%preprocess(i)%name==dep%name) then
588+
call dep%preprocess(i)%add_config(preprocess)
589+
return
590+
end if
591+
end do find_similar
592+
593+
! Similar preprocessor config not found: add a new one
594+
allocate(new_preprocess(n+1))
595+
new_preprocess(1:n) = dep%preprocess
596+
new_preprocess(n+1) = preprocess
597+
call move_alloc(from=new_preprocess,to=dep%preprocess)
598+
599+
end if
600+
else
601+
602+
! Copy configuration
603+
allocate(dep%preprocess(1),source=preprocess)
604+
605+
end if
606+
607+
end subroutine add_preprocess
564608

565609

566610
end module fpm_manifest_dependency

src/fpm/manifest/meta.f90

+62-1
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,10 @@ module fpm_manifest_metapackages
5858

5959
!> BLAS
6060
type(metapackage_request_t) :: blas
61+
62+
contains
63+
64+
procedure :: get_requests
6165

6266
end type metapackage_config_t
6367

@@ -217,7 +221,7 @@ subroutine new_meta_config(self, table, meta_allowed, error)
217221
if (allocated(error)) return
218222

219223
end subroutine new_meta_config
220-
224+
221225
!> Check local schema for allowed entries
222226
logical function is_meta_package(key)
223227

@@ -236,5 +240,62 @@ logical function is_meta_package(key)
236240
end select
237241

238242
end function is_meta_package
243+
244+
!> Return a list of metapackages requested for the current build
245+
function get_requests(meta) result(requests)
246+
247+
!> Instance of the build configuration
248+
class(metapackage_config_t), intent(in) :: meta
249+
250+
!> The list of requested metapackages (always allocated)
251+
type(metapackage_request_t), allocatable :: requests(:)
252+
253+
integer :: nreq
254+
255+
!> Count requests
256+
nreq = 0
257+
if (meta%mpi%on) nreq = nreq + 1
258+
if (meta%openmp%on) nreq = nreq + 1
259+
if (meta%stdlib%on) nreq = nreq + 1
260+
if (meta%minpack%on) nreq = nreq + 1
261+
if (meta%hdf5%on) nreq = nreq + 1
262+
if (meta%netcdf%on) nreq = nreq + 1
263+
if (meta%blas%on) nreq = nreq + 1
264+
265+
!> Prepare requests
266+
allocate(requests(nreq)); if (nreq <= 0) return
267+
268+
nreq = 0
269+
if (meta%mpi%on) then
270+
nreq = nreq + 1
271+
requests(nreq) = meta%mpi
272+
end if
273+
if (meta%openmp%on) then
274+
nreq = nreq + 1
275+
requests(nreq) = meta%openmp
276+
end if
277+
if (meta%stdlib%on) then
278+
nreq = nreq + 1
279+
requests(nreq) = meta%stdlib
280+
end if
281+
if (meta%minpack%on) then
282+
nreq = nreq + 1
283+
requests(nreq) = meta%minpack
284+
end if
285+
if (meta%hdf5%on) then
286+
nreq = nreq + 1
287+
requests(nreq) = meta%hdf5
288+
end if
289+
if (meta%netcdf%on) then
290+
nreq = nreq + 1
291+
requests(nreq) = meta%netcdf
292+
end if
293+
if (meta%blas%on) then
294+
nreq = nreq + 1
295+
requests(nreq) = meta%blas
296+
end if
297+
298+
end function get_requests
299+
239300

240301
end module fpm_manifest_metapackages

src/fpm/manifest/preprocess.f90

+31-3
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ module fpm_manifest_preprocess
2020
implicit none
2121
private
2222

23-
public :: preprocess_config_t, new_preprocess_config, new_preprocessors, operator(==)
23+
public :: preprocess_config_t, new_preprocessors, operator(==)
2424

2525
!> Configuration meta data for a preprocessor
2626
type, extends(serializable_t) :: preprocess_config_t
@@ -41,6 +41,11 @@ module fpm_manifest_preprocess
4141

4242
!> Print information on this instance
4343
procedure :: info
44+
45+
!> Initialization
46+
procedure, private :: new_cpp_config_with_macros
47+
procedure, private :: new_preprocess_config
48+
generic :: new => new_cpp_config_with_macros, new_preprocess_config
4449

4550
!> Serialization interface
4651
procedure :: serializable_is_same => preprocess_is_same
@@ -61,11 +66,34 @@ module fpm_manifest_preprocess
6166

6267
contains
6368

69+
!> Construct a new cpp preprocessor configuration with a list of macros
70+
subroutine new_cpp_config_with_macros(self, macros)
71+
72+
!> Instance of the preprocess configuration
73+
class(preprocess_config_t), intent(out) :: self
74+
75+
!> List of macros
76+
type(string_t), intent(in) :: macros(:)
77+
78+
call self%destroy()
79+
80+
!> Set cpp
81+
self%name = "cpp"
82+
83+
!> Set macros
84+
if (size(macros)<=0) then
85+
allocate(self%macros(0))
86+
else
87+
allocate(self%macros, source=macros)
88+
end if
89+
90+
end subroutine new_cpp_config_with_macros
91+
6492
!> Construct a new preprocess configuration from TOML data structure
6593
subroutine new_preprocess_config(self, table, error)
6694

6795
!> Instance of the preprocess configuration
68-
type(preprocess_config_t), intent(out) :: self
96+
class(preprocess_config_t), intent(out) :: self
6997

7098
!> Instance of the TOML data structure.
7199
type(toml_table), intent(inout) :: table
@@ -145,7 +173,7 @@ subroutine new_preprocessors(preprocessors, table, error)
145173
call syntax_error(error, "Preprocessor "//list(iprep)%key//" must be a table entry")
146174
exit
147175
end if
148-
call new_preprocess_config(preprocessors(iprep), node, error)
176+
call preprocessors(iprep)%new(node, error)
149177
if (allocated(error)) exit
150178
end do
151179

0 commit comments

Comments
 (0)