aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorLKedward <laurence.kedward@bristol.ac.uk>2020-08-26 14:37:30 +0100
committerLKedward <laurence.kedward@bristol.ac.uk>2020-08-26 14:37:30 +0100
commit6d6c3363f2c990930b3aac5c871fe12d0592e124 (patch)
tree6b35f6ab9a67b2e92cb37c0bb3c5b8011520fab7
parenta06b6445de964adeed160b85cf66e5dcf9f7506f (diff)
downloadfpm-6d6c3363f2c990930b3aac5c871fe12d0592e124.tar.gz
fpm-6d6c3363f2c990930b3aac5c871fe12d0592e124.zip
Add: initial fpm build backend.
-rw-r--r--fpm/src/FPM_Backend.f9047
-rw-r--r--fpm/src/fpm.f9066
2 files changed, 103 insertions, 10 deletions
diff --git a/fpm/src/FPM_Backend.f90 b/fpm/src/FPM_Backend.f90
new file mode 100644
index 0000000..f52efb3
--- /dev/null
+++ b/fpm/src/FPM_Backend.f90
@@ -0,0 +1,47 @@
+module FPM_Backend
+use FPM_Strings
+use FPM_Model
+use environment
+implicit none
+
+
+contains
+
+recursive subroutine build_source(source_file,linking)
+ ! Compile Fortran source, called recursively on it dependents
+ !
+ type(srcfile_t), intent(inout) :: source_file
+ character(:), allocatable, intent(inout) :: linking
+
+ integer :: n, i
+ character(:), allocatable :: file_parts(:)
+ character(:), allocatable :: basename
+
+ if (source_file%built) then
+ return
+ end if
+
+ if (source_file%touched) then
+ write(*,*) '(!) Circular dependency found with: ',source_file%unit_name
+ stop
+ else
+ source_file%touched = .true.
+ end if
+
+ do i=1,size(source_file%file_dependencies)
+
+ call build_source(source_file%file_dependencies(i)%ptr,linking)
+
+ end do
+
+ 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"
+
+ source_file%built = .true.
+
+end subroutine build_source
+
+end module FPM_Backend \ No newline at end of file
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index 26a4631..e9771a7 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -2,6 +2,8 @@ module fpm
use FPM_Strings
use environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
use FPM_Filesystem, only: number_of_rows, list_files, exists
+use FPM_Sourcefiles
+use FPM_Backend
implicit none
private
public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
@@ -21,23 +23,67 @@ end if
end subroutine
subroutine cmd_build()
+type(string_t), allocatable :: lib_files(:)
+type(string_t), allocatable :: app_files(:)
type(string_t), allocatable :: files(:)
character(:), allocatable :: basename, pkg_name, linking
integer :: i, n
+
+type(srcfile_t), allocatable :: sources(:)
+character(:), allocatable :: file_parts(:)
+
print *, "# Building project"
-call list_files("src", files)
+
+
+call list_files("src", lib_files)
+lib_files = [(string_t("src/"//lib_files(i)%s),i=1,size(lib_files))]
+
+call list_files("app", app_files)
+app_files = [(string_t("app/"//app_files(i)%s),i=1,size(app_files))]
+
+files = [lib_files, app_files]
+
+call scan_sources(files,sources)
+
linking = ""
-do i = 1, size(files)
- if (str_ends_with(files(i)%s, ".f90")) then
- n = len(files(i)%s)
- basename = files(i)%s(1:n-4)
- call run("gfortran -c src/" // basename // ".f90 -o " // basename // ".o")
- linking = linking // " " // basename // ".o"
+do i=1,size(sources)
+
+ if (sources(i)%unit_type == FPM_UNIT_MODULE .or. &
+ sources(i)%unit_type == FPM_UNIT_SUBMODULE .or. &
+ sources(i)%unit_type == FPM_UNIT_SUBPROGRAM) then
+
+ call build_source(sources(i),linking)
+
end if
+
end do
-call run("gfortran -c app/main.f90 -o main.o")
-call package_name(pkg_name)
-call run("gfortran main.o " // linking // " -o " // pkg_name)
+
+do i=1,size(sources)
+
+ if (sources(i)%unit_type == FPM_UNIT_PROGRAM) then
+
+ call split(sources(i)%file_name,file_parts,delimiters='\/.')
+ basename = file_parts(size(file_parts)-1)
+
+ call run("gfortran " // sources(i)%file_name // linking // " -o " // basename)
+
+ end if
+
+end do
+
+! linking = ""
+! do i = 1, size(files)
+! if (str_ends_with(files(i)%s, ".f90")) then
+! n = len(files(i)%s)
+! basename = files(i)%s(1:n-4)
+! call run("gfortran -c src/" // basename // ".f90 -o " // basename // ".o")
+! linking = linking // " " // basename // ".o"
+! end if
+! end do
+
+! call run("gfortran -c app/main.f90 -o main.o")
+! call package_name(pkg_name)
+! call run("gfortran main.o " // linking // " -o " // pkg_name)
end subroutine
subroutine cmd_install()