diff options
author | init current directory[i] <urbanjost@comcast.net> | 2020-11-29 19:08:42 -0500 |
---|---|---|
committer | init current directory[i] <urbanjost@comcast.net> | 2020-11-29 19:08:42 -0500 |
commit | 15083ad7f5a84d28817b334f5401230a96571b82 (patch) | |
tree | 23b045a1d9603bd6f8ca1878eecb766e11532f98 | |
parent | bd2267317ca87b1ae23608f823b34679754ed1a7 (diff) | |
download | fpm-15083ad7f5a84d28817b334f5401230a96571b82.tar.gz fpm-15083ad7f5a84d28817b334f5401230a96571b82.zip |
suggested changes
-rw-r--r-- | fpm/fpm.toml | 4 | ||||
-rw-r--r-- | fpm/src/fpm.f90 | 211 | ||||
-rw-r--r-- | fpm/src/fpm_command_line.f90 | 155 | ||||
-rw-r--r-- | fpm/src/fpm_compiler.f90 | 198 | ||||
-rw-r--r-- | fpm/src/fpm_filesystem.f90 | 2 |
5 files changed, 280 insertions, 290 deletions
diff --git a/fpm/fpm.toml b/fpm/fpm.toml index fa91f2f..5c61402 100644 --- a/fpm/fpm.toml +++ b/fpm/fpm.toml @@ -12,7 +12,7 @@ tag = "v0.2.1" [dependencies.M_CLI2] git = "https://github.com/urbanjost/M_CLI2.git" -rev = "598e44164eee383b8a0775aa75b7d1bb100481c3" +rev = "a77fabf52a781613609f6a8c80ca5d5f8f30f97c" [[test]] name = "cli-test" @@ -28,5 +28,3 @@ main = "new_test.f90" name = "fpm-test" source-dir = "test/fpm_test" main = "main.f90" - - diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index aa9a4e6..fbd91d9 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -9,6 +9,7 @@ use fpm_model, only: fpm_model_t, srcfile_t, build_target_t, & FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, & FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST, & FPM_TARGET_EXECUTABLE +use fpm_compiler, only: add_compile_flag_defaults use fpm_sources, only: add_executable_sources, add_sources_from_dir use fpm_targets, only: targets_from_sources, resolve_module_dependencies @@ -155,7 +156,6 @@ subroutine build_model(model, settings, package, error) type(string_t), allocatable :: package_list(:) integer :: i - character(len=:),allocatable :: module_path_switch if(settings%verbose)then write(*,*)'<INFO>BUILD_NAME:',settings%build_name @@ -163,6 +163,7 @@ subroutine build_model(model, settings, package, error) endif model%package_name = package%name + if (allocated(package%build%link)) then model%link_libraries = package%build%link else @@ -172,205 +173,15 @@ subroutine build_model(model, settings, package, error) allocate(package_list(1)) package_list(1)%s = package%name - model%fortran_compiler=settings%compiler - - model%output_directory = join_path('build',model%fortran_compiler//'_'//settings%build_name) - - if(settings%compiler.eq.'')then - model%fortran_compiler = 'gfortran' - else - model%fortran_compiler = settings%compiler - endif - -! #TODO: Choose flags and output directory based on cli settings & manifest inputs -! 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 -! Gnu gfortran gcc -J -I -fopenmp X -! Intel ifort icc -module -I -qopenmp X -! Intel(Windows) ifort icc /module:path /I /Qopenmp X -! Intel oneAPI ifx icx -module -I -qopenmp X -! PGI pgfortran pgcc -module -I -mp X -! NVIDIA nvfortran nvc -module -I -mp X -! LLVM flang flang clang -module -I -mp X -! LFortran lfortran --- ? ? ? X -! Lahey/Futjitsu lfc ? -M -I -openmp ? -! NAG nagfor ? -mdir -I -openmp x -! Cray crayftn craycc -J -I -homp ? -! IBM xlf90 ? -qmoddir -I -qsmp X -! Oracle/Sun ? ? -moddir= -M -xopenmp ? -! Silverfrost FTN95 ftn95 ? ? /MOD_PATH ? ? -! Elbrus ? lcc -J -I -fopenmp ? -! Hewlett Packard ? ? ? ? ? discontinued -! Watcom ? ? ? ? ? discontinued -! PathScale ? ? -module -I -mp discontinued -! G95 ? ? -fmod= -I -fopenmp discontinued -! Open64 ? ? -module -I -mp discontinued -! Unisys ? ? ? ? ? discontinued - - select case(settings%build_name//'_'//settings%compiler) - - case('release_gfortran') ! -J - model%fortran_compile_flags=' & - & -O3& - & -Wimplicit-interface& - & -fPIC& - & -fmax-errors=1& - & -ffast-math& - & -funroll-loops& - & ' - case('debug_gfortran') - model%fortran_compile_flags = '& - & -Wall & - & -Wextra & - &-Wimplicit-interface & - &-fPIC -fmax-errors=1 & - &-g & - &-fbounds-check & - &-fcheck-array-temporaries & - &-fbacktrace ' - - case('release_f95') ! -J - model%fortran_compile_flags=' & - & -O3& - & -Wimplicit-interface& - & -fPIC& - & -std=f95 & - & -fmax-errors=1& - & -ffast-math& - & -funroll-loops& - & ' - case('debug_f95') - model%fortran_compile_flags = '& - & -Wall & - & -Wextra & - &-Wimplicit-interface & - &-fPIC -fmax-errors=1 & - &-g & - &-std=f95 & - &-fbounds-check & - &-fcheck-array-temporaries & - &-fbacktrace ' - - case('release_gnu') ! -J - model%fortran_compile_flags=' & - & -O3& - & -Wimplicit-interface& - & -fPIC& - & -fmax-errors=1& - & -ffast-math& - & -funroll-loops& - & -std=f2018 & - & -Wno-maybe-uninitialized -Wno-uninitialized & - & ' - model%fortran_compiler = 'gfortran' - case('debug_gnu') - model%fortran_compile_flags = '& - & -Wall & - & -Wextra & - & -Wimplicit-interface & - & -fPIC -fmax-errors=1 & - & -g & - & -fbounds-check & - & -fcheck-array-temporaries & - & -std=f2018 & - & -Wno-maybe-uninitialized -Wno-uninitialized & - & -fbacktrace ' - model%fortran_compiler = 'gfortran' - - case('release_nvfortran') - model%fortran_compile_flags = ' & - & -Mbackslash& - & ' - case('debug_nvfortran') - model%fortran_compile_flags = '& - & -Minform=inform & - & -Mbackslash & - & -traceback& - & ' - - case('release_ifort') - model%fortran_compile_flags = ' & - & -fp-model precise & - & -pc 64 & - & -align all & - & -error-limit 1 & - & -reentrancy threaded & - & -nogen-interfaces & - & -assume byterecl & - & -assume nounderscore' - case('debug_ifort') - model%fortran_compile_flags = '& - & -warn all & - & -check all & - & -error-limit 1 & - & -O0 & - & -g & - & -assume byterecl & - & -traceback ' - case('release_ifx') - model%fortran_compile_flags = ' ' - case('debug_ifx') - model%fortran_compile_flags = ' ' - - case('release_pgfortran','release_pgf90','release_pgf95') ! Portland Group F90/F95 compilers - model%fortran_compile_flags = ' ' - case('debug_pgfortran','debug_pgf90','debug_pgf95') ! Portland Group F90/F95 compilers - model%fortran_compile_flags = ' ' - - case('release_flang') - model%fortran_compile_flags = ' ' - case('debug_flang') - model%fortran_compile_flags = ' ' - - case('release_lfc') - model%fortran_compile_flags = ' ' - case('debug_lfc') - model%fortran_compile_flags = ' ' - - case('release_nagfor') - model%fortran_compile_flags = ' ' - case('debug_nagfor') - model%fortran_compile_flags = ' ' - - case('release_crayftn') - model%fortran_compile_flags = ' ' - case('debug_crayftn') - model%fortran_compile_flags = ' ' - - case('release_xlf90') - model%fortran_compile_flags = ' ' - case('debug_xlf90') - model%fortran_compile_flags = ' ' - - case default - model%fortran_compile_flags = ' ' - write(*,*)'<WARNING> unknown compiler (',settings%compiler,')' - write(*,*)' and build name (',settings%build_name,')' - write(*,*)' combination.' - write(*,*)' known compilers are gfortran, nvfortran, ifort' - end select - - select case(settings%compiler) - case('gfortran') ; module_path_switch=' -J ' - case('gnu') ; module_path_switch=' -J ' - case('nvfortran') ; module_path_switch=' -module ' - case('ifort') ; module_path_switch=' -module ' - case('ifx') ; module_path_switch=' -module ' - case('pgfortran') ; module_path_switch=' -module ' - case('flang') ; module_path_switch=' -module ' - case('lfc') ; module_path_switch=' -M ' - case('crayftn') ; module_path_switch=' -J ' - case('nagfor') ; module_path_switch=' -mdir ' - case('xlf90') ; module_path_switch=' -qmoddir ' - case default - module_path_switch=' -module ' - write(*,*)'UNKNOWN COMPILER NAME ',settings%compiler - end select - - model%fortran_compile_flags = model%fortran_compile_flags//' '//& - & module_path_switch//join_path(model%output_directory,model%package_name) + if(settings%compiler.eq.'')then + model%fortran_compiler = 'gfortran' + else + model%fortran_compiler = settings%compiler + endif + + 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) model%link_flags = '' diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 656fe5e..dd50200 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -20,6 +20,7 @@ public :: fpm_cmd_settings, & get_command_line_settings type, abstract :: fpm_cmd_settings + logical :: verbose=.true. end type integer,parameter :: ibug=4096 @@ -29,14 +30,12 @@ type, extends(fpm_cmd_settings) :: fpm_new_settings logical :: with_test=.false. logical :: with_lib=.true. logical :: backfill=.true. - logical :: verbose=.true. end type type, extends(fpm_cmd_settings) :: fpm_build_settings logical :: list=.false. character(len=:),allocatable :: compiler character(len=:),allocatable :: build_name - logical :: verbose=.true. end type type, extends(fpm_build_settings) :: fpm_run_settings @@ -46,11 +45,9 @@ type, extends(fpm_build_settings) :: fpm_run_settings end type type, extends(fpm_run_settings) :: fpm_test_settings -integer :: gfortran_bug=0 end type type, extends(fpm_cmd_settings) :: fpm_install_settings - logical :: verbose=.true. end type character(len=:),allocatable :: name @@ -113,10 +110,9 @@ contains & --target " " & & --list F & & --release F& - & --verbose F& & --runner " " & - & --fc "'//basename(get_env('FPM_FC',get_env('FC','gfortran')))//'" & - & --compiler "'//basename(get_env('FPM_FC',get_env('FC','gfortran')))//'" & + & --compiler "'//get_env('FPM_COMPILER','gfortran')//'" & + & --verbose F& & --',help_test,version_text) call check_build_vals() @@ -147,9 +143,8 @@ contains call set_args( '& & --release F & & --list F & + & --compiler "'//get_env('FPM_COMPILER','gfortran')//'" & & --verbose F& - & --fc "'//basename(get_env('FPM_FC',get_env('FC','gfortran')))//'" & - & --compiler "'//basename(get_env('FPM_FC',get_env('FC','gfortran')))//'" & & --',help_test,version_text) call check_build_vals() @@ -172,23 +167,23 @@ contains & help_new, version_text) select case(size(unnamed)) case(1) - write(stderr,'(*(g0,/))')'ERROR: directory name required' + write(stderr,'(*(g0,/))')'<ERROR> directory name required' write(stderr,'(*(7x,g0,/))') & - & 'USAGE: fpm new NAME [--lib|--src] [--app] [--test] [--backfill]' + & '<USAGE> fpm new NAME [--lib|--src] [--app] [--test] [--backfill]' stop 1 case(2) name=trim(unnamed(2)) case default - write(stderr,'(g0)')'ERROR: only one directory name allowed' + write(stderr,'(g0)')'<ERROR> only one directory name allowed' write(stderr,'(7x,g0)') & - & 'USAGE: fpm new NAME [--lib|--src] [--app] [--test] [--backfill]' + & '<USAGE> fpm new NAME [--lib|--src] [--app] [--test] [--backfill]' stop 2 end select !*! canon_path is not converting ".", etc. name=canon_path(name) if( .not.is_fortran_name(basename(name)) )then write(stderr,'(g0)') [ character(len=72) :: & - & 'ERROR: the new directory basename must be an allowed ', & + & '<ERROR>the new directory basename must be an allowed ', & & ' Fortran name. It must be composed of 1 to 63 ASCII', & & ' characters and start with a letter and be composed', & & ' entirely of alphanumeric characters [a-zA-Z0-9]', & @@ -217,7 +212,9 @@ contains endif case('help','manual') - call set_args(' ',help_help,version_text) + call set_args('& + & --verbose F & + & ',help_help,version_text) if(size(unnamed).lt.2)then if(unnamed(1).eq.'help')then unnamed=[' ', 'fpm'] @@ -268,6 +265,7 @@ contains case('list') call set_args('& & --list F& + & --verbose F& &', help_list, version_text) call printhelp(help_list_nodash) if(lget('list'))then @@ -279,8 +277,7 @@ contains & --list F& & --release F& & --runner " " & - & --fc "'//basename(get_env('FPM_FC',get_env('FC','gfortran')))//'" & - & --compiler "'//basename(get_env('FPM_FC',get_env('FC','gfortran')))//'" & + & --compiler "'//get_env('FPM_COMPILER','gfortran')//'" & & --verbose F& & --',help_test,version_text) @@ -310,7 +307,10 @@ contains case default - call set_args(' --list F', help_fpm, version_text) + call set_args('& + & --list F& + & --verbose F& + ', help_fpm, version_text) ! Note: will not get here if --version or --usage or --help ! is present on commandline help_text=help_usage @@ -321,7 +321,7 @@ contains write(stdout,'(*(a))')' ' call printhelp(help_list_nodash) else - write(stderr,'(*(a))')'ERROR: unknown subcommand [', & + write(stderr,'(*(a))')'<ERROR> unknown subcommand [', & & trim(cmdarg), ']' call printhelp(help_list_dash) endif @@ -331,31 +331,13 @@ contains contains subroutine check_build_vals() - integer :: oneword - ! take basename of first word on FC; as other products - ! such as CMake allow FC to include optional compiler options - ! and others allow full pathnames to the decoder - val_compiler='' - val_compiler=sget('fc') - if(specified('compiler') )val_compiler=sget('compiler') - oneword=index(adjustl(val_compiler)//' ',' ')-1 - val_compiler=val_compiler(:oneword) - if(val_compiler.eq.'') then - val_compiler='gfortran' - else - val_compiler=basename(val_compiler) - endif - if( specified('fc').and.specified('compiler') )then - write(stdout,'(a)')& - &'<WARNING> --fc and --compiler are aliases and should not both ', & - &' be specified. Using '//val_compiler - endif - - if(.not.is_fortran_name(val_compiler))then - stop '<ERROR> compiler names must be simple names' - endif - - val_build=trim(merge('release','debug ',lget('release'))) + + val_compiler=sget('compiler') + if(val_compiler.eq.'') then + val_compiler='gfortran' + endif + + val_build=trim(merge('release','debug ',lget('release'))) end subroutine check_build_vals @@ -414,12 +396,14 @@ contains ' '] help_list_dash = [character(len=80) :: & ' ', & - ' build [-fc compiler] [--release] [--list] ', & + ' build [--compiler COMPILER_NAME] [--release] [--list] ', & ' help [NAME(s)] ', & ' new NAME [--lib|--src] [--app] [--test] [--backfill] ', & ' list [--list] ', & - ' run [NAME(s)] [--release] [--runner "CMD"] [--list] [--fc compiler] [-- ARGS] ', & - ' test [NAME(s)] [--release] [--runner "CMD"] [--list][--fc compiler] [-- ARGS] ', & + ' run [NAME(s)] [--release] [--runner "CMD"] [--list] ', & + ' [--compiler COMPILER_NAME] [-- ARGS] ', & + ' test [NAME(s)] [--release] [--runner "CMD"] [--list] ', & + ' [--compiler COMPILER_NAME] [-- ARGS] ', & ' '] help_usage=[character(len=80) :: & '' ] @@ -515,20 +499,22 @@ contains 'SUBCOMMANDS ', & ' Valid fpm(1) subcommands are: ', & ' ', & - ' build [--release] [--list] [-fc COMPILER] ', & - ' Compile the packages into the "build/" directory. ', & + ' + build Compile the packages into the "build/" directory. ', & + ' + new Create a new Fortran package directory with sample files. ', & + ' + run Run the local package binaries. defaults to all binaries for ', & + ' that release. ', & + ' + test Run the tests. ', & + ' + help Alternate method for displaying subcommand help ', & + ' + list Display brief descriptions of all subcommands. ', & + ' ', & + ' Their syntax is ', & + ' ', & + ' build [--release] [--list] [-compiler COMPILER_NAME] ', & ' new NAME [--lib|--src] [--app] [--test] [--backfill] ', & - ' Create a new Fortran package directory ', & - ' with sample files ', & - ' run [NAME(s)] [--release] [--list] [--runner "CMD"] ', & - ' [--fc COMPILER] [-- ARGS] ', & - ' Run the local package binaries. defaults to all ', & - ' binaries for that release. ', & - ' test [NAME(s)] [--release] [--list] [--runner "CMD"] ', & - ' [--fc COMPILER] [-- ARGS] ', & - ' Run the tests ', & - ' help [NAME(s)] Alternate method for displaying subcommand help ', & - ' list [--list] Display brief descriptions of all subcommands. ', & + ' run|test [NAME(s)] [--release] [--list] [--runner "CMD"] ', & + ' [--compiler COMPILER_NAME] [-- ARGS] ', & + ' help [NAME(s)] ', & + ' list [--list] ', & ' ', & 'SUBCOMMAND OPTIONS ', & ' --release Builds or runs in release mode (versus debug mode). fpm(1)', & @@ -539,11 +525,14 @@ contains ' --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. ', & - ' --fc COMPILER Compiler name. ', & + ' --compiler COMPILER_NAME Compiler name. The environment variable ', & + ' FPM_COMPILER sets the default. ', & ' -- ARGS Arguments to pass to executables. ', & - ' --help Show help text and exit. Valid for all subcommands. ', & - ' --version Show version information and exit. Valid for all ', & - ' subcommands. ', & + ' ', & + 'VALID FOR ALL SUBCOMMANDS ', & + ' --help Show help text and exit ', & + ' --verbose Display additional information when available ', & + ' --version Show version information and exit. ', & ' ', & 'EXAMPLES ', & ' sample commands: ', & @@ -559,7 +548,7 @@ contains ' + The fpm(1) home page is at https://github.com/fortran-lang/fpm ', & ' + Registered fpm(1) packages are at https://fortran-lang.org/packages ', & ' + The fpm(1) TOML file format is described at ', & - ' https://github.com/fortran-lang/fpm/blob/master/manifest-reference.md ', & + ' https://github.com/fortran-lang/fpm/blob/master/manifest-reference.md ', & ''] help_list=[character(len=80) :: & 'NAME ', & @@ -588,7 +577,7 @@ contains ' run(1) - the fpm(1) subcommand to run project applications ', & ' ', & 'SYNOPSIS ', & - ' fpm run [[--target] NAME(s)][--release][-fc compiler ] ', & + ' fpm run [[--target] NAME(s)][--release][--compiler COMPILER_NAME] ', & ' [--runner "CMD"] [--list][-- ARGS] ', & ' ', & ' fpm run --help|--version ', & @@ -602,11 +591,9 @@ contains ' or the programs listed in the "fpm.toml" file. ', & ' --release selects the optimized build instead of the debug ', & ' build. ', & - ' --fc COMPILER Specify a compiler name. The default can be set by the ', & - ' environment variable FPM_FC. If not set, the ', & - ' environment variable FC is used to set the default. ', & - ' If that is not set the name "gfortran" becomes the ', & - ' default. "--compiler" is an alias for "--fc". ', & + ' --compiler COMPILER_NAME Specify a compiler name. The default is ', & + ' "gfortran" unless set by the environment ', & + ' variable FPM_COMPILER. ', & ' --runner CMD A command to prefix the program execution paths with. ', & ' see "fpm help runner" for further details. ', & ' --list list candidates instead of building or running them ', & @@ -622,7 +609,7 @@ contains ' # run default programs in /app or as specified in "fpm.toml" ', & ' # using the compiler command "f90". ', & - ' fpm run -fc f90 ', & + ' fpm run -compiler f90 ', & ' ', & ' # run a specific program and pass arguments to the command ', & ' fpm run mytest -- -x 10 -y 20 --title "my title line" ', & @@ -638,7 +625,7 @@ contains ' build(1) - the fpm(1) subcommand to build a project ', & ' ', & 'SYNOPSIS ', & - ' fpm build [--release][-fc COMPILER] [-list] ', & + ' fpm build [--release][-compiler COMPILER_NAME] [-list] ', & ' ', & ' fpm build --help|--version ', & ' ', & @@ -661,11 +648,9 @@ contains 'OPTIONS ', & ' --release build in build/*_release instead of build/*_debug with ', & ' high optimization instead of full debug options. ', & - ' --fc COMPILER Specify a compiler name. The default can be set by the ', & - ' environment variable FPM_FC. If not set, the ', & - ' environment variable FC is used to set the default. ', & - ' If that is not set the name "gfortran" becomes the ', & - ' default. "--compiler" is an alias for "--fc". ', & + ' --compiler COMPILER_NAME Specify a compiler name. The default is ', & + ' "gfortran" unless set by the environment ', & + ' variable FPM_COMPILER. ', & ' --list list candidates instead of building or running them ', & ' --help print this help and exit ', & ' --version print program version information and exit ', & @@ -787,7 +772,7 @@ contains ' test(1) - the fpm(1) subcommand to run project tests ', & ' ', & 'SYNOPSIS ', & - ' fpm test [[--target] NAME(s)][--release][-fc compiler ] ', & + ' fpm test [[--target] NAME(s)][--release][-compiler COMPILER_NAME ] ', & ' [--runner "CMD"] [--list][-- ARGS] ', & ' ', & ' fpm test --help|--version ', & @@ -801,11 +786,9 @@ contains ' or the tests listed in the "fpm.toml" file. ', & ' --release selects the optimized build instead of the debug ', & ' build. ', & - ' --fc COMPILER Specify a compiler name. The default can be set by the ', & - ' environment variable FPM_FC. If not set, the ', & - ' environment variable FC is used to set the default. ', & - ' If that is not set the name "gfortran" becomes the ', & - ' default. "--compiler" is an alias for "--fc". ', & + ' --compiler COMPILER_NAME Specify a compiler name. The default is ', & + ' "gfortran" unless set by the environment ', & + ' variable FPM_COMPILER. ', & ' --runner CMD A command to prefix the program execution paths with. ', & ' see "fpm help runner" for further details. ', & ' --list list candidates instead of building or running them ', & @@ -820,7 +803,7 @@ contains ' fpm test ', & ' ', & ' # run using compiler command "f90" ', & - ' fpm test -fc f90 ', & + ' fpm test -compiler f90 ', & ' ', & ' # run a specific test and pass arguments to the command ', & ' fpm test mytest -- -x 10 -y 20 --title "my title line" ', & @@ -830,7 +813,7 @@ contains help_install=[character(len=80) :: & ' fpm(1) subcommand "install" ', & ' ', & - ' USAGE: fpm install NAME ', & + '<USAGE> fpm install NAME ', & '' ] end subroutine set_help diff --git a/fpm/src/fpm_compiler.f90 b/fpm/src/fpm_compiler.f90 new file mode 100644 index 0000000..a16baa3 --- /dev/null +++ b/fpm/src/fpm_compiler.f90 @@ -0,0 +1,198 @@ +module fpm_compiler +use fpm_model, only: fpm_model_t +use fpm_filesystem, only: join_path +public add_compile_flag_defaults + +contains +subroutine add_compile_flag_defaults(build_name,compiler,model) +! Choose compile flags based on cli settings & manifest inputs +character(len=*),intent(in) :: build_name, compiler + +type(fpm_model_t) :: model +! 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 +character(len=:),allocatable :: module_path_switch + +! 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 +! Gnu gfortran gcc -J -I -fopenmp X +! Intel ifort icc -module -I -qopenmp X +! Intel(Windows) ifort icc /module:path /I /Qopenmp X +! Intel oneAPI ifx icx -module -I -qopenmp X +! PGI pgfortran pgcc -module -I -mp X +! NVIDIA nvfortran nvc -module -I -mp X +! LLVM flang flang clang -module -I -mp X +! LFortran lfortran --- ? ? ? X +! Lahey/Futjitsu lfc ? -M -I -openmp ? +! NAG nagfor ? -mdir -I -openmp x +! Cray crayftn craycc -J -I -homp ? +! IBM xlf90 ? -qmoddir -I -qsmp X +! Oracle/Sun ? ? -moddir= -M -xopenmp ? +! Silverfrost FTN95 ftn95 ? ? /MOD_PATH ? ? +! Elbrus ? lcc -J -I -fopenmp ? +! Hewlett Packard ? ? ? ? ? discontinued +! Watcom ? ? ? ? ? discontinued +! PathScale ? ? -module -I -mp discontinued +! G95 ? ? -fmod= -I -fopenmp discontinued +! Open64 ? ? -module -I -mp discontinued +! Unisys ? ? ? ? ? discontinued + + select case(build_name//'_'//compiler) + + case('release_gfortran') + module_path_switch='-J ' + fflags='& + & -O3& + & -Wimplicit-interface& + & -fPIC& + & -fmax-errors=1& + & -ffast-math& + & -funroll-loops& + &' + case('debug_gfortran') + module_path_switch='-J ' + fflags = '& + & -Wall& + & -Wextra& + & -Wimplicit-interface& + & -fPIC -fmax-errors=1& + & -g& + & -fbounds-check& + & -fcheck-array-temporaries& + & -fbacktrace& + &' + + case('release_f95') + module_path_switch='-J ' + fflags='& + & -O3& + & -Wimplicit-interface& + & -fPIC& + & -fmax-errors=1& + & -ffast-math& + & -funroll-loops& + &' + case('debug_f95') + module_path_switch='-J ' + fflags = '& + & -Wall& + & -Wextra& + & -Wimplicit-interface& + & -fPIC -fmax-errors=1& + & -g& + & -fbounds-check& + & -fcheck-array-temporaries& + & -Wno-maybe-uninitialized -Wno-uninitialized& + & -fbacktrace& + &' + + case('release_nvfortran') + module_path_switch='-module ' + fflags = '& + & -Mbackslash& + &' + case('debug_nvfortran') + module_path_switch='-module ' + fflags = '& + & -Minform=inform& + & -Mbackslash& + & -g& + & -Mbounds& + & -Mchkptr& + & -Mchkstk& + & -traceback& + &' + + case('release_ifort') + module_path_switch='-module ' + fflags = '& + & -fp-model precise& + & -pc 64& + & -align all& + & -error-limit 1& + & -reentrancy threaded& + & -nogen-interfaces& + & -assume byterecl& + & -assume nounderscore& + &' + case('debug_ifort') + module_path_switch='-module ' + fflags = '& + & -warn all& + & -check all& + & -error-limit 1& + & -O0& + & -g& + & -assume byterecl& + & -traceback& + &' + case('release_ifx') + module_path_switch='-module ' + fflags = ' ' + case('debug_ifx') + module_path_switch='-module ' + fflags = ' ' + + case('release_pgfortran','release_pgf90','release_pgf95') ! Portland Group F90/F95 compilers + module_path_switch='-module ' + fflags = ' ' + case('debug_pgfortran','debug_pgf90','debug_pgf95') ! Portland Group F90/F95 compilers + module_path_switch='-module ' + fflags = ' ' + + case('release_flang') + module_path_switch='-module ' + fflags = ' ' + case('debug_flang') + module_path_switch='-module ' + fflags = ' ' + + case('release_lfc') + module_path_switch='-M ' + fflags = ' ' + case('debug_lfc') + module_path_switch='-M ' + fflags = ' ' + + case('release_nagfor') + module_path_switch='-mdir ' + fflags = ' ' + case('debug_nagfor') + module_path_switch='-mdir ' + fflags = ' ' + + case('release_crayftn') + module_path_switch='-J ' + fflags = ' ' + case('debug_crayftn') + module_path_switch='-J ' + fflags = ' ' + + case('release_xlf90') + module_path_switch='-qmoddir ' + fflags = ' ' + case('debug_xlf90') + module_path_switch='-qmoddir ' + fflags = ' ' + + case default + module_path_switch='-module ' + fflags = ' ' + write(*,*)'<WARNING> unknown compiler (',compiler,')' + write(*,*)' and build name (',build_name,')' + write(*,*)' combination.' + write(*,*)' known compilers are gfortran, nvfortran, ifort' + end select + +! NOTE THAT MODULE_PATH_SWITCH IS ASSUMED TO CONTAIN REQUIRED TRAILING SPACE IF NEEDED +! so that values that do not require a space such as -moddir= will work + model%fortran_compile_flags = fflags//' '//& + & module_path_switch//join_path(model%output_directory,model%package_name) + +end subroutine add_compile_flag_defaults + +end module fpm_compiler diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90 index 77b22d1..ce0867e 100644 --- a/fpm/src/fpm_filesystem.f90 +++ b/fpm/src/fpm_filesystem.f90 @@ -38,7 +38,7 @@ function basename(path,suffix) result (base) endif else call split(path,file_parts,delimiters='\/.') - if(size(file_parts).gt.0)then + if(size(file_parts).ge.2)then base = trim(file_parts(size(file_parts)-1)) else base = '' |