From d99ad594f731511413f5bad96f0c0dfe0c2c08aa Mon Sep 17 00:00:00 2001 From: Pedro Costa Date: Mon, 13 Dec 2021 07:02:02 +0000 Subject: Better extraction of the Fortran compiler from the MPI wrapper (#634) - changed command to one supported by more (all?) MPI libraries --- src/fpm_compiler.f90 | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/src/fpm_compiler.f90 b/src/fpm_compiler.f90 index c0c5b73..bccff74 100644 --- a/src/fpm_compiler.f90 +++ b/src/fpm_compiler.f90 @@ -40,7 +40,7 @@ use fpm_environment, only: & OS_UNKNOWN use fpm_filesystem, only: join_path, basename, get_temp_filename, delete_file, unix_path, & & getline -use fpm_strings, only: string_cat, string_t +use fpm_strings, only: split, string_cat, string_t implicit none public :: compiler_t, new_compiler, archiver_t, new_archiver public :: debug @@ -467,7 +467,7 @@ function get_compiler_id(compiler) result(id) character(len=*), intent(in) :: compiler integer(kind=compiler_enum) :: id - character(len=:), allocatable :: command, output + character(len=:), allocatable :: full_command, full_command_parts(:), command, output integer :: stat, io ! Check whether we are dealing with an MPI compiler wrapper first @@ -475,14 +475,18 @@ function get_compiler_id(compiler) result(id) & .or. check_compiler(compiler, "mpif90") & & .or. check_compiler(compiler, "mpif77")) then output = get_temp_filename() - call run(compiler//" -showme:command > "//output//" 2>&1", & + call run(compiler//" -show > "//output//" 2>&1", & & echo=.false., exitstat=stat) if (stat == 0) then open(file=output, newunit=io, iostat=stat) - if (stat == 0) call getline(io, command, stat) + if (stat == 0) call getline(io, full_command, stat) close(io, iostat=stat) ! If we get a command from the wrapper, we will try to identify it + call split(full_command, full_command_parts, delimiters=' ') + if(size(full_command_parts) > 0)then + command = trim(full_command_parts(1)) + endif if (allocated(command)) then id = get_id(command) if (id /= id_unknown) return -- cgit v1.2.3 From 32401f1fa1ed9d42e6a59d988a03fdf6f3fc9716 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Mon, 10 Jan 2022 08:13:17 +0100 Subject: Update module output directory command for flang-new/f18 (#645) --- src/fpm_compiler.f90 | 20 ++++++++++++++++++-- 1 file changed, 18 insertions(+), 2 deletions(-) diff --git a/src/fpm_compiler.f90 b/src/fpm_compiler.f90 index bccff74..98a3650 100644 --- a/src/fpm_compiler.f90 +++ b/src/fpm_compiler.f90 @@ -61,6 +61,8 @@ enum, bind(C) id_nvhpc, & id_nag, & id_flang, & + id_flang_new, & + id_f18, & id_ibmxl, & id_cray, & id_lahey, & @@ -380,7 +382,8 @@ function get_include_flag(self, path) result(flags) case default flags = "-I "//path - case(id_caf, id_gcc, id_f95, id_cray, id_nvhpc, id_pgi, id_flang, & + case(id_caf, id_gcc, id_f95, id_cray, id_nvhpc, id_pgi, & + & id_flang, id_flang_new, id_f18, & & id_intel_classic_nix, id_intel_classic_mac, & & id_intel_llvm_nix, id_lahey, id_nag, id_ibmxl, & & id_lfortran) @@ -407,6 +410,9 @@ function get_module_flag(self, path) result(flags) case(id_nvhpc, id_pgi, id_flang) flags = "-module "//path + case(id_flang_new, id_f18) + flags = "-module-dir "//path + case(id_intel_classic_nix, id_intel_classic_mac, & & id_intel_llvm_nix) flags = "-module "//path @@ -443,7 +449,7 @@ subroutine get_default_c_compiler(f_compiler, c_compiler) case(id_intel_llvm_nix,id_intel_llvm_windows) c_compiler = 'icx' - case(id_flang) + case(id_flang, id_flang_new, id_f18) c_compiler='clang' case(id_ibmxl) @@ -558,6 +564,16 @@ function get_id(compiler) result(id) return end if + if (check_compiler(compiler, "flang-new")) then + id = id_flang_new + return + end if + + if (check_compiler(compiler, "f18")) then + id = id_f18 + return + end if + if (check_compiler(compiler, "flang")) then id = id_flang return -- cgit v1.2.3 From 64ce7b9da5826b3b728d470ae11994c23e234440 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Mon, 10 Jan 2022 08:13:42 +0100 Subject: Respect user provided main-files (#646) - add example package for C-main --- ci/run_tests.sh | 4 ++++ example_packages/c_main/app/main.c | 5 +++++ example_packages/c_main/fpm.toml | 5 +++++ src/fpm_sources.f90 | 16 ++++++++++------ 4 files changed, 24 insertions(+), 6 deletions(-) create mode 100644 example_packages/c_main/app/main.c create mode 100644 example_packages/c_main/fpm.toml diff --git a/ci/run_tests.sh b/ci/run_tests.sh index ff477e7..9525422 100755 --- a/ci/run_tests.sh +++ b/ci/run_tests.sh @@ -98,5 +98,9 @@ pushd c_header_only "$fpm" build popd +pushd c_main +"$fpm" run +popd + # Cleanup rm -rf ./*/build diff --git a/example_packages/c_main/app/main.c b/example_packages/c_main/app/main.c new file mode 100644 index 0000000..398ec67 --- /dev/null +++ b/example_packages/c_main/app/main.c @@ -0,0 +1,5 @@ +int +main (void) +{ + return 0; +} diff --git a/example_packages/c_main/fpm.toml b/example_packages/c_main/fpm.toml new file mode 100644 index 0000000..eb18e9b --- /dev/null +++ b/example_packages/c_main/fpm.toml @@ -0,0 +1,5 @@ +name = "c-main" + +[[executable]] +name = "c-main" +main = "main.c" diff --git a/src/fpm_sources.f90 b/src/fpm_sources.f90 index f349a0e..af2870f 100644 --- a/src/fpm_sources.f90 +++ b/src/fpm_sources.f90 @@ -163,6 +163,7 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error) if (allocated(executables(i)%link)) then sources(j)%link_libraries = executables(i)%link end if + sources(j)%unit_type = FPM_UNIT_PROGRAM cycle exe_loop end if @@ -170,12 +171,15 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error) end do ! Add if not already discovered (auto_discovery off) - exe_source = parse_source(join_path(executables(i)%source_dir,executables(i)%main),error) - exe_source%exe_name = executables(i)%name - if (allocated(executables(i)%link)) then - exe_source%link_libraries = executables(i)%link - end if - exe_source%unit_scope = scope + associate(exe => executables(i)) + exe_source = parse_source(join_path(exe%source_dir,exe%main),error) + exe_source%exe_name = exe%name + if (allocated(exe%link)) then + exe_source%link_libraries = exe%link + end if + exe_source%unit_type = FPM_UNIT_PROGRAM + exe_source%unit_scope = scope + end associate if (allocated(error)) return -- cgit v1.2.3 From 2ae0581eb2a8f79d0cd0ff9d528de6e2fe827362 Mon Sep 17 00:00:00 2001 From: urbanjost Date: Sun, 16 Jan 2022 07:56:48 -0500 Subject: Allow running fpm-new in current directory (#630) --- src/fpm_command_line.f90 | 25 ++++++++++++++++++++----- 1 file changed, 20 insertions(+), 5 deletions(-) diff --git a/src/fpm_command_line.f90 b/src/fpm_command_line.f90 index 0837bf2..cb19192 100644 --- a/src/fpm_command_line.f90 +++ b/src/fpm_command_line.f90 @@ -31,10 +31,12 @@ use M_CLI2, only : get_subcommand, CLI_RESPONSE_FILE use fpm_strings, only : lower, split, fnv_1a, to_fortran_name, is_fortran_name use fpm_filesystem, only : basename, canon_path, which use fpm_environment, only : run, get_command_arguments_quoted -use fpm_error, only : fpm_stop +use fpm_os, only : get_current_directory +use fpm_error, only : fpm_stop, error_t use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, & & stdout=>output_unit, & & stderr=>error_unit + implicit none private @@ -179,6 +181,7 @@ contains character(len=*), parameter :: fc_env = "FC", cc_env = "CC", ar_env = "AR", & & fflags_env = "FFLAGS", cflags_env = "CFLAGS", ldflags_env = "LDFLAGS", & & fc_default = "gfortran", cc_default = " ", ar_default = " ", flags_default = " " + type(error_t), allocatable :: error call set_help() ! text for --version switch, @@ -317,9 +320,13 @@ contains & help_new, version_text) select case(size(unnamed)) case(1) - write(stderr,'(*(7x,g0,/))') & - & ' fpm new NAME [[--lib|--src] [--app] [--test] [--example]]|[--full|--bare] [--backfill]' - call fpm_stop(1,'directory name required') + if(lget('backfill'))then + name='.' + else + write(stderr,'(*(7x,g0,/))') & + & ' fpm new NAME [[--lib|--src] [--app] [--test] [--example]]|[--full|--bare] [--backfill]' + call fpm_stop(1,'directory name required') + endif case(2) name=trim(unnamed(2)) case default @@ -328,6 +335,13 @@ contains call fpm_stop(2,'only one directory name allowed') end select !*! canon_path is not converting ".", etc. + if(name.eq.'.')then + call get_current_directory(name, error) + if (allocated(error)) then + write(stderr, '("[Error]", 1x, a)') error%message + stop 1 + endif + endif name=canon_path(name) if( .not.is_fortran_name(to_fortran_name(basename(name))) )then write(stderr,'(g0)') [ character(len=72) :: & @@ -336,6 +350,7 @@ contains call fpm_stop(4,' ') endif + allocate(fpm_new_settings :: cmd_settings) if (any( specified([character(len=10) :: 'src','lib','app','test','example','bare'])) & & .and.lget('full') )then @@ -1079,7 +1094,7 @@ contains ' fpm new A --full # create example/ and an annotated fpm.toml as well', & ' fpm new A --bare # create no directories ', & ' create any missing files in current directory ', & - ' fpm new `pwd` --full --backfill ', & + ' fpm new --full --backfill ', & '' ] help_test=[character(len=80) :: & 'NAME ', & -- cgit v1.2.3 From 45d3fd8afae5830b9c1eb13045e689078eff4d5a Mon Sep 17 00:00:00 2001 From: Andre Smit Date: Thu, 20 Jan 2022 08:50:18 -0600 Subject: get user name and email using git config if available else use defaults --- src/fpm/cmd/new.f90 | 48 +++++++++++++++++++++++++++++++++++++++++++++--- 1 file changed, 45 insertions(+), 3 deletions(-) diff --git a/src/fpm/cmd/new.f90 b/src/fpm/cmd/new.f90 index a402432..c0ec3b8 100644 --- a/src/fpm/cmd/new.f90 +++ b/src/fpm/cmd/new.f90 @@ -575,6 +575,48 @@ character(len=:,kind=tfc),allocatable :: littlefile(:) call run('git init ' // settings%name) contains +function default_user(what) result(user) + implicit none + character(len=5), intent(in) :: what + character(len=:), allocatable :: user + if (what=="uname") then + user = "Jane Doe" + else + user = "jane.doe@example.com" + end if + return +end function default_user + +function git_user(what) result(user) + use fpm_filesystem, only : get_temp_filename, getline + implicit none + character(len=5), intent(in) :: what + character(len=:), allocatable :: user + character(len=:), allocatable :: temp_user, iomsg + integer :: stat, unit + allocate(temp_user, source=get_temp_filename()) + if (what=="uname") then + user = "git config --get user.name > " // temp_user + else + user = "git config --get user.email > " // temp_user + end if + call execute_command_line(user, exitstat=stat) + if (stat /= 0) then + user = default_user(what) + return + end if + open(file=temp_user, newunit=unit) + call getline(unit, user, stat, iomsg) + if (stat /= 0) then + user = default_user(what) + end if + close(unit, status="delete") + if (len(user)==0) then + user = default_user(what) + end if + return +end function git_user + subroutine create_verified_basic_manifest(filename) !> create a basic but verified default manifest file use fpm_toml, only : toml_table, toml_serializer, set_value @@ -603,9 +645,9 @@ character(len=*),intent(in) :: filename call set_value(table, "name", BNAME) call set_value(table, "version", "0.1.0") call set_value(table, "license", "license") - call set_value(table, "author", "Jane Doe") - call set_value(table, "maintainer", "jane.doe@example.com") - call set_value(table, "copyright", 'Copyright '//date(1:4)//', Jane Doe') + call set_value(table, "author", git_user("uname")) + call set_value(table, "maintainer", git_user("email")) + call set_value(table, "copyright", 'Copyright '//date(1:4)//', '//git_user("uname")) ! continue building of manifest ! ... call new_package(package, table, error=error) -- cgit v1.2.3 From 1a3d5cfee58075979774dfae2a0e3f68ba6031b2 Mon Sep 17 00:00:00 2001 From: Andre Smit Date: Thu, 20 Jan 2022 12:05:38 -0600 Subject: Update src/fpm/cmd/new.f90 Co-authored-by: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> --- src/fpm/cmd/new.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/fpm/cmd/new.f90 b/src/fpm/cmd/new.f90 index c0ec3b8..f5a3ea4 100644 --- a/src/fpm/cmd/new.f90 +++ b/src/fpm/cmd/new.f90 @@ -577,7 +577,7 @@ contains function default_user(what) result(user) implicit none - character(len=5), intent(in) :: what + character(len=*), intent(in) :: what character(len=:), allocatable :: user if (what=="uname") then user = "Jane Doe" -- cgit v1.2.3 From 679bc5d7c25f8160375e02f53f04caa8ffcaacbf Mon Sep 17 00:00:00 2001 From: Andre Smit Date: Thu, 20 Jan 2022 12:05:45 -0600 Subject: Update src/fpm/cmd/new.f90 Co-authored-by: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> --- src/fpm/cmd/new.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/fpm/cmd/new.f90 b/src/fpm/cmd/new.f90 index f5a3ea4..414623b 100644 --- a/src/fpm/cmd/new.f90 +++ b/src/fpm/cmd/new.f90 @@ -590,7 +590,7 @@ end function default_user function git_user(what) result(user) use fpm_filesystem, only : get_temp_filename, getline implicit none - character(len=5), intent(in) :: what + character(len=*), intent(in) :: what character(len=:), allocatable :: user character(len=:), allocatable :: temp_user, iomsg integer :: stat, unit -- cgit v1.2.3 From be201c9b80b839d90e8c4caf266e621664ff3f85 Mon Sep 17 00:00:00 2001 From: Andre Smit Date: Thu, 20 Jan 2022 12:05:55 -0600 Subject: Update src/fpm/cmd/new.f90 Co-authored-by: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> --- src/fpm/cmd/new.f90 | 1 - 1 file changed, 1 deletion(-) diff --git a/src/fpm/cmd/new.f90 b/src/fpm/cmd/new.f90 index 414623b..bb21d73 100644 --- a/src/fpm/cmd/new.f90 +++ b/src/fpm/cmd/new.f90 @@ -576,7 +576,6 @@ character(len=:,kind=tfc),allocatable :: littlefile(:) contains function default_user(what) result(user) - implicit none character(len=*), intent(in) :: what character(len=:), allocatable :: user if (what=="uname") then -- cgit v1.2.3 From f2ceb1664d8b637e1390f94a73ce2f53797185f1 Mon Sep 17 00:00:00 2001 From: Andre Smit Date: Thu, 20 Jan 2022 12:06:00 -0600 Subject: Update src/fpm/cmd/new.f90 Co-authored-by: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> --- src/fpm/cmd/new.f90 | 1 - 1 file changed, 1 deletion(-) diff --git a/src/fpm/cmd/new.f90 b/src/fpm/cmd/new.f90 index bb21d73..d69f6f2 100644 --- a/src/fpm/cmd/new.f90 +++ b/src/fpm/cmd/new.f90 @@ -588,7 +588,6 @@ end function default_user function git_user(what) result(user) use fpm_filesystem, only : get_temp_filename, getline - implicit none character(len=*), intent(in) :: what character(len=:), allocatable :: user character(len=:), allocatable :: temp_user, iomsg -- cgit v1.2.3 From 5143d1968f8299673c6712dc0074f1e40db16361 Mon Sep 17 00:00:00 2001 From: Andre Smit Date: Thu, 20 Jan 2022 12:06:09 -0600 Subject: Update src/fpm/cmd/new.f90 Co-authored-by: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> --- src/fpm/cmd/new.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/fpm/cmd/new.f90 b/src/fpm/cmd/new.f90 index d69f6f2..b00aa06 100644 --- a/src/fpm/cmd/new.f90 +++ b/src/fpm/cmd/new.f90 @@ -592,7 +592,7 @@ function git_user(what) result(user) character(len=:), allocatable :: user character(len=:), allocatable :: temp_user, iomsg integer :: stat, unit - allocate(temp_user, source=get_temp_filename()) + temp_user = get_temp_filename() if (what=="uname") then user = "git config --get user.name > " // temp_user else -- cgit v1.2.3 From 18e5f5941728bbeedf2a3a604aa82d9aea8689f9 Mon Sep 17 00:00:00 2001 From: Andre Smit Date: Thu, 20 Jan 2022 12:06:13 -0600 Subject: Update src/fpm/cmd/new.f90 Co-authored-by: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> --- src/fpm/cmd/new.f90 | 1 - 1 file changed, 1 deletion(-) diff --git a/src/fpm/cmd/new.f90 b/src/fpm/cmd/new.f90 index b00aa06..6b04336 100644 --- a/src/fpm/cmd/new.f90 +++ b/src/fpm/cmd/new.f90 @@ -612,7 +612,6 @@ function git_user(what) result(user) if (len(user)==0) then user = default_user(what) end if - return end function git_user subroutine create_verified_basic_manifest(filename) -- cgit v1.2.3 From fe93a5b868a37b9bb80f8573e80124d5a20afb8b Mon Sep 17 00:00:00 2001 From: Andre Smit Date: Thu, 20 Jan 2022 12:06:19 -0600 Subject: Update src/fpm/cmd/new.f90 Co-authored-by: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> --- src/fpm/cmd/new.f90 | 1 - 1 file changed, 1 deletion(-) diff --git a/src/fpm/cmd/new.f90 b/src/fpm/cmd/new.f90 index 6b04336..c14ee3c 100644 --- a/src/fpm/cmd/new.f90 +++ b/src/fpm/cmd/new.f90 @@ -583,7 +583,6 @@ function default_user(what) result(user) else user = "jane.doe@example.com" end if - return end function default_user function git_user(what) result(user) -- cgit v1.2.3 From 21a9261862df80ed071e3b5c9f4432c524c2a48a Mon Sep 17 00:00:00 2001 From: Andre Smit Date: Mon, 24 Jan 2022 06:28:01 -0600 Subject: fix git_metadata function to handle edge cases --- src/fpm/cmd/new.f90 | 90 ++++++++++++++++++++++++++++++----------------------- 1 file changed, 51 insertions(+), 39 deletions(-) diff --git a/src/fpm/cmd/new.f90 b/src/fpm/cmd/new.f90 index c14ee3c..0d5bf30 100644 --- a/src/fpm/cmd/new.f90 +++ b/src/fpm/cmd/new.f90 @@ -56,9 +56,10 @@ module fpm_cmd_new use fpm_command_line, only : fpm_new_settings use fpm_environment, only : run, OS_LINUX, OS_MACOS, OS_WINDOWS use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir -use fpm_filesystem, only : fileopen, fileclose, filewrite, warnwrite +use fpm_filesystem, only : fileopen, fileclose, filewrite, warnwrite, which use fpm_strings, only : join, to_fortran_name use fpm_error, only : fpm_stop + use,intrinsic :: iso_fortran_env, only : stderr=>error_unit implicit none private @@ -572,46 +573,57 @@ character(len=:,kind=tfc),allocatable :: littlefile(:) call create_verified_basic_manifest(join_path(settings%name, 'fpm.toml')) endif ! assumes git(1) is installed and in path - call run('git init ' // settings%name) + if(which('git').ne.'')then + call run('git init ' // settings%name) + endif contains -function default_user(what) result(user) - character(len=*), intent(in) :: what - character(len=:), allocatable :: user - if (what=="uname") then - user = "Jane Doe" - else - user = "jane.doe@example.com" - end if -end function default_user - -function git_user(what) result(user) +function git_metadata(what) result(returned) +!> get metadata values such as email address and git name from git(1) or return appropriate default use fpm_filesystem, only : get_temp_filename, getline - character(len=*), intent(in) :: what - character(len=:), allocatable :: user - character(len=:), allocatable :: temp_user, iomsg + character(len=*), intent(in) :: what !> keyword designating what git metatdata to query + character(len=:), allocatable :: returned !> value to return for requested keyword + character(len=:), allocatable :: command + character(len=:), allocatable :: temp_filename + character(len=:), allocatable :: iomsg + character(len=:), allocatable :: temp_value integer :: stat, unit - temp_user = get_temp_filename() - if (what=="uname") then - user = "git config --get user.name > " // temp_user - else - user = "git config --get user.email > " // temp_user - end if - call execute_command_line(user, exitstat=stat) - if (stat /= 0) then - user = default_user(what) + temp_filename = get_temp_filename() + ! for known keywords set default value for RETURNED and associated git(1) command for query + select case(what) + case('uname') + returned = "Jane Doe" + command = "git config --get user.name > " // temp_filename + case('email') + returned = "jane.doe@example.com" + command = "git config --get user.email > " // temp_filename + case default + write(stderr,'(*(g0,1x))')& + & ' *git_metadata* unknown metadata name ',trim(what) + returned='' return - end if - open(file=temp_user, newunit=unit) - call getline(unit, user, stat, iomsg) - if (stat /= 0) then - user = default_user(what) - end if - close(unit, status="delete") - if (len(user)==0) then - user = default_user(what) - end if -end function git_user + end select + ! Execute command if git(1) is in command path + if(which('git')/='')then + call run(command, exitstat=stat) + if (stat /= 0) then ! If command failed just return default + return + else ! Command did not return an error so try to read expected output file + open(file=temp_filename, newunit=unit,iostat=stat) + if(stat == 0)then + ! Read file into a scratch variable until status of doing so is checked + call getline(unit, temp_value, stat, iomsg) + if (stat == 0 .and. temp_value /= '') then + ! Return output from successful command + returned=temp_value + endif + endif + ! Always do the CLOSE because a failed open has unpredictable results. + ! Add IOSTAT so a failed close does not cause program to stop + close(unit, status="delete",iostat=stat) + endif + endif +end function git_metadata subroutine create_verified_basic_manifest(filename) !> create a basic but verified default manifest file @@ -641,9 +653,9 @@ character(len=*),intent(in) :: filename call set_value(table, "name", BNAME) call set_value(table, "version", "0.1.0") call set_value(table, "license", "license") - call set_value(table, "author", git_user("uname")) - call set_value(table, "maintainer", git_user("email")) - call set_value(table, "copyright", 'Copyright '//date(1:4)//', '//git_user("uname")) + call set_value(table, "author", git_metadata('uname')) + call set_value(table, "maintainer", git_metadata('email')) + call set_value(table, "copyright", 'Copyright '//date(1:4)//', '//git_metadata('uname')) ! continue building of manifest ! ... call new_package(package, table, error=error) -- cgit v1.2.3 From cb5d94e93ae3da4ececa46150feb17fdd78e6d6d Mon Sep 17 00:00:00 2001 From: Andre Smit Date: Mon, 24 Jan 2022 06:36:33 -0600 Subject: remove inline documentation lines --- src/fpm/cmd/new.f90 | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/fpm/cmd/new.f90 b/src/fpm/cmd/new.f90 index 0d5bf30..99aa4c5 100644 --- a/src/fpm/cmd/new.f90 +++ b/src/fpm/cmd/new.f90 @@ -581,8 +581,8 @@ contains function git_metadata(what) result(returned) !> get metadata values such as email address and git name from git(1) or return appropriate default use fpm_filesystem, only : get_temp_filename, getline - character(len=*), intent(in) :: what !> keyword designating what git metatdata to query - character(len=:), allocatable :: returned !> value to return for requested keyword + character(len=*), intent(in) :: what ! keyword designating what git metatdata to query + character(len=:), allocatable :: returned ! value to return for requested keyword character(len=:), allocatable :: command character(len=:), allocatable :: temp_filename character(len=:), allocatable :: iomsg -- cgit v1.2.3