@@ -2,9 +2,10 @@ module fpm
2
2
3
3
use fpm_strings, only: string_t, str_ends_with
4
4
use fpm_backend, only: build_package
5
- use fpm_command_line, only: fpm_build_settings
5
+ use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
6
+ fpm_run_settings, fpm_install_settings, fpm_test_settings
6
7
use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
7
- use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists
8
+ use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
8
9
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
9
10
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
10
11
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
@@ -14,6 +15,9 @@ module fpm
14
15
use fpm_manifest, only : get_package_data, default_executable, &
15
16
default_library, package_t
16
17
use fpm_error, only : error_t
18
+ use ,intrinsic :: iso_fortran_env, only : stdin= >input_unit, &
19
+ & stdout= >output_unit, &
20
+ & stderr= >error_unit
17
21
implicit none
18
22
private
19
23
public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
@@ -33,10 +37,23 @@ subroutine build_model(model, settings, package, error)
33
37
34
38
! #TODO: Choose flags and output directory based on cli settings & manifest inputs
35
39
model% fortran_compiler = ' gfortran'
36
- model% output_directory = ' build/gfortran_debug'
37
- model% fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g ' // &
38
- ' -fbounds-check -fcheck-array-temporaries -fbacktrace ' // &
39
- ' -J' // join_path(model% output_directory,model% package_name)
40
+
41
+ if (settings% release)then
42
+ model% output_directory = ' build/gfortran_release'
43
+ model% fortran_compile_flags= ' &
44
+ & -O3 &
45
+ & -Wimplicit-interface &
46
+ & -fPIC &
47
+ & -fmax-errors=1 &
48
+ & -ffast-math &
49
+ & -funroll-loops ' // &
50
+ & ' -J' // join_path(model% output_directory,model% package_name)
51
+ else
52
+ model% output_directory = ' build/gfortran_debug'
53
+ model% fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g ' // &
54
+ ' -fbounds-check -fcheck-array-temporaries -fbacktrace ' // &
55
+ ' -J' // join_path(model% output_directory,model% package_name)
56
+ endif
40
57
model% link_flags = ' '
41
58
42
59
! Add sources from executable directories
@@ -130,24 +147,91 @@ subroutine cmd_build(settings)
130
147
131
148
end subroutine
132
149
133
- subroutine cmd_install ()
150
+ subroutine cmd_install (settings )
151
+ type (fpm_install_settings), intent (in ) :: settings
134
152
print * , " fpm error: 'fpm install' not implemented."
135
153
error stop 1
136
- end subroutine
137
-
138
- subroutine cmd_new ()
139
- print * , " fpm error: 'fpm new' not implemented."
140
- error stop 1
141
- end subroutine
154
+ end subroutine cmd_install
155
+
156
+ subroutine cmd_new (settings ) ! --with-executable F --with-test F '
157
+ type (fpm_new_settings), intent (in ) :: settings
158
+ character (len= :),allocatable :: message(:)
159
+ character (len= :),allocatable :: bname
160
+ bname= basename(settings% name) ! ! new basename(dirname) if full paths are allowed ???
161
+
162
+ message= [character (len= 80 ) :: & ! create fpm.toml
163
+ &' name = "' // bname// ' " ' , &
164
+ &' version = "0.1.0" ' , &
165
+ &' license = "license" ' , &
166
+ &' author = "Jane Doe" ' , &
167
+ &
' maintainer = "[email protected] " ' , &
168
+ &' copyright = "2020 Jane Doe" ' , &
169
+ &' ' , &
170
+ &' [library] ' , &
171
+ &' source-dir="src" ' , &
172
+ &' ' ]
173
+
174
+ if (settings% with_test)then
175
+ message= [character (len= 80 ) :: message, & ! create next section of fpm.toml
176
+ &' [[test]] ' , &
177
+ &' name="runTests" ' , &
178
+ &' source-dir="test" ' , &
179
+ &' main="main.f90" ' , &
180
+ &' ' ]
181
+ endif
182
+
183
+ if (settings% with_executable)then
184
+ message= [character (len= 80 ) :: message, & ! create next section of fpm.toml
185
+ &' [[executable]] ' , &
186
+ &' name="' // bname// ' " ' , &
187
+ &' source-dir="app" ' , &
188
+ &' main="main.f90" ' , &
189
+ &' ' ]
190
+ endif
191
+
192
+ write (* ,' (a)' )message
193
+ print * , " fpm error: 'fpm new' not implemented."
194
+ error stop 1
195
+ end subroutine cmd_new
196
+
197
+ subroutine cmd_run (settings )
198
+ type (fpm_run_settings), intent (in ) :: settings
199
+ integer :: i
200
+
201
+ write (* ,* )' RELEASE=' ,settings% release
202
+ if (size (settings% name).eq. 0 )then
203
+ write (* ,* )' RUN DEFAULTS with arguments [' // settings% args// ' ]'
204
+ else
205
+ do i= 1 ,size (settings% name)
206
+ write (* ,* )' RUN:' // trim (settings% name (i))// ' with arguments [' // settings% args// ' ]'
207
+ enddo
208
+ endif
142
209
143
- subroutine cmd_run ()
144
210
print * , " fpm error: 'fpm run' not implemented."
145
211
error stop 1
146
- end subroutine
147
212
148
- subroutine cmd_test ()
213
+ end subroutine cmd_run
214
+
215
+ subroutine cmd_test (settings )
216
+ type (fpm_test_settings), intent (in ) :: settings
217
+ character (len= :),allocatable :: release_name
218
+ integer :: i
219
+
220
+ ! ! looks like would get this from model when cmd_test is implimented
221
+ release_name= trim (merge (' gfortran_release' ,' gfortran_debug ' ,settings% release))
222
+
223
+ write (* ,* )' RELEASE=' ,settings% release,' RELEASE_NAME=' ,release_name,' ARGS=' ,settings% args
224
+ if ( size (settings% name) .gt. 0 )then
225
+ write (* ,* )' RUN THESE:'
226
+ do i= 1 ,size (settings% name)
227
+ write (* ,* )' RUN:' // trim (settings% name (i))// ' with arguments [' // settings% args// ' ]'
228
+ enddo
229
+ else
230
+ write (* ,* )' RUN DEFAULTS: with arguments [' // settings% args// ' ]'
231
+ endif
232
+
149
233
print * , " fpm error: 'fpm test' not implemented."
150
234
error stop 1
151
- end subroutine
235
+ end subroutine cmd_test
152
236
153
237
end module fpm
0 commit comments