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,13 +41,7 @@ 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
- public :: compiler_t, archiver_t
44
+ public :: compiler_t, new_compiler, archiver_t, new_archiver
50
45
public :: debug
51
46
52
47
enum, bind(C)
@@ -76,19 +71,29 @@ 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
@@ -106,12 +111,6 @@ module fpm_compiler
106
111
end type archiver_t
107
112
108
113
109
- ! > Constructor for archiver
110
- interface archiver_t
111
- module procedure :: new_archiver
112
- end interface archiver_t
113
-
114
-
115
114
! > Create debug printout
116
115
interface debug
117
116
module procedure :: debug_compiler
@@ -121,20 +120,19 @@ module fpm_compiler
121
120
122
121
contains
123
122
124
- subroutine get_default_compile_flags (compiler , release , flags )
125
- character (len=* ), intent (in ) :: compiler
123
+
124
+ function get_default_flags (self , release ) result(flags)
125
+ class(compiler_t), intent (in ) :: self
126
126
logical , intent (in ) :: release
127
- character (len= :), allocatable , intent (out ) :: flags
128
- integer :: id
127
+ character (len= :), allocatable :: flags
129
128
130
- id = get_compiler_id(compiler)
131
129
if (release) then
132
- call get_release_compile_flags(id, flags)
130
+ call get_release_compile_flags(self % id, flags)
133
131
else
134
- call get_debug_compile_flags(id, flags)
132
+ call get_debug_compile_flags(self % id, flags)
135
133
end if
136
134
137
- end subroutine get_default_compile_flags
135
+ end function get_default_flags
138
136
139
137
subroutine get_release_compile_flags (id , flags )
140
138
integer (compiler_enum), intent (in ) :: id
@@ -343,42 +341,63 @@ subroutine get_debug_compile_flags(id, flags)
343
341
end select
344
342
end subroutine get_debug_compile_flags
345
343
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
344
+ function get_include_flag (self , path ) result(flags)
345
+ class(compiler_t), intent (in ) :: self
346
+ character (len=* ), intent (in ) :: path
347
+ character (len= :), allocatable :: flags
351
348
352
- id = get_compiler_id(compiler)
349
+ select case (self% id)
350
+ case default
351
+ flags = " -I " // path
353
352
354
- select case (id)
353
+ case (id_caf, id_gcc, id_f95, id_cray, id_nvhpc, id_pgi, id_flang, &
354
+ & id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_unknown, &
355
+ & id_intel_llvm_nix, id_intel_llvm_unknown, id_lahey, id_nag, &
356
+ & id_ibmxl)
357
+ flags = " -I " // path
358
+
359
+ case (id_intel_classic_windows, id_intel_llvm_windows)
360
+ flags = " /I" // path
361
+
362
+ end select
363
+ end function get_include_flag
364
+
365
+ function get_module_flag (self , path ) result(flags)
366
+ class(compiler_t), intent (in ) :: self
367
+ character (len=* ), intent (in ) :: path
368
+ character (len= :), allocatable :: flags
369
+
370
+ select case (self% id)
355
371
case default
356
- flags= ' -module ' // modpath // ' -I ' // modpath
372
+ flags = " -module " // path
357
373
358
374
case (id_caf, id_gcc, id_f95, id_cray)
359
- flags= ' -J ' // modpath // ' -I ' // modpath
375
+ flags = " -J " // path
360
376
361
377
case (id_nvhpc, id_pgi, id_flang)
362
- flags= ' -module ' // modpath // ' -I ' // modpath
378
+ flags = " -module " // path
363
379
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
380
+ case (id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_unknown, &
381
+ & id_intel_llvm_nix, id_intel_llvm_unknown)
382
+ flags = " -module " // path
366
383
367
384
case (id_intel_classic_windows, id_intel_llvm_windows)
368
- flags= ' /module:' // modpath // ' /I ' // modpath
385
+ flags = " /module:" // path
369
386
370
387
case (id_lahey)
371
- flags= ' -M ' // modpath // ' -I ' // modpath
388
+ flags = " -M " // path
372
389
373
390
case (id_nag)
374
- flags= ' -mdir ' // modpath // ' -I ' // modpath !
391
+ flags = " -mdir " // path
375
392
376
393
case (id_ibmxl)
377
- flags= ' -qmoddir ' // modpath // ' -I ' // modpath
394
+ flags = " -qmoddir " // path
378
395
379
396
end select
397
+ flags = flags// " " // self% get_include_flag(path)
398
+
399
+ end function get_module_flag
380
400
381
- end subroutine get_module_flags
382
401
383
402
subroutine get_default_c_compiler (f_compiler , c_compiler )
384
403
character (len=* ), intent (in ) :: f_compiler
@@ -408,10 +427,13 @@ subroutine get_default_c_compiler(f_compiler, c_compiler)
408
427
409
428
end subroutine get_default_c_compiler
410
429
430
+
411
431
function get_compiler_id (compiler ) result(id)
412
432
character (len=* ), intent (in ) :: compiler
413
433
integer (kind= compiler_enum) :: id
414
434
435
+ integer :: stat
436
+
415
437
if (check_compiler(compiler, " gfortran" )) then
416
438
id = id_gcc
417
439
return
@@ -510,17 +532,34 @@ function check_compiler(compiler, expected) result(match)
510
532
end function check_compiler
511
533
512
534
513
- function is_unknown_compiler ( compiler ) result( is_unknown)
514
- character (len =* ), intent (in ) :: compiler
535
+ pure function is_unknown ( self )
536
+ class(compiler_t ), intent (in ) :: self
515
537
logical :: is_unknown
516
- is_unknown = get_compiler_id(compiler) == id_unknown
517
- end function is_unknown_compiler
538
+ is_unknown = self% id == id_unknown
539
+ end function is_unknown
540
+
541
+
542
+ ! > Create new compiler instance
543
+ subroutine new_compiler (self , fc )
544
+ ! > Fortran compiler name or path
545
+ character (len=* ), intent (in ) :: fc
546
+ ! > New instance of the compiler
547
+ type (compiler_t), intent (out ) :: self
548
+
549
+ character (len=* ), parameter :: cc_env = " FPM_C_COMPILER"
550
+
551
+ self% id = get_compiler_id(fc)
552
+
553
+ self% fc = fc
554
+ call get_default_c_compiler(self% fc, self% cc)
555
+ self% cc = get_env(cc_env, self% cc)
556
+ end subroutine new_compiler
518
557
519
558
520
- ! > Create new archiver
521
- function new_archiver () result (self)
559
+ ! > Create new archiver instance
560
+ subroutine new_archiver (self )
522
561
! > New instance of the archiver
523
- type (archiver_t) :: self
562
+ type (archiver_t), intent ( out ) :: self
524
563
integer :: estat, os_type
525
564
526
565
os_type = get_os_type()
@@ -537,7 +576,7 @@ function new_archiver() result(self)
537
576
end if
538
577
self% use_response_file = os_type == OS_WINDOWS
539
578
self% echo = .true.
540
- end function new_archiver
579
+ end subroutine new_archiver
541
580
542
581
543
582
! > Compile a Fortran object
0 commit comments