Skip to content

Commit e4010c6

Browse files
committed
Use objects to represent compilers and archiver
- Fortran and C compiler are represented by thin compiler_t object - archiver is represented by thin archiver_t object
1 parent fbbfb2c commit e4010c6

File tree

5 files changed

+118
-36
lines changed

5 files changed

+118
-36
lines changed

src/fpm.f90

Lines changed: 18 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,8 @@ 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
12+
use fpm_compiler, only: get_module_flags, is_unknown_compiler, get_default_c_compiler, &
13+
& archiver_t, compiler_t
1314

1415

1516
use fpm_sources, only: add_executable_sources, add_sources_from_dir
@@ -43,6 +44,7 @@ subroutine build_model(model, settings, package, error)
4344
integer :: i, j
4445
type(package_config_t) :: dependency
4546
character(len=:), allocatable :: manifest, lib_dir
47+
character(len=:), allocatable :: fortran_compiler, fortran_compiler_flags, c_compiler
4648

4749
logical :: duplicates_found = .false.
4850
type(string_t) :: include_dir
@@ -58,25 +60,27 @@ subroutine build_model(model, settings, package, error)
5860
if (allocated(error)) return
5961

6062
if(settings%compiler.eq.'')then
61-
model%fortran_compiler = 'gfortran'
63+
fortran_compiler = 'gfortran'
6264
else
63-
model%fortran_compiler = settings%compiler
65+
fortran_compiler = settings%compiler
6466
endif
6567

66-
call get_default_c_compiler(model%fortran_compiler, model%c_compiler)
67-
model%c_compiler = get_env('FPM_C_COMPILER',model%c_compiler)
68+
call get_default_c_compiler(fortran_compiler, c_compiler)
69+
c_compiler = get_env('FPM_C_COMPILER', c_compiler)
6870

69-
if (is_unknown_compiler(model%fortran_compiler)) then
71+
if (is_unknown_compiler(fortran_compiler)) then
7072
write(*, '(*(a:,1x))') &
71-
"<WARN>", "Unknown compiler", model%fortran_compiler, "requested!", &
73+
"<WARN>", "Unknown compiler", fortran_compiler, "requested!", &
7274
"Defaults for this compiler might be incorrect"
7375
end if
74-
model%output_directory = join_path('build',basename(model%fortran_compiler)//'_'//settings%build_name)
76+
model%output_directory = join_path('build',basename(fortran_compiler)//'_'//settings%build_name)
7577

76-
call get_module_flags(model%fortran_compiler, &
78+
call get_module_flags(fortran_compiler, &
7779
& join_path(model%output_directory,model%package_name), &
78-
& model%fortran_compile_flags)
79-
model%fortran_compile_flags = settings%flag // model%fortran_compile_flags
80+
& fortran_compiler_flags)
81+
model%compiler = compiler_t(fortran_compiler, settings%flag // fortran_compiler_flags)
82+
model%c_compiler = compiler_t(c_compiler, settings%flag // fortran_compiler_flags)
83+
model%archiver = archiver_t()
8084

8185
allocate(model%packages(model%deps%ndep))
8286

@@ -185,9 +189,9 @@ subroutine build_model(model, settings, package, error)
185189

186190
if (settings%verbose) then
187191
write(*,*)'<INFO> BUILD_NAME: ',settings%build_name
188-
write(*,*)'<INFO> COMPILER: ',settings%compiler
189-
write(*,*)'<INFO> C COMPILER: ',model%c_compiler
190-
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
192+
write(*,*)'<INFO> COMPILER: ',model%compiler%prog
193+
write(*,*)'<INFO> C COMPILER: ',model%c_compiler%prog
194+
write(*,*)'<INFO> COMPILER OPTIONS: ', model%compiler%flags
191195
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
192196
end if
193197

src/fpm_backend.f90

Lines changed: 6 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -238,20 +238,18 @@ subroutine build_target(model,target)
238238
select case(target%target_type)
239239

240240
case (FPM_TARGET_OBJECT)
241-
call run(model%fortran_compiler//" -c " // target%source%file_name // target%compile_flags &
242-
// " -o " // target%output_file)
241+
call model%compiler%compile(target%output_file, target%source%file_name, &
242+
target%compile_flags)
243243

244244
case (FPM_TARGET_C_OBJECT)
245-
call run(model%c_compiler//" -c " // target%source%file_name // target%compile_flags &
246-
// " -o " // target%output_file)
245+
call model%c_compiler%compile(target%output_file, target%source%file_name, &
246+
target%compile_flags)
247247

248248
case (FPM_TARGET_EXECUTABLE)
249-
250-
call run(model%fortran_compiler// " " // target%compile_flags &
251-
//" "//target%link_flags// " -o " // target%output_file)
249+
call model%compiler%link(target%output_file, target%link_flags, target%compile_flags)
252250

253251
case (FPM_TARGET_ARCHIVE)
254-
call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," "))
252+
call model%archiver%archive(target%output_file, target%link_objects)
255253

256254
end select
257255

src/fpm_compiler.f90

Lines changed: 80 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -26,9 +26,10 @@
2626
! Open64 ? ? -module -I -mp discontinued
2727
! Unisys ? ? ? ? ? discontinued
2828
module fpm_compiler
29-
use fpm_model, only: fpm_model_t
3029
use fpm_filesystem, only: join_path, basename
30+
use fpm_strings, only : string_t, string_cat
3131
use fpm_environment, only: &
32+
run, &
3233
get_os_type, &
3334
OS_LINUX, &
3435
OS_MACOS, &
@@ -67,7 +68,85 @@ module fpm_compiler
6768
end enum
6869
integer, parameter :: compiler_enum = kind(id_unknown)
6970

71+
!> Abstraction for the compiler
72+
type :: compiler_t
73+
character(len=:), allocatable :: prog
74+
character(len=:), allocatable :: flags
7075
contains
76+
procedure :: compile
77+
procedure :: link
78+
end type compiler_t
79+
interface compiler_t
80+
module procedure :: new_compiler
81+
end interface compiler_t
82+
83+
!> Abstraction for the archive / static library creation
84+
type :: archiver_t
85+
character(len=:), allocatable :: prog
86+
character(len=:), allocatable :: flags
87+
contains
88+
procedure :: archive
89+
end type archiver_t
90+
interface archiver_t
91+
module procedure :: new_archiver
92+
end interface archiver_t
93+
94+
contains
95+
96+
!> Create a new archiver object
97+
function new_archiver() result(new)
98+
type(archiver_t) :: new
99+
character(len=*), parameter :: default_archiver = "ar"
100+
character(len=*), parameter :: default_archiver_flags = "-rs"
101+
new%prog = default_archiver
102+
new%flags = default_archiver_flags
103+
end function new_archiver
104+
105+
!> Create an archive / static library from a given set of object files
106+
subroutine archive(self, output, objects)
107+
class(archiver_t), intent(in) :: self
108+
character(len=*), intent(in) :: output
109+
type(string_t), intent(in) :: objects(:)
110+
111+
call run(self%prog //" "// self%flags //" "// output //" "// string_cat(objects, " "))
112+
end subroutine archive
113+
114+
!> Create a new compiler object
115+
function new_compiler(compiler, compiler_flags) result(new)
116+
type(compiler_t) :: new
117+
character(len=*), intent(in) :: compiler
118+
character(len=*), intent(in) :: compiler_flags
119+
new%prog = compiler
120+
new%flags = compiler_flags
121+
end function new_compiler
122+
123+
!> Compile an object file from a given source file
124+
subroutine compile(self, output, input, flags)
125+
class(compiler_t), intent(in) :: self
126+
character(len=*), intent(in) :: output
127+
character(len=*), intent(in) :: input
128+
character(len=*), intent(in), optional :: flags
129+
130+
if (present(flags)) then
131+
call run(self%prog // " " // flags // " -o " // output // " -c " // input)
132+
else
133+
call run(self%prog // " " // self%flags // " -o " // output // " -c " // input)
134+
end if
135+
end subroutine compile
136+
137+
!> Link an executable from a given set of object files (might contain link flags as well)
138+
subroutine link(self, output, objects, flags)
139+
class(compiler_t), intent(in) :: self
140+
character(len=*), intent(in) :: output
141+
character(len=*), intent(in) :: objects
142+
character(len=*), intent(in), optional :: flags
143+
144+
if (present(flags)) then
145+
call run(self%prog // " " // flags // " -o " // output // " " // objects)
146+
else
147+
call run(self%prog // " " // self%flags // " -o " // output // " " // objects)
148+
end if
149+
end subroutine link
71150

72151
subroutine get_default_compile_flags(compiler, release, flags)
73152
character(len=*), intent(in) :: compiler

src/fpm_model.f90

Lines changed: 12 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@
1919
!>
2020
module fpm_model
2121
use iso_fortran_env, only: int64
22+
use fpm_compiler, only : archiver_t, compiler_t
2223
use fpm_strings, only: string_t, str
2324
use fpm_dependency, only: dependency_tree_t
2425
implicit none
@@ -114,15 +115,6 @@ module fpm_model
114115
!> Array of packages (including the root package)
115116
type(package_t), allocatable :: packages(:)
116117

117-
!> Command line name to invoke fortran compiler
118-
character(:), allocatable :: fortran_compiler
119-
120-
!> Command line name to invoke c compiler
121-
character(:), allocatable :: c_compiler
122-
123-
!> Command line flags passed to fortran for compilation
124-
character(:), allocatable :: fortran_compile_flags
125-
126118
!> Base directory for build
127119
character(:), allocatable :: output_directory
128120

@@ -138,6 +130,15 @@ module fpm_model
138130
!> Project dependencies
139131
type(dependency_tree_t) :: deps
140132

133+
!> Compiler command
134+
type(compiler_t) :: compiler
135+
136+
!> Compiler command
137+
type(compiler_t) :: c_compiler
138+
139+
!> Archiver command
140+
type(archiver_t) :: archiver
141+
141142
end type fpm_model_t
142143

143144
contains
@@ -270,9 +271,9 @@ function info_model(model) result(s)
270271
end do
271272
s = s // "]"
272273
! character(:), allocatable :: fortran_compiler
273-
s = s // ', fortran_compiler="' // model%fortran_compiler // '"'
274+
s = s // ', fortran_compiler="' // model%compiler%prog // '"'
274275
! character(:), allocatable :: fortran_compile_flags
275-
s = s // ', fortran_compile_flags="' // model%fortran_compile_flags // '"'
276+
s = s // ', fortran_compile_flags="' // model%compiler%flags // '"'
276277
! character(:), allocatable :: output_directory
277278
s = s // ', output_directory="' // model%output_directory // '"'
278279
! type(string_t), allocatable :: link_libraries(:)

src/fpm_targets.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -480,9 +480,9 @@ subroutine resolve_target_linking(targets, model)
480480
associate(target => targets(i)%ptr)
481481

482482
if (target%target_type /= FPM_TARGET_C_OBJECT) then
483-
target%compile_flags = model%fortran_compile_flags//" "//global_include_flags
483+
target%compile_flags = model%compiler%flags//" "//global_include_flags
484484
else
485-
target%compile_flags = global_include_flags
485+
target%compile_flags = model%c_compiler%flags//" "//global_include_flags
486486
end if
487487

488488
allocate(target%link_objects(0))

0 commit comments

Comments
 (0)