diff options
author | LKedward <laurence.kedward@bristol.ac.uk> | 2020-09-02 10:41:18 +0100 |
---|---|---|
committer | LKedward <laurence.kedward@bristol.ac.uk> | 2020-09-02 10:50:00 +0100 |
commit | f466572a8bc255cce1bb05ac50a96e47995c782b (patch) | |
tree | 3075109c3e3fd6f5e550d284a6b19e43ee4d8697 | |
parent | 54a5c6de29c3d7aa70797ff2d14aa962e9e169d8 (diff) | |
download | fpm-f466572a8bc255cce1bb05ac50a96e47995c782b.tar.gz fpm-f466572a8bc255cce1bb05ac50a96e47995c782b.zip |
Add basic fields to model structure.
Adds output directory, compiler and compiler flags to model structure - currently hard-coded values.
Adds mkdir subroutine in filesystem, implemented via command line shell.
-rw-r--r-- | fpm/src/fpm.f90 | 3 | ||||
-rw-r--r-- | fpm/src/fpm_backend.f90 | 30 | ||||
-rw-r--r-- | fpm/src/fpm_filesystem.f90 | 22 | ||||
-rw-r--r-- | fpm/src/fpm_model.f90 | 28 | ||||
-rw-r--r-- | fpm/src/fpm_sources.f90 | 24 |
5 files changed, 86 insertions, 21 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index a4d830b..4fb6bd4 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -1,5 +1,8 @@ module fpm use fpm_strings +use fpm_command_line +use fpm_manifest +use fpm_model use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS use fpm_filesystem, only: number_of_rows, list_files, exists use fpm_sources diff --git a/fpm/src/fpm_backend.f90 b/fpm/src/fpm_backend.f90 index 37afe65..475dcdd 100644 --- a/fpm/src/fpm_backend.f90 +++ b/fpm/src/fpm_backend.f90 @@ -1,10 +1,15 @@ module fpm_backend +! Implements the native fpm build backend +! use fpm_strings use fpm_environment use fpm_sources use fpm_model +use fpm_filesystem implicit none +private +public :: build_package contains @@ -16,6 +21,10 @@ subroutine build_package(model) character(:), allocatable :: basename, linking character(:), allocatable :: file_parts(:) + if(.not.exists(model%output_directory)) then + call mkdir(model%output_directory) + end if + linking = "" do i=1,size(model%sources) @@ -24,7 +33,7 @@ subroutine build_package(model) model%sources(i)%unit_type == FPM_UNIT_SUBPROGRAM .or. & model%sources(i)%unit_type == FPM_UNIT_CSOURCE) then - call build_source(model%sources(i),linking) + call build_source(model,model%sources(i),linking) end if @@ -37,7 +46,12 @@ subroutine build_package(model) call split(model%sources(i)%file_name,file_parts,delimiters='\/.') basename = file_parts(size(file_parts)-1) - call run("gfortran " // model%sources(i)%file_name // linking // " -o " // basename) + call run("gfortran -c " // model%sources(i)%file_name // ' '//model%fortran_compile_flags & + // " -o " // model%output_directory // '/' // basename // ".o") + + call run("gfortran " // model%output_directory // '/' // basename // ".o "// & + linking //" " //model%link_flags // " -o " // model%output_directory & + // '/' // model%package_name) end if @@ -47,13 +61,14 @@ end subroutine build_package -recursive subroutine build_source(source_file,linking) +recursive subroutine build_source(model,source_file,linking) ! Compile Fortran source, called recursively on it dependents ! + type(fpm_model_t), intent(in) :: model type(srcfile_t), intent(inout) :: source_file character(:), allocatable, intent(inout) :: linking - integer :: n, i + integer :: i character(:), allocatable :: file_parts(:) character(:), allocatable :: basename @@ -71,7 +86,7 @@ recursive subroutine build_source(source_file,linking) do i=1,size(source_file%file_dependencies) if (associated(source_file%file_dependencies(i)%ptr)) then - call build_source(source_file%file_dependencies(i)%ptr,linking) + call build_source(model,source_file%file_dependencies(i)%ptr,linking) end if end do @@ -79,8 +94,9 @@ recursive subroutine build_source(source_file,linking) call split(source_file%file_name,file_parts,delimiters='\/.') basename = file_parts(size(file_parts)-1) - call run("gfortran -c " // source_file%file_name // " -o " // basename // ".o") - linking = linking // " " // basename // ".o" + call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags & + // " -o " // model%output_directory//'/'//basename // ".o") + linking = linking // " " // model%output_directory//'/'// basename // ".o" source_file%built = .true. diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90 index 2b2793a..c531e84 100644 --- a/fpm/src/fpm_filesystem.f90 +++ b/fpm/src/fpm_filesystem.f90 @@ -4,7 +4,7 @@ use fpm_environment, only: get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS implicit none private -public :: number_of_rows, read_lines, list_files, exists, get_temp_filename +public :: number_of_rows, read_lines, list_files, mkdir, exists, get_temp_filename integer, parameter :: LINE_BUFFER_LEN = 1000 @@ -41,6 +41,26 @@ function read_lines(fh) result(lines) end function read_lines +subroutine mkdir(dir) + character(*), intent(in) :: dir + + integer :: stat + + select case (get_os_type()) + case (OS_LINUX,OS_MACOS) + call execute_command_line("mkdir -p " // dir , exitstat=stat) + write(*,*) "mkdir -p " // dir + case (OS_WINDOWS) + call execute_command_line("mkdir " // dir, exitstat=stat) + write(*,*) "mkdir " // dir + end select + if (stat /= 0) then + print *, "execute_command_line() failed" + error stop + end if + +end subroutine mkdir + subroutine list_files(dir, files) character(len=*), intent(in) :: dir diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90 index 501ea29..a0bbdb5 100644 --- a/fpm/src/fpm_model.f90 +++ b/fpm/src/fpm_model.f90 @@ -4,22 +4,48 @@ module fpm_model use fpm_strings
use fpm_sources
use fpm_command_line
+use fpm_filesystem
use fpm_manifest
implicit none
type fpm_model_t
+ character(:), allocatable :: package_name
+ ! Name of package
type(srcfile_t), allocatable :: sources(:)
! Array of sources with module-dependencies resolved
-
+ character(:), allocatable :: fortran_compiler
+ ! Command line name to invoke fortran compiler
+ character(:), allocatable :: fortran_compile_flags
+ ! Command line flags passed to fortran for compilation
+ character(:), allocatable :: link_flags
+ ! Command line flags pass for linking
+ character(:), allocatable :: output_directory
+ ! Base directory for build
end type fpm_model_t
contains
subroutine build_model(model, settings, manifest)
+ ! Constructs a valid fpm model from command line settings and toml manifest
+ !
type(fpm_model_t), intent(out) :: model
type(fpm_build_settings), intent(in) :: settings
type(fpm_manifest_t), intent(in) :: manifest
+ if (exists("src/fpm.f90")) then
+ model%package_name = "fpm"
+ else
+ model%package_name = "hello_world"
+ end if
+
+ ! #TODO: Choose flags and output directory based on cli settings & manifest inputs
+ model%fortran_compiler = 'gfortran'
+ model%output_directory = 'build/gfortran_debug'
+ model%fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g '// &
+ '-fbounds-check -fcheck-array-temporaries -fbacktrace '// &
+ '-J'//model%output_directory
+ model%link_flags = ''
+
call scan_sources(model%sources,[string_t('app'),string_t('src')])
call resolve_dependencies(model%sources)
diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90 index d65b9f3..2960339 100644 --- a/fpm/src/fpm_sources.f90 +++ b/fpm/src/fpm_sources.f90 @@ -89,18 +89,18 @@ subroutine scan_sources(sources,directories) end do - do i=1,size(sources) - write(*,*) 'Filename: "',sources(i)%file_name,'"' - do j=1,size(sources(i)%modules_provided) - write(*,*) ' Provides: "',sources(i)%modules_provided(j)%s,'"' - end do - do j=1,size(sources(i)%modules_used) - write(*,*) ' Uses: "',sources(i)%modules_used(j)%s,'"' - end do - do j=1,size(sources(i)%include_dependencies) - write(*,*) ' Includes: "',sources(i)%include_dependencies(j)%s,'"' - end do - end do + ! do i=1,size(sources) + ! write(*,*) 'Filename: "',sources(i)%file_name,'"' + ! do j=1,size(sources(i)%modules_provided) + ! write(*,*) ' Provides: "',sources(i)%modules_provided(j)%s,'"' + ! end do + ! do j=1,size(sources(i)%modules_used) + ! write(*,*) ' Uses: "',sources(i)%modules_used(j)%s,'"' + ! end do + ! do j=1,size(sources(i)%include_dependencies) + ! write(*,*) ' Includes: "',sources(i)%include_dependencies(j)%s,'"' + ! end do + ! end do end subroutine scan_sources |