1
1
module fpm
2
2
3
- use fpm_strings, only : string_t, str_ends_with
4
- use fpm_backend, only : build_package
5
- use fpm_command_line, only : fpm_build_settings, fpm_new_settings, &
6
- fpm_run_settings, fpm_install_settings, fpm_test_settings
7
- use fpm_environment, only : run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
8
- use fpm_filesystem, only : join_path, number_of_rows, list_files, exists, basename, mkdir
9
- use fpm_model, only : srcfile_ptr, srcfile_t, fpm_model_t
10
- use fpm_sources, only : add_executable_sources, add_sources_from_dir, &
11
- resolve_module_dependencies
3
+ use fpm_strings, only: string_t, str_ends_with
4
+ use fpm_backend, only: build_package
5
+ use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
6
+ fpm_run_settings, fpm_install_settings, fpm_test_settings
7
+ use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
8
+ use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename, mkdir
9
+ use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
10
+ FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
11
+ FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
12
+
13
+ use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
14
+ resolve_module_dependencies
12
15
use fpm_manifest, only : get_package_data, default_executable, &
13
16
default_library, package_t, default_test
14
17
use fpm_error, only : error_t
@@ -56,20 +59,38 @@ subroutine build_model(model, settings, package, error)
56
59
model% link_flags = ' '
57
60
58
61
! Add sources from executable directories
59
- if (allocated (package% executable)) then
62
+ if (is_dir(' app' ) .and. package% build_config% auto_executables) then
63
+ call add_sources_from_dir(model% sources,' app' , FPM_SCOPE_APP, &
64
+ with_executables= .true. , error= error)
60
65
61
- call add_executable_sources(model% sources, package% executable, &
62
- is_test= .false. , error= error)
66
+ if (allocated (error)) then
67
+ return
68
+ end if
69
+
70
+ end if
71
+ if (is_dir(' test' ) .and. package% build_config% auto_tests) then
72
+ call add_sources_from_dir(model% sources,' test' , FPM_SCOPE_TEST, &
73
+ with_executables= .true. , error= error)
63
74
64
75
if (allocated (error)) then
65
76
return
66
77
endif
67
78
68
- endif
69
- if (allocated (package% test)) then
79
+ end if
80
+ if (allocated (package% executable)) then
81
+ call add_executable_sources(model% sources, package% executable, FPM_SCOPE_APP, &
82
+ auto_discover= package% build_config% auto_executables, &
83
+ error= error)
84
+
85
+ if (allocated (error)) then
86
+ return
87
+ end if
70
88
71
- call add_executable_sources(model% sources, package% test, &
72
- is_test= .true. , error= error)
89
+ end if
90
+ if (allocated (package% test)) then
91
+ call add_executable_sources(model% sources, package% test, FPM_SCOPE_TEST, &
92
+ auto_discover= package% build_config% auto_tests, &
93
+ error= error)
73
94
74
95
if (allocated (error)) then
75
96
return
@@ -79,13 +100,14 @@ subroutine build_model(model, settings, package, error)
79
100
80
101
if (allocated (package% library)) then
81
102
82
- call add_sources_from_dir(model% sources,package% library% source_dir, &
83
- error= error)
103
+ call add_sources_from_dir(model% sources, package% library% source_dir, &
104
+ FPM_SCOPE_LIB, error= error)
84
105
85
106
if (allocated (error)) then
86
107
return
87
108
endif
88
109
110
+
89
111
endif
90
112
if (settings% list)then
91
113
do i= 1 ,size (model% sources)
@@ -94,7 +116,7 @@ subroutine build_model(model, settings, package, error)
94
116
enddo
95
117
stop
96
118
else
97
- call resolve_module_dependencies(model% sources)
119
+ call resolve_module_dependencies(model% sources,error )
98
120
endif
99
121
100
122
end subroutine build_model
@@ -106,45 +128,39 @@ subroutine cmd_build(settings)
106
128
type (fpm_model_t) :: model
107
129
type (error_t), allocatable :: error
108
130
109
- call get_package_data(package, " fpm.toml" , error)
110
- if (allocated (error)) then
111
- print ' (a)' , error% message
112
- error stop 5
113
- endif
114
-
115
- ! Populate library in case we find the default src directory
116
- if (.not. allocated (package% library) .and. exists(" src" )) then
117
- allocate (package% library)
118
- call default_library(package% library)
119
- endif
120
-
121
- ! Populate executable in case we find the default app directory
122
- if (.not. allocated (package% executable) .and. exists(" app" )) then
123
- allocate (package% executable(1 ))
124
- call default_executable(package% executable(1 ), package% name)
125
- endif
126
-
127
- ! Populate test in case we find the default test directory
128
- if (.not. allocated (package% test) .and. exists(" test" )) then
129
- allocate (package% test(1 ))
130
- call default_test(package% test(1 ), package% name)
131
- endif
132
-
133
- if (.not. (allocated (package% library) .or. allocated (package% executable) .or. allocated (package% test) )) then
134
- print ' (a)' , " Neither library nor executable found, there is nothing to do"
135
- error stop 6
136
- endif
137
-
138
- call build_model(model, settings, package, error)
139
- if (allocated (error)) then
140
- print ' (a)' , error% message
141
- error stop 7
142
- endif
143
-
144
- call build_package(model)
145
-
146
- end subroutine cmd_build
147
-
131
+ call get_package_data(package, " fpm.toml" , error)
132
+ if (allocated (error)) then
133
+ print ' (a)' , error% message
134
+ error stop 1
135
+ end if
136
+
137
+ ! Populate library in case we find the default src directory
138
+ if (.not. allocated (package% library) .and. exists(" src" )) then
139
+ allocate (package% library)
140
+ call default_library(package% library)
141
+ end if
142
+
143
+ ! Populate executable in case we find the default app
144
+ if (.not. allocated (package% executable) .and. &
145
+ exists(join_path(' app' ," main.f90" ))) then
146
+ allocate (package% executable(1 ))
147
+ call default_executable(package% executable(1 ), package% name)
148
+ end if
149
+
150
+ if (.not. (allocated (package% library) .or. allocated (package% executable))) then
151
+ print ' (a)' , " Neither library nor executable found, there is nothing to do"
152
+ error stop 1
153
+ end if
154
+
155
+ call build_model(model, settings, package, error)
156
+ if (allocated (error)) then
157
+ print ' (a)' , error% message
158
+ error stop 1
159
+ end if
160
+
161
+ call build_package(model)
162
+
163
+ end subroutine
148
164
149
165
subroutine cmd_install (settings )
150
166
type (fpm_install_settings), intent (in ) :: settings
0 commit comments