Skip to content

Commit 69d26bf

Browse files
committed
fortran-lang minpack
1 parent f8e13ee commit 69d26bf

File tree

6 files changed

+72
-6
lines changed

6 files changed

+72
-6
lines changed

ci/meta_tests.sh

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,11 @@ pushd metapackage_stdlib
2727
"$fpm" run --verbose
2828
popd
2929

30+
pushd metapackage_minpack
31+
"$fpm" build --verbose
32+
"$fpm" run --verbose
33+
popd
34+
3035
pushd metapackage_mpi
3136
"$fpm" build --verbose
3237
"$fpm" run --verbose
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
program main
2+
use metapackage_minpack, only: simple_test
3+
implicit none
4+
logical :: success
5+
call simple_test(success)
6+
stop merge(0,1,success)
7+
end program main
Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
name = "metapackage_minpack"
2+
dependencies.minpack="*"
Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,14 @@
1+
module metapackage_minpack
2+
use minpack_module, only: wp
3+
use iso_fortran_env, only: real64
4+
implicit none
5+
private
6+
7+
public :: simple_test
8+
contains
9+
subroutine simple_test(success)
10+
logical, intent(out) :: success
11+
! Success! can read minpack module
12+
success = wp == real64
13+
end subroutine simple_test
14+
end module metapackage_minpack

src/fpm/manifest/meta.f90

Lines changed: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,9 @@ module fpm_manifest_metapackages
4545
!> Request stdlib support
4646
type(metapackage_request_t) :: stdlib
4747

48+
!> fortran-lang minpack
49+
type(metapackage_request_t) :: minpack
50+
4851
end type metapackage_config_t
4952

5053

@@ -158,12 +161,15 @@ subroutine new_meta_config(self, table, error)
158161

159162
!> The toml table is not checked here because it already passed
160163
!> the "new_dependencies" check
161-
call new_request(self%openmp, "openmp", table, error);
164+
call new_request(self%openmp, "openmp", table, error)
162165
if (allocated(error)) return
163166

164167
call new_request(self%stdlib, "stdlib", table, error)
165168
if (allocated(error)) return
166169

170+
call new_request(self%minpack, "minpack", table, error)
171+
if (allocated(error)) return
172+
167173
call new_request(self%mpi, "mpi", table, error)
168174
if (allocated(error)) return
169175

@@ -178,7 +184,7 @@ logical function is_meta_package(key)
178184
select case (key)
179185

180186
!> Supported metapackages
181-
case ("openmp","stdlib","mpi")
187+
case ("openmp","stdlib","mpi","minpack")
182188
is_meta_package = .true.
183189

184190
case default

src/fpm_meta.f90

Lines changed: 36 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ module fpm_meta
1919
use fpm_model
2020
use fpm_command_line
2121
use fpm_manifest_dependency, only: dependency_config_t
22-
use fpm_git, only : git_target_branch
22+
use fpm_git, only : git_target_branch, git_target_tag
2323
use fpm_manifest, only: package_config_t
2424
use fpm_environment, only: get_env,os_is_unix
2525
use fpm_filesystem, only: run, get_temp_filename, getline, exists, canon_path, is_dir, get_dos_path
@@ -153,9 +153,10 @@ subroutine init_from_name(this,name,compiler,error)
153153

154154
!> Initialize metapackage by name
155155
select case(name)
156-
case("openmp"); call init_openmp(this,compiler,error)
157-
case("stdlib"); call init_stdlib(this,compiler,error)
158-
case("mpi"); call init_mpi (this,compiler,error)
156+
case("openmp"); call init_openmp (this,compiler,error)
157+
case("stdlib"); call init_stdlib (this,compiler,error)
158+
case("minpack"); call init_minpack(this,compiler,error)
159+
case("mpi"); call init_mpi (this,compiler,error)
159160
case default
160161
call syntax_error(error, "Package "//name//" is not supported in [metapackages]")
161162
return
@@ -216,6 +217,30 @@ subroutine init_openmp(this,compiler,error)
216217

217218
end subroutine init_openmp
218219

220+
!> Initialize minpack metapackage for the current system
221+
subroutine init_minpack(this,compiler,error)
222+
class(metapackage_t), intent(inout) :: this
223+
type(compiler_t), intent(in) :: compiler
224+
type(error_t), allocatable, intent(out) :: error
225+
226+
!> Cleanup
227+
call destroy(this)
228+
229+
!> minpack is queried as a dependency from the official repository
230+
this%has_dependencies = .true.
231+
232+
allocate(this%dependency(1))
233+
234+
!> 1) minpack. There are no true releases currently. Fetch HEAD
235+
this%dependency(1)%name = "minpack"
236+
this%dependency(1)%git = git_target_tag("https://github.com/fortran-lang/minpack", "v2.0.0-rc.1")
237+
if (.not.allocated(this%dependency(1)%git)) then
238+
call fatal_error(error,'cannot initialize git repo dependency for minpack metapackage')
239+
return
240+
end if
241+
242+
end subroutine init_minpack
243+
219244
!> Initialize stdlib metapackage for the current system
220245
subroutine init_stdlib(this,compiler,error)
221246
class(metapackage_t), intent(inout) :: this
@@ -408,6 +433,13 @@ subroutine resolve_metapackage_model(model,package,settings,error)
408433
if (allocated(error)) return
409434
endif
410435

436+
! stdlib
437+
if (package%meta%minpack%on) then
438+
call add_metapackage_model(model,package,settings,"minpack",error)
439+
if (allocated(error)) return
440+
endif
441+
442+
411443
! Stdlib is not 100% thread safe. print a warning to the user
412444
if (package%meta%stdlib%on .and. package%meta%openmp%on) then
413445
write(stdout,'(a)')'<WARNING> both openmp and stdlib requested: some functions may not be thread-safe!'

0 commit comments

Comments
 (0)