Skip to content

Commit 142d259

Browse files
committed
Add: --no-prune argument to disable tree-shaking/pruning of dependencies
1 parent 5d044df commit 142d259

File tree

4 files changed

+35
-34
lines changed

4 files changed

+35
-34
lines changed

src/fpm.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -275,7 +275,7 @@ subroutine cmd_build(settings)
275275
call fpm_stop(1,'*cmd_build*:model error:'//error%message)
276276
end if
277277

278-
call targets_from_sources(targets, model, error)
278+
call targets_from_sources(targets, model, settings%prune, error)
279279
if (allocated(error)) then
280280
call fpm_stop(1,'*cmd_build*:target error:'//error%message)
281281
end if
@@ -321,7 +321,7 @@ subroutine cmd_run(settings,test)
321321
call fpm_stop(1, '*cmd_run*:model error:'//error%message)
322322
end if
323323

324-
call targets_from_sources(targets, model, error)
324+
call targets_from_sources(targets, model, settings%prune, error)
325325
if (allocated(error)) then
326326
call fpm_stop(1, '*cmd_run*:targets error:'//error%message)
327327
end if

src/fpm/cmd/install.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ subroutine cmd_install(settings)
3838
call build_model(model, settings%fpm_build_settings, package, error)
3939
call handle_error(error)
4040

41-
call targets_from_sources(targets, model, error)
41+
call targets_from_sources(targets, model, settings%prune, error)
4242
call handle_error(error)
4343

4444
installable = (allocated(package%library) .and. package%install%library) &

src/fpm_command_line.f90

Lines changed: 25 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -70,6 +70,7 @@ module fpm_command_line
7070
logical :: list=.false.
7171
logical :: show_model=.false.
7272
logical :: build_tests=.false.
73+
logical :: prune=.true.
7374
character(len=:),allocatable :: compiler
7475
character(len=:),allocatable :: c_compiler
7576
character(len=:),allocatable :: archiver
@@ -122,6 +123,15 @@ module fpm_command_line
122123
val_profile
123124

124125
! '12345678901234567890123456789012345678901234567890123456789012345678901234567890',&
126+
character(len=80), parameter :: help_text_build_common(*) = [character(len=80) :: &
127+
' --profile PROF Selects the compilation profile for the build. ',&
128+
' Currently available profiles are "release" for ',&
129+
' high optimization and "debug" for full debug options. ',&
130+
' If --flag is not specified the "debug" flags are the ',&
131+
' default. ',&
132+
' --no-prune Disable tree-shaking/pruning of unused module dependencies '&
133+
]
134+
! '12345678901234567890123456789012345678901234567890123456789012345678901234567890',&
125135
character(len=80), parameter :: help_text_compiler(*) = [character(len=80) :: &
126136
' --compiler NAME Specify a compiler name. The default is "gfortran" ',&
127137
' unless set by the environment variable FPM_FC. ',&
@@ -219,6 +229,7 @@ subroutine get_command_line_settings(cmd_settings)
219229

220230
compiler_args = &
221231
' --profile " "' // &
232+
' --no-prune F' // &
222233
' --compiler "'//get_fpm_env(fc_env, fc_default)//'"' // &
223234
' --c-compiler "'//get_fpm_env(cc_env, cc_default)//'"' // &
224235
' --archiver "'//get_fpm_env(ar_env, ar_default)//'"' // &
@@ -269,6 +280,7 @@ subroutine get_command_line_settings(cmd_settings)
269280
cmd_settings=fpm_run_settings(&
270281
& args=remaining,&
271282
& profile=val_profile,&
283+
& prune=.not.lget('no-prune'), &
272284
& compiler=val_compiler, &
273285
& c_compiler=c_compiler, &
274286
& archiver=archiver, &
@@ -296,6 +308,7 @@ subroutine get_command_line_settings(cmd_settings)
296308
allocate( fpm_build_settings :: cmd_settings )
297309
cmd_settings=fpm_build_settings( &
298310
& profile=val_profile,&
311+
& prune=.not.lget('no-prune'), &
299312
& compiler=val_compiler, &
300313
& c_compiler=c_compiler, &
301314
& archiver=archiver, &
@@ -447,6 +460,7 @@ subroutine get_command_line_settings(cmd_settings)
447460
install_settings = fpm_install_settings(&
448461
list=lget('list'), &
449462
profile=val_profile,&
463+
prune=.not.lget('no-prune'), &
450464
compiler=val_compiler, &
451465
c_compiler=c_compiler, &
452466
archiver=archiver, &
@@ -500,6 +514,7 @@ subroutine get_command_line_settings(cmd_settings)
500514
cmd_settings=fpm_test_settings(&
501515
& args=remaining, &
502516
& profile=val_profile, &
517+
& prune=.not.lget('no-prune'), &
503518
& compiler=val_compiler, &
504519
& c_compiler=c_compiler, &
505520
& archiver=archiver, &
@@ -614,7 +629,7 @@ subroutine set_help()
614629
help_list_dash = [character(len=80) :: &
615630
' ', &
616631
' build [--compiler COMPILER_NAME] [--profile PROF] [--flag FFLAGS] [--list] ', &
617-
' [--tests] ', &
632+
' [--tests] [--no-prune] ', &
618633
' help [NAME(s)] ', &
619634
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
620635
' [--full|--bare][--backfill] ', &
@@ -732,14 +747,15 @@ subroutine set_help()
732747
' Their syntax is ', &
733748
' ', &
734749
' build [--profile PROF] [--flag FFLAGS] [--list] [--compiler COMPILER_NAME] ', &
735-
' [--tests] ', &
750+
' [--tests] [--no-prune] ', &
736751
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
737752
' [--full|--bare][--backfill] ', &
738753
' update [NAME(s)] [--fetch-only] [--clean] ', &
739754
' run [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list] [--all] ', &
740-
' [--example] [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
755+
' [--example] [--runner "CMD"] [--compiler COMPILER_NAME] ', &
756+
' [--no-prune] [-- ARGS] ', &
741757
' test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list] ', &
742-
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
758+
' [--runner "CMD"] [--compiler COMPILER_NAME] [--no-prune] [-- ARGS] ', &
743759
' help [NAME(s)] ', &
744760
' list [--list] ', &
745761
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] ', &
@@ -748,11 +764,7 @@ subroutine set_help()
748764
'SUBCOMMAND OPTIONS ', &
749765
' -C, --directory PATH', &
750766
' Change working directory to PATH before running any command', &
751-
' --profile PROF selects the compilation profile for the build.',&
752-
' Currently available profiles are "release" for',&
753-
' high optimization and "debug" for full debug options.',&
754-
' If --flag is not specified the "debug" flags are the',&
755-
' default. ',&
767+
help_text_build_common, &
756768
help_text_compiler, &
757769
help_text_flag, &
758770
' --list List candidates instead of building or running them. On ', &
@@ -870,11 +882,7 @@ subroutine set_help()
870882
' the special characters from shell expansion. ', &
871883
' --all Run all examples or applications. An alias for --target ''*''. ', &
872884
' --example Run example programs instead of applications. ', &
873-
' --profile PROF selects the compilation profile for the build.',&
874-
' Currently available profiles are "release" for',&
875-
' high optimization and "debug" for full debug options.',&
876-
' If --flag is not specified the "debug" flags are the',&
877-
' default. ',&
885+
help_text_build_common, &
878886
help_text_compiler, &
879887
help_text_flag, &
880888
' --runner CMD A command to prefix the program execution paths with. ', &
@@ -941,11 +949,7 @@ subroutine set_help()
941949
' specified in the "fpm.toml" file. ', &
942950
' ', &
943951
'OPTIONS ', &
944-
' --profile PROF selects the compilation profile for the build.',&
945-
' Currently available profiles are "release" for',&
946-
' high optimization and "debug" for full debug options.',&
947-
' If --flag is not specified the "debug" flags are the',&
948-
' default. ',&
952+
help_text_build_common,&
949953
help_text_compiler, &
950954
help_text_flag, &
951955
' --list list candidates instead of building or running them ', &
@@ -1118,11 +1122,7 @@ subroutine set_help()
11181122
' any single character and "*" represents any string. ', &
11191123
' Note The glob string normally needs quoted to ', &
11201124
' protect the special characters from shell expansion.', &
1121-
' --profile PROF selects the compilation profile for the build.',&
1122-
' Currently available profiles are "release" for',&
1123-
' high optimization and "debug" for full debug options.',&
1124-
' If --flag is not specified the "debug" flags are the',&
1125-
' default. ',&
1125+
help_text_build_common,&
11261126
help_text_compiler, &
11271127
help_text_flag, &
11281128
' --runner CMD A command to prefix the program execution paths with. ', &
@@ -1187,11 +1187,7 @@ subroutine set_help()
11871187
'OPTIONS', &
11881188
' --list list all installable targets for this project,', &
11891189
' but do not install any of them', &
1190-
' --profile PROF selects the compilation profile for the build.',&
1191-
' Currently available profiles are "release" for',&
1192-
' high optimization and "debug" for full debug options.',&
1193-
' If --flag is not specified the "debug" flags are the',&
1194-
' default. ',&
1190+
help_text_build_common,&
11951191
help_text_flag, &
11961192
' --no-rebuild do not rebuild project before installation', &
11971193
' --prefix DIR path to installation directory (requires write access),', &

src/fpm_targets.f90

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -120,14 +120,17 @@ module fpm_targets
120120
contains
121121

122122
!> High-level wrapper to generate build target information
123-
subroutine targets_from_sources(targets,model,error)
123+
subroutine targets_from_sources(targets,model,prune,error)
124124

125125
!> The generated list of build targets
126126
type(build_target_ptr), intent(out), allocatable :: targets(:)
127127

128128
!> The package model from which to construct the target list
129129
type(fpm_model_t), intent(inout), target :: model
130130

131+
!> Enable tree-shaking/pruning of module dependencies
132+
logical, intent(in) :: prune
133+
131134
!> Error structure
132135
type(error_t), intent(out), allocatable :: error
133136

@@ -136,7 +139,9 @@ subroutine targets_from_sources(targets,model,error)
136139
call resolve_module_dependencies(targets,model%external_modules,error)
137140
if (allocated(error)) return
138141

139-
call prune_build_targets(targets)
142+
if (prune) then
143+
call prune_build_targets(targets)
144+
end if
140145

141146
call resolve_target_linking(targets,model)
142147

0 commit comments

Comments
 (0)