Skip to content

Commit 7e9c339

Browse files
committed
Merge branch 'upstream_master' into backend-grace
2 parents 086ae55 + 845217f commit 7e9c339

18 files changed

+456
-87
lines changed

CONTRIBUTING.md

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -8,8 +8,7 @@ help address your problem, evaluate changes, and guide you through your pull
88
requests.
99

1010
By contributing to *fpm*, you certify that you own or are allowed to share the
11-
content of your contribution under the
12-
[fpm license](https://github.com/fortran-lang/fpm/blob/master/LICENSE).
11+
content of your contribution under the [fpm license](LICENSE).
1312

1413
* [Style](#style)
1514
* [Reporting a bug](#reporting-a-bug)
@@ -35,7 +34,7 @@ Before opening a bug report:
3534
1. Check if the issue has already been reported
3635
([issues](https://github.com/fortran-lang/fpm/issues)).
3736
2. Check if it is still an issue or it has been fixed?
38-
Try to reproduce it with the latest version from the master branch.
37+
Try to reproduce it with the latest version from the default branch.
3938
3. Isolate the problem and create a minimal test case.
4039

4140
A good bug report should include all information needed to reproduce the bug.

README.md

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,7 @@ or from [miniconda](https://docs.conda.io/en/latest/miniconda.html).
6060

6161
To setup *fpm* within Github actions for automated testing, you can use the [fortran-lang/setup-fpm](https://github.com/marketplace/actions/setup-fpm) action.
6262

63-
#### Bootstraping on other platforms
63+
#### Bootstrapping on other platforms
6464

6565
For other platforms and architectures have a look at the [bootstrapping instructions](#bootstrapping-instructions).
6666

@@ -101,7 +101,7 @@ This guide explains the process of building *fpm* on a platform for the first ti
101101
To build *fpm* without a prior *fpm* version a single source file version is available
102102
at each release.
103103

104-
To build manually using the single source distribution use
104+
To build manually using the single source distribution, run the following code (from within the current directory)
105105

106106
```
107107
mkdir _tmp

app/main.f90

Lines changed: 77 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
program main
2+
use, intrinsic :: iso_fortran_env, only : error_unit, output_unit
23
use fpm_command_line, only: &
34
fpm_cmd_settings, &
45
fpm_new_settings, &
@@ -8,17 +9,57 @@ program main
89
fpm_install_settings, &
910
fpm_update_settings, &
1011
get_command_line_settings
12+
use fpm_error, only: error_t
13+
use fpm_filesystem, only: exists, parent_dir, join_path
1114
use fpm, only: cmd_build, cmd_run
1215
use fpm_cmd_install, only: cmd_install
1316
use fpm_cmd_new, only: cmd_new
1417
use fpm_cmd_update, only : cmd_update
18+
use fpm_os, only: change_directory, get_current_directory
1519

1620
implicit none
1721

1822
class(fpm_cmd_settings), allocatable :: cmd_settings
23+
type(error_t), allocatable :: error
24+
character(len=:), allocatable :: pwd_start, pwd_working, working_dir, project_root
1925

2026
call get_command_line_settings(cmd_settings)
2127

28+
call get_current_directory(pwd_start, error)
29+
call handle_error(error)
30+
31+
call get_working_dir(cmd_settings, working_dir)
32+
if (allocated(working_dir)) then
33+
! Change working directory if requested
34+
if (len_trim(working_dir) > 0) then
35+
call change_directory(working_dir, error)
36+
call handle_error(error)
37+
38+
call get_current_directory(pwd_working, error)
39+
call handle_error(error)
40+
write(output_unit, '(*(a))') "fpm: Entering directory '"//pwd_working//"'"
41+
else
42+
pwd_working = pwd_start
43+
end if
44+
else
45+
pwd_working = pwd_start
46+
end if
47+
48+
if (.not.has_manifest(pwd_working)) then
49+
project_root = pwd_working
50+
do while(.not.has_manifest(project_root))
51+
working_dir = parent_dir(project_root)
52+
if (len(working_dir) == 0) exit
53+
project_root = working_dir
54+
end do
55+
56+
if (has_manifest(project_root)) then
57+
call change_directory(project_root, error)
58+
call handle_error(error)
59+
write(output_unit, '(*(a))') "fpm: Entering directory '"//project_root//"'"
60+
end if
61+
end if
62+
2263
select type(settings=>cmd_settings)
2364
type is (fpm_new_settings)
2465
call cmd_new(settings)
@@ -34,4 +75,40 @@ program main
3475
call cmd_update(settings)
3576
end select
3677

78+
if (allocated(project_root)) then
79+
write(output_unit, '(*(a))') "fpm: Leaving directory '"//project_root//"'"
80+
end if
81+
82+
if (pwd_start /= pwd_working) then
83+
write(output_unit, '(*(a))') "fpm: Leaving directory '"//pwd_working//"'"
84+
end if
85+
86+
contains
87+
88+
function has_manifest(dir)
89+
character(len=*), intent(in) :: dir
90+
logical :: has_manifest
91+
92+
character(len=:), allocatable :: manifest
93+
94+
has_manifest = exists(join_path(dir, "fpm.toml"))
95+
end function has_manifest
96+
97+
subroutine handle_error(error)
98+
type(error_t), optional, intent(in) :: error
99+
if (present(error)) then
100+
write(error_unit, '("[Error]", 1x, a)') error%message
101+
stop 1
102+
end if
103+
end subroutine handle_error
104+
105+
!> Save access to working directory in settings, in case setting have not been allocated
106+
subroutine get_working_dir(settings, working_dir)
107+
class(fpm_cmd_settings), optional, intent(in) :: settings
108+
character(len=:), allocatable, intent(out) :: working_dir
109+
if (present(settings)) then
110+
working_dir = settings%working_dir
111+
end if
112+
end subroutine get_working_dir
113+
37114
end program main

ci/run_tests.sh

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -13,11 +13,10 @@ fi
1313
pushd example_packages/
1414
rm -rf ./*/build
1515

16-
pushd hello_world
17-
"$fpm" build
18-
"$fpm" run --target hello_world
19-
"$fpm" run
20-
popd
16+
dir=hello_world
17+
"$fpm" -C $dir build
18+
"$fpm" -C $dir run --target hello_world
19+
"$fpm" -C $dir/app run
2120

2221
pushd hello_fpm
2322
"$fpm" build

manifest-reference.md

Lines changed: 27 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,8 @@ Every manifest file consists of the following sections:
3333
Toggle automatic discovery of executables
3434
- [*link*](#link-external-libraries):
3535
Link with external dependencies
36+
- [*external-modules*](#use-system-installed-modules):
37+
Specify modules used that are not within your fpm package
3638
- Target sections:
3739
- [*library*](#library-configuration)
3840
Configuration of the library target
@@ -353,6 +355,30 @@ In this case the order of the libraries matters:
353355
link = ["blas", "lapack"]
354356
```
355357

358+
## Use system-installed modules
359+
360+
To use modules that are not defined within your fpm package or its dependencies,
361+
specify the module name using the *external-modules* key in the *build* table.
362+
363+
> __Important:__ *fpm* cannot automatically locate external module files; it is the responsibility
364+
> of the user to specify the necessary include directories using compiler flags such that
365+
> the compiler can locate external module files during compilation.
366+
367+
*Example:*
368+
369+
```toml
370+
[build]
371+
external-modules = "netcdf"
372+
```
373+
374+
Multiple external modules can be specified as a list.
375+
376+
*Example:*
377+
378+
```toml
379+
[build]
380+
external-modules = ["netcdf", "h5lt"]
381+
```
356382

357383
## Automatic target discovery
358384

@@ -403,7 +429,7 @@ To use a specific upstream branch declare the *branch* name with
403429

404430
```toml
405431
[dependencies]
406-
toml-f = { git = "https://github.com/toml-f/toml-f", branch = "master" }
432+
toml-f = { git = "https://github.com/toml-f/toml-f", branch = "main" }
407433
```
408434

409435
Alternatively, reference tags by using the *tag* entry

src/fpm.f90

Lines changed: 19 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -4,12 +4,12 @@ module fpm
44
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
55
fpm_run_settings, fpm_install_settings, fpm_test_settings
66
use fpm_dependency, only : new_dependency_tree
7-
use fpm_environment, only: run
7+
use fpm_environment, only: run, get_env, get_archiver
88
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
99
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
1010
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
1111
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
12-
use fpm_compiler, only: get_module_flags, is_unknown_compiler
12+
use fpm_compiler, only: get_module_flags, is_unknown_compiler, get_default_c_compiler
1313

1414

1515
use fpm_sources, only: add_executable_sources, add_sources_from_dir
@@ -51,6 +51,7 @@ subroutine build_model(model, settings, package, error)
5151

5252
allocate(model%include_dirs(0))
5353
allocate(model%link_libraries(0))
54+
allocate(model%external_modules(0))
5455

5556
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"))
5657
call model%deps%add(package, error)
@@ -62,6 +63,10 @@ subroutine build_model(model, settings, package, error)
6263
model%fortran_compiler = settings%compiler
6364
endif
6465

66+
model%archiver = get_archiver()
67+
call get_default_c_compiler(model%fortran_compiler, model%c_compiler)
68+
model%c_compiler = get_env('FPM_C_COMPILER',model%c_compiler)
69+
6570
if (is_unknown_compiler(model%fortran_compiler)) then
6671
write(*, '(*(a:,1x))') &
6772
"<WARN>", "Unknown compiler", model%fortran_compiler, "requested!", &
@@ -147,7 +152,7 @@ subroutine build_model(model, settings, package, error)
147152
if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))
148153

149154
if (allocated(dependency%library)) then
150-
155+
151156
if (allocated(dependency%library%source_dir)) then
152157
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
153158
if (is_dir(lib_dir)) then
@@ -165,21 +170,26 @@ subroutine build_model(model, settings, package, error)
165170
end if
166171
end do
167172
end if
168-
173+
169174
end if
170175

171176
if (allocated(dependency%build%link)) then
172177
model%link_libraries = [model%link_libraries, dependency%build%link]
173178
end if
179+
180+
if (allocated(dependency%build%external_modules)) then
181+
model%external_modules = [model%external_modules, dependency%build%external_modules]
182+
end if
174183
end associate
175184
end do
176185
if (allocated(error)) return
177186

178187
if (settings%verbose) then
179188
write(*,*)'<INFO> BUILD_NAME: ',settings%build_name
180189
write(*,*)'<INFO> COMPILER: ',settings%compiler
181-
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
182-
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
190+
write(*,*)'<INFO> C COMPILER: ',model%c_compiler
191+
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
192+
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
183193
end if
184194

185195
! Check for duplicate modules
@@ -190,7 +200,7 @@ subroutine build_model(model, settings, package, error)
190200
end subroutine build_model
191201

192202
! Check for duplicate modules
193-
subroutine check_modules_for_duplicates(model, duplicates_found)
203+
subroutine check_modules_for_duplicates(model, duplicates_found)
194204
type(fpm_model_t), intent(in) :: model
195205
integer :: maxsize
196206
integer :: i,j,k,l,m,modi
@@ -370,7 +380,7 @@ subroutine cmd_run(settings,test)
370380

371381
! Check all names are valid
372382
! or no name and found more than one file
373-
toomany= size(settings%name).eq.0 .and. size(executables).gt.1
383+
toomany= size(settings%name).eq.0 .and. size(executables).gt.1
374384
if ( any(.not.found) &
375385
& .or. &
376386
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
@@ -420,7 +430,7 @@ subroutine cmd_run(settings,test)
420430
end if
421431
end do
422432
endif
423-
contains
433+
contains
424434
subroutine compact_list_all()
425435
integer, parameter :: LINE_WIDTH = 80
426436
integer :: i, j, nCol

src/fpm/cmd/new.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -347,7 +347,7 @@ subroutine cmd_new(settings)
347347
&' # git repository. ',&
348348
&' # ',&
349349
&' # You can be specific about which version of a dependency you would ',&
350-
&' # like. By default the latest master master branch is used. You can ',&
350+
&' # like. By default the latest default branch is used. You can ',&
351351
&' # optionally specify a branch, a tag or a commit value. ',&
352352
&' # ',&
353353
&' # So here are several alternates for specifying a remote dependency (you ',&

src/fpm/manifest/build.f90

Lines changed: 14 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -34,6 +34,9 @@ module fpm_manifest_build
3434
!> Libraries to link against
3535
type(string_t), allocatable :: link(:)
3636

37+
!> External modules to use
38+
type(string_t), allocatable :: external_modules(:)
39+
3740
contains
3841

3942
!> Print information on this instance
@@ -87,6 +90,9 @@ subroutine new_build_config(self, table, error)
8790
call get_value(table, "link", self%link, error)
8891
if (allocated(error)) return
8992

93+
call get_value(table, "external-modules", self%external_modules, error)
94+
if (allocated(error)) return
95+
9096
end subroutine new_build_config
9197

9298

@@ -110,7 +116,7 @@ subroutine check(table, error)
110116
do ikey = 1, size(list)
111117
select case(list(ikey)%key)
112118

113-
case("auto-executables", "auto-examples", "auto-tests", "link")
119+
case("auto-executables", "auto-examples", "auto-tests", "link", "external-modules")
114120
continue
115121

116122
case default
@@ -135,7 +141,7 @@ subroutine info(self, unit, verbosity)
135141
!> Verbosity of the printout
136142
integer, intent(in), optional :: verbosity
137143

138-
integer :: pr, ilink
144+
integer :: pr, ilink, imod
139145
character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)'
140146

141147
if (present(verbosity)) then
@@ -156,6 +162,12 @@ subroutine info(self, unit, verbosity)
156162
write(unit, fmt) " - " // self%link(ilink)%s
157163
end do
158164
end if
165+
if (allocated(self%external_modules)) then
166+
write(unit, fmt) " - external modules"
167+
do imod = 1, size(self%external_modules)
168+
write(unit, fmt) " - " // self%external_modules(imod)%s
169+
end do
170+
end if
159171

160172
end subroutine info
161173

0 commit comments

Comments
 (0)