2828module fpm_compiler
2929use fpm_environment, only: &
3030 run, &
31+ get_env, &
3132 get_os_type, &
3233 OS_LINUX, &
3334 OS_MACOS, &
@@ -40,12 +41,6 @@ module fpm_compiler
4041use fpm_filesystem, only: join_path, basename, get_temp_filename, delete_file, unix_path
4142use fpm_strings, only: string_cat, string_t
4243implicit 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-
4944public :: compiler_t, archiver_t
5045public :: debug
5146
@@ -76,22 +71,37 @@ module fpm_compiler
7671
7772! > Definition of compiler object
7873type :: compiler_t
74+ ! > Identifier of the compiler
75+ integer (compiler_enum) :: id = id_unknown
7976 ! > Path to the Fortran compiler
8077 character (len= :), allocatable :: fc
8178 ! > Path to the C compiler
8279 character (len= :), allocatable :: cc
8380 ! > Print all commands
8481 logical :: echo = .true.
8582contains
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
8689 ! > Compile a Fortran object
8790 procedure :: compile_fortran
8891 ! > Compile a C object
8992 procedure :: compile_c
9093 ! > Link executable
9194 procedure :: link
95+ ! > Check whether compiler is recognized
96+ procedure :: is_unknown
9297end type compiler_t
9398
9499
100+ interface compiler_t
101+ module procedure :: new_compiler
102+ end interface compiler_t
103+
104+
95105! > Definition of archiver object
96106type :: archiver_t
97107 ! > Path to archiver
@@ -121,20 +131,19 @@ module fpm_compiler
121131
122132contains
123133
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
126137 logical , intent (in ) :: release
127- character (len= :), allocatable , intent (out ) :: flags
128- integer :: id
138+ character (len= :), allocatable :: flags
129139
130- id = get_compiler_id(compiler)
131140 if (release) then
132- call get_release_compile_flags(id, flags)
141+ call get_release_compile_flags(self % id, flags)
133142 else
134- call get_debug_compile_flags(id, flags)
143+ call get_debug_compile_flags(self % id, flags)
135144 end if
136145
137- end subroutine get_default_compile_flags
146+ end function get_default_flags
138147
139148subroutine get_release_compile_flags (id , flags )
140149 integer (compiler_enum), intent (in ) :: id
@@ -343,42 +352,63 @@ subroutine get_debug_compile_flags(id, flags)
343352 end select
344353end subroutine get_debug_compile_flags
345354
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
351359
352- id = get_compiler_id(compiler)
360+ select case (self% id)
361+ case default
362+ flags = " -I " // path
353363
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)
355382 case default
356- flags= ' -module ' // modpath // ' -I ' // modpath
383+ flags = " -module " // path
357384
358385 case (id_caf, id_gcc, id_f95, id_cray)
359- flags= ' -J ' // modpath // ' -I ' // modpath
386+ flags = " -J " // path
360387
361388 case (id_nvhpc, id_pgi, id_flang)
362- flags= ' -module ' // modpath // ' -I ' // modpath
389+ flags = " -module " // path
363390
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
366394
367395 case (id_intel_classic_windows, id_intel_llvm_windows)
368- flags= ' /module:' // modpath // ' /I ' // modpath
396+ flags = " /module:" // path
369397
370398 case (id_lahey)
371- flags= ' -M ' // modpath // ' -I ' // modpath
399+ flags = " -M " // path
372400
373401 case (id_nag)
374- flags= ' -mdir ' // modpath // ' -I ' // modpath !
402+ flags = " -mdir " // path
375403
376404 case (id_ibmxl)
377- flags= ' -qmoddir ' // modpath // ' -I ' // modpath
405+ flags = " -qmoddir " // path
378406
379407 end select
408+ flags = flags// " " // self% get_include_flag(path)
409+
410+ end function get_module_flag
380411
381- end subroutine get_module_flags
382412
383413subroutine get_default_c_compiler (f_compiler , c_compiler )
384414 character (len=* ), intent (in ) :: f_compiler
@@ -408,10 +438,13 @@ subroutine get_default_c_compiler(f_compiler, c_compiler)
408438
409439end subroutine get_default_c_compiler
410440
441+
411442function get_compiler_id (compiler ) result(id)
412443 character (len=* ), intent (in ) :: compiler
413444 integer (kind= compiler_enum) :: id
414445
446+ integer :: stat
447+
415448 if (check_compiler(compiler, " gfortran" )) then
416449 id = id_gcc
417450 return
@@ -510,14 +543,31 @@ function check_compiler(compiler, expected) result(match)
510543end function check_compiler
511544
512545
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
515548 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
518568
519569
520- ! > Create new archiver
570+ ! > Create new archiver instance
521571function new_archiver () result(self)
522572 ! > New instance of the archiver
523573 type (archiver_t) :: self
0 commit comments