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