Skip to content

Commit 28c4f16

Browse files
authored
Merge branch 'main' into fix_cached_dependency_update
2 parents 7d4f190 + 36edb6c commit 28c4f16

15 files changed

+864
-106
lines changed

.gitignore

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,3 +5,4 @@ build/*
55

66
# CodeBlocks
77
project/
8+

README.md

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -33,10 +33,10 @@ non-Fortran related package manager.
3333

3434
**Website: <https://fpm.fortran-lang.org/>**
3535

36-
## [Download](https://fpm.fortran-lang.org/en/how-to/installation.html)
36+
## [Download](https://fpm.fortran-lang.org/en/install/index.html)
3737

3838
Fpm is available on many platforms and through multiple package managers, see our Documentation
39-
webpage for a list of **[All Supported Installations](https://fpm.fortran-lang.org/en/how-to/installation.html)**.
39+
webpage for a list of **[All Supported Installations](https://fpm.fortran-lang.org/en/install/index.html)**.
4040

4141
The easiest installation routes are shown below.
4242

install.sh

100755100644
Lines changed: 38 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,28 @@ usage()
1818
echo ""
1919
}
2020

21+
# Return a download command
22+
get_fetch_command()
23+
{
24+
if command -v curl > /dev/null 2>&1; then
25+
echo "curl -L"
26+
elif command -v wget > /dev/null 2>&1; then
27+
echo "wget -O -"
28+
else
29+
echo "No download mechanism found. Install curl or wget first."
30+
return 1
31+
fi
32+
}
33+
34+
# Return value of the latest published release on GitHub, with no heading "v" (e.g., "0.7.0")
35+
get_latest_release()
36+
{
37+
$2 "https://api.github.com/repos/$1/releases/latest" | # Get latest release from GitHub api
38+
grep '"tag_name":' | # Get tag line
39+
sed -E 's/.*"([^"]+)".*/\1/' | # Pluck JSON value
40+
sed -E 's/^v//' # Remove heading "v" if present
41+
}
42+
2143
PREFIX="$HOME/.local"
2244

2345
while [ "$1" != "" ]; do
@@ -42,8 +64,23 @@ done
4264

4365
set -u # error on use of undefined variable
4466

45-
SOURCE_URL="https://github.com/fortran-lang/fpm/releases/download/v0.6.0/fpm-0.6.0.F90"
67+
# Get download command
68+
FETCH=$(get_fetch_command)
69+
if [ $? -ne 0 ]; then
70+
echo "No download mechanism found. Install curl or wget first."
71+
exit 2
72+
fi
73+
74+
LATEST_RELEASE=$(get_latest_release "fortran-lang/fpm" "$FETCH")
75+
76+
if [ -z "$LATEST_RELEASE" ]; then
77+
echo "Could not fetch the latest release from GitHub. Install curl or wget, and ensure network connectivity."
78+
exit 3
79+
fi
80+
81+
SOURCE_URL="https://github.com/fortran-lang/fpm/releases/download/v${LATEST_RELEASE}/fpm-${LATEST_RELEASE}.F90"
4682
BOOTSTRAP_DIR="build/bootstrap"
83+
4784
if [ -z ${FC+x} ]; then
4885
FC="gfortran"
4986
fi
@@ -53,15 +90,6 @@ fi
5390

5491
mkdir -p $BOOTSTRAP_DIR
5592

56-
if command -v curl > /dev/null 2>&1; then
57-
FETCH="curl -L"
58-
elif command -v wget > /dev/null 2>&1; then
59-
FETCH="wget -O -"
60-
else
61-
echo "No download mechanism found. Install curl or wget first."
62-
exit 1
63-
fi
64-
6593
$FETCH $SOURCE_URL > $BOOTSTRAP_DIR/fpm.F90
6694

6795
SAVEDIR="$(pwd)"

src/filesystem_utilities.c

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
#include <sys/stat.h>
22
#include <dirent.h>
33

4-
#if defined(__APPLE__) && !defined(__aarch64__)
4+
#if defined(__APPLE__) && !defined(__aarch64__) && !defined(__POWERPC__)
55
DIR * opendir$INODE64( const char * dirName );
66
struct dirent * readdir$INODE64( DIR * dir );
77
#define opendir opendir$INODE64

src/fpm.f90

Lines changed: 107 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
module fpm
22
use fpm_strings, only: string_t, operator(.in.), glob, join, string_cat, &
3-
lower, str_ends_with
3+
lower, str_ends_with, is_fortran_name, str_begins_with_str, &
4+
is_valid_module_name, len_trim
45
use fpm_backend, only: build_package
56
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
67
fpm_run_settings, fpm_install_settings, fpm_test_settings, &
@@ -96,6 +97,8 @@ subroutine build_model(model, settings, package, error)
9697
model%build_prefix = join_path("build", basename(model%compiler%fc))
9798

9899
model%include_tests = settings%build_tests
100+
model%enforce_module_names = package%build%module_naming
101+
model%module_prefix = package%build%module_prefix
99102

100103
allocate(model%packages(model%deps%ndep))
101104

@@ -157,6 +160,11 @@ subroutine build_model(model, settings, package, error)
157160
if (allocated(dependency%build%external_modules)) then
158161
model%external_modules = [model%external_modules, dependency%build%external_modules]
159162
end if
163+
164+
! Copy naming conventions from this dependency's manifest
165+
model%packages(i)%enforce_module_names = dependency%build%module_naming
166+
model%packages(i)%module_prefix = dependency%build%module_prefix
167+
160168
end associate
161169
end do
162170
if (allocated(error)) return
@@ -237,7 +245,11 @@ subroutine build_model(model, settings, package, error)
237245
write(*,*)'<INFO> CXX COMPILER OPTIONS: ', model%cxx_compile_flags
238246
write(*,*)'<INFO> LINKER OPTIONS: ', model%link_flags
239247
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
240-
end if
248+
end if
249+
250+
! Check for invalid module names
251+
call check_module_names(model, error)
252+
if (allocated(error)) return
241253

242254
! Check for duplicate modules
243255
call check_modules_for_duplicates(model, duplicates_found)
@@ -290,6 +302,99 @@ subroutine check_modules_for_duplicates(model, duplicates_found)
290302
end do
291303
end subroutine check_modules_for_duplicates
292304

305+
! Check names of all modules in this package and its dependencies
306+
subroutine check_module_names(model, error)
307+
type(fpm_model_t), intent(in) :: model
308+
type(error_t), allocatable, intent(out) :: error
309+
integer :: i,j,k,l,m
310+
logical :: valid,errors_found,enforce_this_file
311+
type(string_t) :: package_name,module_name,package_prefix
312+
313+
errors_found = .false.
314+
315+
! Loop through modules provided by each source file of every package
316+
! Add it to the array if it is not already there
317+
! Otherwise print out warning about duplicates
318+
do k=1,size(model%packages)
319+
320+
package_name = string_t(model%packages(k)%name)
321+
322+
! Custom prefix is taken from each dependency's manifest
323+
if (model%packages(k)%enforce_module_names) then
324+
package_prefix = model%packages(k)%module_prefix
325+
else
326+
package_prefix = string_t("")
327+
end if
328+
329+
! Warn the user if some of the dependencies have loose naming
330+
if (model%enforce_module_names .and. .not.model%packages(k)%enforce_module_names) then
331+
write(stderr, *) "Warning: Dependency ",package_name%s // &
332+
" does not enforce module naming, but project does. "
333+
end if
334+
335+
do l=1,size(model%packages(k)%sources)
336+
337+
! Module naming is not enforced in test modules
338+
enforce_this_file = model%enforce_module_names .and. &
339+
model%packages(k)%sources(l)%unit_scope/=FPM_SCOPE_TEST
340+
341+
if (allocated(model%packages(k)%sources(l)%modules_provided)) then
342+
343+
do m=1,size(model%packages(k)%sources(l)%modules_provided)
344+
345+
module_name = model%packages(k)%sources(l)%modules_provided(m)
346+
347+
valid = is_valid_module_name(module_name, &
348+
package_name, &
349+
package_prefix, &
350+
enforce_this_file)
351+
352+
if (.not.valid) then
353+
354+
if (enforce_this_file) then
355+
356+
if (len_trim(package_prefix)>0) then
357+
358+
write(stderr, *) "ERROR: Module ",module_name%s, &
359+
" in ",model%packages(k)%sources(l)%file_name, &
360+
" does not match its package name ("//package_name%s// &
361+
") or custom prefix ("//package_prefix%s//")."
362+
else
363+
364+
write(stderr, *) "ERROR: Module ",module_name%s, &
365+
" in ",model%packages(k)%sources(l)%file_name, &
366+
" does not match its package name ("//package_name%s//")."
367+
368+
endif
369+
370+
else
371+
372+
write(stderr, *) "ERROR: Module ",module_name%s, &
373+
" in ",model%packages(k)%sources(l)%file_name, &
374+
" has an invalid Fortran name. "
375+
376+
end if
377+
378+
errors_found = .true.
379+
380+
end if
381+
end do
382+
end if
383+
end do
384+
end do
385+
386+
if (errors_found) then
387+
388+
if (model%enforce_module_names) &
389+
write(stderr, *) " Hint: Try disabling module naming in the manifest: [build] module-naming=false . "
390+
391+
call fatal_error(error,"The package contains invalid module names. "// &
392+
"Naming conventions "//merge('are','not',model%enforce_module_names)// &
393+
" being requested.")
394+
end if
395+
396+
end subroutine check_module_names
397+
293398
subroutine cmd_build(settings)
294399
type(fpm_build_settings), intent(in) :: settings
295400
type(package_config_t) :: package

src/fpm/error.f90

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -166,12 +166,16 @@ subroutine fpm_stop(value,message)
166166
integer, intent(in) :: value
167167
!> Error message
168168
character(len=*), intent(in) :: message
169+
integer :: iostat
169170
if(message/='')then
171+
flush(unit=stderr,iostat=iostat)
172+
flush(unit=stdout,iostat=iostat)
170173
if(value>0)then
171174
write(stderr,'("<ERROR>",a)')trim(message)
172175
else
173176
write(stderr,'("<INFO> ",a)')trim(message)
174177
endif
178+
flush(unit=stderr,iostat=iostat)
175179
endif
176180
stop value
177181
end subroutine fpm_stop

src/fpm/manifest/build.f90

Lines changed: 38 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -11,14 +11,13 @@
1111
!>```
1212
module fpm_manifest_build
1313
use fpm_error, only : error_t, syntax_error, fatal_error
14-
use fpm_strings, only : string_t
14+
use fpm_strings, only : string_t, len_trim, is_valid_module_prefix
1515
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value, get_list
1616
implicit none
1717
private
1818

1919
public :: build_config_t, new_build_config
2020

21-
2221
!> Configuration data for build
2322
type :: build_config_t
2423

@@ -31,6 +30,10 @@ module fpm_manifest_build
3130
!> Automatic discovery of tests
3231
logical :: auto_tests
3332

33+
!> Enforcing of package module names
34+
logical :: module_naming = .false.
35+
type(string_t) :: module_prefix
36+
3437
!> Libraries to link against
3538
type(string_t), allocatable :: link(:)
3639

@@ -86,6 +89,35 @@ subroutine new_build_config(self, table, error)
8689
return
8790
end if
8891

92+
!> Module naming: fist, attempt boolean value first
93+
call get_value(table, "module-naming", self%module_naming, .false., stat=stat)
94+
95+
if (stat == toml_stat%success) then
96+
97+
! Boolean value found. Set no custom prefix. This also falls back to
98+
! key not provided
99+
self%module_prefix = string_t("")
100+
101+
else
102+
103+
!> Value found, but not a boolean. Attempt to read a prefix string
104+
call get_value(table, "module-naming", self%module_prefix%s)
105+
106+
if (.not.allocated(self%module_prefix%s)) then
107+
call syntax_error(error,"Could not read value for 'module-naming' in fpm.toml, expecting logical or a string")
108+
return
109+
end if
110+
111+
if (.not.is_valid_module_prefix(self%module_prefix)) then
112+
call syntax_error(error,"Invalid custom module name prefix for in fpm.toml: <"//self%module_prefix%s// &
113+
">, expecting a valid alphanumeric string")
114+
return
115+
end if
116+
117+
! Set module naming to ON
118+
self%module_naming = .true.
119+
120+
end if
89121

90122
call get_list(table, "link", self%link, error)
91123
if (allocated(error)) return
@@ -95,7 +127,6 @@ subroutine new_build_config(self, table, error)
95127

96128
end subroutine new_build_config
97129

98-
99130
!> Check local schema for allowed entries
100131
subroutine check(table, error)
101132

@@ -119,6 +150,9 @@ subroutine check(table, error)
119150
case("auto-executables", "auto-examples", "auto-tests", "link", "external-modules")
120151
continue
121152

153+
case ("module-naming")
154+
continue
155+
122156
case default
123157
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in [build]")
124158
exit
@@ -156,6 +190,7 @@ subroutine info(self, unit, verbosity)
156190
write(unit, fmt) " - auto-discovery (apps) ", merge("enabled ", "disabled", self%auto_executables)
157191
write(unit, fmt) " - auto-discovery (examples) ", merge("enabled ", "disabled", self%auto_examples)
158192
write(unit, fmt) " - auto-discovery (tests) ", merge("enabled ", "disabled", self%auto_tests)
193+
write(unit, fmt) " - enforce module naming ", merge("enabled ", "disabled", self%module_naming)
159194
if (allocated(self%link)) then
160195
write(unit, fmt) " - link against"
161196
do ilink = 1, size(self%link)

src/fpm_compiler.f90 renamed to src/fpm_compiler.F90

Lines changed: 18 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -937,9 +937,9 @@ end subroutine link
937937

938938

939939
!> Create an archive
940-
!> @todo An OMP critical section is added for Windows OS,
941-
!> which may be related to a bug in Mingw64-openmp and is expected to be resolved in the future,
942-
!> see issue #707 and #708.
940+
!> @todo For Windows OS, use the local `delete_file_win32` in stead of `delete_file`.
941+
!> This may be related to a bug in Mingw64-openmp and is expected to be resolved in the future,
942+
!> see issue #707, #708 and #808.
943943
subroutine make_archive(self, output, args, log_file, stat)
944944
!> Instance of the archiver object
945945
class(archiver_t), intent(in) :: self
@@ -953,16 +953,27 @@ subroutine make_archive(self, output, args, log_file, stat)
953953
integer, intent(out) :: stat
954954

955955
if (self%use_response_file) then
956-
!$omp critical
957956
call write_response_file(output//".resp" , args)
958957
call run(self%ar // output // " @" // output//".resp", echo=self%echo, &
959958
& verbose=self%verbose, redirect=log_file, exitstat=stat)
960-
call delete_file(output//".resp")
961-
!$omp end critical
959+
call delete_file_win32(output//".resp")
960+
962961
else
963962
call run(self%ar // output // " " // string_cat(args, " "), &
964963
& echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
965964
end if
965+
966+
contains
967+
subroutine delete_file_win32(file)
968+
character(len=*), intent(in) :: file
969+
logical :: exist
970+
integer :: unit, iostat
971+
inquire(file=file, exist=exist)
972+
if (exist) then
973+
open(file=file, newunit=unit)
974+
close(unit, status='delete', iostat=iostat)
975+
end if
976+
end subroutine delete_file_win32
966977
end subroutine make_archive
967978

968979

@@ -976,7 +987,7 @@ subroutine write_response_file(name, argv)
976987

977988
integer :: iarg, io
978989

979-
open(file=name, newunit=io)
990+
open(file=name, newunit=io, status='replace')
980991
do iarg = 1, size(argv)
981992
write(io, '(a)') unix_path(argv(iarg)%s)
982993
end do

0 commit comments

Comments
 (0)