Skip to content

Commit c6f0ec6

Browse files
committed
Move default flags fetching and build name generation to model
1 parent 5d22f5a commit c6f0ec6

File tree

3 files changed

+107
-82
lines changed

3 files changed

+107
-82
lines changed

src/fpm.f90

Lines changed: 21 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
module fpm
2-
use fpm_strings, only: string_t, operator(.in.), glob, join, string_cat
2+
use fpm_strings, only: string_t, operator(.in.), glob, join, string_cat, fnv_1a
33
use fpm_backend, only: build_package
44
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
55
fpm_run_settings, fpm_install_settings, fpm_test_settings
@@ -9,8 +9,7 @@ module fpm
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, get_default_c_compiler, &
13-
archiver_t
12+
use fpm_compiler, only: new_compiler, new_archiver
1413

1514

1615
use fpm_sources, only: add_executable_sources, add_sources_from_dir
@@ -43,10 +42,11 @@ subroutine build_model(model, settings, package, error)
4342

4443
integer :: i, j
4544
type(package_config_t) :: dependency
46-
character(len=:), allocatable :: manifest, lib_dir
45+
character(len=:), allocatable :: manifest, lib_dir, flags
4746

4847
logical :: duplicates_found = .false.
4948
type(string_t) :: include_dir
49+
character(len=16) :: build_name
5050

5151
model%package_name = package%name
5252

@@ -58,27 +58,30 @@ subroutine build_model(model, settings, package, error)
5858
call model%deps%add(package, error)
5959
if (allocated(error)) return
6060

61-
if(settings%compiler.eq.'')then
62-
model%compiler%fc = "gfortran"
61+
call new_compiler(model%compiler, settings%compiler)
62+
call new_archiver(model%archiver)
63+
64+
if (settings%flag == '') then
65+
flags = model%compiler%get_default_flags(settings%profile == "release")
6366
else
64-
model%compiler%fc = settings%compiler
65-
endif
67+
flags = settings%flag
68+
select case(settings%profile)
69+
case("release", "debug")
70+
flags = flags // model%compiler%get_default_flags(settings%profile == "release")
71+
end select
72+
end if
6673

67-
model%archiver = archiver_t()
68-
call get_default_c_compiler(model%compiler%fc, model%compiler%cc)
69-
model%compiler%cc = get_env('FPM_C_COMPILER',model%compiler%cc)
74+
write(build_name, '(z16.16)') fnv_1a(flags)
7075

71-
if (is_unknown_compiler(model%compiler%fc)) then
76+
if (model%compiler%is_unknown()) then
7277
write(*, '(*(a:,1x))') &
7378
"<WARN>", "Unknown compiler", model%compiler%fc, "requested!", &
7479
"Defaults for this compiler might be incorrect"
7580
end if
76-
model%output_directory = join_path('build',basename(model%compiler%fc)//'_'//settings%build_name)
81+
model%output_directory = join_path('build',basename(model%compiler%fc)//'_'//build_name)
7782

78-
call get_module_flags(model%compiler%fc, &
79-
& join_path(model%output_directory,model%package_name), &
80-
& model%fortran_compile_flags)
81-
model%fortran_compile_flags = settings%flag // model%fortran_compile_flags
83+
model%fortran_compile_flags = flags // " " // &
84+
& model%compiler%get_module_flag(join_path(model%output_directory, model%package_name))
8285

8386
allocate(model%packages(model%deps%ndep))
8487

@@ -186,7 +189,7 @@ subroutine build_model(model, settings, package, error)
186189
if (allocated(error)) return
187190

188191
if (settings%verbose) then
189-
write(*,*)'<INFO> BUILD_NAME: ',settings%build_name
192+
write(*,*)'<INFO> BUILD_NAME: ',build_name
190193
write(*,*)'<INFO> COMPILER: ',model%compiler%fc
191194
write(*,*)'<INFO> C COMPILER: ',model%compiler%cc
192195
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags

src/fpm_command_line.f90

Lines changed: 1 addition & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,6 @@ module fpm_command_line
3131
use fpm_strings, only : lower, split, fnv_1a, to_fortran_name, is_fortran_name
3232
use fpm_filesystem, only : basename, canon_path, which
3333
use fpm_environment, only : run, get_command_arguments_quoted
34-
use fpm_compiler, only : get_default_compile_flags
3534
use fpm_error, only : fpm_stop
3635
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
3736
& stdout=>output_unit, &
@@ -70,7 +69,6 @@ module fpm_command_line
7069
logical :: show_model=.false.
7170
character(len=:),allocatable :: compiler
7271
character(len=:),allocatable :: profile
73-
character(len=:),allocatable :: build_name
7472
character(len=:),allocatable :: flag
7573
end type
7674

@@ -113,7 +111,7 @@ module fpm_command_line
113111
& ' ', 'fpm', 'new', 'build', 'run', &
114112
& 'test', 'runner', 'install', 'update', 'list', 'help', 'version' ]
115113

116-
character(len=:), allocatable :: val_runner, val_build, val_compiler, val_flag, val_profile
114+
character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_profile
117115

118116
contains
119117
subroutine get_command_line_settings(cmd_settings)
@@ -199,7 +197,6 @@ subroutine get_command_line_settings(cmd_settings)
199197
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
200198
cmd_settings=fpm_run_settings(&
201199
& args=remaining,&
202-
& build_name=val_build,&
203200
& profile=val_profile,&
204201
& compiler=val_compiler, &
205202
& flag=val_flag, &
@@ -223,7 +220,6 @@ subroutine get_command_line_settings(cmd_settings)
223220

224221
allocate( fpm_build_settings :: cmd_settings )
225222
cmd_settings=fpm_build_settings( &
226-
& build_name=val_build,&
227223
& profile=val_profile,&
228224
& compiler=val_compiler, &
229225
& flag=val_flag, &
@@ -361,7 +357,6 @@ subroutine get_command_line_settings(cmd_settings)
361357
allocate(install_settings)
362358
install_settings = fpm_install_settings(&
363359
list=lget('list'), &
364-
build_name=val_build, &
365360
profile=val_profile,&
366361
compiler=val_compiler, &
367362
flag=val_flag, &
@@ -417,7 +412,6 @@ subroutine get_command_line_settings(cmd_settings)
417412
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
418413
cmd_settings=fpm_test_settings(&
419414
& args=remaining, &
420-
& build_name=val_build, &
421415
& profile=val_profile, &
422416
& compiler=val_compiler, &
423417
& flag=val_flag, &
@@ -487,17 +481,6 @@ subroutine check_build_vals()
487481

488482
val_flag = " " // sget('flag')
489483
val_profile = sget('profile')
490-
if (val_flag == '') then
491-
call get_default_compile_flags(val_compiler, val_profile == "release", val_flag)
492-
else
493-
select case(val_profile)
494-
case("release", "debug")
495-
call get_default_compile_flags(val_compiler, val_profile == "release", flags)
496-
val_flag = flags // val_flag
497-
end select
498-
end if
499-
allocate(character(len=16) :: val_build)
500-
write(val_build, '(z16.16)') fnv_1a(val_flag)
501484

502485
end subroutine check_build_vals
503486

src/fpm_compiler.f90

Lines changed: 85 additions & 46 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@
2828
module fpm_compiler
2929
use fpm_environment, only: &
3030
run, &
31+
get_env, &
3132
get_os_type, &
3233
OS_LINUX, &
3334
OS_MACOS, &
@@ -40,13 +41,7 @@ module fpm_compiler
4041
use fpm_filesystem, only: join_path, basename, get_temp_filename, delete_file, unix_path
4142
use fpm_strings, only: string_cat, string_t
4243
implicit none
43-
public :: is_unknown_compiler
44-
public :: get_module_flags
45-
public :: get_default_compile_flags
46-
public :: get_debug_compile_flags
47-
public :: get_release_compile_flags
48-
49-
public :: compiler_t, archiver_t
44+
public :: compiler_t, new_compiler, archiver_t, new_archiver
5045
public :: debug
5146

5247
enum, bind(C)
@@ -76,19 +71,29 @@ module fpm_compiler
7671

7772
!> Definition of compiler object
7873
type :: compiler_t
74+
!> Identifier of the compiler
75+
integer(compiler_enum) :: id = id_unknown
7976
!> Path to the Fortran compiler
8077
character(len=:), allocatable :: fc
8178
!> Path to the C compiler
8279
character(len=:), allocatable :: cc
8380
!> Print all commands
8481
logical :: echo = .true.
8582
contains
83+
!> Get default compiler flags
84+
procedure :: get_default_flags
85+
!> Get flag for module output directories
86+
procedure :: get_module_flag
87+
!> Get flag for include directories
88+
procedure :: get_include_flag
8689
!> Compile a Fortran object
8790
procedure :: compile_fortran
8891
!> Compile a C object
8992
procedure :: compile_c
9093
!> Link executable
9194
procedure :: link
95+
!> Check whether compiler is recognized
96+
procedure :: is_unknown
9297
end type compiler_t
9398

9499

@@ -106,12 +111,6 @@ module fpm_compiler
106111
end type archiver_t
107112

108113

109-
!> Constructor for archiver
110-
interface archiver_t
111-
module procedure :: new_archiver
112-
end interface archiver_t
113-
114-
115114
!> Create debug printout
116115
interface debug
117116
module procedure :: debug_compiler
@@ -121,20 +120,19 @@ module fpm_compiler
121120

122121
contains
123122

124-
subroutine get_default_compile_flags(compiler, release, flags)
125-
character(len=*), intent(in) :: compiler
123+
124+
function get_default_flags(self, release) result(flags)
125+
class(compiler_t), intent(in) :: self
126126
logical, intent(in) :: release
127-
character(len=:), allocatable, intent(out) :: flags
128-
integer :: id
127+
character(len=:), allocatable :: flags
129128

130-
id = get_compiler_id(compiler)
131129
if (release) then
132-
call get_release_compile_flags(id, flags)
130+
call get_release_compile_flags(self%id, flags)
133131
else
134-
call get_debug_compile_flags(id, flags)
132+
call get_debug_compile_flags(self%id, flags)
135133
end if
136134

137-
end subroutine get_default_compile_flags
135+
end function get_default_flags
138136

139137
subroutine get_release_compile_flags(id, flags)
140138
integer(compiler_enum), intent(in) :: id
@@ -343,42 +341,63 @@ subroutine get_debug_compile_flags(id, flags)
343341
end select
344342
end subroutine get_debug_compile_flags
345343

346-
subroutine get_module_flags(compiler, modpath, flags)
347-
character(len=*), intent(in) :: compiler
348-
character(len=*), intent(in) :: modpath
349-
character(len=:), allocatable, intent(out) :: flags
350-
integer(compiler_enum) :: id
344+
function get_include_flag(self, path) result(flags)
345+
class(compiler_t), intent(in) :: self
346+
character(len=*), intent(in) :: path
347+
character(len=:), allocatable :: flags
351348

352-
id = get_compiler_id(compiler)
349+
select case(self%id)
350+
case default
351+
flags = "-I "//path
353352

354-
select case(id)
353+
case(id_caf, id_gcc, id_f95, id_cray, id_nvhpc, id_pgi, id_flang, &
354+
& id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_unknown, &
355+
& id_intel_llvm_nix, id_intel_llvm_unknown, id_lahey, id_nag, &
356+
& id_ibmxl)
357+
flags = "-I "//path
358+
359+
case(id_intel_classic_windows, id_intel_llvm_windows)
360+
flags = "/I"//path
361+
362+
end select
363+
end function get_include_flag
364+
365+
function get_module_flag(self, path) result(flags)
366+
class(compiler_t), intent(in) :: self
367+
character(len=*), intent(in) :: path
368+
character(len=:), allocatable :: flags
369+
370+
select case(self%id)
355371
case default
356-
flags=' -module '//modpath//' -I '//modpath
372+
flags = "-module "//path
357373

358374
case(id_caf, id_gcc, id_f95, id_cray)
359-
flags=' -J '//modpath//' -I '//modpath
375+
flags = "-J "//path
360376

361377
case(id_nvhpc, id_pgi, id_flang)
362-
flags=' -module '//modpath//' -I '//modpath
378+
flags = "-module "//path
363379

364-
case(id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_unknown, id_intel_llvm_nix, id_intel_llvm_unknown)
365-
flags=' -module '//modpath//' -I'//modpath
380+
case(id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_unknown, &
381+
& id_intel_llvm_nix, id_intel_llvm_unknown)
382+
flags = "-module "//path
366383

367384
case(id_intel_classic_windows, id_intel_llvm_windows)
368-
flags=' /module:'//modpath//' /I'//modpath
385+
flags = "/module:"//path
369386

370387
case(id_lahey)
371-
flags=' -M '//modpath//' -I '//modpath
388+
flags = "-M "//path
372389

373390
case(id_nag)
374-
flags=' -mdir '//modpath//' -I '//modpath !
391+
flags = "-mdir "//path
375392

376393
case(id_ibmxl)
377-
flags=' -qmoddir '//modpath//' -I '//modpath
394+
flags = "-qmoddir "//path
378395

379396
end select
397+
flags = flags//" "//self%get_include_flag(path)
398+
399+
end function get_module_flag
380400

381-
end subroutine get_module_flags
382401

383402
subroutine get_default_c_compiler(f_compiler, c_compiler)
384403
character(len=*), intent(in) :: f_compiler
@@ -408,10 +427,13 @@ subroutine get_default_c_compiler(f_compiler, c_compiler)
408427

409428
end subroutine get_default_c_compiler
410429

430+
411431
function get_compiler_id(compiler) result(id)
412432
character(len=*), intent(in) :: compiler
413433
integer(kind=compiler_enum) :: id
414434

435+
integer :: stat
436+
415437
if (check_compiler(compiler, "gfortran")) then
416438
id = id_gcc
417439
return
@@ -510,17 +532,34 @@ function check_compiler(compiler, expected) result(match)
510532
end function check_compiler
511533

512534

513-
function is_unknown_compiler(compiler) result(is_unknown)
514-
character(len=*), intent(in) :: compiler
535+
pure function is_unknown(self)
536+
class(compiler_t), intent(in) :: self
515537
logical :: is_unknown
516-
is_unknown = get_compiler_id(compiler) == id_unknown
517-
end function is_unknown_compiler
538+
is_unknown = self%id == id_unknown
539+
end function is_unknown
540+
541+
542+
!> Create new compiler instance
543+
subroutine new_compiler(self, fc)
544+
!> Fortran compiler name or path
545+
character(len=*), intent(in) :: fc
546+
!> New instance of the compiler
547+
type(compiler_t), intent(out) :: self
548+
549+
character(len=*), parameter :: cc_env = "FPM_C_COMPILER"
550+
551+
self%id = get_compiler_id(fc)
552+
553+
self%fc = fc
554+
call get_default_c_compiler(self%fc, self%cc)
555+
self%cc = get_env(cc_env, self%cc)
556+
end subroutine new_compiler
518557

519558

520-
!> Create new archiver
521-
function new_archiver() result(self)
559+
!> Create new archiver instance
560+
subroutine new_archiver(self)
522561
!> New instance of the archiver
523-
type(archiver_t) :: self
562+
type(archiver_t), intent(out) :: self
524563
integer :: estat, os_type
525564

526565
os_type = get_os_type()
@@ -537,7 +576,7 @@ function new_archiver() result(self)
537576
end if
538577
self%use_response_file = os_type == OS_WINDOWS
539578
self%echo = .true.
540-
end function new_archiver
579+
end subroutine new_archiver
541580

542581

543582
!> Compile a Fortran object

0 commit comments

Comments
 (0)