Skip to content

Commit 117d4aa

Browse files
committed
simplify ext BLAS test; streamline adding preprocessor directives
1 parent e8e60b2 commit 117d4aa

File tree

4 files changed

+51
-93
lines changed

4 files changed

+51
-93
lines changed

example_packages/metapackage_stdlib_extblas/app/main.f90

+6-12
Original file line numberDiff line numberDiff line change
@@ -1,19 +1,13 @@
1-
! fortran-lang stdlib test case
2-
! This test program will only run if stdlib is properly built and linked to this project.
1+
! fortran-lang stdlib + external BLAS test case
2+
! Program will fail if an external BLAS has not been linked against.
33
program test_stdlib_metapackage
4-
5-
! These USEs would not be possible if stdlib is not found
6-
use metapackage_stdlib, only: external_blas_test,external_lapack_test
4+
use stdlib_linalg_constants, only: external_blas_ilp32,external_lapack_ilp32, &
5+
external_blas_ilp64,external_lapack_ilp64
76
implicit none
87

9-
logical :: ext_blas,ext_lapack
10-
11-
call external_blas_test(ext_blas)
12-
call external_lapack_test(ext_lapack)
13-
14-
if (.not.ext_blas) then
8+
if (.not.(external_blas_ilp32 .or. external_blas_ilp64)) then
159
stop 1
16-
elseif (.not.ext_lapack) then
10+
elseif (.not.(external_lapack_ilp32 .or. external_lapack_ilp64)) then
1711
stop 2
1812
else
1913
stop 0

example_packages/metapackage_stdlib_extblas/src/metapackage_stdlib.f90

-81
This file was deleted.

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/metapackage/fpm_meta_stdlib.f90

+1
Original file line numberDiff line numberDiff line change
@@ -57,6 +57,7 @@ subroutine init_stdlib(this,compiler,all_meta,error)
5757
if (with_blas) then
5858
allocate(this%preprocess)
5959
call this%preprocess%new([string_t('STDLIB_EXTERNAL_BLAS'),string_t('STDLIB_EXTERNAL_LAPACK')])
60+
call this%dependency(2)%add_preprocess(this%preprocess)
6061
end if
6162

6263
! Stdlib is not 100% thread safe. print a warning to the user

0 commit comments

Comments
 (0)