@@ -56,9 +56,10 @@ module fpm_cmd_new
56
56
use fpm_command_line, only : fpm_new_settings
57
57
use fpm_environment, only : run, OS_LINUX, OS_MACOS, OS_WINDOWS
58
58
use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir
59
- use fpm_filesystem, only : fileopen, fileclose, filewrite, warnwrite
59
+ use fpm_filesystem, only : fileopen, fileclose, filewrite, warnwrite, which
60
60
use fpm_strings, only : join, to_fortran_name
61
61
use fpm_error, only : fpm_stop
62
+
62
63
use ,intrinsic :: iso_fortran_env, only : stderr= >error_unit
63
64
implicit none
64
65
private
@@ -572,9 +573,58 @@ subroutine cmd_new(settings)
572
573
call create_verified_basic_manifest(join_path(settings% name, ' fpm.toml' ))
573
574
endif
574
575
! assumes git(1) is installed and in path
575
- call run(' git init ' // settings% name)
576
+ if (which(' git' ).ne. ' ' )then
577
+ call run(' git init ' // settings% name)
578
+ endif
576
579
contains
577
580
581
+ function git_metadata (what ) result(returned)
582
+ ! > get metadata values such as email address and git name from git(1) or return appropriate default
583
+ use fpm_filesystem, only : get_temp_filename, getline
584
+ character (len=* ), intent (in ) :: what ! keyword designating what git metatdata to query
585
+ character (len= :), allocatable :: returned ! value to return for requested keyword
586
+ character (len= :), allocatable :: command
587
+ character (len= :), allocatable :: temp_filename
588
+ character (len= :), allocatable :: iomsg
589
+ character (len= :), allocatable :: temp_value
590
+ integer :: stat, unit
591
+ temp_filename = get_temp_filename()
592
+ ! for known keywords set default value for RETURNED and associated git(1) command for query
593
+ select case (what)
594
+ case (' uname' )
595
+ returned = " Jane Doe"
596
+ command = " git config --get user.name > " // temp_filename
597
+ case (' email' )
598
+
599
+ command = " git config --get user.email > " // temp_filename
600
+ case default
601
+ write (stderr,' (*(g0,1x))' )&
602
+ & ' <ERROR> *git_metadata* unknown metadata name ' ,trim (what)
603
+ returned= ' '
604
+ return
605
+ end select
606
+ ! Execute command if git(1) is in command path
607
+ if (which(' git' )/= ' ' )then
608
+ call run(command, exitstat= stat)
609
+ if (stat /= 0 ) then ! If command failed just return default
610
+ return
611
+ else ! Command did not return an error so try to read expected output file
612
+ open (file= temp_filename, newunit= unit,iostat= stat)
613
+ if (stat == 0 )then
614
+ ! Read file into a scratch variable until status of doing so is checked
615
+ call getline(unit, temp_value, stat, iomsg)
616
+ if (stat == 0 .and. temp_value /= ' ' ) then
617
+ ! Return output from successful command
618
+ returned= temp_value
619
+ endif
620
+ endif
621
+ ! Always do the CLOSE because a failed open has unpredictable results.
622
+ ! Add IOSTAT so a failed close does not cause program to stop
623
+ close (unit, status= " delete" ,iostat= stat)
624
+ endif
625
+ endif
626
+ end function git_metadata
627
+
578
628
subroutine create_verified_basic_manifest (filename )
579
629
! > create a basic but verified default manifest file
580
630
use fpm_toml, only : toml_table, toml_serializer, set_value
@@ -603,9 +653,9 @@ subroutine create_verified_basic_manifest(filename)
603
653
call set_value(table, " name" , BNAME)
604
654
call set_value(table, " version" , " 0.1.0" )
605
655
call set_value(table, " license" , " license" )
606
- call set_value(table, " author" , " Jane Doe " )
607
- call set_value(table,
" maintainer" ,
" [email protected] " )
608
- call set_value(table, " copyright" , ' Copyright ' // date(1 :4 )// ' , Jane Doe ' )
656
+ call set_value(table, " author" , git_metadata( ' uname ' ) )
657
+ call set_value(table, " maintainer" , git_metadata( ' email ' ) )
658
+ call set_value(table, " copyright" , ' Copyright ' // date(1 :4 )// ' , ' // git_metadata( ' uname ' ) )
609
659
! continue building of manifest
610
660
! ...
611
661
call new_package(package, table, error= error)
0 commit comments