Skip to content

Commit 3c1d638

Browse files
Merge branch 'master' into response-files
2 parents 7a8f337 + 6d9004d commit 3c1d638

13 files changed

+137
-64
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: 1 addition & 1 deletion
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

manifest-reference.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -429,7 +429,7 @@ To use a specific upstream branch declare the *branch* name with
429429

430430
```toml
431431
[dependencies]
432-
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" }
433433
```
434434

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

src/fpm.f90

Lines changed: 14 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
@@ -63,6 +63,10 @@ subroutine build_model(model, settings, package, error)
6363
model%fortran_compiler = settings%compiler
6464
endif
6565

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+
6670
if (is_unknown_compiler(model%fortran_compiler)) then
6771
write(*, '(*(a:,1x))') &
6872
"<WARN>", "Unknown compiler", model%fortran_compiler, "requested!", &
@@ -148,7 +152,7 @@ subroutine build_model(model, settings, package, error)
148152
if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))
149153

150154
if (allocated(dependency%library)) then
151-
155+
152156
if (allocated(dependency%library%source_dir)) then
153157
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
154158
if (is_dir(lib_dir)) then
@@ -166,7 +170,7 @@ subroutine build_model(model, settings, package, error)
166170
end if
167171
end do
168172
end if
169-
173+
170174
end if
171175

172176
if (allocated(dependency%build%link)) then
@@ -183,8 +187,9 @@ subroutine build_model(model, settings, package, error)
183187
if (settings%verbose) then
184188
write(*,*)'<INFO> BUILD_NAME: ',settings%build_name
185189
write(*,*)'<INFO> COMPILER: ',settings%compiler
186-
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
187-
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,','),']'
188193
end if
189194

190195
! Check for duplicate modules
@@ -195,7 +200,7 @@ subroutine build_model(model, settings, package, error)
195200
end subroutine build_model
196201

197202
! Check for duplicate modules
198-
subroutine check_modules_for_duplicates(model, duplicates_found)
203+
subroutine check_modules_for_duplicates(model, duplicates_found)
199204
type(fpm_model_t), intent(in) :: model
200205
integer :: maxsize
201206
integer :: i,j,k,l,m,modi
@@ -375,7 +380,7 @@ subroutine cmd_run(settings,test)
375380

376381
! Check all names are valid
377382
! or no name and found more than one file
378-
toomany= size(settings%name).eq.0 .and. size(executables).gt.1
383+
toomany= size(settings%name).eq.0 .and. size(executables).gt.1
379384
if ( any(.not.found) &
380385
& .or. &
381386
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
@@ -425,7 +430,7 @@ subroutine cmd_run(settings,test)
425430
end if
426431
end do
427432
endif
428-
contains
433+
contains
429434
subroutine compact_list_all()
430435
integer, parameter :: LINE_WIDTH = 80
431436
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_backend.f90

Lines changed: 24 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -1,38 +1,37 @@
11
!># Build backend
2-
!> Uses a list of `[[build_target_ptr]]` and a valid `[[fpm_model]]` instance
2+
!> Uses a list of `[[build_target_ptr]]` and a valid `[[fpm_model]]` instance
33
!> to schedule and execute the compilation and linking of package targets.
4-
!>
4+
!>
55
!> The package build process (`[[build_package]]`) comprises three steps:
66
!>
77
!> 1. __Target sorting:__ topological sort of the target dependency graph (`[[sort_target]]`)
88
!> 2. __Target scheduling:__ group targets into schedule regions based on the sorting (`[[schedule_targets]]`)
99
!> 3. __Target building:__ generate targets by compilation or linking
10-
!>
10+
!>
1111
!> @note If compiled with OpenMP, targets will be build in parallel where possible.
1212
!>
1313
!>### Incremental compilation
14-
!> The backend process supports *incremental* compilation whereby targets are not
14+
!> The backend process supports *incremental* compilation whereby targets are not
1515
!> re-compiled if their corresponding dependencies have not been modified.
16-
!>
16+
!>
1717
!> - Source-based targets (*i.e.* objects) are not re-compiled if the corresponding source
1818
!> file is unmodified AND all of the target dependencies are not marked for re-compilation
1919
!>
20-
!> - Link targets (*i.e.* executables and libraries) are not re-compiled if the
20+
!> - Link targets (*i.e.* executables and libraries) are not re-compiled if the
2121
!> target output file already exists AND all of the target dependencies are not marked for
2222
!> re-compilation
2323
!>
2424
!> Source file modification is determined by a file digest (hash) which is calculated during
25-
!> the source parsing phase ([[fpm_source_parsing]]) and cached to disk after a target is
25+
!> the source parsing phase ([[fpm_source_parsing]]) and cached to disk after a target is
2626
!> successfully generated.
2727
!>
2828
module fpm_backend
2929

3030
use fpm_environment, only: run, get_os_type, OS_WINDOWS
3131
use fpm_filesystem, only: dirname, join_path, exists, mkdir, unix_path
3232
use fpm_model, only: fpm_model_t
33-
use fpm_targets, only: build_target_t, build_target_ptr, &
34-
FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
35-
33+
use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
34+
FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
3635
use fpm_strings, only: string_cat, string_t
3736

3837
implicit none
@@ -58,9 +57,9 @@ subroutine build_package(targets,model)
5857

5958
! Perform depth-first topological sort of targets
6059
do i=1,size(targets)
61-
60+
6261
call sort_target(targets(i)%ptr)
63-
62+
6463
end do
6564

6665
! Construct build schedule queue
@@ -78,20 +77,20 @@ subroutine build_package(targets,model)
7877
end do
7978

8079
end do
81-
80+
8281
end subroutine build_package
8382

8483

85-
!> Topologically sort a target for scheduling by
84+
!> Topologically sort a target for scheduling by
8685
!> recursing over its dependencies.
87-
!>
86+
!>
8887
!> Checks disk-cached source hashes to determine if objects are
8988
!> up-to-date. Up-to-date sources are tagged as skipped.
9089
!>
91-
!> On completion, `target` should either be marked as
90+
!> On completion, `target` should either be marked as
9291
!> sorted (`target%sorted=.true.`) or skipped (`target%skip=.true.`)
9392
!>
94-
!> If `target` is marked as sorted, `target%schedule` should be an
93+
!> If `target` is marked as sorted, `target%schedule` should be an
9594
!> integer greater than zero indicating the region for scheduling
9695
!>
9796
recursive subroutine sort_target(target)
@@ -162,7 +161,7 @@ recursive subroutine sort_target(target)
162161
end if
163162

164163
end do
165-
164+
166165
! Mark flag as processed: either sorted or skipped
167166
target%sorted = .not.target%skip
168167

@@ -241,8 +240,12 @@ subroutine build_target(model,target)
241240
call run(model%fortran_compiler//" -c " // target%source%file_name // target%compile_flags &
242241
// " -o " // target%output_file)
243242

243+
case (FPM_TARGET_C_OBJECT)
244+
call run(model%c_compiler//" -c " // target%source%file_name // target%compile_flags &
245+
// " -o " // target%output_file)
246+
244247
case (FPM_TARGET_EXECUTABLE)
245-
248+
246249
call run(model%fortran_compiler// " " // target%compile_flags &
247250
//" "//target%link_flags// " -o " // target%output_file)
248251

@@ -251,10 +254,10 @@ subroutine build_target(model,target)
251254
select case (get_os_type())
252255
case (OS_WINDOWS)
253256
call write_response_file(target%output_file//".resp" ,target%link_objects)
254-
call run("ar -rs " // target%output_file // " @" // target%output_file//".resp")
257+
call run(model%archiver // target%output_file // " @" // target%output_file//".resp")
255258

256259
case default
257-
call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," "))
260+
call run(model%archiver // target%output_file // " " // string_cat(target%link_objects," "))
258261

259262
end select
260263

src/fpm_command_line.f90

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@
2525
module fpm_command_line
2626
use fpm_environment, only : get_os_type, get_env, &
2727
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
28-
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
28+
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
2929
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
3030
use fpm_strings, only : lower, split, fnv_1a
3131
use fpm_filesystem, only : basename, canon_path, to_fortran_name
@@ -129,6 +129,7 @@ subroutine get_command_line_settings(cmd_settings)
129129
case (OS_CYGWIN); os_type = "OS Type: Cygwin"
130130
case (OS_SOLARIS); os_type = "OS Type: Solaris"
131131
case (OS_FREEBSD); os_type = "OS Type: FreeBSD"
132+
case (OS_OPENBSD); os_type = "OS Type: OpenBSD"
132133
case (OS_UNKNOWN); os_type = "OS Type: Unknown"
133134
case default ; os_type = "OS Type: UNKNOWN"
134135
end select

src/fpm_compiler.f90

Lines changed: 30 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,8 @@ module fpm_compiler
3535
OS_WINDOWS, &
3636
OS_CYGWIN, &
3737
OS_SOLARIS, &
38-
OS_FREEBSD
38+
OS_FREEBSD, &
39+
OS_OPENBSD
3940
implicit none
4041
public :: is_unknown_compiler
4142
public :: get_module_flags
@@ -239,7 +240,6 @@ subroutine get_debug_compile_flags(id, flags)
239240
& -g&
240241
& -assume byterecl&
241242
& -traceback&
242-
& -coarray=single&
243243
&'
244244
case(id_intel_classic_mac)
245245
flags = '&
@@ -260,7 +260,6 @@ subroutine get_debug_compile_flags(id, flags)
260260
& /Z7&
261261
& /assume:byterecl&
262262
& /traceback&
263-
& /Qcoarray:single&
264263
&'
265264
case(id_intel_llvm_nix, id_intel_llvm_unknown)
266265
flags = '&
@@ -271,7 +270,6 @@ subroutine get_debug_compile_flags(id, flags)
271270
& -g&
272271
& -assume byterecl&
273272
& -traceback&
274-
& -coarray=single&
275273
&'
276274
case(id_intel_llvm_windows)
277275
flags = '&
@@ -281,7 +279,6 @@ subroutine get_debug_compile_flags(id, flags)
281279
& /Od&
282280
& /Z7&
283281
& /assume:byterecl&
284-
& /Qcoarray:single&
285282
&'
286283
case(id_nag)
287284
flags = '&
@@ -332,6 +329,34 @@ subroutine get_module_flags(compiler, modpath, flags)
332329

333330
end subroutine get_module_flags
334331

332+
subroutine get_default_c_compiler(f_compiler, c_compiler)
333+
character(len=*), intent(in) :: f_compiler
334+
character(len=:), allocatable, intent(out) :: c_compiler
335+
integer(compiler_enum) :: id
336+
337+
id = get_compiler_id(f_compiler)
338+
339+
select case(id)
340+
341+
case(id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_windows, id_intel_classic_unknown)
342+
c_compiler = 'icc'
343+
344+
case(id_intel_llvm_nix,id_intel_llvm_windows, id_intel_llvm_unknown)
345+
c_compiler = 'icx'
346+
347+
case(id_flang)
348+
c_compiler='clang'
349+
350+
case(id_ibmxl)
351+
c_compiler='xlc'
352+
353+
case default
354+
! Fall-back to using Fortran compiler
355+
c_compiler = f_compiler
356+
end select
357+
358+
end subroutine get_default_c_compiler
359+
335360
function get_compiler_id(compiler) result(id)
336361
character(len=*), intent(in) :: compiler
337362
integer(kind=compiler_enum) :: id

0 commit comments

Comments
 (0)