Skip to content

Commit

Permalink
Allow usage of --c-flag / CFLAGS and --link-flag / LDFLAGS
Browse files Browse the repository at this point in the history
  • Loading branch information
awvwgk committed Aug 29, 2021
1 parent 9bc3b78 commit ec88660
Show file tree
Hide file tree
Showing 4 changed files with 89 additions and 46 deletions.
9 changes: 7 additions & 2 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ subroutine build_model(model, settings, package, error)

integer :: i, j
type(package_config_t) :: dependency
character(len=:), allocatable :: manifest, lib_dir, flags
character(len=:), allocatable :: manifest, lib_dir, flags, cflags, ldflags

logical :: duplicates_found = .false.
type(string_t) :: include_dir
Expand Down Expand Up @@ -73,7 +73,10 @@ subroutine build_model(model, settings, package, error)
end select
end if

write(build_name, '(z16.16)') fnv_1a(flags)
cflags = trim(settings%cflag)
ldflags = trim(settings%ldflag)

write(build_name, '(z16.16)') fnv_1a(flags//cflags//ldflags)

if (model%compiler%is_unknown()) then
write(*, '(*(a:,1x))') &
Expand Down Expand Up @@ -195,6 +198,8 @@ subroutine build_model(model, settings, package, error)
write(*,*)'<INFO> COMPILER: ',model%compiler%fc
write(*,*)'<INFO> C COMPILER: ',model%compiler%cc
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
write(*,*)'<INFO> C COMPILER OPTIONS: ', model%c_compile_flags
write(*,*)'<INFO> LINKER OPTIONS: ', model%link_flags
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
end if

Expand Down
114 changes: 72 additions & 42 deletions src/fpm_command_line.f90
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,8 @@ module fpm_command_line
character(len=:),allocatable :: compiler
character(len=:),allocatable :: profile
character(len=:),allocatable :: flag
character(len=:),allocatable :: cflag
character(len=:),allocatable :: ldflag
end type

type, extends(fpm_build_settings) :: fpm_run_settings
Expand Down Expand Up @@ -111,7 +113,45 @@ module fpm_command_line
& ' ', 'fpm', 'new', 'build', 'run', &
& 'test', 'runner', 'install', 'update', 'list', 'help', 'version' ]

character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_profile
character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_cflag, val_ldflag, &
val_profile

character(len=80), parameter :: help_text_flag(*) = [character(len=80) :: &
' --flag FFLAGS selects compile arguments for the build, the default',&
' value is set by the FFLAGS environment variable.', &
' These are added to the profile options if --profile', &
' is specified, else these options override the defaults.',&
' Note object and .mod directory locations are always',&
' built in.',&
' --c-flag CFLAGS selects compile arguments specific for C source in the build.',&
' The default value is set by the CFLAGS environment variable.',&
' --link-flag LDFLAGS',&
' select arguments passed to the linker for the build.',&
' The default value is set by the LDFLAGS environment variable.'&
]


character(len=80), parameter :: help_text_environment(*) = [character(len=80) :: &
'ENVIRONMENT VARIABLES',&
' FPM_COMPILER sets the path to the Fortran compiler used for the build,', &
' will be overwritten by --compiler command line option', &
'', &
' FC sets the path to the Fortran compiler used for the build,', &
' will be overwritten by FPM_COMPILER environment variable', &
'', &
' FFLAGS sets the arguments for the Fortran compiler', &
' will be overwritten by --flag command line option', &
'', &
' CC sets the path to the C compiler used for the build,', &
'', &
' CFLAGS sets the arguments for the C compiler', &
' will be overwritten by --c-flag command line option', &
'', &
' AR sets the path to the archiver used for the build,', &
'', &
' LDFLAGS sets additional link arguments for creating executables', &
' will be overwritten by --link-flag command line option' &
]

contains
subroutine get_command_line_settings(cmd_settings)
Expand All @@ -123,6 +163,9 @@ subroutine get_command_line_settings(cmd_settings)
type(fpm_install_settings), allocatable :: install_settings
character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir

character(len=*), parameter :: fflags_env = "FFLAGS", cflags_env = "CFLAGS", &
& ldflags_env = "LDFLAGS", flags_default = " "

call set_help()
! text for --version switch,
select case (get_os_type())
Expand Down Expand Up @@ -160,7 +203,9 @@ subroutine get_command_line_settings(cmd_settings)
compiler_args = &
' --profile " "' // &
' --compiler "'//get_fc_env()//'"' // &
' --flag:: "'//get_fflags_env()//'"'
' --flag:: "'//get_env(fflags_env, flags_default)//'"' // &
' --c-flag:: "'//get_env(cflags_env, flags_default)//'"' // &
' --link-flag:: "'//get_env(ldflags_env, flags_default)//'"'

! now set subcommand-specific help text and process commandline
! arguments. Then call subcommand routine
Expand Down Expand Up @@ -205,6 +250,8 @@ subroutine get_command_line_settings(cmd_settings)
& profile=val_profile,&
& compiler=val_compiler, &
& flag=val_flag, &
& cflag=val_cflag, &
& ldflag=val_ldflag, &
& example=lget('example'), &
& list=lget('list'),&
& name=names,&
Expand All @@ -224,6 +271,8 @@ subroutine get_command_line_settings(cmd_settings)
& profile=val_profile,&
& compiler=val_compiler, &
& flag=val_flag, &
& cflag=val_cflag, &
& ldflag=val_ldflag, &
& list=lget('list'),&
& show_model=lget('show-model'),&
& verbose=lget('verbose') )
Expand Down Expand Up @@ -356,6 +405,8 @@ subroutine get_command_line_settings(cmd_settings)
profile=val_profile,&
compiler=val_compiler, &
flag=val_flag, &
cflag=val_cflag, &
ldflag=val_ldflag, &
no_rebuild=lget('no-rebuild'), &
verbose=lget('verbose'))
call get_char_arg(install_settings%prefix, 'prefix')
Expand Down Expand Up @@ -403,6 +454,8 @@ subroutine get_command_line_settings(cmd_settings)
& profile=val_profile, &
& compiler=val_compiler, &
& flag=val_flag, &
& cflag=val_cflag, &
& ldflag=val_ldflag, &
& example=.false., &
& list=lget('list'), &
& name=names, &
Expand Down Expand Up @@ -467,6 +520,8 @@ subroutine check_build_vals()
endif

val_flag = " " // sget('flag')
val_cflag = " " // sget('c-flag')
val_ldflag = " " // sget('link-flag')
val_profile = sget('profile')

end subroutine check_build_vals
Expand Down Expand Up @@ -645,12 +700,7 @@ subroutine set_help()
' high optimization and "debug" for full debug options.',&
' If --flag is not specified the "debug" flags are the',&
' default. ',&
' --flag FFLAGS selects compile arguments for the build, the default',&
' value is set by the FFLAGS environment variable.', &
' These are added to the profile options if --profile', &
' is specified, else these options override the defaults.',&
' Note object and .mod directory locations are always',&
' built in.',&
help_text_flag, &
' --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. ', &
Expand Down Expand Up @@ -694,6 +744,8 @@ subroutine set_help()
' (currently) allow for continued lines or multiple specifications of ', &
' the same option. ', &
' ', &
help_text_environment, &
' ', &
'EXAMPLES ', &
' sample commands: ', &
' ', &
Expand Down Expand Up @@ -771,12 +823,7 @@ subroutine set_help()
' high optimization and "debug" for full debug options.',&
' If --flag is not specified the "debug" flags are the',&
' default. ',&
' --flag FFLAGS selects compile arguments for the build, the default',&
' value is set by the FFLAGS environment variable.', &
' These are added to the profile options if --profile', &
' is specified, else these options override the defaults.',&
' Note object and .mod directory locations are always',&
' built in.',&
help_text_flag, &
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
' "gfortran" unless set by the environment ', &
' variable FC. ', &
Expand All @@ -788,6 +835,8 @@ subroutine set_help()
' -- ARGS optional arguments to pass to the program(s). The same ', &
' arguments are passed to all program names specified. ', &
' ', &
help_text_environment, &
' ', &
'EXAMPLES ', &
' fpm(1) - run or display project applications: ', &
' ', &
Expand Down Expand Up @@ -844,12 +893,7 @@ subroutine set_help()
' high optimization and "debug" for full debug options.',&
' If --flag is not specified the "debug" flags are the',&
' default. ',&
' --flag FFLAGS selects compile arguments for the build, the default',&
' value is set by the FFLAGS environment variable.', &
' These are added to the profile options if --profile', &
' is specified, else these options override the defaults.',&
' Note object and .mod directory locations are always',&
' built in.',&
help_text_flag, &
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
' "gfortran" unless set by the environment ', &
' variable FC. ', &
Expand All @@ -858,6 +902,8 @@ subroutine set_help()
' --help print this help and exit ', &
' --version print program version information and exit ', &
' ', &
help_text_environment, &
' ', &
'EXAMPLES ', &
' Sample commands: ', &
' ', &
Expand Down Expand Up @@ -1025,12 +1071,7 @@ subroutine set_help()
' high optimization and "debug" for full debug options.',&
' If --flag is not specified the "debug" flags are the',&
' default. ',&
' --flag FFLAGS selects compile arguments for the build, the default',&
' value is set by the FFLAGS environment variable.', &
' These are added to the profile options if --profile', &
' is specified, else these options override the defaults.',&
' Note object and .mod directory locations are always',&
' built in.',&
help_text_flag, &
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
' "gfortran" unless set by the environment ', &
' variable FC. ', &
Expand All @@ -1041,6 +1082,8 @@ subroutine set_help()
' The same arguments are passed to all test names ', &
' specified. ', &
' ', &
help_text_environment, &
' ', &
'EXAMPLES ', &
'run tests ', &
' ', &
Expand Down Expand Up @@ -1098,12 +1141,7 @@ subroutine set_help()
' high optimization and "debug" for full debug options.',&
' If --flag is not specified the "debug" flags are the',&
' default. ',&
' --flag FFLAGS selects compile arguments for the build, the default',&
' value is set by the FFLAGS environment variable.', &
' These are added to the profile options if --profile', &
' is specified, else these options override the defaults.',&
' Note object and .mod directory locations are always',&
' built in.',&
help_text_flag, &
' --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', &
Expand All @@ -1115,6 +1153,8 @@ subroutine set_help()
' (default: include)', &
' --verbose print more information', &
'', &
help_text_environment, &
'', &
'EXAMPLES', &
' 1. Install release version of project:', &
'', &
Expand Down Expand Up @@ -1148,14 +1188,4 @@ function get_fc_env() result(fc)
fc = get_env(fc_env_long, get_env(fc_env, fc_default))
end function get_fc_env

!> Get Fortran compiler arguments from environment.
function get_fflags_env() result(fflags)
character(len=:), allocatable :: fflags

character(len=*), parameter :: fflags_env = "FFLAGS"
character(len=*), parameter :: fflags_default = " "

fflags = get_env(fflags_env, fflags_default)
end function get_fflags_env

end module fpm_command_line
8 changes: 8 additions & 0 deletions src/fpm_model.f90
Original file line number Diff line number Diff line change
Expand Up @@ -124,6 +124,12 @@ module fpm_model
!> Command line flags passed to fortran for compilation
character(:), allocatable :: fortran_compile_flags

!> Command line flags passed to C for compilation
character(:), allocatable :: c_compile_flags

!> Command line flags passed to the linker
character(:), allocatable :: link_flags

!> Base directory for build
character(:), allocatable :: output_directory

Expand Down Expand Up @@ -273,6 +279,8 @@ function info_model(model) result(s)
s = s // ', archiver=(' // debug(model%archiver) // ')'
! character(:), allocatable :: fortran_compile_flags
s = s // ', fortran_compile_flags="' // model%fortran_compile_flags // '"'
s = s // ', c_compile_flags="' // model%c_compile_flags // '"'
s = s // ', link_flags="' // model%link_flags // '"'
! character(:), allocatable :: output_directory
s = s // ', output_directory="' // model%output_directory // '"'
! type(string_t), allocatable :: link_libraries(:)
Expand Down
4 changes: 2 additions & 2 deletions src/fpm_targets.f90
Original file line number Diff line number Diff line change
Expand Up @@ -479,7 +479,7 @@ subroutine resolve_target_linking(targets, model)
if (target%target_type /= FPM_TARGET_C_OBJECT) then
target%compile_flags = model%fortran_compile_flags//" "//global_include_flags
else
target%compile_flags = global_include_flags
target%compile_flags = model%c_compile_flags//" "//global_include_flags
end if

allocate(target%link_objects(0))
Expand All @@ -494,7 +494,7 @@ subroutine resolve_target_linking(targets, model)

call get_link_objects(target%link_objects,target,is_exe=.true.)

target%link_flags = string_cat(target%link_objects," ")
target%link_flags = model%link_flags//" "//string_cat(target%link_objects," ")

if (allocated(target%link_libraries)) then
if (size(target%link_libraries) > 0) then
Expand Down

0 comments on commit ec88660

Please sign in to comment.