@@ -3,8 +3,8 @@ module fpm
3
3
use fpm_backend, only: build_package
4
4
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
5
5
fpm_run_settings, fpm_install_settings, fpm_test_settings
6
- 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, basename, mkdir
6
+ use fpm_environment, only: run
7
+ use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
8
8
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
9
9
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
10
10
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
@@ -21,7 +21,7 @@ module fpm
21
21
use fpm_manifest_dependency, only: dependency_t
22
22
implicit none
23
23
private
24
- public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
24
+ public :: cmd_build, cmd_install, cmd_run, cmd_test
25
25
26
26
contains
27
27
@@ -284,160 +284,6 @@ subroutine cmd_install(settings)
284
284
error stop 8
285
285
end subroutine cmd_install
286
286
287
-
288
- subroutine cmd_new (settings ) ! --with-executable F --with-test F '
289
- type (fpm_new_settings), intent (in ) :: settings
290
- integer :: ierr
291
- character (len= :),allocatable :: bname ! baeename of NAME
292
- character (len= :),allocatable :: message(:)
293
- character (len= :),allocatable :: littlefile(:)
294
-
295
- call mkdir(settings% name) ! make new directory
296
- call run(' cd ' // settings% name) ! change to new directory as a test. New OS routines to improve this; system dependent potentially
297
- ! ! NOTE: need some system routines to handle filenames like "." like realpath() or getcwd().
298
- bname= basename(settings% name)
299
-
300
- ! ! weird gfortran bug?? lines truncated to concatenated string length, not 80
301
- ! ! hit some weird gfortran bug when littlefile data was an argument to warnwrite(3f), ok when a variable
302
-
303
- call warnwrite(join_path(settings% name, ' .gitignore' ), [' build/*' ]) ! create NAME/.gitignore file
304
-
305
- littlefile= [character (len= 80 ) :: ' # ' // bname, ' My cool new project!' ]
306
-
307
- call warnwrite(join_path(settings% name, ' README.md' ), littlefile) ! create NAME/README.md
308
-
309
- message= [character (len= 80 ) :: & ! start building NAME/fpm.toml
310
- &' name = "' // bname// ' " ' , &
311
- &' version = "0.1.0" ' , &
312
- &' license = "license" ' , &
313
- &' author = "Jane Doe" ' , &
314
- &
' maintainer = "[email protected] " ' , &
315
- &' copyright = "2020 Jane Doe" ' , &
316
- &' ' , &
317
- &' ' ]
318
-
319
- if (settings% with_lib)then
320
- call mkdir(join_path(settings% name,' src' ) )
321
- message= [character (len= 80 ) :: message, & ! create next section of fpm.toml
322
- &' [library] ' , &
323
- &' source-dir="src" ' , &
324
- &' ' ]
325
- littlefile= [character (len= 80 ) :: & ! create placeholder module src/bname.f90
326
- &' module ' // bname, &
327
- &' implicit none' , &
328
- &' private' , &
329
- &' ' , &
330
- &' public :: say_hello' , &
331
- &' contains' , &
332
- &' subroutine say_hello' , &
333
- &' print *, "Hello, ' // bname// ' !"' , &
334
- &' end subroutine say_hello' , &
335
- &' end module ' // bname]
336
- ! a proposed alternative default
337
- call warnwrite(join_path(settings% name, ' src' , bname// ' .f90' ), littlefile) ! create NAME/src/NAME.f90
338
- endif
339
-
340
- if (settings% with_test)then
341
- call mkdir(join_path(settings% name, ' test' )) ! create NAME/test or stop
342
- message= [character (len= 80 ) :: message, & ! create next section of fpm.toml
343
- &' [[test]] ' , &
344
- &' name="runTests" ' , &
345
- &' source-dir="test" ' , &
346
- &' main="main.f90" ' , &
347
- &' ' ]
348
-
349
- littlefile= [character (len= 80 ) :: &
350
- &' program main' , &
351
- &' implicit none' , &
352
- &' ' , &
353
- &' print *, "Put some tests in here!"' , &
354
- &' end program main' ]
355
- ! a proposed alternative default a little more substantive
356
- call warnwrite(join_path(settings% name, ' test/main.f90' ), littlefile) ! create NAME/test/main.f90
357
- endif
358
-
359
- if (settings% with_executable)then
360
- call mkdir(join_path(settings% name, ' app' )) ! create NAME/app or stop
361
- message= [character (len= 80 ) :: message, & ! create next section of fpm.toml
362
- &' [[executable]] ' , &
363
- &' name="' // bname// ' " ' , &
364
- &' source-dir="app" ' , &
365
- &' main="main.f90" ' , &
366
- &' ' ]
367
-
368
- littlefile= [character (len= 80 ) :: &
369
- &' program main' , &
370
- &' use ' // bname// ' , only: say_hello' , &
371
- &' ' , &
372
- &' implicit none' , &
373
- &' ' , &
374
- &' call say_hello' , &
375
- &' end program main' ]
376
- call warnwrite(join_path(settings% name, ' app/main.f90' ), littlefile)
377
- endif
378
-
379
- call warnwrite(join_path(settings% name, ' fpm.toml' ), message) ! now that built it write NAME/fpm.toml
380
-
381
- call run(' cd ' // settings% name // ' ;git init' ) ! assumes these commands work on all systems and git(1) is installed
382
- contains
383
-
384
- subroutine warnwrite (fname ,data )
385
- character (len=* ),intent (in ) :: fname
386
- character (len=* ),intent (in ) :: data (:)
387
-
388
- if (.not. exists(fname))then
389
- call filewrite(fname,data )
390
- else
391
- write (stderr,' (*(g0,1x))' )' fpm::new<WARNING>' ,fname,' already exists. Not overwriting'
392
- endif
393
-
394
- end subroutine warnwrite
395
-
396
- subroutine filewrite (filename ,filedata )
397
- use ,intrinsic :: iso_fortran_env, only : stdin= >input_unit, stdout= >output_unit, stderr= >error_unit
398
- ! write filedata to file filename
399
- character (len=* ),intent (in ) :: filename
400
- character (len=* ),intent (in ) :: filedata(:)
401
- integer :: lun, i, ios
402
- character (len= 256 ) :: message
403
-
404
- message= ' '
405
- ios= 0
406
- if (filename.ne. ' ' )then
407
- open (file= filename, &
408
- & newunit= lun, &
409
- & form= ' formatted' , & ! FORM = FORMATTED | UNFORMATTED
410
- & access= ' sequential' , & ! ACCESS = SEQUENTIAL | DIRECT | STREAM
411
- & action= ' write' , & ! ACTION = READ|WRITE | READWRITE
412
- & position= ' rewind' , & ! POSITION = ASIS | REWIND | APPEND
413
- & status= ' new' , & ! STATUS = NEW | REPLACE | OLD | SCRATCH | UNKNOWN
414
- & iostat= ios, &
415
- & iomsg= message)
416
- else
417
- lun= stdout
418
- ios= 0
419
- endif
420
- if (ios.ne. 0 )then
421
- write (stderr,' (*(a:,1x))' )' *filewrite* error:' ,filename,trim (message)
422
- error stop 1
423
- endif
424
- do i= 1 ,size (filedata) ! write file
425
- write (lun,' (a)' ,iostat= ios,iomsg= message)trim (filedata(i))
426
- if (ios.ne. 0 )then
427
- write (stderr,' (*(a:,1x))' )' *filewrite* error:' ,filename,trim (message)
428
- error stop 4
429
- endif
430
- enddo
431
- close (unit= lun,iostat= ios,iomsg= message) ! close file
432
- if (ios.ne. 0 )then
433
- write (stderr,' (*(a:,1x))' )' *filewrite* error:' ,trim (message)
434
- error stop 2
435
- endif
436
- end subroutine filewrite
437
-
438
- end subroutine cmd_new
439
-
440
-
441
287
subroutine cmd_run (settings )
442
288
type (fpm_run_settings), intent (in ) :: settings
443
289
character (len= :),allocatable :: release_name, cmd, fname
0 commit comments