diff options
author | Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> | 2021-07-30 19:59:26 +0200 |
---|---|---|
committer | Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> | 2021-07-30 23:41:34 +0200 |
commit | c6f0ec64b8060523beaf828ceae32fa3827f65fb (patch) | |
tree | 0aeb9c87496fd09e8d6b9596cacd5355d53c10ee /src/fpm_compiler.f90 | |
parent | 5d22f5aac698c4b8f135a226e944be9ded9475b0 (diff) | |
download | fpm-c6f0ec64b8060523beaf828ceae32fa3827f65fb.tar.gz fpm-c6f0ec64b8060523beaf828ceae32fa3827f65fb.zip |
Move default flags fetching and build name generation to model
Diffstat (limited to 'src/fpm_compiler.f90')
-rw-r--r-- | src/fpm_compiler.f90 | 131 |
1 files changed, 85 insertions, 46 deletions
diff --git a/src/fpm_compiler.f90 b/src/fpm_compiler.f90 index b432f11..a6d9871 100644 --- a/src/fpm_compiler.f90 +++ b/src/fpm_compiler.f90 @@ -28,6 +28,7 @@ module fpm_compiler use fpm_environment, only: & run, & + get_env, & get_os_type, & OS_LINUX, & OS_MACOS, & @@ -40,13 +41,7 @@ use fpm_environment, only: & use fpm_filesystem, only: join_path, basename, get_temp_filename, delete_file, unix_path use fpm_strings, only: string_cat, string_t implicit none -public :: is_unknown_compiler -public :: get_module_flags -public :: get_default_compile_flags -public :: get_debug_compile_flags -public :: get_release_compile_flags - -public :: compiler_t, archiver_t +public :: compiler_t, new_compiler, archiver_t, new_archiver public :: debug enum, bind(C) @@ -76,6 +71,8 @@ integer, parameter :: compiler_enum = kind(id_unknown) !> Definition of compiler object type :: compiler_t + !> Identifier of the compiler + integer(compiler_enum) :: id = id_unknown !> Path to the Fortran compiler character(len=:), allocatable :: fc !> Path to the C compiler @@ -83,12 +80,20 @@ type :: compiler_t !> Print all commands logical :: echo = .true. contains + !> Get default compiler flags + procedure :: get_default_flags + !> Get flag for module output directories + procedure :: get_module_flag + !> Get flag for include directories + procedure :: get_include_flag !> Compile a Fortran object procedure :: compile_fortran !> Compile a C object procedure :: compile_c !> Link executable procedure :: link + !> Check whether compiler is recognized + procedure :: is_unknown end type compiler_t @@ -106,12 +111,6 @@ contains end type archiver_t -!> Constructor for archiver -interface archiver_t - module procedure :: new_archiver -end interface archiver_t - - !> Create debug printout interface debug module procedure :: debug_compiler @@ -121,20 +120,19 @@ end interface debug contains -subroutine get_default_compile_flags(compiler, release, flags) - character(len=*), intent(in) :: compiler + +function get_default_flags(self, release) result(flags) + class(compiler_t), intent(in) :: self logical, intent(in) :: release - character(len=:), allocatable, intent(out) :: flags - integer :: id + character(len=:), allocatable :: flags - id = get_compiler_id(compiler) if (release) then - call get_release_compile_flags(id, flags) + call get_release_compile_flags(self%id, flags) else - call get_debug_compile_flags(id, flags) + call get_debug_compile_flags(self%id, flags) end if -end subroutine get_default_compile_flags +end function get_default_flags subroutine get_release_compile_flags(id, flags) integer(compiler_enum), intent(in) :: id @@ -343,42 +341,63 @@ subroutine get_debug_compile_flags(id, flags) end select end subroutine get_debug_compile_flags -subroutine get_module_flags(compiler, modpath, flags) - character(len=*), intent(in) :: compiler - character(len=*), intent(in) :: modpath - character(len=:), allocatable, intent(out) :: flags - integer(compiler_enum) :: id +function get_include_flag(self, path) result(flags) + class(compiler_t), intent(in) :: self + character(len=*), intent(in) :: path + character(len=:), allocatable :: flags - id = get_compiler_id(compiler) + select case(self%id) + case default + flags = "-I "//path - select case(id) + case(id_caf, id_gcc, id_f95, id_cray, id_nvhpc, id_pgi, id_flang, & + & id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_unknown, & + & id_intel_llvm_nix, id_intel_llvm_unknown, id_lahey, id_nag, & + & id_ibmxl) + flags = "-I "//path + + case(id_intel_classic_windows, id_intel_llvm_windows) + flags = "/I"//path + + end select +end function get_include_flag + +function get_module_flag(self, path) result(flags) + class(compiler_t), intent(in) :: self + character(len=*), intent(in) :: path + character(len=:), allocatable :: flags + + select case(self%id) case default - flags=' -module '//modpath//' -I '//modpath + flags = "-module "//path case(id_caf, id_gcc, id_f95, id_cray) - flags=' -J '//modpath//' -I '//modpath + flags = "-J "//path case(id_nvhpc, id_pgi, id_flang) - flags=' -module '//modpath//' -I '//modpath + flags = "-module "//path - case(id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_unknown, id_intel_llvm_nix, id_intel_llvm_unknown) - flags=' -module '//modpath//' -I'//modpath + case(id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_unknown, & + & id_intel_llvm_nix, id_intel_llvm_unknown) + flags = "-module "//path case(id_intel_classic_windows, id_intel_llvm_windows) - flags=' /module:'//modpath//' /I'//modpath + flags = "/module:"//path case(id_lahey) - flags=' -M '//modpath//' -I '//modpath + flags = "-M "//path case(id_nag) - flags=' -mdir '//modpath//' -I '//modpath ! + flags = "-mdir "//path case(id_ibmxl) - flags=' -qmoddir '//modpath//' -I '//modpath + flags = "-qmoddir "//path end select + flags = flags//" "//self%get_include_flag(path) + +end function get_module_flag -end subroutine get_module_flags subroutine get_default_c_compiler(f_compiler, c_compiler) character(len=*), intent(in) :: f_compiler @@ -408,10 +427,13 @@ subroutine get_default_c_compiler(f_compiler, c_compiler) end subroutine get_default_c_compiler + function get_compiler_id(compiler) result(id) character(len=*), intent(in) :: compiler integer(kind=compiler_enum) :: id + integer :: stat + if (check_compiler(compiler, "gfortran")) then id = id_gcc return @@ -510,17 +532,34 @@ function check_compiler(compiler, expected) result(match) end function check_compiler -function is_unknown_compiler(compiler) result(is_unknown) - character(len=*), intent(in) :: compiler +pure function is_unknown(self) + class(compiler_t), intent(in) :: self logical :: is_unknown - is_unknown = get_compiler_id(compiler) == id_unknown -end function is_unknown_compiler + is_unknown = self%id == id_unknown +end function is_unknown + + +!> Create new compiler instance +subroutine new_compiler(self, fc) + !> Fortran compiler name or path + character(len=*), intent(in) :: fc + !> New instance of the compiler + type(compiler_t), intent(out) :: self + + character(len=*), parameter :: cc_env = "FPM_C_COMPILER" + + self%id = get_compiler_id(fc) + + self%fc = fc + call get_default_c_compiler(self%fc, self%cc) + self%cc = get_env(cc_env, self%cc) +end subroutine new_compiler -!> Create new archiver -function new_archiver() result(self) +!> Create new archiver instance +subroutine new_archiver(self) !> New instance of the archiver - type(archiver_t) :: self + type(archiver_t), intent(out) :: self integer :: estat, os_type os_type = get_os_type() @@ -537,7 +576,7 @@ function new_archiver() result(self) end if self%use_response_file = os_type == OS_WINDOWS self%echo = .true. -end function new_archiver +end subroutine new_archiver !> Compile a Fortran object |