diff options
author | init current directory[i] <urbanjost@comcast.net> | 2020-10-07 03:21:33 -0400 |
---|---|---|
committer | init current directory[i] <urbanjost@comcast.net> | 2020-10-07 03:21:33 -0400 |
commit | 898bf2c648911a016deb24dbf5b707688f6b051c (patch) | |
tree | f46fb63e3090587c416cc52abe81f6a3fd9bdeeb | |
parent | 14db0715c4bc7a03f806858e990d63a95827dd5a (diff) | |
download | fpm-898bf2c648911a016deb24dbf5b707688f6b051c.tar.gz fpm-898bf2c648911a016deb24dbf5b707688f6b051c.zip |
complete new modifications for #109 #110 #111 #135 #138 #154 #196
-rw-r--r-- | README.md | 2 | ||||
-rw-r--r-- | fpm/fpm.toml | 3 | ||||
-rw-r--r-- | fpm/src/fpm_command_line.f90 | 384 |
3 files changed, 236 insertions, 153 deletions
@@ -77,7 +77,7 @@ with the following contents and initialized as a git repository. * `fpm test` – run tests The command `fpm run` can optionally accept the name of the specific executable -to run, as can `fpm test`; like `fpm run specifc_executable`. Command line +to run, as can `fpm test`; like `fpm run specific_executable`. Command line arguments can also be passed to the executable(s) or test(s) with the option `--args "some arguments"`. diff --git a/fpm/fpm.toml b/fpm/fpm.toml index 9418204..03434ec 100644 --- a/fpm/fpm.toml +++ b/fpm/fpm.toml @@ -14,6 +14,9 @@ tag = "v0.2" git = "https://github.com/urbanjost/M_CLI2.git" rev = "649075aceb97f997665a1a4656514fd2e9b4becc" +[dependencies.fortran-intrinsic-manpages] +git = "https://github.com/urbanjost/fortran-intrinsic-manpages.git" + [[test]] name = "cli-test" source-dir = "test/cli_test" diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 1a7e4ab..d8c9598 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -3,10 +3,12 @@ use fpm_environment, only : get_os_type, & OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, & OS_CYGWIN, OS_SOLARIS, OS_FREEBSD use M_CLI2, only : set_args, lget, unnamed, remaining, specified +use M_intrinsics, only : help_intrinsics +use fpm_strings, only : lower use fpm_filesystem, only : basename use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, & - & stdout=>output_unit, & - & stderr=>error_unit + & stdout=>output_unit, & + & stderr=>error_unit implicit none private @@ -27,6 +29,7 @@ type, extends(fpm_cmd_settings) :: fpm_new_settings logical :: with_executable=.false. logical :: with_test=.false. logical :: with_lib=.true. + logical :: backfill=.true. end type type, extends(fpm_cmd_settings) :: fpm_build_settings @@ -52,11 +55,13 @@ type, extends(fpm_cmd_settings) :: fpm_install_settings end type character(len=:),allocatable :: name +character(len=:),allocatable :: os_type character(len=ibug),allocatable :: names(:) character(len=:), allocatable :: version_text(:) -character(len=:), allocatable :: help_new(:), help_fpm(:), help_run(:), help_test(:), help_build(:) -character(len=:), allocatable :: help_text(:), help_install(:), help_help(:) +character(len=:), allocatable :: help_new(:), help_fpm(:), help_run(:), & + & help_test(:), help_build(:), help_usage(:), & + & help_text(:), help_install(:), help_help(:) contains subroutine get_command_line_settings(cmd_settings) @@ -64,24 +69,37 @@ contains character(len=4096) :: cmdarg integer :: i + integer :: widest call set_help() ! text for --version switch, + select case (get_os_type()) + case (OS_LINUX); os_type = "OS Type: Linux" + case (OS_MACOS); os_type = "OS Type: macOS" + case (OS_WINDOWS); os_type = "OS Type: Windows" + case (OS_CYGWIN); os_type = "OS Type: Cygwin" + case (OS_SOLARIS); os_type = "OS Type: Solaris" + case (OS_FREEBSD); os_type = "OS Type: FreeBSD" + case (OS_UNKNOWN); os_type = "OS Type: Unknown" + case default ; os_type = "OS Type: UNKNOWN" + end select version_text = [character(len=80) :: & - & 'Version: 0.1.0, Pre-alpha', & - & 'Program: fpm(1)', & - & 'Description: A Fortran package manager and build system', & - & 'Home Page: https://github.com/fortran-lang/fpm', & - & 'License: MIT', & - & ''] - ! find the subcommand name by looking for first word on command not starting with dash + & 'Version: 0.1.0, Pre-alpha', & + & 'Program: fpm(1)', & + & 'Description: A Fortran package manager and build system', & + & 'Home Page: https://github.com/fortran-lang/fpm', & + & 'License: MIT', & + & os_type] + ! find the subcommand name by looking for first word on command + ! not starting with dash cmdarg = '' do i = 1, command_argument_count() call get_command_argument(i, cmdarg) if(adjustl(cmdarg(1:1)) .ne. '-')exit enddo - ! now set subcommand-specific help text and process commandline arguments. Then call subcommand routine + ! now set subcommand-specific help text and process commandline + ! arguments. Then call subcommand routine select case(trim(cmdarg)) case('run') @@ -101,51 +119,51 @@ contains call set_args( '--release F --list F --',help_build,version_text ) allocate( fpm_build_settings :: cmd_settings ) - cmd_settings=fpm_build_settings( release=lget('release'),list=lget('list') ) + cmd_settings=fpm_build_settings( release=lget('release'), & + & list=lget('list') ) case('new') - call set_args(' --with-executable F --with-test F --lib F --app F --test F', help_new, version_text) + call set_args(' --lib F --app F --test F -backfill F', & + & help_new, version_text) select case(size(unnamed)) case(1) - write(stderr,'(*(g0))')'ERROR: directory name required' - write(stderr,'(*(g0))')' usage: fpm new NAME [--with-executable] [--with-test]' + write(stderr,'(*(g0,/))')'ERROR: directory name required' + write(stderr,'(*(7x,g0,/))') & + & 'usage: fpm new NAME [--lib] [--app] [--test] [--backfill]' stop 1 case(2) name=trim(unnamed(2)) case default - write(stderr,'(*(g0))')'ERROR: only one directory name allowed' - write(stderr,'(*(g0))')' usage: fpm new NAME [--with-executable] [--with-test]' + write(stderr,'(g0)')'ERROR: only one directory name allowed' + write(stderr,'(7x,g0)') & + & 'usage: fpm new NAME [--lib] [--app] [--test] [--backfill]' stop 2 end select if( .not.is_fortran_name(basename(name)) )then - write(stderr,'(*(g0))')'ERROR: the new directory basename must be an allowed Fortran name.' - write(stderr,'(*(g0))')' It must be composed of 1 to 63 ASCII characters and start' - write(stderr,'(*(g0))')' with a letter and be composed entirely of alphanumeric' - write(stderr,'(*(g0))')' characters [A-Za-z0-9] and underscores.' + write(stderr,'(g0)') [ character(len=72) :: & + & 'ERROR: the new directory basename must be an allowed ', & + & ' Fortran name. It must be composed of 1 to 63 ASCII', & + & ' characters and start with a letter and be composed', & + & ' entirely of alphanumeric characters [a-zA-Z0-9]', & + & ' and underscores.'] stop 4 endif allocate(fpm_new_settings :: cmd_settings) - cmd_settings=fpm_new_settings(name=name, & - & with_executable=lget('with-executable'), & - & with_test=lget('with-test'), & - & with_lib=.true.) - ! use alternative --lib --test --app switches. In production pick one - ! method or probably an error should be using --with and one of these if (any( specified(['lib ','app ','test']) ) )then - if (any( specified(['with-executable','with-test ']) ) )then - write(stderr,'(*(g0))') 'A BIT FROWARD:' - write(stderr,'(*(g0))') ' DO NOT MIX --with-* with [--lib|--app|--test]' - write(stderr,'(*(g0))') ' THEY ARE TWO DIFFERENT PROTOTYPE PROPOSALS ' - write(stderr,'(*(g0))') ' SEE ISSUES #111 #110 #109' - write(stderr,'(*(g0))') ' START WITH https://github.com/fortran-lang/fpm/issues/111' - endif cmd_settings=fpm_new_settings(name=name, & & with_executable=lget('app'), & & with_test=lget('test'), & - & with_lib=lget('lib') ) + & with_lib=lget('lib'), & + & backfill=lget('backfill') ) + else + cmd_settings=fpm_new_settings(name=name, & + & with_executable=.true., & + & with_test=.true., & + & with_lib=.true., & + & backfill=lget('backfill') ) endif case('help') @@ -153,32 +171,38 @@ contains if(size(unnamed).lt.2)then unnamed=['help', 'fpm '] endif - allocate(character(len=80) :: help_text(0)) + widest=256 + allocate(character(len=widest) :: help_text(0)) do i=2,size(unnamed) select case(unnamed(i)) case('build ' ) - help_text=[character(len=80) :: help_text, help_build] + help_text=[character(len=widest) :: help_text, help_build] case('run ' ) - help_text=[character(len=80) :: help_text, help_run] + help_text=[character(len=widest) :: help_text, help_run] case('help ' ) - help_text=[character(len=80) :: help_text, help_help] + help_text=[character(len=widest) :: help_text, help_help] case('test ' ) - help_text=[character(len=80) :: help_text, help_test] + help_text=[character(len=widest) :: help_text, help_test] case('new ' ) - help_text=[character(len=80) :: help_text, help_new] + help_text=[character(len=widest) :: help_text, help_new] case('fpm ' ) - help_text=[character(len=80) :: help_text, help_fpm] + help_text=[character(len=widest) :: help_text, help_fpm] case('version' ) - help_text=[character(len=80) :: help_text, version_text] - case('all ' ) - help_text=[character(len=80) :: help_text, help_fpm] - help_text=[character(len=80) :: help_text, help_new] - help_text=[character(len=80) :: help_text, help_build] - help_text=[character(len=80) :: help_text, help_run] - help_text=[character(len=80) :: help_text, help_test] - help_text=[character(len=80) :: help_text, version_text] + help_text=[character(len=widest) :: help_text, version_text] + case('manual ' ) + help_text=[character(len=widest) :: help_text, help_fpm] + help_text=[character(len=widest) :: help_text, help_new] + help_text=[character(len=widest) :: help_text, help_build] + help_text=[character(len=widest) :: help_text, help_run] + help_text=[character(len=widest) :: help_text, help_test] + help_text=[character(len=widest) :: help_text, help_help] + help_text=[character(len=widest) :: help_text, version_text] case default - help_text=[character(len=80) :: help_text, 'unknown subcommand'//unnamed(i)] + help_text=[character(len=widest) :: help_text, help_intrinsics( lower( unnamed(i) ) ) ] + if(size(help_text).eq.0)then + help_text=[character(len=widest) :: help_text, & + & 'ERROR: unknown help topic "'//trim(unnamed(i))//'"'] + endif end select enddo write(stderr,'(g0)')(trim(help_text(i)), i=1, size(help_text) ) @@ -204,23 +228,22 @@ contains case default call set_args(' ', help_fpm, version_text) - ! Note: will not get here if --version or --usage or --help is present on commandline + ! Note: will not get here if --version or --usage or --help + ! is present on commandline if(len_trim(cmdarg).eq.0)then write(stderr,'(*(a))')'ERROR: missing subcommand' else - write(stderr,'(*(a))')'ERROR: unknown subcommand [', trim(cmdarg), ']' + write(stderr,'(*(a))')'ERROR: unknown subcommand [', & + & trim(cmdarg), ']' endif - help_text=[character(len=80) :: & - 'USAGE: fpm [ SUBCOMMAND [SUBCOMMAND_OPTIONS] ] | [|--help|--version] ', & - ' Enter "fpm --help" for more information ', & - '' ] - write(stderr,'(g0)')(trim(help_text(i)), i=1, size(help_text) ) + write(stderr,'(g0)')(trim(help_usage(i)), i=1, size(help_usage) ) end select end subroutine get_command_line_settings function is_fortran_name(line) result (lout) - ! determine if a string is a valid Fortran name ignoring trailing spaces (but not leading spaces) + ! determine if a string is a valid Fortran name ignoring trailing spaces + ! (but not leading spaces) character(len=*),parameter :: int='0123456789' character(len=*),parameter :: lower='abcdefghijklmnopqrstuvwxyz' character(len=*),parameter :: upper='ABCDEFGHIJKLMNOPQRSTUVWXYZ' @@ -240,75 +263,75 @@ contains end function is_fortran_name subroutine set_help() + help_usage=[character(len=80) :: & + ' ', & + 'USAGE: fpm [ SUBCOMMAND [SUBCOMMAND_OPTIONS] ] | [|--help|--version]', & + ' ', & + ' where SUBCOMMAND is commonly new|build|run|test|install|help ', & + ' Enter "fpm --help" or "fpm SUBCOMMAND --help" for more ', & + ' information.', & + '' ] help_fpm=[character(len=80) :: & 'NAME', & ' fpm(1) - A Fortran package manager and build system', & 'OS TYPE' ] - select case (get_os_type()) - case (OS_LINUX); help_fpm=[character(len=80) :: help_fpm, " Linux" ] - case (OS_MACOS); help_fpm=[character(len=80) :: help_fpm, " macOS" ] - case (OS_WINDOWS); help_fpm=[character(len=80) :: help_fpm, " Windows" ] - case (OS_CYGWIN); help_fpm=[character(len=80) :: help_fpm, " Cygwin" ] - case (OS_SOLARIS); help_fpm=[character(len=80) :: help_fpm, " Solaris" ] - case (OS_FREEBSD); help_fpm=[character(len=80) :: help_fpm, " FreeBSD" ] - case (OS_UNKNOWN); help_fpm=[character(len=80) :: help_fpm, " Unknown" ] - case default ; help_fpm=[character(len=80) :: help_fpm, " UNKNOWN" ] - end select help_fpm=[character(len=80) :: help_fpm, & - 'SYNOPSIS ', & - ' fpm SUBCOMMAND [SUBCOMMAND_OPTIONS] ', & - ' ', & - ' fpm --help|--version ', & - ' ', & - 'DESCRIPTION ', & - ' fpm is a package manager that helps you create Fortran projects that are ', & - ' optionally dependent on multiple files and other fpm(1) packages. ', & - ' ', & - ' Most significantly fpm(1) lets you pull upon other fpm(1) packages in ', & - ' distributed git(1) repositories as if the packages were a basic part ', & - ' of your default programming environment, as well as letting you share ', & - ' your projects with others in a similar manner. ', & - ' ', & - ' See the fpm(1) repository for a listing of such available projects. ', & - ' ', & - ' All output goes into the directory "build/". ', & - ' ', & - 'SUBCOMMANDS ', & - ' Valid fpm subcommands are: ', & - ' ', & - ' build [--release] [--list] ', & - ' Compile the packages into the "build/" directory. ', & - ' new NAME [--with-executable] [--with-test] ', & - ' Create a new Fortran package directory ', & - ' with sample files ', & - ' run [NAME(s)] [--release] [--list] [-- ARGS] ', & - ' Run the local package binaries. defaults to all ', & - ' binaries for that release. ', & - ' test [NAME(s)] [--release] [--list] [-- ARGS] ', & - ' Run the tests ', & - ' help [NAME(s)] Alternate method for displaying subcommand help ', & - ' ', & - 'SUBCOMMAND OPTIONS ', & - ' --release Builds or runs in release mode (versus debug mode). fpm(1) ', & - ' Defaults to using common compiler debug flags and building ', & - ' in "build/gfortran_debug/". When this flag is present build ', & - ' output goes into "build/gfortran_release/" and common ', & - ' compiler optimization flags are used. ', & - ' --list list candidates instead of building or running them ', & - ' -- ARGS Arguments to pass to executables/tests ', & - ' --help Show this help text and exit. Valid for all subcommands. ', & - ' --version Show version information and exit. Valid for all subcommands.', & - 'EXAMPLES ', & - ' sample commands: ', & - ' ', & - ' fpm build ', & - ' fpm test ', & - ' fpm run ', & - ' fpm new --help ', & - ' fpm new mypackage --with-executable --with-test ', & - ' fpm run myprogram --release -- -x 10 -y 20 --title "my title" ', & - 'SEE ALSO ', & - ' The fpm(1) home page is https://github.com/fortran-lang/fpm ', & + 'SYNOPSIS ', & + ' fpm SUBCOMMAND [SUBCOMMAND_OPTIONS] ', & + ' ', & + ' fpm --help|--version ', & + ' ', & + 'DESCRIPTION ', & + ' fpm(1) is a package manager that helps you create Fortran projects ', & + ' from source. ', & + ' ', & + ' Most significantly fpm(1) lets you pull upon other fpm(1) packages ', & + ' in distributed git(1) repositories as if the packages were a basic ', & + ' part of your default programming environment, as well as letting ', & + ' you share your projects with others in a similar manner. ', & + ' ', & + ' See the fpm(1) repository at https://fortran-lang.org/packages ', & + ' for a listing of such registered projects. ', & + ' ', & + ' All output goes into the directory "build/". ', & + ' ', & + 'SUBCOMMANDS ', & + ' Valid fpm subcommands are: ', & + ' ', & + ' build [--release] [--list] ', & + ' Compile the packages into the "build/" directory. ', & + ' new NAME [--lib] [--app] [--test] ', & + ' Create a new Fortran package directory ', & + ' with sample files ', & + ' run [NAME(s)] [--release] [--list] [-- ARGS] ', & + ' Run the local package binaries. defaults to all ', & + ' binaries for that release. ', & + ' test [NAME(s)] [--release] [--list] [-- ARGS] ', & + ' Run the tests ', & + ' help [NAME(s)] Alternate method for displaying subcommand help ', & + ' ', & + 'SUBCOMMAND OPTIONS ', & + ' --release Builds or runs in release mode (versus debug mode). fpm(1)', & + ' Defaults to using common compiler debug flags and building', & + ' in "build/gfortran_debug/". When this flag is present ', & + ' build output goes into "build/gfortran_release/" and ', & + ' common compiler optimization flags are used. ', & + ' --list list candidates instead of building or running them ', & + ' -- ARGS Arguments to pass to executables/tests ', & + ' --help Show help text and exit. Valid for all subcommands. ', & + ' --version Show version information and exit. Valid for all ', & + ' subcommands. ', & + 'EXAMPLES ', & + ' sample commands: ', & + ' ', & + ' fpm build ', & + ' fpm test ', & + ' fpm run ', & + ' fpm new --help ', & + ' fpm new mypackage --app --test ', & + ' fpm run myprogram --release -- -x 10 -y 20 --title "my title" ', & + 'SEE ALSO ', & + ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & ''] help_run=[character(len=80) :: & 'NAME ', & @@ -345,13 +368,14 @@ contains ' # production version of two applications ', & ' fpm run tst1 test2 -release ', & 'SEE ALSO ', & - ' The fpm(1) home page is https://github.com/fortran-lang/fpm ', & + ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & '' ] help_build=[character(len=80) :: & 'NAME ', & ' build(1) - the fpm(1) subcommand to build a project ', & 'SYNOPSIS ', & ' fpm build [--release]|[-list] ', & + ' ', & ' fpm build --help|--version ', & ' ', & 'DESCRIPTION ', & @@ -380,45 +404,82 @@ contains ' fpm build # build with debug options ', & ' fpm build -release # build with high optimization ', & 'SEE ALSO ', & - ' The fpm(1) home page is https://github.com/fortran-lang/fpm ', & + ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & '' ] + help_help=[character(len=80) :: & 'NAME ', & - ' help(1) - the fpm(1) subcommand to display help ', & + ' help(1) - the fpm(1) subcommand to display help ', & + ' ', & 'SYNOPSIS ', & - ' fpm help [fpm][new][build][run][test][help][version][all] ', & + ' fpm help [fpm] [new] [build] [run] [test] [help] [version] [manual]', & + ' ', & + ' fpm help [fortran|fortrnmanual][FORTRAN_INTRINSIC_NAME] ', & ' ', & 'DESCRIPTION ', & - ' The "fpm help" command is an alternative to the --help parameter ', & - ' on the fpm(1) command and its subcommands. ', & + ' The "fpm help" command is an alternative to the --help parameter ', & + ' on the fpm(1) command and its subcommands. ', & ' ', & 'OPTIONS ', & - ' NAME(s) A list of topic names to display. ', & + ' NAME(s) A list of topic names to display. All the subcommands ', & + ' have their own page (new, build, run, test, ...). ', & + ' ', & + ' The special name "manual" displays all the fpm(1) ', & + ' built-in documentation. ', & ' ', & + ' The default is to display help for the fpm(1) command ', & + ' itself. ', & + ' INTRINSIC(s) In addition, Fortran intrinsics can be described. ', & + ' The special name "fortran" prints a list of available', & + ' topics. "fortranmanual" displays all the built-in ', & + ' fortran documentation. Entries should be in ', & + ' uppercase to avoid conflicts with fpm(1) topics; ', & + ' but can be in lowercase if there is no conflict. ', & 'EXAMPLES ', & + ' Sample usage: ', & + ' ', & + ' fpm help # general fpm(1) command help ', & + ' fpm help version # show program version ', & + ' fpm help new # display help for "new" subcommand ', & + ' fpm help manual # All fpm(1) built-in documentation ', & + ' ', & + ' FORTRAN INTRINSICS ', & + ' Additional general Fortran documentation ', & + ' ', & + ' fpm help SIN COS TAN # selected Fortran Intrinsic help ', & + ' fpm help fortran # index of Fortran documentation ', & + ' fpm help fortranmanual # all Fortran documentation ', & ' ', & - ' fpm help ', & - ' fpm help version ', & - ' fpm all ', & 'SEE ALSO ', & - ' The fpm(1) home page is https://github.com/fortran-lang/fpm ', & + ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & '' ] help_new=[character(len=80) :: & 'NAME ', & ' new(1) - the fpm(1) subcommand to initialize a new project ', & 'SYNOPSIS ', & - ' fpm new NAME [--with-executable] [--with-test] ', & + ' fpm new NAME [--lib] [--app] [--test] [--backfill] ', & ' ', & ' fpm new --help|--version ', & ' ', & 'DESCRIPTION ', & - ' Create a new programming project in a new directory ', & + ' "fpm new" creates a new programming project in a new directory.', & ' ', & - ' The "new" subcommand creates a directory and runs the command ', & - ' "git init" in that directory and makes an example "fpm.toml" ', & - ' file. and src/ directory and a sample module file. It ', & - ' optionally also creates a test/ and app/ directory with ', & - ' trivial example Fortran program sources. ', & + ' The "new" subcommand creates a directory with the specified ', & + ' name and runs the command "git init" in that directory and ', & + ' populates it with an example "fpm.toml" file, a src/, test/, ', & + ' and app/ directory with trivial example Fortran source files ', & + ' and a ".gitignore" file for ignoring the build/ directory ', & + ' (where fpm-generated output will be placed): ', & + ' ', & + ' NAME/ ', & + ' fpm.toml ', & + ' .gitignore ', & + ' src/ ', & + ' NAME.f90 ', & + ' app/ ', & + ' main.f90 ', & + ' test/ ', & + ' main.f90 ', & ' ', & ' Remember to update the information in the sample "fpm.toml" ', & ' file with such information as your name and e-mail address. ', & @@ -428,12 +489,31 @@ contains ' must be a valid Fortran name composed of 1 to 63 ', & ' ASCII alphanumeric characters and underscores, ', & ' starting with a letter. ', & - ' --with-executable additionally create optional directory app/ ', & - ' and placeholder program for "fpm run". ', & - ' --with-test additionally create optional directory test/', & - ' and placeholder program for "fpm test". ', & - ' --help print this help and exit ', & - ' --version print program version information and exit ', & + ' ', & + ' The default is to create all of the src/, app/, and test/ ', & + ' directories. If any of the following options are specified ', & + ' then only specified subdirectories are generated: ', & + ' ', & + ' --lib create directory src/ and a placeholder module ', & + ' named "NAME.f90" for use with subcommand "build". ', & + ' --app create directory app/ and a placeholder main ', & + ' program for use with subcommand "run". ', & + ' --test create directory test/ and a placeholder program ', & + ' for use with the subcommand "test". Note that sans ', & + ' "--lib" it really does not have anything to test. ', & + ' ', & + ' So the default is equivalent to "fpm NAME --lib --app --test". ', & + ' ', & + ' --backfill By default the directory must not exist. If this ', & + ' option is present the directory may pre-exist and ', & + ' only subdirectories and files that do not ', & + ' already exist will be created. For example, if you ', & + ' previously entered "fpm new myname -lib" entering ', & + ' "fpm new myname -backfill" will create the missing ', & + ' app/ and test/ directories and missing programs. ', & + ' ', & + ' --help print this help and exit ', & + ' --version print program version information and exit ', & ' ', & 'EXAMPLES ', & ' Sample use ', & @@ -442,10 +522,10 @@ contains ' cd myproject # Enter the new directory ', & ' # and run commands such as ', & ' fpm build ', & - ' fpm run # if you selected --with-executable ', & - ' fpm test # if you selected --with-test ', & + ' fpm run # run example application program ', & + ' fpm test # run example test program ', & 'SEE ALSO ', & - ' The fpm(1) home page is https://github.com/fortran-lang/fpm ', & + ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & ' ', & ' Registered packages are at https://fortran-lang.org/packages ', & '' ] @@ -483,7 +563,7 @@ contains ' ', & ' fpm test tst1 test2 -release # production version of two tests', & 'SEE ALSO ', & - ' The fpm(1) home page is https://github.com/fortran-lang/fpm ', & + ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & '' ] help_install=[character(len=80) :: & ' fpm(1) subcommand "install" ', & |