28
28
module fpm_compiler
29
29
use fpm_environment, only: &
30
30
run, &
31
+ get_env, &
31
32
get_os_type, &
32
33
OS_LINUX, &
33
34
OS_MACOS, &
@@ -40,12 +41,6 @@ module fpm_compiler
40
41
use fpm_filesystem, only: join_path, basename, get_temp_filename, delete_file, unix_path
41
42
use fpm_strings, only: string_cat, string_t
42
43
implicit none
43
- public :: is_unknown_compiler
44
- public :: get_module_flags
45
- public :: get_default_compile_flags
46
- public :: get_debug_compile_flags
47
- public :: get_release_compile_flags
48
-
49
44
public :: compiler_t, archiver_t
50
45
public :: debug
51
46
@@ -76,22 +71,37 @@ module fpm_compiler
76
71
77
72
! > Definition of compiler object
78
73
type :: compiler_t
74
+ ! > Identifier of the compiler
75
+ integer (compiler_enum) :: id = id_unknown
79
76
! > Path to the Fortran compiler
80
77
character (len= :), allocatable :: fc
81
78
! > Path to the C compiler
82
79
character (len= :), allocatable :: cc
83
80
! > Print all commands
84
81
logical :: echo = .true.
85
82
contains
83
+ ! > Get default compiler flags
84
+ procedure :: get_default_flags
85
+ ! > Get flag for module output directories
86
+ procedure :: get_module_flag
87
+ ! > Get flag for include directories
88
+ procedure :: get_include_flag
86
89
! > Compile a Fortran object
87
90
procedure :: compile_fortran
88
91
! > Compile a C object
89
92
procedure :: compile_c
90
93
! > Link executable
91
94
procedure :: link
95
+ ! > Check whether compiler is recognized
96
+ procedure :: is_unknown
92
97
end type compiler_t
93
98
94
99
100
+ interface compiler_t
101
+ module procedure :: new_compiler
102
+ end interface compiler_t
103
+
104
+
95
105
! > Definition of archiver object
96
106
type :: archiver_t
97
107
! > Path to archiver
@@ -121,20 +131,19 @@ module fpm_compiler
121
131
122
132
contains
123
133
124
- subroutine get_default_compile_flags (compiler , release , flags )
125
- character (len=* ), intent (in ) :: compiler
134
+
135
+ function get_default_flags (self , release ) result(flags)
136
+ class(compiler_t), intent (in ) :: self
126
137
logical , intent (in ) :: release
127
- character (len= :), allocatable , intent (out ) :: flags
128
- integer :: id
138
+ character (len= :), allocatable :: flags
129
139
130
- id = get_compiler_id(compiler)
131
140
if (release) then
132
- call get_release_compile_flags(id, flags)
141
+ call get_release_compile_flags(self % id, flags)
133
142
else
134
- call get_debug_compile_flags(id, flags)
143
+ call get_debug_compile_flags(self % id, flags)
135
144
end if
136
145
137
- end subroutine get_default_compile_flags
146
+ end function get_default_flags
138
147
139
148
subroutine get_release_compile_flags (id , flags )
140
149
integer (compiler_enum), intent (in ) :: id
@@ -343,42 +352,63 @@ subroutine get_debug_compile_flags(id, flags)
343
352
end select
344
353
end subroutine get_debug_compile_flags
345
354
346
- subroutine get_module_flags (compiler , modpath , flags )
347
- character (len=* ), intent (in ) :: compiler
348
- character (len=* ), intent (in ) :: modpath
349
- character (len= :), allocatable , intent (out ) :: flags
350
- integer (compiler_enum) :: id
355
+ function get_include_flag (self , path ) result(flags)
356
+ class(compiler_t), intent (in ) :: self
357
+ character (len=* ), intent (in ) :: path
358
+ character (len= :), allocatable :: flags
351
359
352
- id = get_compiler_id(compiler)
360
+ select case (self% id)
361
+ case default
362
+ flags = " -I " // path
353
363
354
- select case (id)
364
+ case (id_caf, id_gcc, id_f95, id_cray, id_nvhpc, id_pgi, id_flang, &
365
+ & id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_unknown, &
366
+ & id_intel_llvm_nix, id_intel_llvm_unknown, id_lahey, id_nag, &
367
+ & id_ibmxl)
368
+ flags = " -I " // path
369
+
370
+ case (id_intel_classic_windows, id_intel_llvm_windows)
371
+ flags = " /I" // path
372
+
373
+ end select
374
+ end function get_include_flag
375
+
376
+ function get_module_flag (self , path ) result(flags)
377
+ class(compiler_t), intent (in ) :: self
378
+ character (len=* ), intent (in ) :: path
379
+ character (len= :), allocatable :: flags
380
+
381
+ select case (self% id)
355
382
case default
356
- flags= ' -module ' // modpath // ' -I ' // modpath
383
+ flags = " -module " // path
357
384
358
385
case (id_caf, id_gcc, id_f95, id_cray)
359
- flags= ' -J ' // modpath // ' -I ' // modpath
386
+ flags = " -J " // path
360
387
361
388
case (id_nvhpc, id_pgi, id_flang)
362
- flags= ' -module ' // modpath // ' -I ' // modpath
389
+ flags = " -module " // path
363
390
364
- case (id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_unknown, id_intel_llvm_nix, id_intel_llvm_unknown)
365
- flags= ' -module ' // modpath// ' -I' // modpath
391
+ case (id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_unknown, &
392
+ & id_intel_llvm_nix, id_intel_llvm_unknown)
393
+ flags = " -module " // path
366
394
367
395
case (id_intel_classic_windows, id_intel_llvm_windows)
368
- flags= ' /module:' // modpath // ' /I ' // modpath
396
+ flags = " /module:" // path
369
397
370
398
case (id_lahey)
371
- flags= ' -M ' // modpath // ' -I ' // modpath
399
+ flags = " -M " // path
372
400
373
401
case (id_nag)
374
- flags= ' -mdir ' // modpath // ' -I ' // modpath !
402
+ flags = " -mdir " // path
375
403
376
404
case (id_ibmxl)
377
- flags= ' -qmoddir ' // modpath // ' -I ' // modpath
405
+ flags = " -qmoddir " // path
378
406
379
407
end select
408
+ flags = flags// " " // self% get_include_flag(path)
409
+
410
+ end function get_module_flag
380
411
381
- end subroutine get_module_flags
382
412
383
413
subroutine get_default_c_compiler (f_compiler , c_compiler )
384
414
character (len=* ), intent (in ) :: f_compiler
@@ -408,10 +438,13 @@ subroutine get_default_c_compiler(f_compiler, c_compiler)
408
438
409
439
end subroutine get_default_c_compiler
410
440
441
+
411
442
function get_compiler_id (compiler ) result(id)
412
443
character (len=* ), intent (in ) :: compiler
413
444
integer (kind= compiler_enum) :: id
414
445
446
+ integer :: stat
447
+
415
448
if (check_compiler(compiler, " gfortran" )) then
416
449
id = id_gcc
417
450
return
@@ -510,14 +543,31 @@ function check_compiler(compiler, expected) result(match)
510
543
end function check_compiler
511
544
512
545
513
- function is_unknown_compiler ( compiler ) result( is_unknown)
514
- character (len =* ), intent (in ) :: compiler
546
+ pure function is_unknown ( self )
547
+ class(compiler_t ), intent (in ) :: self
515
548
logical :: is_unknown
516
- is_unknown = get_compiler_id(compiler) == id_unknown
517
- end function is_unknown_compiler
549
+ is_unknown = self% id == id_unknown
550
+ end function is_unknown
551
+
552
+
553
+ ! > Create new compiler instance
554
+ function new_compiler (fc ) result(self)
555
+ ! > Fortran compiler name or path
556
+ character (len=* ), intent (in ) :: fc
557
+ ! > New instance of the compiler
558
+ type (compiler_t) :: self
559
+
560
+ character (len=* ), parameter :: cc_env = " FPM_C_COMPILER"
561
+
562
+ self% id = get_compiler_id(fc)
563
+
564
+ self% fc = fc
565
+ call get_default_c_compiler(self% fc, self% cc)
566
+ self% cc = get_env(cc_env, self% cc)
567
+ end function new_compiler
518
568
519
569
520
- ! > Create new archiver
570
+ ! > Create new archiver instance
521
571
function new_archiver () result(self)
522
572
! > New instance of the archiver
523
573
type (archiver_t) :: self
0 commit comments