Skip to content

Commit eed082b

Browse files
committed
Isolate model definition from model construction
1 parent fd49a2e commit eed082b

File tree

4 files changed

+87
-94
lines changed

4 files changed

+87
-94
lines changed

fpm/src/fpm.f90

Lines changed: 38 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -4,10 +4,12 @@ module fpm
44
use fpm_backend, only: build_package
55
use fpm_command_line, only: fpm_build_settings
66
use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
7-
use fpm_filesystem, only: number_of_rows, list_files, exists
8-
use fpm_model, only: build_model, fpm_model_t
9-
use fpm_manifest, only : get_package_data, default_executable, default_library, &
10-
& package_t
7+
use fpm_filesystem, only: join_path, number_of_rows, list_files, exists
8+
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t
9+
use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
10+
resolve_module_dependencies
11+
use fpm_manifest, only : get_package_data, default_executable, &
12+
default_library, package_t
1113
use fpm_error, only : error_t
1214
implicit none
1315
private
@@ -16,6 +18,38 @@ module fpm
1618

1719
contains
1820

21+
subroutine build_model(model, settings, package)
22+
! Constructs a valid fpm model from command line settings and toml manifest
23+
!
24+
type(fpm_model_t), intent(out) :: model
25+
type(fpm_build_settings), intent(in) :: settings
26+
type(package_t), intent(in) :: package
27+
28+
model%package_name = package%name
29+
30+
! #TODO: Choose flags and output directory based on cli settings & manifest inputs
31+
model%fortran_compiler = 'gfortran'
32+
model%output_directory = 'build/gfortran_debug'
33+
model%fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g '// &
34+
'-fbounds-check -fcheck-array-temporaries -fbacktrace '// &
35+
'-J'//join_path(model%output_directory,model%package_name)
36+
model%link_flags = ''
37+
38+
! Add sources from executable directories
39+
if (allocated(package%executable)) then
40+
call add_executable_sources(model%sources, package%executable,is_test=.false.)
41+
end if
42+
if (allocated(package%test)) then
43+
call add_executable_sources(model%sources, package%test,is_test=.true.)
44+
end if
45+
46+
if (allocated(package%library)) then
47+
call add_sources_from_dir(model%sources,package%library%source_dir)
48+
end if
49+
50+
call resolve_module_dependencies(model%sources)
51+
52+
end subroutine build_model
1953

2054
subroutine cmd_build(settings)
2155
type(fpm_build_settings), intent(in) :: settings

fpm/src/fpm_backend.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,9 +4,9 @@ module fpm_backend
44

55
use fpm_environment, only: run
66
use fpm_filesystem, only: basename, join_path, exists, mkdir
7-
use fpm_model, only: fpm_model_t
8-
use fpm_sources, only: srcfile_t, FPM_UNIT_MODULE, FPM_UNIT_SUBMODULE, &
9-
FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM
7+
use fpm_model, only: fpm_model_t, srcfile_t, FPM_UNIT_MODULE, &
8+
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
9+
FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM
1010
use fpm_strings, only: split
1111

1212
implicit none

fpm/src/fpm_model.f90

Lines changed: 42 additions & 45 deletions
Original file line numberDiff line numberDiff line change
@@ -1,19 +1,51 @@
11
module fpm_model
2-
32
! Definition and validation of the backend model
4-
5-
use fpm_command_line, only: fpm_build_settings
6-
use fpm_filesystem, only: exists, join_path
7-
use fpm_manifest, only: package_t, default_library, default_executable
8-
use fpm_manifest_executable, only: executable_t
9-
use fpm_sources, only: resolve_module_dependencies, add_sources_from_dir, &
10-
add_executable_sources, srcfile_t
113
use fpm_strings, only: string_t
12-
134
implicit none
145

156
private
16-
public :: build_model, fpm_model_t
7+
public :: srcfile_ptr, srcfile_t, fpm_model_t
8+
9+
public :: FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
10+
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
11+
FPM_UNIT_CHEADER
12+
13+
integer, parameter :: FPM_UNIT_UNKNOWN = -1
14+
integer, parameter :: FPM_UNIT_PROGRAM = 1
15+
integer, parameter :: FPM_UNIT_MODULE = 2
16+
integer, parameter :: FPM_UNIT_SUBMODULE = 3
17+
integer, parameter :: FPM_UNIT_SUBPROGRAM = 4
18+
integer, parameter :: FPM_UNIT_CSOURCE = 5
19+
integer, parameter :: FPM_UNIT_CHEADER = 6
20+
21+
type srcfile_ptr
22+
! For constructing arrays of src_file pointers
23+
type(srcfile_t), pointer :: ptr => null()
24+
end type srcfile_ptr
25+
26+
type srcfile_t
27+
! Type for encapsulating a source file
28+
! and it's metadata
29+
character(:), allocatable :: file_name
30+
! File path relative to cwd
31+
character(:), allocatable :: exe_name
32+
! Name of executable for FPM_UNIT_PROGRAM
33+
logical :: is_test = .false.
34+
! Is executable a test?
35+
type(string_t), allocatable :: modules_provided(:)
36+
! Modules provided by this source file (lowerstring)
37+
integer :: unit_type = FPM_UNIT_UNKNOWN
38+
! Type of program unit
39+
type(string_t), allocatable :: modules_used(:)
40+
! Modules USEd by this source file (lowerstring)
41+
type(string_t), allocatable :: include_dependencies(:)
42+
! Files INCLUDEd by this source file
43+
type(srcfile_ptr), allocatable :: file_dependencies(:)
44+
! Resolved source file dependencies
45+
46+
logical :: built = .false.
47+
logical :: touched = .false.
48+
end type srcfile_t
1749

1850
type :: fpm_model_t
1951
character(:), allocatable :: package_name
@@ -30,39 +62,4 @@ module fpm_model
3062
! Base directory for build
3163
end type fpm_model_t
3264

33-
contains
34-
35-
subroutine build_model(model, settings, package)
36-
! Constructs a valid fpm model from command line settings and toml manifest
37-
!
38-
type(fpm_model_t), intent(out) :: model
39-
type(fpm_build_settings), intent(in) :: settings
40-
type(package_t), intent(in) :: package
41-
42-
model%package_name = package%name
43-
44-
! #TODO: Choose flags and output directory based on cli settings & manifest inputs
45-
model%fortran_compiler = 'gfortran'
46-
model%output_directory = 'build/gfortran_debug'
47-
model%fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g '// &
48-
'-fbounds-check -fcheck-array-temporaries -fbacktrace '// &
49-
'-J'//join_path(model%output_directory,model%package_name)
50-
model%link_flags = ''
51-
52-
! Add sources from executable directories
53-
if (allocated(package%executable)) then
54-
call add_executable_sources(model%sources, package%executable,is_test=.false.)
55-
end if
56-
if (allocated(package%test)) then
57-
call add_executable_sources(model%sources, package%test,is_test=.true.)
58-
end if
59-
60-
if (allocated(package%library)) then
61-
call add_sources_from_dir(model%sources,package%library%source_dir)
62-
end if
63-
64-
call resolve_module_dependencies(model%sources)
65-
66-
end subroutine build_model
67-
6865
end module fpm_model

fpm/src/fpm_sources.f90

Lines changed: 4 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -1,23 +1,15 @@
11
module fpm_sources
2+
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
3+
FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
4+
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
5+
FPM_UNIT_CSOURCE, FPM_UNIT_CHEADER
26
use fpm_filesystem, only: basename, read_lines, list_files
37
use fpm_strings, only: lower, split, str_ends_with, string_t, operator(.in.)
48
use fpm_manifest_executable, only: executable_t
59
implicit none
610

711
private
8-
public :: srcfile_ptr, srcfile_t
912
public :: add_sources_from_dir, add_executable_sources, resolve_module_dependencies
10-
public :: FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
11-
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
12-
FPM_UNIT_CHEADER
13-
14-
integer, parameter :: FPM_UNIT_UNKNOWN = -1
15-
integer, parameter :: FPM_UNIT_PROGRAM = 1
16-
integer, parameter :: FPM_UNIT_MODULE = 2
17-
integer, parameter :: FPM_UNIT_SUBMODULE = 3
18-
integer, parameter :: FPM_UNIT_SUBPROGRAM = 4
19-
integer, parameter :: FPM_UNIT_CSOURCE = 5
20-
integer, parameter :: FPM_UNIT_CHEADER = 6
2113

2214
character(15), parameter :: INTRINSIC_MODULE_NAMES(*) = &
2315
['iso_c_binding ', &
@@ -26,36 +18,6 @@ module fpm_sources
2618
'ieee_exceptions', &
2719
'ieee_features ']
2820

29-
type srcfile_ptr
30-
! For constructing arrays of src_file pointers
31-
type(srcfile_t), pointer :: ptr => null()
32-
end type srcfile_ptr
33-
34-
type srcfile_t
35-
! Type for encapsulating a source file
36-
! and it's metadata
37-
character(:), allocatable :: file_name
38-
! File path relative to cwd
39-
character(:), allocatable :: exe_name
40-
! Name of executable for FPM_UNIT_PROGRAM
41-
logical :: is_test = .false.
42-
! Is executable a test?
43-
type(string_t), allocatable :: modules_provided(:)
44-
! Modules provided by this source file (lowerstring)
45-
integer :: unit_type = FPM_UNIT_UNKNOWN
46-
! Type of program unit
47-
type(string_t), allocatable :: modules_used(:)
48-
! Modules USEd by this source file (lowerstring)
49-
type(string_t), allocatable :: include_dependencies(:)
50-
! Files INCLUDEd by this source file
51-
type(srcfile_ptr), allocatable :: file_dependencies(:)
52-
! Resolved source file dependencies
53-
54-
logical :: built = .false.
55-
logical :: touched = .false.
56-
end type srcfile_t
57-
58-
5921
contains
6022

6123
subroutine add_sources_from_dir(sources,directory,with_executables)

0 commit comments

Comments
 (0)