@@ -4,8 +4,8 @@ module fpm
4
4
use fpm_backend, only: build_package
5
5
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
6
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
7
+ use fpm_environment, only: run
8
+ use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
9
9
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
10
10
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
11
11
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
@@ -16,12 +16,10 @@ module fpm
16
16
default_library, package_t, default_test
17
17
use fpm_error, only : error_t
18
18
use fpm_manifest_test, only : test_t
19
- use ,intrinsic :: iso_fortran_env, only : stdin= >input_unit, &
20
- & stdout= >output_unit, &
21
- & stderr= >error_unit
19
+ use ,intrinsic :: iso_fortran_env, only : stderr= >error_unit
22
20
implicit none
23
21
private
24
- public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
22
+ public :: cmd_build, cmd_install, cmd_run, cmd_test
25
23
26
24
contains
27
25
@@ -168,160 +166,6 @@ subroutine cmd_install(settings)
168
166
error stop 8
169
167
end subroutine cmd_install
170
168
171
-
172
- subroutine cmd_new (settings ) ! --with-executable F --with-test F '
173
- type (fpm_new_settings), intent (in ) :: settings
174
- integer :: ierr
175
- character (len= :),allocatable :: bname ! baeename of NAME
176
- character (len= :),allocatable :: message(:)
177
- character (len= :),allocatable :: littlefile(:)
178
-
179
- call mkdir(settings% name) ! make new directory
180
- call run(' cd ' // settings% name) ! change to new directory as a test. New OS routines to improve this; system dependent potentially
181
- ! ! NOTE: need some system routines to handle filenames like "." like realpath() or getcwd().
182
- bname= basename(settings% name)
183
-
184
- ! ! weird gfortran bug?? lines truncated to concatenated string length, not 80
185
- ! ! hit some weird gfortran bug when littlefile data was an argument to warnwrite(3f), ok when a variable
186
-
187
- call warnwrite(join_path(settings% name, ' .gitignore' ), [' build/*' ]) ! create NAME/.gitignore file
188
-
189
- littlefile= [character (len= 80 ) :: ' # ' // bname, ' My cool new project!' ]
190
-
191
- call warnwrite(join_path(settings% name, ' README.md' ), littlefile) ! create NAME/README.md
192
-
193
- message= [character (len= 80 ) :: & ! start building NAME/fpm.toml
194
- &' name = "' // bname// ' " ' , &
195
- &' version = "0.1.0" ' , &
196
- &' license = "license" ' , &
197
- &' author = "Jane Doe" ' , &
198
- &
' maintainer = "[email protected] " ' , &
199
- &' copyright = "2020 Jane Doe" ' , &
200
- &' ' , &
201
- &' ' ]
202
-
203
- if (settings% with_lib)then
204
- call mkdir(join_path(settings% name,' src' ) )
205
- message= [character (len= 80 ) :: message, & ! create next section of fpm.toml
206
- &' [library] ' , &
207
- &' source-dir="src" ' , &
208
- &' ' ]
209
- littlefile= [character (len= 80 ) :: & ! create placeholder module src/bname.f90
210
- &' module ' // bname, &
211
- &' implicit none' , &
212
- &' private' , &
213
- &' ' , &
214
- &' public :: say_hello' , &
215
- &' contains' , &
216
- &' subroutine say_hello' , &
217
- &' print *, "Hello, ' // bname// ' !"' , &
218
- &' end subroutine say_hello' , &
219
- &' end module ' // bname]
220
- ! a proposed alternative default
221
- call warnwrite(join_path(settings% name, ' src' , bname// ' .f90' ), littlefile) ! create NAME/src/NAME.f90
222
- endif
223
-
224
- if (settings% with_test)then
225
- call mkdir(join_path(settings% name, ' test' )) ! create NAME/test or stop
226
- message= [character (len= 80 ) :: message, & ! create next section of fpm.toml
227
- &' [[test]] ' , &
228
- &' name="runTests" ' , &
229
- &' source-dir="test" ' , &
230
- &' main="main.f90" ' , &
231
- &' ' ]
232
-
233
- littlefile= [character (len= 80 ) :: &
234
- &' program main' , &
235
- &' implicit none' , &
236
- &' ' , &
237
- &' print *, "Put some tests in here!"' , &
238
- &' end program main' ]
239
- ! a proposed alternative default a little more substantive
240
- call warnwrite(join_path(settings% name, ' test/main.f90' ), littlefile) ! create NAME/test/main.f90
241
- endif
242
-
243
- if (settings% with_executable)then
244
- call mkdir(join_path(settings% name, ' app' )) ! create NAME/app or stop
245
- message= [character (len= 80 ) :: message, & ! create next section of fpm.toml
246
- &' [[executable]] ' , &
247
- &' name="' // bname// ' " ' , &
248
- &' source-dir="app" ' , &
249
- &' main="main.f90" ' , &
250
- &' ' ]
251
-
252
- littlefile= [character (len= 80 ) :: &
253
- &' program main' , &
254
- &' use ' // bname// ' , only: say_hello' , &
255
- &' ' , &
256
- &' implicit none' , &
257
- &' ' , &
258
- &' call say_hello' , &
259
- &' end program main' ]
260
- call warnwrite(join_path(settings% name, ' app/main.f90' ), littlefile)
261
- endif
262
-
263
- call warnwrite(join_path(settings% name, ' fpm.toml' ), message) ! now that built it write NAME/fpm.toml
264
-
265
- call run(' cd ' // settings% name // ' ;git init' ) ! assumes these commands work on all systems and git(1) is installed
266
- contains
267
-
268
- subroutine warnwrite (fname ,data )
269
- character (len=* ),intent (in ) :: fname
270
- character (len=* ),intent (in ) :: data (:)
271
-
272
- if (.not. exists(fname))then
273
- call filewrite(fname,data )
274
- else
275
- write (stderr,' (*(g0,1x))' )' fpm::new<WARNING>' ,fname,' already exists. Not overwriting'
276
- endif
277
-
278
- end subroutine warnwrite
279
-
280
- subroutine filewrite (filename ,filedata )
281
- use ,intrinsic :: iso_fortran_env, only : stdin= >input_unit, stdout= >output_unit, stderr= >error_unit
282
- ! write filedata to file filename
283
- character (len=* ),intent (in ) :: filename
284
- character (len=* ),intent (in ) :: filedata(:)
285
- integer :: lun, i, ios
286
- character (len= 256 ) :: message
287
-
288
- message= ' '
289
- ios= 0
290
- if (filename.ne. ' ' )then
291
- open (file= filename, &
292
- & newunit= lun, &
293
- & form= ' formatted' , & ! FORM = FORMATTED | UNFORMATTED
294
- & access= ' sequential' , & ! ACCESS = SEQUENTIAL | DIRECT | STREAM
295
- & action= ' write' , & ! ACTION = READ|WRITE | READWRITE
296
- & position= ' rewind' , & ! POSITION = ASIS | REWIND | APPEND
297
- & status= ' new' , & ! STATUS = NEW | REPLACE | OLD | SCRATCH | UNKNOWN
298
- & iostat= ios, &
299
- & iomsg= message)
300
- else
301
- lun= stdout
302
- ios= 0
303
- endif
304
- if (ios.ne. 0 )then
305
- write (stderr,' (*(a:,1x))' )' *filewrite* error:' ,filename,trim (message)
306
- error stop 1
307
- endif
308
- do i= 1 ,size (filedata) ! write file
309
- write (lun,' (a)' ,iostat= ios,iomsg= message)trim (filedata(i))
310
- if (ios.ne. 0 )then
311
- write (stderr,' (*(a:,1x))' )' *filewrite* error:' ,filename,trim (message)
312
- error stop 4
313
- endif
314
- enddo
315
- close (unit= lun,iostat= ios,iomsg= message) ! close file
316
- if (ios.ne. 0 )then
317
- write (stderr,' (*(a:,1x))' )' *filewrite* error:' ,trim (message)
318
- error stop 2
319
- endif
320
- end subroutine filewrite
321
-
322
- end subroutine cmd_new
323
-
324
-
325
169
subroutine cmd_run (settings )
326
170
type (fpm_run_settings), intent (in ) :: settings
327
171
character (len= :),allocatable :: release_name, cmd, fname
0 commit comments