Skip to content

Commit 8b75096

Browse files
committed
Added NetCDF metapackage
1 parent 6073158 commit 8b75096

File tree

3 files changed

+76
-1
lines changed

3 files changed

+76
-1
lines changed

src/fpm/manifest/meta.f90

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -52,6 +52,9 @@ module fpm_manifest_metapackages
5252
!> HDF5
5353
type(metapackage_request_t) :: hdf5
5454

55+
!> NetCDF
56+
type(metapackage_request_t) :: netcdf
57+
5558
end type metapackage_config_t
5659

5760

@@ -203,6 +206,9 @@ subroutine new_meta_config(self, table, meta_allowed, error)
203206
call new_meta_request(self%hdf5, "hdf5", table, meta_allowed, error)
204207
if (allocated(error)) return
205208

209+
call new_meta_request(self%netcdf, "netcdf", table, meta_allowed, error)
210+
if (allocated(error)) return
211+
206212
end subroutine new_meta_config
207213

208214
!> Check local schema for allowed entries
@@ -214,7 +220,7 @@ logical function is_meta_package(key)
214220
select case (key)
215221

216222
!> Supported metapackages
217-
case ("openmp","stdlib","mpi","minpack","hdf5")
223+
case ("openmp","stdlib","mpi","minpack","hdf5","netcdf")
218224
is_meta_package = .true.
219225

220226
case default

src/fpm_meta.f90

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ module fpm_meta
3030
use fpm_meta_minpack, only: init_minpack
3131
use fpm_meta_mpi, only: init_mpi
3232
use fpm_meta_hdf5, only: init_hdf5
33+
use fpm_meta_netcdf, only: init_netcdf
3334

3435
use shlex_module, only: shlex_split => split
3536
use regex_module, only: regex
@@ -61,6 +62,7 @@ subroutine init_from_name(this,name,compiler,error)
6162
case("minpack"); call init_minpack(this,compiler,error)
6263
case("mpi"); call init_mpi (this,compiler,error)
6364
case("hdf5"); call init_hdf5 (this,compiler,error)
65+
case("netcdf"); call init_netcdf (this,compiler,error)
6466
case default
6567
call syntax_error(error, "Package "//name//" is not supported in [metapackages]")
6668
return
@@ -153,6 +155,12 @@ subroutine resolve_metapackage_model(model,package,settings,error)
153155
if (allocated(error)) return
154156
endif
155157

158+
! netcdf
159+
if (package%meta%netcdf%on) then
160+
call add_metapackage_model(model,package,settings,"netcdf",error)
161+
if (allocated(error)) return
162+
endif
163+
156164
end subroutine resolve_metapackage_model
157165

158166
end module fpm_meta

src/metapackage/fpm_meta_netcdf.f90

Lines changed: 61 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,61 @@
1+
module fpm_meta_netcdf
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, pkgcfg_list_all
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_netcdf
14+
15+
contains
16+
17+
!> Initialize NetCDF metapackage for the current system
18+
subroutine init_netcdf(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+
34+
!> Assert pkg-config is installed
35+
if (.not.assert_pkg_config()) then
36+
call fatal_error(error, 'netcdf metapackage requires pkg-config')
37+
return
38+
end if
39+
40+
if (.not. pkgcfg_has_package('netcdf')) then
41+
call fatal_error(error,'pkg-config could not find a suitable netcdf package.')
42+
end if
43+
call add_pkg_config_compile_options(this, 'netcdf', include_flag, libdir, error)
44+
if (allocated(error)) return
45+
46+
if (.not. pkgcfg_has_package('netcdf-fortran')) then
47+
call fatal_error(error, &
48+
'pkg-config could not find a suitable netcdf-fortran package.')
49+
end if
50+
call add_pkg_config_compile_options(this, 'netcdf-fortran', include_flag, libdir, error)
51+
if (allocated(error)) return
52+
53+
54+
!> Add NetCDF modules as external
55+
this%has_external_modules = .true.
56+
this%external_modules = [string_t('netcdf')]
57+
58+
print *, 'NetCDF metapackage initialized successfully.'
59+
60+
end subroutine init_netcdf
61+
end module fpm_meta_netcdf

0 commit comments

Comments
 (0)