Skip to content

Commit b69042d

Browse files
authored
Merge pull request #527 from awvwgk/compiler-object
Add objects for handling compiler and archiver
2 parents fed8635 + d16c374 commit b69042d

File tree

5 files changed

+532
-316
lines changed

5 files changed

+532
-316
lines changed

src/fpm.f90

Lines changed: 25 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
module fpm
2-
use fpm_strings, only: string_t, operator(.in.), glob, join, string_cat
2+
use fpm_strings, only: string_t, operator(.in.), glob, join, string_cat, fnv_1a
33
use fpm_backend, only: build_package
44
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
55
fpm_run_settings, fpm_install_settings, fpm_test_settings
@@ -9,8 +9,7 @@ module fpm
99
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
1010
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
1111
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
12-
use fpm_compiler, only: get_module_flags, is_unknown_compiler, get_default_c_compiler, &
13-
get_archiver
12+
use fpm_compiler, only: new_compiler, new_archiver
1413

1514

1615
use fpm_sources, only: add_executable_sources, add_sources_from_dir
@@ -19,12 +18,9 @@ module fpm
1918
FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE
2019
use fpm_manifest, only : get_package_data, package_config_t
2120
use fpm_error, only : error_t, fatal_error, fpm_stop
22-
use fpm_manifest_test, only : test_config_t
2321
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
2422
& stdout=>output_unit, &
2523
& stderr=>error_unit
26-
use fpm_manifest_dependency, only: dependency_config_t
27-
use, intrinsic :: iso_fortran_env, only: error_unit
2824
implicit none
2925
private
3026
public :: cmd_build, cmd_run
@@ -43,10 +39,11 @@ subroutine build_model(model, settings, package, error)
4339

4440
integer :: i, j
4541
type(package_config_t) :: dependency
46-
character(len=:), allocatable :: manifest, lib_dir
42+
character(len=:), allocatable :: manifest, lib_dir, flags
4743

4844
logical :: duplicates_found = .false.
4945
type(string_t) :: include_dir
46+
character(len=16) :: build_name
5047

5148
model%package_name = package%name
5249

@@ -63,27 +60,30 @@ subroutine build_model(model, settings, package, error)
6360
call filewrite(join_path("build", ".gitignore"),["*"])
6461
end if
6562

66-
if(settings%compiler.eq.'')then
67-
model%fortran_compiler = 'gfortran'
63+
call new_compiler(model%compiler, settings%compiler)
64+
call new_archiver(model%archiver)
65+
66+
if (settings%flag == '') then
67+
flags = model%compiler%get_default_flags(settings%profile == "release")
6868
else
69-
model%fortran_compiler = settings%compiler
70-
endif
69+
flags = settings%flag
70+
select case(settings%profile)
71+
case("release", "debug")
72+
flags = flags // model%compiler%get_default_flags(settings%profile == "release")
73+
end select
74+
end if
7175

72-
model%archiver = get_archiver()
73-
call get_default_c_compiler(model%fortran_compiler, model%c_compiler)
74-
model%c_compiler = get_env('FPM_C_COMPILER',model%c_compiler)
76+
write(build_name, '(z16.16)') fnv_1a(flags)
7577

76-
if (is_unknown_compiler(model%fortran_compiler)) then
78+
if (model%compiler%is_unknown()) then
7779
write(*, '(*(a:,1x))') &
78-
"<WARN>", "Unknown compiler", model%fortran_compiler, "requested!", &
80+
"<WARN>", "Unknown compiler", model%compiler%fc, "requested!", &
7981
"Defaults for this compiler might be incorrect"
8082
end if
81-
model%output_directory = join_path('build',basename(model%fortran_compiler)//'_'//settings%build_name)
83+
model%output_directory = join_path('build',basename(model%compiler%fc)//'_'//build_name)
8284

83-
call get_module_flags(model%fortran_compiler, &
84-
& join_path(model%output_directory,model%package_name), &
85-
& model%fortran_compile_flags)
86-
model%fortran_compile_flags = settings%flag // model%fortran_compile_flags
85+
model%fortran_compile_flags = flags // " " // &
86+
& model%compiler%get_module_flag(join_path(model%output_directory, model%package_name))
8787

8888
allocate(model%packages(model%deps%ndep))
8989

@@ -191,9 +191,9 @@ subroutine build_model(model, settings, package, error)
191191
if (allocated(error)) return
192192

193193
if (settings%verbose) then
194-
write(*,*)'<INFO> BUILD_NAME: ',settings%build_name
195-
write(*,*)'<INFO> COMPILER: ',settings%compiler
196-
write(*,*)'<INFO> C COMPILER: ',model%c_compiler
194+
write(*,*)'<INFO> BUILD_NAME: ',build_name
195+
write(*,*)'<INFO> COMPILER: ',model%compiler%fc
196+
write(*,*)'<INFO> C COMPILER: ',model%compiler%cc
197197
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
198198
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
199199
end if
@@ -236,7 +236,7 @@ subroutine check_modules_for_duplicates(model, duplicates_found)
236236
if (allocated(model%packages(k)%sources(l)%modules_provided)) then
237237
do m=1,size(model%packages(k)%sources(l)%modules_provided)
238238
if (model%packages(k)%sources(l)%modules_provided(m)%s.in.modules(:modi-1)) then
239-
write(error_unit, *) "Warning: Module ",model%packages(k)%sources(l)%modules_provided(m)%s, &
239+
write(stderr, *) "Warning: Module ",model%packages(k)%sources(l)%modules_provided(m)%s, &
240240
" in ",model%packages(k)%sources(l)%file_name," is a duplicate"
241241
duplicates_found = .true.
242242
else

src/fpm_backend.f90

Lines changed: 8 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -30,12 +30,10 @@ module fpm_backend
3030
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
3131
use fpm_error, only : fpm_stop
3232
use fpm_environment, only: run, get_os_type, OS_WINDOWS
33-
use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir, unix_path
33+
use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir
3434
use fpm_model, only: fpm_model_t
3535
use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
3636
FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
37-
use fpm_strings, only: string_cat, string_t
38-
3937
implicit none
4038

4139
private
@@ -265,31 +263,19 @@ subroutine build_target(model,target,stat)
265263
select case(target%target_type)
266264

267265
case (FPM_TARGET_OBJECT)
268-
call run(model%fortran_compiler//" -c " // target%source%file_name // target%compile_flags &
269-
// " -o " // target%output_file, echo=.true., exitstat=stat)
266+
call model%compiler%compile_fortran(target%source%file_name, target%output_file, &
267+
& target%compile_flags, stat)
270268

271269
case (FPM_TARGET_C_OBJECT)
272-
call run(model%c_compiler//" -c " // target%source%file_name // target%compile_flags &
273-
// " -o " // target%output_file, echo=.true., exitstat=stat)
270+
call model%compiler%compile_c(target%source%file_name, target%output_file, &
271+
& target%compile_flags, stat)
274272

275273
case (FPM_TARGET_EXECUTABLE)
276-
277-
call run(model%fortran_compiler// " " // target%compile_flags &
278-
//" "//target%link_flags// " -o " // target%output_file, echo=.true., exitstat=stat)
274+
call model%compiler%link(target%output_file, &
275+
& target%compile_flags//" "//target%link_flags, stat)
279276

280277
case (FPM_TARGET_ARCHIVE)
281-
282-
select case (get_os_type())
283-
case (OS_WINDOWS)
284-
call write_response_file(target%output_file//".resp" ,target%link_objects)
285-
call run(model%archiver // target%output_file // " @" // target%output_file//".resp", &
286-
echo=.true., exitstat=stat)
287-
288-
case default
289-
call run(model%archiver // target%output_file // " " // string_cat(target%link_objects," "), &
290-
echo=.true., exitstat=stat)
291-
292-
end select
278+
call model%archiver%make_archive(target%output_file, target%link_objects, stat)
293279

294280
end select
295281

@@ -301,19 +287,5 @@ subroutine build_target(model,target,stat)
301287

302288
end subroutine build_target
303289

304-
!> Response files allow to read command line options from files.
305-
!> Whitespace is used to separate the arguments, we will use newlines
306-
!> as separator to create readable response files which can be inspected
307-
!> in case of errors.
308-
subroutine write_response_file(name, argv)
309-
character(len=*), intent(in) :: name
310-
type(string_t), intent(in) :: argv(:)
311-
integer :: iarg, io
312-
open(file=name, newunit=io)
313-
do iarg = 1, size(argv)
314-
write(io, '(a)') unix_path(argv(iarg)%s)
315-
end do
316-
close(io)
317-
end subroutine write_response_file
318290

319291
end module fpm_backend

src/fpm_command_line.f90

Lines changed: 1 addition & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,6 @@ module fpm_command_line
3131
use fpm_strings, only : lower, split, fnv_1a, to_fortran_name, is_fortran_name
3232
use fpm_filesystem, only : basename, canon_path, which
3333
use fpm_environment, only : run, get_command_arguments_quoted
34-
use fpm_compiler, only : get_default_compile_flags
3534
use fpm_error, only : fpm_stop
3635
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
3736
& stdout=>output_unit, &
@@ -70,7 +69,6 @@ module fpm_command_line
7069
logical :: show_model=.false.
7170
character(len=:),allocatable :: compiler
7271
character(len=:),allocatable :: profile
73-
character(len=:),allocatable :: build_name
7472
character(len=:),allocatable :: flag
7573
end type
7674

@@ -113,7 +111,7 @@ module fpm_command_line
113111
& ' ', 'fpm', 'new', 'build', 'run', &
114112
& 'test', 'runner', 'install', 'update', 'list', 'help', 'version' ]
115113

116-
character(len=:), allocatable :: val_runner, val_build, val_compiler, val_flag, val_profile
114+
character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_profile
117115

118116
contains
119117
subroutine get_command_line_settings(cmd_settings)
@@ -199,7 +197,6 @@ subroutine get_command_line_settings(cmd_settings)
199197
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
200198
cmd_settings=fpm_run_settings(&
201199
& args=remaining,&
202-
& build_name=val_build,&
203200
& profile=val_profile,&
204201
& compiler=val_compiler, &
205202
& flag=val_flag, &
@@ -223,7 +220,6 @@ subroutine get_command_line_settings(cmd_settings)
223220

224221
allocate( fpm_build_settings :: cmd_settings )
225222
cmd_settings=fpm_build_settings( &
226-
& build_name=val_build,&
227223
& profile=val_profile,&
228224
& compiler=val_compiler, &
229225
& flag=val_flag, &
@@ -361,7 +357,6 @@ subroutine get_command_line_settings(cmd_settings)
361357
allocate(install_settings)
362358
install_settings = fpm_install_settings(&
363359
list=lget('list'), &
364-
build_name=val_build, &
365360
profile=val_profile,&
366361
compiler=val_compiler, &
367362
flag=val_flag, &
@@ -417,7 +412,6 @@ subroutine get_command_line_settings(cmd_settings)
417412
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
418413
cmd_settings=fpm_test_settings(&
419414
& args=remaining, &
420-
& build_name=val_build, &
421415
& profile=val_profile, &
422416
& compiler=val_compiler, &
423417
& flag=val_flag, &
@@ -487,17 +481,6 @@ subroutine check_build_vals()
487481

488482
val_flag = " " // sget('flag')
489483
val_profile = sget('profile')
490-
if (val_flag == '') then
491-
call get_default_compile_flags(val_compiler, val_profile == "release", val_flag)
492-
else
493-
select case(val_profile)
494-
case("release", "debug")
495-
call get_default_compile_flags(val_compiler, val_profile == "release", flags)
496-
val_flag = flags // val_flag
497-
end select
498-
end if
499-
allocate(character(len=16) :: val_build)
500-
write(val_build, '(z16.16)') fnv_1a(val_flag)
501484

502485
end subroutine check_build_vals
503486

0 commit comments

Comments
 (0)