Skip to content

Commit 79d4baf

Browse files
committed
add missing Fortran libs for Ubuntu
1 parent 559b9b0 commit 79d4baf

File tree

1 file changed

+112
-55
lines changed

1 file changed

+112
-55
lines changed

src/fpm_meta.f90

Lines changed: 112 additions & 55 deletions
Original file line numberDiff line numberDiff line change
@@ -1684,23 +1684,67 @@ subroutine filter_link_arguments(compiler,command)
16841684

16851685
end subroutine filter_link_arguments
16861686

1687+
!> Given a library name and folder, find extension and prefix
1688+
subroutine lib_get_trailing(lib_name,lib_dir,prefix,suffix,found)
1689+
character(*), intent(in) :: lib_name,lib_dir
1690+
character(:), allocatable, intent(out) :: prefix,suffix
1691+
logical, intent(out) :: found
1692+
1693+
character(*), parameter :: extensions(*) = [character(11) :: '.dll.a','.a','.dylib','.dll']
1694+
logical :: is_file
1695+
character(:), allocatable :: noext,tokens(:),path
1696+
integer :: l,k
1697+
1698+
! Extract name with no extension
1699+
call split(lib_name,tokens,'.')
1700+
noext = trim(tokens(1))
1701+
1702+
! Get library extension: find file name: NAME.a, NAME.dll.a, NAME.dylib, libNAME.a, etc.
1703+
found = .false.
1704+
suffix = ""
1705+
prefix = ""
1706+
with_pref: do l=1,2
1707+
if (l==2) then
1708+
prefix = "lib"
1709+
else
1710+
prefix = ""
1711+
end if
1712+
find_ext: do k=1,size(extensions)
1713+
path = join_path(lib_dir,prefix//noext//trim(extensions(k)))
1714+
inquire(file=path,exist=is_file)
1715+
1716+
if (is_file) then
1717+
suffix = trim(extensions(k))
1718+
found = .true.
1719+
exit with_pref
1720+
end if
1721+
end do find_ext
1722+
end do with_pref
1723+
1724+
if (.not.found) then
1725+
prefix = ""
1726+
suffix = ""
1727+
end if
1728+
1729+
end subroutine lib_get_trailing
1730+
16871731
!> Initialize HDF5 metapackage for the current system
16881732
subroutine init_hdf5(this,compiler,error)
16891733
class(metapackage_t), intent(inout) :: this
16901734
type(compiler_t), intent(in) :: compiler
16911735
type(error_t), allocatable, intent(out) :: error
1692-
1736+
16931737
character(*), parameter :: find_hl(*) = &
16941738
[character(11) :: '_hl_fortran','hl_fortran','_fortran','_hl']
1695-
character(*), parameter :: candidates(5) = &
1739+
character(*), parameter :: candidates(*) = &
16961740
[character(15) :: 'hdf5_hl_fortran','hdf5-hl-fortran','hdf5_fortran','hdf5-fortran',&
16971741
'hdf5_hl','hdf5','hdf5-serial']
16981742

1699-
integer :: i,j,k
1700-
logical :: s,found_hl(size(find_hl))
1701-
type(string_t) :: log
1743+
integer :: i,j,k,l
1744+
logical :: s,found_hl(size(find_hl)),found
1745+
type(string_t) :: log,this_lib
17021746
type(string_t), allocatable :: libs(:),flags(:),modules(:),non_fortran(:)
1703-
character(len=:), allocatable :: name,module_flag,include_flag
1747+
character(len=:), allocatable :: name,module_flag,include_flag,libdir,ext,pref
17041748

17051749
module_flag = get_module_flag(compiler,"")
17061750
include_flag = get_include_flag(compiler,"")
@@ -1752,6 +1796,8 @@ subroutine init_hdf5(this,compiler,error)
17521796
!> Get libraries
17531797
libs = pkgcfg_get_libs(name,error)
17541798
if (allocated(error)) return
1799+
1800+
libdir = ""
17551801
do i=1,size(libs)
17561802

17571803
if (str_begins_with_str(libs(i)%s,'-l')) then
@@ -1760,66 +1806,77 @@ subroutine init_hdf5(this,compiler,error)
17601806

17611807
print *, 'HDF5: add link library '//libs(i)%s(3:)
17621808

1763-
else ! -L and other: concatenate
1809+
else ! -L and others: concatenate
17641810
this%has_link_flags = .true.
17651811
this%link_flags = string_t(trim(this%link_flags%s)//' '//libs(i)%s)
1812+
1813+
! Also save library dir
1814+
if (str_begins_with_str(libs(i)%s,'-L')) then
1815+
libdir = libs(i)%s(3:)
1816+
elseif (str_begins_with_str(libs(i)%s,'/LIBPATH')) then
1817+
libdir = libs(i)%s(9:)
1818+
endif
17661819

17671820
print *, 'HDF5: add link flag '//libs(i)%s
17681821

17691822
end if
17701823
end do
17711824

1825+
print *, 'libdir = ',libdir
1826+
do i=1,size(this%link_libs)
1827+
print *, '-l'//this%link_libs(i)%s
1828+
end do
1829+
1830+
17721831
! Some pkg-config hdf5.pc (e.g. Ubuntu) don't include the commonly-used HL HDF5 libraries,
17731832
! so let's add them if they exist
1774-
do i=1,size(this%link_libs)
1775-
1776-
found_hl = .false.
1777-
1778-
if (.not.str_ends_with(this%link_libs(i)%s, find_hl)) then
1833+
if (len_trim(libdir)>0) then
1834+
do i=1,size(this%link_libs)
17791835

1780-
finals: do k=1,size(find_hl)
1781-
do j=1,size(this%link_libs)
1782-
if (str_begins_with_str(this%link_libs(j)%s,this%link_libs(i)%s) .and. &
1783-
str_ends_with(this%link_libs(j)%s,find_hl(k))) then
1784-
found_hl(k) = .true.
1785-
cycle finals
1786-
end if
1787-
end do
1788-
end do finals
1789-
1790-
! For each of the missing libraries, if there is a file,
1791-
!
1792-
1793-
1794-
print *, this%link_libs(i)%s,' does not end: ',found_hl
1795-
1796-
end if
1797-
1798-
!
1799-
! for larg in self.get_link_args():
1800-
! lpath = Path(larg)
1801-
! # some pkg-config hdf5.pc (e.g. Ubuntu) don't include the commonly-used HL HDF5 libraries,
1802-
! # so let's add them if they exist
1803-
! # additionally, some pkgconfig HDF5 HL files are malformed so let's be sure to find HL anyway
1804-
! if lpath.is_file():
1805-
! hl = []
1806-
! if language == 'cpp':
1807-
! hl += ['_hl_cpp', '_cpp']
1808-
! elif language == 'fortran':
1809-
! hl += ['_hl_fortran', 'hl_fortran', '_fortran']
1810-
! hl += ['_hl'] # C HL library, always needed
1811-
!
1812-
! suffix = '.' + lpath.name.split('.', 1)[1] # in case of .dll.a
1813-
! for h in hl:
1814-
! hlfn = lpath.parent / (lpath.name.split('.', 1)[0] + h + suffix)
1815-
! if hlfn.is_file():
1816-
! link_args.append(str(hlfn))
1817-
! # HDF5 C libs are required by other HDF5 languages
1818-
! link_args.append(larg)
1819-
! else:
1820-
! link_args.append(larg)
1821-
!
1822-
1836+
found_hl = .false.
1837+
1838+
if (.not.str_ends_with(this%link_libs(i)%s, find_hl)) then
1839+
1840+
! Extract name with no extension
1841+
call lib_get_trailing(this%link_libs(i)%s, libdir, pref, ext, found)
1842+
1843+
! Search how many versions with the Fortran endings there are
1844+
finals: do k=1,size(find_hl)
1845+
do j=1,size(this%link_libs)
1846+
print *, this%link_libs(j)%s,' begins? ',str_begins_with_str(this%link_libs(j)%s,this%link_libs(i)%s), &
1847+
' ends? ',str_ends_with(this%link_libs(j)%s,trim(find_hl(k)))
1848+
if (str_begins_with_str(this%link_libs(j)%s,this%link_libs(i)%s) .and. &
1849+
str_ends_with(this%link_libs(j)%s,trim(find_hl(k)))) then
1850+
found_hl(k) = .true.
1851+
cycle finals
1852+
end if
1853+
end do
1854+
end do finals
1855+
1856+
print *, 'lib ',this%link_libs(i)%s,' found = ',found_hl
1857+
1858+
! For each of the missing ones, if there is a file, add it
1859+
add_missing: do k=1,size(find_hl)
1860+
if (found_hl(k)) cycle add_missing
1861+
1862+
! Build file name
1863+
this_lib%s = join_path(libdir,pref//this%link_libs(i)%s//trim(find_hl(k))//ext)
1864+
inquire(file=this_lib%s,exist=found)
1865+
1866+
! File exists, but it is not linked against
1867+
if (found) this%link_libs = [this%link_libs, &
1868+
string_t(this%link_libs(i)%s//trim(find_hl(k)))]
1869+
1870+
end do add_missing
1871+
1872+
end if
1873+
1874+
end do
1875+
endif
1876+
1877+
print *, 'final link libs: '
1878+
do i=1,size(this%link_libs)
1879+
print *, '-l'//this%link_libs(i)%s
18231880
end do
18241881

18251882
!

0 commit comments

Comments
 (0)