@@ -75,15 +75,20 @@ subroutine build_model(model, settings, package_config, error)
75
75
76
76
! Extract the target platform for this build
77
77
target_platform = model% target_platform()
78
-
79
- call new_compiler_flags(model,settings)
78
+
80
79
model% build_dir = settings% build_dir
81
80
model% build_prefix = join_path(settings% build_dir, basename(model% compiler% fc))
82
- model% include_tests = settings% build_tests
83
-
81
+ model% include_tests = settings% build_tests
82
+
83
+ if (allocated (settings% features)) print * , ' features: ' ,(settings% features(i)% s// ' ' ,i= 1 ,size (settings% features))
84
+ if (allocated (settings% profile)) print * , ' profile: ' ,settings% profile
85
+
84
86
! Extract the current package configuration request
85
87
package = package_config% export_config(target_platform,settings% features,settings% profile,error)
86
- if (allocated (error)) return
88
+ if (allocated (error)) return
89
+
90
+ ! Initialize compiler flags using the feature-enabled package configuration
91
+ call new_compiler_flags(model, settings, package)
87
92
88
93
! Resolve meta-dependencies into the package and the model
89
94
call resolve_metapackages(model,package,settings,error)
@@ -311,42 +316,50 @@ subroutine build_model(model, settings, package_config, error)
311
316
end if
312
317
end subroutine build_model
313
318
314
- ! > Initialize model compiler flags
315
- subroutine new_compiler_flags (model ,settings )
319
+ ! > Helper: safely get string from either CLI or package, with fallback
320
+ pure function assemble_flags (cli_flag , package_flag , fallback ) result(flags)
321
+ character (len=* ), optional , intent (in ) :: cli_flag, package_flag, fallback
322
+ character (len= :), allocatable :: flags
323
+
324
+ allocate (character (len= 0 ) :: flags)
325
+
326
+ if (present (cli_flag)) flags = flags // ' ' // trim (cli_flag)
327
+ if (present (package_flag)) flags = flags // ' ' // trim (package_flag)
328
+ if (present (fallback)) flags = flags // ' ' // trim (fallback)
329
+
330
+ end function assemble_flags
331
+
332
+ ! > Initialize model compiler flags from CLI settings and package configuration
333
+ subroutine new_compiler_flags (model , settings , package )
316
334
type (fpm_model_t), intent (inout ) :: model
317
335
type (fpm_build_settings), intent (in ) :: settings
336
+ type (package_config_t), intent (in ) :: package
318
337
319
- character (len= :), allocatable :: flags, cflags, cxxflags, ldflags
320
- logical :: release_profile
338
+ logical :: release_profile, debug_profile
321
339
322
- if (allocated (settings% profile)) then
323
- release_profile = settings% profile == " release"
340
+ release_profile = .false.
341
+ debug_profile = .false.
342
+ if (allocated (settings% profile)) release_profile = settings% profile == " release"
343
+ if (allocated (settings% profile)) debug_profile = settings% profile == " debug"
344
+
345
+ ! Debug./Release profile requested but not defined:
346
+ ! fallback to backward-compatible behavior
347
+ if ( (release_profile .and. package% find_profile(" release" )==0 ) &
348
+ .or. (debug_profile .and. package% find_profile(" debug" )==0 ) ) then
349
+
350
+ model% fortran_compile_flags = assemble_flags(settings% flag,package% flags,&
351
+ model% compiler% get_default_flags(release_profile))
352
+
353
+
324
354
else
325
- release_profile = .false.
355
+
356
+ model% fortran_compile_flags = assemble_flags(settings% flag, package% flags)
357
+
326
358
end if
327
359
328
- if (.not. allocated (settings% flag)) then
329
- flags = model% compiler% get_default_flags(release_profile)
330
- elseif (settings% flag == ' ' ) then
331
- flags = model% compiler% get_default_flags(release_profile)
332
- else
333
- flags = settings% flag
334
- if (allocated (settings% profile)) then
335
- select case (settings% profile)
336
- case (" release" , " debug" )
337
- flags = flags // model% compiler% get_default_flags(release_profile)
338
- end select
339
- endif
340
- end if
341
-
342
- cflags = trim (settings% cflag)
343
- cxxflags = trim (settings% cxxflag)
344
- ldflags = trim (settings% ldflag)
345
-
346
- model% fortran_compile_flags = flags
347
- model% c_compile_flags = cflags
348
- model% cxx_compile_flags = cxxflags
349
- model% link_flags = ldflags
360
+ model% c_compile_flags = assemble_flags(settings% cflag, package% c_flags)
361
+ model% cxx_compile_flags = assemble_flags(settings% cxxflag, package% cxx_flags)
362
+ model% link_flags = assemble_flags(settings% ldflag, package% link_time_flags)
350
363
351
364
end subroutine new_compiler_flags
352
365
0 commit comments