Skip to content

Commit a3617e5

Browse files
committed
Refactor: Move common functionality into fpm_meta_util
1 parent e249419 commit a3617e5

File tree

2 files changed

+122
-96
lines changed

2 files changed

+122
-96
lines changed

src/metapackage/fpm_meta_hdf5.f90

Lines changed: 4 additions & 96 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,11 @@
11
module fpm_meta_hdf5
22
use fpm_compiler, only: compiler_t, get_include_flag
3-
use fpm_strings, only: str_begins_with_str, str_ends_with
3+
use fpm_strings, only: str_begins_with_str, str_ends_with, string_t
44
use fpm_filesystem, only: join_path
5-
use fpm_pkg_config, only: assert_pkg_config, pkgcfg_has_package, &
6-
pkgcfg_get_libs, pkgcfg_get_build_flags, pkgcfg_get_version, pkgcfg_list_all
5+
use fpm_pkg_config, only: assert_pkg_config, pkgcfg_has_package, pkgcfg_list_all
76
use fpm_meta_base, only: metapackage_t, destroy
8-
use fpm_strings, only: string_t, split
7+
use fpm_meta_util, only: add_pkg_config_compile_options, lib_get_trailing
98
use fpm_error, only: error_t, fatal_error
10-
use fpm_versioning, only: new_version
119

1210
implicit none
1311

@@ -74,37 +72,8 @@ subroutine init_hdf5(this,compiler,error)
7472
return
7573
end if
7674

77-
!> Get version
78-
log = pkgcfg_get_version(name,error)
75+
call add_pkg_config_compile_options(this, name, include_flag, libdir, error)
7976
if (allocated(error)) return
80-
allocate(this%version)
81-
call new_version(this%version,log%s,error)
82-
if (allocated(error)) return
83-
84-
!> Get libraries
85-
libs = pkgcfg_get_libs(name,error)
86-
if (allocated(error)) return
87-
88-
libdir = ""
89-
do i=1,size(libs)
90-
91-
if (str_begins_with_str(libs(i)%s,'-l')) then
92-
this%has_link_libraries = .true.
93-
this%link_libs = [this%link_libs, string_t(libs(i)%s(3:))]
94-
95-
else ! -L and others: concatenate
96-
this%has_link_flags = .true.
97-
this%link_flags = string_t(trim(this%link_flags%s)//' '//libs(i)%s)
98-
99-
! Also save library dir
100-
if (str_begins_with_str(libs(i)%s,'-L')) then
101-
libdir = libs(i)%s(3:)
102-
elseif (str_begins_with_str(libs(i)%s,'/LIBPATH')) then
103-
libdir = libs(i)%s(9:)
104-
endif
105-
106-
end if
107-
end do
10877

10978
! Some pkg-config hdf5.pc (e.g. Ubuntu) don't include the commonly-used HL HDF5 libraries,
11079
! so let's add them if they exist
@@ -148,22 +117,6 @@ subroutine init_hdf5(this,compiler,error)
148117
end do
149118
endif
150119

151-
!> Get compiler flags
152-
flags = pkgcfg_get_build_flags(name,.true.,error)
153-
if (allocated(error)) return
154-
155-
do i=1,size(flags)
156-
157-
if (str_begins_with_str(flags(i)%s,include_flag)) then
158-
this%has_include_dirs = .true.
159-
this%incl_dirs = [this%incl_dirs, string_t(flags(i)%s(len(include_flag)+1:))]
160-
else
161-
this%has_build_flags = .true.
162-
this%flags = string_t(trim(this%flags%s)//' '//flags(i)%s)
163-
end if
164-
165-
end do
166-
167120
!> Add HDF5 modules as external
168121
this%has_external_modules = .true.
169122
this%external_modules = [string_t('h5a'), &
@@ -189,49 +142,4 @@ subroutine init_hdf5(this,compiler,error)
189142
string_t('hdf5')]
190143

191144
end subroutine init_hdf5
192-
193-
!> Given a library name and folder, find extension and prefix
194-
subroutine lib_get_trailing(lib_name,lib_dir,prefix,suffix,found)
195-
character(*), intent(in) :: lib_name,lib_dir
196-
character(:), allocatable, intent(out) :: prefix,suffix
197-
logical, intent(out) :: found
198-
199-
character(*), parameter :: extensions(*) = [character(11) :: '.dll.a','.a','.dylib','.dll']
200-
logical :: is_file
201-
character(:), allocatable :: noext,tokens(:),path
202-
integer :: l,k
203-
204-
! Extract name with no extension
205-
call split(lib_name,tokens,'.')
206-
noext = trim(tokens(1))
207-
208-
! Get library extension: find file name: NAME.a, NAME.dll.a, NAME.dylib, libNAME.a, etc.
209-
found = .false.
210-
suffix = ""
211-
prefix = ""
212-
with_pref: do l=1,2
213-
if (l==2) then
214-
prefix = "lib"
215-
else
216-
prefix = ""
217-
end if
218-
find_ext: do k=1,size(extensions)
219-
path = join_path(lib_dir,prefix//noext//trim(extensions(k)))
220-
inquire(file=path,exist=is_file)
221-
222-
if (is_file) then
223-
suffix = trim(extensions(k))
224-
found = .true.
225-
exit with_pref
226-
end if
227-
end do find_ext
228-
end do with_pref
229-
230-
if (.not.found) then
231-
prefix = ""
232-
suffix = ""
233-
end if
234-
235-
end subroutine lib_get_trailing
236-
237145
end module fpm_meta_hdf5

src/metapackage/fpm_meta_util.f90

Lines changed: 118 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,118 @@
1+
module fpm_meta_util
2+
use fpm_meta_base, only: metapackage_t, destroy
3+
use fpm_filesystem, only: join_path
4+
use fpm_strings, only: split, string_t, str_begins_with_str
5+
use fpm_error, only: error_t
6+
use fpm_versioning, only: new_version
7+
use fpm_pkg_config, only: pkgcfg_get_libs, pkgcfg_get_build_flags, pkgcfg_get_version
8+
9+
implicit none
10+
11+
private
12+
13+
public :: add_pkg_config_compile_options, lib_get_trailing
14+
15+
contains
16+
17+
!> Add pkgconfig compile options to a metapackage
18+
subroutine add_pkg_config_compile_options(this, name, include_flag, libdir, error)
19+
class(metapackage_t), intent(inout) :: this
20+
character(len=*), intent(in) :: name
21+
character(len=*), intent(in) :: include_flag
22+
type(error_t), allocatable, intent(out) :: error
23+
24+
character(len=:), allocatable :: libdir, ext, pref
25+
type(string_t) :: log, this_lib
26+
type(string_t), allocatable :: libs(:), flags(:)
27+
integer :: i
28+
29+
!> Get version
30+
if (.not. allocated(this%version)) then
31+
log = pkgcfg_get_version(name, error)
32+
if (allocated(error)) return
33+
allocate(this%version)
34+
call new_version(this%version, log%s, error)
35+
if (allocated(error)) return
36+
end if
37+
38+
!> Get libraries
39+
libs = pkgcfg_get_libs(name, error)
40+
if (allocated(error)) return
41+
42+
libdir = ""
43+
do i = 1, size(libs)
44+
if (str_begins_with_str(libs(i)%s, '-l')) then
45+
this%has_link_libraries = .true.
46+
this%link_libs = [this%link_libs, string_t(libs(i)%s(3:))]
47+
else ! -L and others: concatenate
48+
this%has_link_flags = .true.
49+
this%link_flags = string_t(trim(this%link_flags%s)//' '//libs(i)%s)
50+
51+
! Also save library dir
52+
if (str_begins_with_str(libs(i)%s, '-L')) then
53+
libdir = libs(i)%s(3:)
54+
elseif (str_begins_with_str(libs(i)%s, '/LIBPATH')) then
55+
libdir = libs(i)%s(9:)
56+
end if
57+
end if
58+
end do
59+
60+
!> Get compiler flags
61+
flags = pkgcfg_get_build_flags(name, .true., error)
62+
if (allocated(error)) return
63+
64+
do i = 1, size(flags)
65+
if (str_begins_with_str(flags(i)%s, include_flag)) then
66+
this%has_include_dirs = .true.
67+
this%incl_dirs = [this%incl_dirs, string_t(flags(i)%s(len(include_flag)+1:))]
68+
else
69+
this%has_build_flags = .true.
70+
this%flags = string_t(trim(this%flags%s)//' '//flags(i)%s)
71+
end if
72+
end do
73+
end subroutine add_pkg_config_compile_options
74+
75+
!> Given a library name and folder, find extension and prefix
76+
subroutine lib_get_trailing(lib_name,lib_dir,prefix,suffix,found)
77+
character(*), intent(in) :: lib_name,lib_dir
78+
character(:), allocatable, intent(out) :: prefix,suffix
79+
logical, intent(out) :: found
80+
81+
character(*), parameter :: extensions(*) = [character(11) :: '.dll.a','.a','.dylib','.dll']
82+
logical :: is_file
83+
character(:), allocatable :: noext,tokens(:),path
84+
integer :: l,k
85+
86+
! Extract name with no extension
87+
call split(lib_name,tokens,'.')
88+
noext = trim(tokens(1))
89+
90+
! Get library extension: find file name: NAME.a, NAME.dll.a, NAME.dylib, libNAME.a, etc.
91+
found = .false.
92+
suffix = ""
93+
prefix = ""
94+
with_pref: do l=1,2
95+
if (l==2) then
96+
prefix = "lib"
97+
else
98+
prefix = ""
99+
end if
100+
find_ext: do k=1,size(extensions)
101+
path = join_path(lib_dir,prefix//noext//trim(extensions(k)))
102+
inquire(file=path,exist=is_file)
103+
104+
if (is_file) then
105+
suffix = trim(extensions(k))
106+
found = .true.
107+
exit with_pref
108+
end if
109+
end do find_ext
110+
end do with_pref
111+
112+
if (.not.found) then
113+
prefix = ""
114+
suffix = ""
115+
end if
116+
117+
end subroutine lib_get_trailing
118+
end module fpm_meta_util

0 commit comments

Comments
 (0)