aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSebastian Ehlert <28669218+awvwgk@users.noreply.github.com>2021-03-14 15:39:17 +0100
committerSebastian Ehlert <28669218+awvwgk@users.noreply.github.com>2021-03-18 09:23:18 +0100
commitb4a266f52cbc1414b11f9ce0492301c244f0b6a8 (patch)
tree3cdca388dfe3152c72dc6e523c521f17c6590138
parent8cbbd80d9d8e611229f334f09480310437bb826e (diff)
downloadfpm-b4a266f52cbc1414b11f9ce0492301c244f0b6a8.tar.gz
fpm-b4a266f52cbc1414b11f9ce0492301c244f0b6a8.zip
Implement --flag option for Fortran fpm
-rw-r--r--fpm/src/fpm.f907
-rw-r--r--fpm/src/fpm_command_line.f9078
-rw-r--r--fpm/src/fpm_compiler.f90511
3 files changed, 350 insertions, 246 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index 68385cd..c66abf2 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -9,7 +9,7 @@ use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists,
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
-use fpm_compiler, only: add_compile_flag_defaults
+use fpm_compiler, only: get_module_flags
use fpm_sources, only: add_executable_sources, add_sources_from_dir
@@ -64,7 +64,10 @@ subroutine build_model(model, settings, package, error)
model%output_directory = join_path('build',basename(model%fortran_compiler)//'_'//settings%build_name)
- call add_compile_flag_defaults(settings%build_name, basename(model%fortran_compiler), model)
+ call get_module_flags(model%fortran_compiler, &
+ & join_path(model%output_directory,model%package_name), &
+ & model%fortran_compile_flags)
+ model%fortran_compile_flags = settings%flag // model%fortran_compile_flags
if(settings%verbose)then
write(*,*)'<INFO>COMPILER OPTIONS: ', model%fortran_compile_flags
endif
diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90
index 72a4000..65812b8 100644
--- a/fpm/src/fpm_command_line.f90
+++ b/fpm/src/fpm_command_line.f90
@@ -27,8 +27,9 @@ use fpm_environment, only : get_os_type, get_env, &
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
-use fpm_strings, only : lower, split
+use fpm_strings, only : lower, split, fnv_1a
use fpm_filesystem, only : basename, canon_path, to_fortran_name
+use fpm_compiler, only : get_default_compile_flags
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
& stdout=>output_unit, &
& stderr=>error_unit
@@ -65,6 +66,7 @@ type, extends(fpm_cmd_settings) :: fpm_build_settings
logical :: show_model=.false.
character(len=:),allocatable :: compiler
character(len=:),allocatable :: build_name
+ character(len=:),allocatable :: flag
end type
type, extends(fpm_build_settings) :: fpm_run_settings
@@ -106,7 +108,7 @@ character(len=20),parameter :: manual(*)=[ character(len=20) ::&
& ' ', 'fpm', 'new', 'build', 'run', &
& 'test', 'runner', 'install', 'update', 'list', 'help', 'version' ]
-character(len=:), allocatable :: val_runner, val_build, val_compiler
+character(len=:), allocatable :: val_runner, val_build, val_compiler, val_flag
contains
subroutine get_command_line_settings(cmd_settings)
@@ -157,6 +159,7 @@ contains
& --example F&
& --runner " " &
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
+ & --flag:: " "&
& --verbose F&
& --',help_run,version_text)
@@ -192,6 +195,7 @@ contains
& args=remaining,&
& build_name=val_build,&
& compiler=val_compiler, &
+ & flag=val_flag, &
& example=lget('example'), &
& list=lget('list'),&
& name=names,&
@@ -204,6 +208,7 @@ contains
& --list F &
& --show-model F &
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
+ & --flag:: " "&
& --verbose F&
& --',help_build,version_text)
@@ -213,6 +218,7 @@ contains
cmd_settings=fpm_build_settings( &
& build_name=val_build,&
& compiler=val_compiler, &
+ & flag=val_flag, &
& list=lget('list'),&
& show_model=lget('show-model'),&
& verbose=lget('verbose') )
@@ -339,6 +345,7 @@ contains
call set_args('--release F --no-rebuild F --verbose F --prefix " " &
& --list F &
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
+ & --flag:: " "&
& --libdir "lib" --bindir "bin" --includedir "include"', &
help_install, version_text)
@@ -349,6 +356,7 @@ contains
list=lget('list'), &
build_name=val_build, &
compiler=val_compiler, &
+ flag=val_flag, &
no_rebuild=lget('no-rebuild'), &
verbose=lget('verbose'))
call get_char_arg(install_settings%prefix, 'prefix')
@@ -373,6 +381,7 @@ contains
& --release F&
& --runner " " &
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
+ & --flag:: " "&
& --verbose F&
& --',help_test,version_text)
@@ -402,6 +411,7 @@ contains
& args=remaining, &
& build_name=val_build, &
& compiler=val_compiler, &
+ & flag=val_flag, &
& example=.false., &
& list=lget('list'), &
& name=names, &
@@ -455,7 +465,17 @@ contains
val_compiler='gfortran'
endif
- val_build=trim(merge('release','debug ',lget('release')))
+ val_flag = sget('flag')
+ if (val_flag == '') then
+ call get_default_compile_flags(val_compiler, lget('release'), val_flag)
+ else
+ if (lget('release')) then
+ write(stdout,'(a)') &
+ '<WARNING> --release ignored since explicit --flag argument provided'
+ end if
+ end if
+ allocate(character(len=16) :: val_build)
+ write(val_build, '(z16.16)') fnv_1a(val_flag)
end subroutine check_build_vals
@@ -516,17 +536,17 @@ contains
' ']
help_list_dash = [character(len=80) :: &
' ', &
- ' build [--compiler COMPILER_NAME] [--release] [--list] ', &
+ ' build [--compiler COMPILER_NAME] [--release] [--flag FFLAGS] [--list] ', &
' help [NAME(s)] ', &
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
' [--full|--bare][--backfill] ', &
' update [NAME(s)] [--fetch-only] [--clean] [--verbose] ', &
' list [--list] ', &
- ' run [[--target] NAME(s) [--example] [--release] [--all] [--runner "CMD"] ', &
- ' [--compiler COMPILER_NAME] [--list] [-- ARGS] ', &
- ' test [[--target] NAME(s)] [--release] [--runner "CMD"] [--list] ', &
+ ' run [[--target] NAME(s) [--example] [--release] [--flag FFLAGS] [--all] ', &
+ ' [--runner "CMD"] [--compiler COMPILER_NAME] [--list] [-- ARGS] ', &
+ ' test [[--target] NAME(s)] [--release] [--flag FFLAGS] [--runner "CMD"] [--list]', &
' [--compiler COMPILER_NAME] [-- ARGS] ', &
- ' install [--release] [--no-rebuild] [--prefix PATH] [options] ', &
+ ' install [--release] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] [options] ', &
' ']
help_usage=[character(len=80) :: &
'' ]
@@ -632,24 +652,26 @@ contains
' ', &
' Their syntax is ', &
' ', &
- ' build [--release] [--list] [--compiler COMPILER_NAME] ', &
+ ' build [--release] [--flag FFLAGS] [--list] [--compiler COMPILER_NAME]', &
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
- ' [--full|--bare][--backfill] ', &
+ ' [--full|--bare][--backfill] ', &
' update [NAME(s)] [--fetch-only] [--clean] ', &
- ' run [[--target] NAME(s)] [--release] [--list] [--example] [--all] ', &
- ' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
- ' test [[--target] NAME(s)] [--release] [--list] ', &
+ ' run [[--target] NAME(s)] [--release] [--flag FFLAGS] [--list] [--example]', &
+ ' [--all] [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
+ ' test [[--target] NAME(s)] [--release] [--flag FFLAGS] [--list] ', &
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
' help [NAME(s)] ', &
' list [--list] ', &
- ' install [--release] [--no-rebuild] [--prefix PATH] [options] ', &
+ ' install [--release] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] [options]', &
' ', &
'SUBCOMMAND OPTIONS ', &
' --release Builds or runs in release mode (versus debug mode). fpm(1)', &
- ' Defaults to using common compiler debug flags and building', &
- ' in "build/*_debug/". When this flag is present build ', &
- ' output goes into "build/*_release/" and common compiler ', &
- ' optimization flags are used. ', &
+ ' Defaults to using common compiler debug flags. ', &
+ ' When this flag is present common compiler optimization flags', &
+ ' are used.', &
+ ' --flag FFLAGS Use compile arguments provided in FFLAGS rather than', &
+ ' defaults from debug or release mode, module flags are', &
+ ' provided by fpm(1) and must not be present in FFLAGS', &
' --list List candidates instead of building or running them. On ', &
' the fpm(1) command this shows a brief list of subcommands.', &
' --runner CMD Provides a command to prefix program execution paths. ', &
@@ -708,8 +730,9 @@ contains
' run(1) - the fpm(1) subcommand to run project applications ', &
' ', &
'SYNOPSIS ', &
- ' fpm run [[--target] NAME(s)[--release][--compiler COMPILER_NAME] ', &
- ' [--runner "CMD"] [--example] [--list] [--all] [-- ARGS] ', &
+ ' fpm run [[--target] NAME(s) [--release] [--flag FFLAGS]', &
+ ' [--compiler COMPILER_NAME] [--runner "CMD"] [--example]', &
+ ' [--list] [--all] [-- ARGS]', &
' ', &
' fpm run --help|--version ', &
' ', &
@@ -734,6 +757,7 @@ contains
' --all Run all examples or applications. An alias for --target ''*''. ', &
' --example Run example programs instead of applications. ', &
' --release selects the optimized build instead of the debug build. ', &
+ ' --flags FFLAGS selects compile arguments for the build', &
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
' "gfortran" unless set by the environment ', &
' variable FPM_COMPILER. ', &
@@ -774,7 +798,7 @@ contains
' build(1) - the fpm(1) subcommand to build a project ', &
' ', &
'SYNOPSIS ', &
- ' fpm build [--release][--compiler COMPILER_NAME] [-list] ', &
+ ' fpm build [--release] [--flags FFLAGS] [--compiler COMPILER_NAME] [-list]', &
' ', &
' fpm build --help|--version ', &
' ', &
@@ -798,6 +822,7 @@ contains
'OPTIONS ', &
' --release build in build/*_release instead of build/*_debug with ', &
' high optimization instead of full debug options. ', &
+ ' --flags FFLAGS selects compile arguments for the build', &
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
' "gfortran" unless set by the environment ', &
' variable FPM_COMPILER. ', &
@@ -954,8 +979,8 @@ contains
' test(1) - the fpm(1) subcommand to run project tests ', &
' ', &
'SYNOPSIS ', &
- ' fpm test [[--target] NAME(s)][--release][--compiler COMPILER_NAME ] ', &
- ' [--runner "CMD"] [--list][-- ARGS] ', &
+ ' fpm test [[--target] NAME(s)] [--release] [--flag FFLAGS]', &
+ ' [--compiler COMPILER_NAME ] [--runner "CMD"] [--list][-- ARGS]', &
' ', &
' fpm test --help|--version ', &
' ', &
@@ -971,8 +996,8 @@ contains
' any single character and "*" represents any string. ', &
' Note The glob string normally needs quoted to ', &
' protect the special characters from shell expansion.', &
- ' --release selects the optimized build instead of the debug ', &
- ' build. ', &
+ ' --release selects the optimized build instead of the debug build. ', &
+ ' --flags FFLAGS selects compile arguments for the build', &
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
' "gfortran" unless set by the environment ', &
' variable FPM_COMPILER. ', &
@@ -1021,7 +1046,7 @@ contains
' install(1) - install fpm projects', &
'', &
'SYNOPSIS', &
- ' fpm install [--release] [--list] [--no-rebuild] [--prefix DIR]', &
+ ' fpm install [--release] [--flag FFLAGS] [--list] [--no-rebuild] [--prefix DIR]', &
' [--bindir DIR] [--libdir DIR] [--includedir DIR]', &
' [--verbose]', &
'', &
@@ -1036,6 +1061,7 @@ contains
' --list list all installable targets for this project,', &
' but do not install any of them', &
' --release selects the optimized build instead of the debug build', &
+ ' --flags FFLAGS selects compile arguments for the build', &
' --no-rebuild do not rebuild project before installation', &
' --prefix DIR path to installation directory (requires write access),', &
' the default prefix on Unix systems is $HOME/.local', &
diff --git a/fpm/src/fpm_compiler.f90 b/fpm/src/fpm_compiler.f90
index 3335b11..955f00a 100644
--- a/fpm/src/fpm_compiler.f90
+++ b/fpm/src/fpm_compiler.f90
@@ -1,27 +1,6 @@
!># Define compiler command options
!!
!! This module defines compiler options to use for the debug and release builds.
-module fpm_compiler
-use fpm_model, only: fpm_model_t
-use fpm_filesystem, only: join_path
-public add_compile_flag_defaults
-
-contains
-!> Choose compile flags based on cli settings & manifest inputs
-subroutine add_compile_flag_defaults(build_name,compiler,model)
-character(len=*),intent(in) :: build_name !! select build from {release,debug}
-character(len=*),intent(in) :: compiler !! compiler name
-type(fpm_model_t), intent(inout) :: model !! model to add compiler options to
-
-! could just be a function to return a string instead of passing model
-! but likely to change other components like matching C compiler
-
-character(len=:),allocatable :: fflags ! optional flags that might be overridden by user
-character(len=:),allocatable :: modpath
-character(len=:),allocatable :: mandatory ! flags required for fpm to function properly;
- ! ie. add module path and module include directory as appropriate
-
-! special reserved names "debug" and "release" are for supported compilers with no user-specified compile or load flags
! vendor Fortran C Module output Module include OpenMP Free for OSS
! compiler compiler directory directory
@@ -46,206 +25,302 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p
! G95 ? ? -fmod= -I -fopenmp discontinued
! Open64 ? ? -module -I -mp discontinued
! Unisys ? ? ? ? ? discontinued
-character(len=*),parameter :: names(*)=[ character(len=10) :: &
-& 'caf', &
-& 'gfortran', &
-& 'f95', &
-& 'nvfortran', &
-& 'ifort', &
-& 'ifx', &
-& 'pgfortran', &
-& 'pgf90', &
-& 'pgf95', &
-& 'flang', &
-& 'lfc', &
-& 'nagfor', &
-& 'crayftn', &
-& 'xlf90', &
-& 'unknown']
-integer :: i
-
- modpath=join_path(model%output_directory,model%package_name)
- fflags=''
- mandatory=''
-
- select case(build_name//'_'//compiler)
-
- case('release_caf')
- fflags='&
- & -O3&
- & -Wimplicit-interface&
- & -fPIC&
- & -fmax-errors=1&
- & -funroll-loops&
- &'
- mandatory=' -J '//modpath//' -I '//modpath
- case('debug_caf')
- fflags = '&
- & -Wall&
- & -Wextra&
- & -Wimplicit-interface&
- & -fPIC -fmax-errors=1&
- & -g&
- & -fbounds-check&
- & -fcheck-array-temporaries&
- & -fbacktrace&
- &'
- mandatory=' -J '//modpath//' -I '//modpath
- case('release_gfortran')
- fflags='&
- & -O3&
- & -Wimplicit-interface&
- & -fPIC&
- & -fmax-errors=1&
- & -funroll-loops&
- & -fcoarray=single&
- &'
- mandatory=' -J '//modpath//' -I '//modpath
- case('debug_gfortran')
- fflags = '&
- & -Wall&
- & -Wextra&
- & -Wimplicit-interface&
- & -fPIC -fmax-errors=1&
- & -g&
- & -fcheck=bounds&
- & -fcheck=array-temps&
- & -fbacktrace&
- & -fcoarray=single&
- &'
- mandatory=' -J '//modpath//' -I '//modpath
-
- case('release_f95')
- fflags='&
- & -O3&
- & -Wimplicit-interface&
- & -fPIC&
- & -fmax-errors=1&
- & -ffast-math&
- & -funroll-loops&
- &'
- mandatory=' -J '//modpath//' -I '//modpath
- case('debug_f95')
- fflags = '&
- & -Wall&
- & -Wextra&
- & -Wimplicit-interface&
- & -fPIC -fmax-errors=1&
- & -g&
- & -fbounds-check&
- & -fcheck-array-temporaries&
- & -Wno-maybe-uninitialized -Wno-uninitialized&
- & -fbacktrace&
- &'
- mandatory=' -J '//modpath//' -I '//modpath
-
- case('release_nvfortran')
- fflags = '&
- & -Mbackslash&
- &'
- mandatory=' -module '//modpath//' -I '//modpath
- case('debug_nvfortran')
- fflags = '&
- & -Minform=inform&
- & -Mbackslash&
- & -g&
- & -Mbounds&
- & -Mchkptr&
- & -Mchkstk&
- & -traceback&
- &'
- mandatory=' -module '//modpath//' -I '//modpath
-
- case('release_ifort')
- fflags = '&
- & -fp-model precise&
- & -pc 64&
- & -align all&
- & -error-limit 1&
- & -reentrancy threaded&
- & -nogen-interfaces&
- & -assume byterecl&
- &'
- mandatory=' -module '//modpath//' -I '//modpath
- case('debug_ifort')
- fflags = '&
- & -warn all&
- & -check:all:noarg_temp_created&
- & -error-limit 1&
- & -O0&
- & -g&
- & -assume byterecl&
- & -traceback&
- &'
- mandatory=' -module '//modpath//' -I '//modpath
- case('release_ifx')
- fflags = ' '
- mandatory=' -module '//modpath//' -I '//modpath
- case('debug_ifx')
- fflags = ' '
- mandatory=' -module '//modpath//' -I '//modpath
-
- case('release_pgfortran','release_pgf90','release_pgf95') ! Portland Group F90/F95 compilers
- fflags = ' '
- mandatory=' -module '//modpath//' -I '//modpath
- case('debug_pgfortran','debug_pgf90','debug_pgf95') ! Portland Group F90/F95 compilers
- fflags = ' '
- mandatory=' -module '//modpath//' -I '//modpath
-
- case('release_flang')
- fflags = ' '
- mandatory=' -module '//modpath//' -I '//modpath
- case('debug_flang')
- fflags = ' '
- mandatory=' -module '//modpath//' -I '//modpath
-
- case('release_lfc')
- fflags = ' '
- mandatory=' -M '//modpath//' -I '//modpath
- case('debug_lfc')
- fflags = ' '
- mandatory=' -M '//modpath//' -I '//modpath
-
- case('release_nagfor')
- fflags = ' &
- & -O4&
- & -coarray=single&
- & -PIC&
- &'
- mandatory=' -mdir '//modpath//' -I '//modpath !
- case('debug_nagfor')
- fflags = '&
- & -g&
- & -C=all&
- & -O0&
- & -gline&
- & -coarray=single&
- & -PIC&
- &'
- mandatory=' -mdir '//modpath//' -I '//modpath !
- case('release_crayftn')
- fflags = ' '
- mandatory=' -J '//modpath//' -I '//modpath
- case('debug_crayftn')
- fflags = ' '
- mandatory=' -J '//modpath//' -I '//modpath
-
- case('release_xlf90')
- fflags = ' '
- mandatory=' -qmoddir '//modpath//' -I '//modpath
- case('debug_xlf90')
- fflags = ' '
- mandatory=' -qmoddir '//modpath//' -I '//modpath
+module fpm_compiler
+use fpm_model, only: fpm_model_t
+use fpm_filesystem, only: join_path, basename
+implicit none
+public :: get_module_flags
+public :: get_default_compile_flags
+public :: get_debug_compile_flags
+public :: get_release_compile_flags
+
+enum, bind(C)
+ enumerator :: &
+ id_unknown, &
+ id_gcc, &
+ id_f95, &
+ id_caf, &
+ id_intel_classic, &
+ id_intel_llvm, &
+ id_pgi, &
+ id_nvhpc, &
+ id_nag, &
+ id_flang, &
+ id_ibmxl, &
+ id_cray, &
+ id_lahey, &
+ id_lfortran
+end enum
+integer, parameter :: compiler_enum = kind(id_unknown)
+
+contains
+
+subroutine get_default_compile_flags(compiler, release, flags)
+ character(len=*), intent(in) :: compiler
+ logical, intent(in) :: release
+ character(len=:), allocatable, intent(out) :: flags
+ integer :: id
+
+ id = get_compiler_id(compiler)
+ if (release) then
+ call get_release_compile_flags(id, flags)
+ else
+ call get_debug_compile_flags(id, flags)
+ end if
+end subroutine get_default_compile_flags
+
+subroutine get_release_compile_flags(id, flags)
+ integer(compiler_enum), intent(in) :: id
+ character(len=:), allocatable, intent(out) :: flags
+
+ select case(id)
+ case default
+ flags = ""
+
+ case(id_caf)
+ flags='&
+ & -O3&
+ & -Wimplicit-interface&
+ & -fPIC&
+ & -fmax-errors=1&
+ & -funroll-loops&
+ &'
+ case(id_gcc)
+ flags='&
+ & -O3&
+ & -Wimplicit-interface&
+ & -fPIC&
+ & -fmax-errors=1&
+ & -funroll-loops&
+ & -fcoarray=single&
+ &'
+ case(id_f95)
+ flags='&
+ & -O3&
+ & -Wimplicit-interface&
+ & -fPIC&
+ & -fmax-errors=1&
+ & -ffast-math&
+ & -funroll-loops&
+ &'
+ case(id_nvhpc)
+ flags = '&
+ & -Mbackslash&
+ &'
+ case(id_intel_classic)
+ flags = '&
+ & -fp-model precise&
+ & -pc 64&
+ & -align all&
+ & -error-limit 1&
+ & -reentrancy threaded&
+ & -nogen-interfaces&
+ & -assume byterecl&
+ &'
+ case(id_nag)
+ flags = ' &
+ & -O4&
+ & -coarray=single&
+ & -PIC&
+ &'
+ end select
+end subroutine get_release_compile_flags
+
+subroutine get_debug_compile_flags(id, flags)
+ integer(compiler_enum), intent(in) :: id
+ character(len=:), allocatable, intent(out) :: flags
+
+ select case(id)
case default
- fflags = ' '
- mandatory=' -module '//modpath//' -I '//modpath
- write(*,'(*(a))')'<WARNING> unknown compiler (',compiler,') and build name (',build_name,') combination.'
- write(*,'(a,*(T31,6(a:,", "),/))')' known compilers are ',(trim(names(i)),i=1,size(names)-1)
+ flags = ""
+
+ case(id_caf)
+ flags = '&
+ & -Wall&
+ & -Wextra&
+ & -Wimplicit-interface&
+ & -fPIC -fmax-errors=1&
+ & -g&
+ & -fbounds-check&
+ & -fcheck-array-temporaries&
+ & -fbacktrace&
+ &'
+
+ case(id_gcc)
+ flags = '&
+ & -Wall&
+ & -Wextra&
+ & -Wimplicit-interface&
+ & -fPIC -fmax-errors=1&
+ & -g&
+ & -fbounds-check&
+ & -fcheck-array-temporaries&
+ & -fbacktrace&
+ & -fcoarray=single&
+ &'
+
+ case(id_f95)
+ flags = '&
+ & -Wall&
+ & -Wextra&
+ & -Wimplicit-interface&
+ & -fPIC -fmax-errors=1&
+ & -g&
+ & -fbounds-check&
+ & -fcheck-array-temporaries&
+ & -Wno-maybe-uninitialized -Wno-uninitialized&
+ & -fbacktrace&
+ &'
+
+ case(id_nvhpc)
+ flags = '&
+ & -Minform=inform&
+ & -Mbackslash&
+ & -g&
+ & -Mbounds&
+ & -Mchkptr&
+ & -Mchkstk&
+ & -traceback&
+ &'
+
+ case(id_intel_classic)
+ flags = '&
+ & -warn all&
+ & -check:all:noarg_temp_created&
+ & -error-limit 1&
+ & -O0&
+ & -g&
+ & -assume byterecl&
+ & -traceback&
+ &'
+
+ case(id_nag)
+ flags = '&
+ & -g&
+ & -C=all&
+ & -O0&
+ & -gline&
+ & -coarray=single&
+ & -PIC&
+ &'
end select
+end subroutine get_debug_compile_flags
+
+subroutine get_module_flags(compiler, modpath, flags)
+ character(len=*), intent(in) :: compiler
+ character(len=*), intent(in) :: modpath
+ character(len=:), allocatable, intent(out) :: flags
+ integer(compiler_enum) :: id
+
+ id = get_compiler_id(compiler)
+
+ select case(id)
+ case default
+ flags=' -module '//modpath//' -I '//modpath
+
+ case(id_caf, id_gcc, id_f95, id_cray)
+ flags=' -J '//modpath//' -I '//modpath
+
+ case(id_intel_classic, id_intel_llvm, id_nvhpc, id_pgi, id_flang)
+ flags=' -module '//modpath//' -I '//modpath
+
+ case(id_lahey)
+ flags=' -M '//modpath//' -I '//modpath
+
+ case(id_nag)
+ flags=' -mdir '//modpath//' -I '//modpath !
+
+ case(id_ibmxl)
+ flags=' -qmoddir '//modpath//' -I '//modpath
+
+ end select
+
+end subroutine get_module_flags
+
+function get_compiler_id(compiler) result(id)
+ character(len=*), intent(in) :: compiler
+ integer(kind=compiler_enum) :: id
+
+ if (check_compiler(compiler, "gfortran")) then
+ id = id_gcc
+ return
+ end if
+
+ if (check_compiler(compiler, "f95")) then
+ id = id_f95
+ return
+ end if
+
+ if (check_compiler(compiler, "caf")) then
+ id = id_caf
+ return
+ end if
+
+ if (check_compiler(compiler, "ifort")) then
+ id = id_intel_classic
+ return
+ end if
+
+ if (check_compiler(compiler, "ifx")) then
+ id = id_intel_llvm
+ return
+ end if
+
+ if (check_compiler(compiler, "nvfortran")) then
+ id = id_nvhpc
+ return
+ end if
+
+ if (check_compiler(compiler, "pgfortran") &
+ & .or. check_compiler(compiler, "pgf90") &
+ & .or. check_compiler(compiler, "pgf95")) then
+ id = id_pgi
+ return
+ end if
+
+ if (check_compiler(compiler, "nagfor")) then
+ id = id_nag
+ return
+ end if
+
+ if (check_compiler(compiler, "flang")) then
+ id = id_flang
+ return
+ end if
+
+ if (check_compiler(compiler, "xlf90")) then
+ id = id_ibmxl
+ return
+ end if
+
+ if (check_compiler(compiler, "crayftn")) then
+ id = id_cray
+ return
+ end if
+
+ if (check_compiler(compiler, "lfc")) then
+ id = id_lahey
+ return
+ end if
+
+ if (check_compiler(compiler, "lfort")) then
+ id = id_lfortran
+ return
+ end if
+
+ id = id_unknown
+
+end function get_compiler_id
- model%fortran_compile_flags = fflags//' '//mandatory
-
-end subroutine add_compile_flag_defaults
+function check_compiler(compiler, expected) result(match)
+ character(len=*), intent(in) :: compiler
+ character(len=*), intent(in) :: expected
+ logical :: match
+ match = compiler == expected
+ if (.not. match) then
+ match = index(basename(compiler), expected) > 0
+ end if
+end function check_compiler
end module fpm_compiler