@@ -7,7 +7,7 @@ module fpm_backend
7
7
use fpm_model, only: fpm_model_t, srcfile_t, FPM_UNIT_MODULE, &
8
8
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
9
9
FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM, &
10
- FPM_SCOPE_TEST
10
+ FPM_SCOPE_TEST, build_target_t
11
11
12
12
use fpm_strings, only: split
13
13
@@ -22,137 +22,107 @@ module fpm_backend
22
22
subroutine build_package (model )
23
23
type (fpm_model_t), intent (inout ) :: model
24
24
25
- integer :: i
26
- character (:), allocatable :: base, linking, subdir
25
+ ! integer :: i
26
+ ! character(:), allocatable :: base, linking, subdir
27
27
28
- if (.not. exists(model% output_directory)) then
29
- call mkdir(model% output_directory)
30
- end if
31
- if (.not. exists(join_path(model% output_directory,model% package_name))) then
32
- call mkdir(join_path(model% output_directory,model% package_name))
33
- end if
28
+ ! if (.not.exists(model%output_directory)) then
29
+ ! call mkdir(model%output_directory)
30
+ ! end if
31
+ ! if (.not.exists(join_path(model%output_directory,model%package_name))) then
32
+ ! call mkdir(join_path(model%output_directory,model%package_name))
33
+ ! end if
34
34
35
- linking = " "
36
- do i= 1 ,size (model% sources )
35
+ ! linking = ""
36
+ ! do i=1,size(model%targets )
37
37
38
- if (model% sources(i)% unit_type == FPM_UNIT_MODULE .or. &
39
- model% sources(i)% unit_type == FPM_UNIT_SUBMODULE .or. &
40
- model% sources(i)% unit_type == FPM_UNIT_SUBPROGRAM .or. &
41
- model% sources(i)% unit_type == FPM_UNIT_CSOURCE) then
38
+ ! ! if (model%sources(i)%unit_type == FPM_UNIT_MODULE .or. &
39
+ ! ! model%sources(i)%unit_type == FPM_UNIT_SUBMODULE .or. &
40
+ ! ! model%sources(i)%unit_type == FPM_UNIT_SUBPROGRAM .or. &
41
+ ! ! model%sources(i)%unit_type == FPM_UNIT_CSOURCE) then
42
42
43
- call build_source(model,model% sources(i),linking)
43
+ ! call build_source(model,model%sources(i),linking)
44
44
45
- end if
45
+ ! ! end if
46
46
47
- end do
47
+ ! end do
48
48
49
- if (any ([(model% sources(i)% unit_type == FPM_UNIT_PROGRAM,i= 1 ,size (model% sources))])) then
50
- if (.not. exists(join_path(model% output_directory,' test' ))) then
51
- call mkdir(join_path(model% output_directory,' test' ))
52
- end if
53
- if (.not. exists(join_path(model% output_directory,' app' ))) then
54
- call mkdir(join_path(model% output_directory,' app' ))
55
- end if
56
- end if
49
+ ! if (any([(model%sources(i)%unit_type == FPM_UNIT_PROGRAM,i=1,size(model%sources))])) then
50
+ ! if (.not.exists(join_path(model%output_directory,'test'))) then
51
+ ! call mkdir(join_path(model%output_directory,'test'))
52
+ ! end if
53
+ ! if (.not.exists(join_path(model%output_directory,'app'))) then
54
+ ! call mkdir(join_path(model%output_directory,'app'))
55
+ ! end if
56
+ ! end if
57
57
58
- do i= 1 ,size (model% sources)
58
+ ! do i=1,size(model%sources)
59
59
60
- if (model% sources(i)% unit_type == FPM_UNIT_PROGRAM) then
60
+ ! if (model%sources(i)%unit_type == FPM_UNIT_PROGRAM) then
61
61
62
- base = basename(model% sources(i)% file_name,suffix= .false. )
62
+ ! base = basename(model%sources(i)%file_name,suffix=.false.)
63
63
64
- if (model% sources(i)% unit_scope == FPM_SCOPE_TEST) then
65
- subdir = ' test'
66
- else
67
- subdir = ' app'
68
- end if
64
+ ! if (model%sources(i)%unit_scope == FPM_SCOPE_TEST) then
65
+ ! subdir = 'test'
66
+ ! else
67
+ ! subdir = 'app'
68
+ ! end if
69
69
70
- call run(" gfortran -c " // model% sources(i)% file_name // ' ' // model% fortran_compile_flags &
71
- // " -o " // join_path(model% output_directory,subdir,base) // " .o" )
70
+ ! call run("gfortran -c " // model%sources(i)%file_name // ' '//model%fortran_compile_flags &
71
+ ! // " -o " // join_path(model%output_directory,subdir,base) // ".o")
72
72
73
- call run(" gfortran " // join_path(model% output_directory, subdir, base) // " .o " // &
74
- linking // " " // model% link_flags // " -o " // &
75
- join_path(model% output_directory,subdir,model% sources(i)% exe_name) )
73
+ ! call run("gfortran " // join_path(model%output_directory, subdir, base) // ".o "// &
74
+ ! linking //" " //model%link_flags // " -o " // &
75
+ ! join_path(model%output_directory,subdir,model%sources(i)%exe_name) )
76
76
77
- end if
77
+ ! end if
78
78
79
- end do
79
+ ! end do
80
80
81
81
end subroutine build_package
82
82
83
83
84
84
85
- recursive subroutine build_source (model ,source_file ,linking )
85
+ recursive subroutine build_target (model ,target ,linking )
86
86
! Compile Fortran source, called recursively on it dependents
87
87
!
88
88
type (fpm_model_t), intent (in ) :: model
89
- type (srcfile_t ), intent (inout ) :: source_file
89
+ type (build_target_t ), intent (inout ) :: target
90
90
character (:), allocatable , intent (inout ) :: linking
91
91
92
- integer :: i
93
- character (:), allocatable :: object_file
92
+ ! integer :: i
93
+ ! character(:), allocatable :: object_file
94
94
95
- if (source_file% built) then
96
- return
97
- end if
95
+ ! if (source_file%built) then
96
+ ! return
97
+ ! end if
98
98
99
- if (source_file% touched) then
100
- write (* ,* ) ' (!) Circular dependency found with: ' ,source_file% file_name
101
- stop
102
- else
103
- source_file% touched = .true.
104
- end if
99
+ ! if (source_file%touched) then
100
+ ! write(*,*) '(!) Circular dependency found with: ',source_file%file_name
101
+ ! stop
102
+ ! else
103
+ ! source_file%touched = .true.
104
+ ! end if
105
105
106
- do i= 1 ,size (source_file% file_dependencies)
106
+ ! do i=1,size(source_file%file_dependencies)
107
107
108
- if (associated (source_file% file_dependencies(i)% ptr)) then
109
- call build_source(model,source_file% file_dependencies(i)% ptr,linking)
110
- end if
108
+ ! if (associated(source_file%file_dependencies(i)%ptr)) then
109
+ ! call build_source(model,source_file%file_dependencies(i)%ptr,linking)
110
+ ! end if
111
111
112
- end do
112
+ ! end do
113
113
114
- object_file = get_object_name(model,source_file% file_name)
114
+ ! object_file = get_object_name(model,source_file%file_name)
115
115
116
- if (.not. exists(dirname(object_file))) then
117
- call mkdir(dirname(object_file))
118
- end if
116
+ ! if (.not.exists(dirname(object_file))) then
117
+ ! call mkdir(dirname(object_file))
118
+ ! end if
119
119
120
- call run(" gfortran -c " // source_file% file_name // model% fortran_compile_flags &
121
- // " -o " // object_file)
122
- linking = linking // " " // object_file
120
+ ! call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags &
121
+ ! // " -o " // object_file)
122
+ ! linking = linking // " " // object_file
123
123
124
- source_file% built = .true.
124
+ ! source_file%built = .true.
125
125
126
- end subroutine build_source
127
-
128
-
129
- function get_object_name (model ,source_file_name ) result(object_file)
130
- ! Generate object target path from source name and model params
131
- !
132
- ! src/test.f90 -> <output-dir>/<package-name>/test.o
133
- ! src/subdir/test.f90 -> <output-dir>/<package-name>/subdir_test.o
134
- !
135
- type (fpm_model_t), intent (in ) :: model
136
- character (* ), intent (in ) :: source_file_name
137
- character (:), allocatable :: object_file
138
-
139
- integer :: i
140
- character (1 ) :: filesep
141
-
142
- select case (get_os_type())
143
- case (OS_WINDOWS)
144
- filesep = ' \'
145
- case default
146
- filesep = ' /'
147
- end select
148
-
149
- ! Exclude first directory level from path
150
- object_file = source_file_name(index (source_file_name,filesep)+ 1 :)
151
-
152
- ! Construct full target path
153
- object_file = join_path(model% output_directory, model% package_name, &
154
- object_file// ' .o' )
155
-
156
- end function get_object_name
126
+ end subroutine build_target
157
127
158
128
end module fpm_backend
0 commit comments