From 898bf2c648911a016deb24dbf5b707688f6b051c Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Wed, 7 Oct 2020 03:21:33 -0400 Subject: complete new modifications for #109 #110 #111 #135 #138 #154 #196 --- README.md | 2 +- fpm/fpm.toml | 3 + fpm/src/fpm_command_line.f90 | 384 ++++++++++++++++++++++++++----------------- 3 files changed, 236 insertions(+), 153 deletions(-) diff --git a/README.md b/README.md index 48121ea..666ebad 100644 --- a/README.md +++ b/README.md @@ -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" ', & -- cgit v1.2.3 From d845e206f58ba442889db1084842ac830d460e52 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Wed, 7 Oct 2020 08:57:03 -0400 Subject: matching tests --- fpm/test/cli_test/cli_test.f90 | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/fpm/test/cli_test/cli_test.f90 b/fpm/test/cli_test/cli_test.f90 index b0140e1..59f1f7a 100644 --- a/fpm/test/cli_test/cli_test.f90 +++ b/fpm/test/cli_test/cli_test.f90 @@ -41,11 +41,11 @@ character(len=*),parameter :: tests(*)= [ character(len=256) :: & 'CMD="new", ESTAT=1,', & !'CMD="new -unknown", ESTAT=2,', & -'CMD="new my_project another yet_another -with-test", ESTAT=2,', & -'CMD="new my_project --with-executable", W_E=T, NAME="my_project",', & -'CMD="new my_project --with-executable -with-test", W_E=T,W_T=T, NAME="my_project",', & -'CMD="new my_project -with-test", W_T=T, NAME="my_project",', & -'CMD="new my_project", NAME="my_project",', & +'CMD="new my_project another yet_another -test", ESTAT=2,', & +'CMD="new my_project --app", W_E=T, NAME="my_project",', & +'CMD="new my_project --app --test", W_E=T,W_T=T, NAME="my_project",', & +'CMD="new my_project --test", W_T=T, NAME="my_project",', & +'CMD="new my_project", W_E=T,W_T=T, NAME="my_project",', & 'CMD="run", ', & 'CMD="run my_project", NAME="my_project", ', & @@ -91,8 +91,8 @@ if(command_argument_count().eq.0)then ! assume if called with no arguments to d ! blank out name group EXPECTED name=[(repeat(' ',len(name)),i=1,max_names)] ! the words on the command line sans the subcommand name release=.false. ! --release - w_e=.false. ! --with-executable - w_t=.false. ! --with-test + w_e=.false. ! --app + w_t=.false. ! --test args=repeat(' ',132) ! -- ARGS cmd=repeat(' ',132) ! the command line arguments to test cstat=0 ! status values from EXECUTE_COMMAND_LINE() -- cgit v1.2.3 From cd95c91c221b032b46687e713e281bd6a9028cd7 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Wed, 7 Oct 2020 17:13:04 -0400 Subject: rename to M_intrinsics to possibly avoid MSWindows bug or requirement --- fpm/fpm.toml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/fpm/fpm.toml b/fpm/fpm.toml index 03434ec..532e010 100644 --- a/fpm/fpm.toml +++ b/fpm/fpm.toml @@ -15,7 +15,7 @@ git = "https://github.com/urbanjost/M_CLI2.git" rev = "649075aceb97f997665a1a4656514fd2e9b4becc" [dependencies.fortran-intrinsic-manpages] -git = "https://github.com/urbanjost/fortran-intrinsic-manpages.git" +git = "https://github.com/urbanjost/M_intrinsics.git" [[test]] name = "cli-test" -- cgit v1.2.3 From 8c36afbcf6be723bf17f06f1c05aa9a2495b5736 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Thu, 8 Oct 2020 19:33:44 -0400 Subject: push with work-around for gfortran 8 issue --- fpm/src/fpm_command_line.f90 | 1 + 1 file changed, 1 insertion(+) diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index d8c9598..502db99 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -198,6 +198,7 @@ contains help_text=[character(len=widest) :: help_text, help_help] help_text=[character(len=widest) :: help_text, version_text] case default + ! note help_intrinsics is returning a fixed-length array to avoid compiler issues 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, & -- cgit v1.2.3 From e546dfb7d5952abf8331cb9c1c9e687745fdf580 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Fri, 9 Oct 2020 20:53:05 -0400 Subject: missing backfill implementation and only specifying --app on new subcommand --- fpm/src/fpm/cmd/new.f90 | 36 +++++++++++++++++++++++++----------- fpm/src/fpm_command_line.f90 | 18 +++++++++--------- 2 files changed, 34 insertions(+), 20 deletions(-) diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 index 03d9ed4..0293033 100644 --- a/fpm/src/fpm/cmd/new.f90 +++ b/fpm/src/fpm/cmd/new.f90 @@ -16,7 +16,13 @@ character(len=:),allocatable :: bname ! baeename of NAME character(len=:),allocatable :: message(:) character(len=:),allocatable :: littlefile(:) - call mkdir(settings%name) ! make new directory + if(exists(settings%name) .and. .not.settings%backfill )then + write(stderr,'(*(g0,1x))')'fpm::new',settings%name,'already exists.' + write(stderr,'(*(g0,1x))')' perhaps you wanted to add --backfill ?' + return + else + call mkdir(settings%name) ! make new directory + endif call run('cd '//settings%name) ! change to new directory as a test. System dependent potentially !! NOTE: need some system routines to handle filenames like "." like realpath() or getcwd(). bname=basename(settings%name) @@ -89,17 +95,25 @@ character(len=:),allocatable :: littlefile(:) &'main="main.f90" ', & &''] - littlefile=[character(len=80) :: & - &'program main', & - &' use '//bname//', only: say_hello', & - &'', & - &' implicit none', & - &'', & - &' call say_hello', & - &'end program main'] + + if(exists(bname//'/src/'))then + littlefile=[character(len=80) :: & + &'program main', & + &' use '//bname//', only: say_hello', & + &' implicit none', & + &'', & + &' call say_hello()', & + &'end program main'] + else + littlefile=[character(len=80) :: & + &'program main', & + &' implicit none', & + &'', & + &' print *, "hello from project '//bname//'"', & + &'end program main'] + endif call warnwrite(join_path(settings%name, 'app/main.f90'), littlefile) endif - call warnwrite(join_path(settings%name, 'fpm.toml'), message) ! now that built it write NAME/fpm.toml call run('cd ' // settings%name // ';git init') ! assumes these commands work on all systems and git(1) is installed @@ -112,7 +126,7 @@ character(len=*),intent(in) :: data(:) if(.not.exists(fname))then call filewrite(fname,data) else - write(stderr,'(*(g0,1x))')'fpm::new',fname,'already exists. Not overwriting' + write(stderr,'(*(g0,1x))')'fpm::new',fname,'already exists. Not overwriting' endif end subroutine warnwrite diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 502db99..fc76e05 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -123,7 +123,7 @@ contains & list=lget('list') ) case('new') - call set_args(' --lib F --app F --test F -backfill F', & + call set_args(' --lib F --app F --test F --backfill F', & & help_new, version_text) select case(size(unnamed)) case(1) @@ -364,10 +364,10 @@ contains ' fpm run ', & ' ', & ' # run a specific program and pass arguments to the command ', & - ' fpm run mytest -- -x 10 -y 20 -title "my title line" ', & + ' fpm run mytest -- -x 10 -y 20 --title "my title line" ', & ' ', & ' # production version of two applications ', & - ' fpm run tst1 test2 -release ', & + ' fpm run tst1 tst2 --release ', & 'SEE ALSO ', & ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & '' ] @@ -402,8 +402,8 @@ contains 'EXAMPLES ', & ' Sample commands: ', & ' ', & - ' fpm build # build with debug options ', & - ' fpm build -release # build with high optimization ', & + ' fpm build # build with debug options ', & + ' fpm build --release # build with high optimization ', & 'SEE ALSO ', & ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & '' ] @@ -509,8 +509,8 @@ contains ' 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 ', & + ' 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 ', & @@ -560,9 +560,9 @@ contains ' fpm test ', & ' ', & ' # run a specific test and pass arguments to the command ', & - ' fpm test mytest -- -x 10 -y 20 -title "my title line" ', & + ' fpm test mytest -- -x 10 -y 20 --title "my title line" ', & ' ', & - ' fpm test tst1 test2 -release # production version of two tests', & + ' fpm test tst1 tst2 --release # production version of two tests', & 'SEE ALSO ', & ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & '' ] -- cgit v1.2.3 From 22ddc545cec0821e8328a2cb657fee2cc453e9ef Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Fri, 9 Oct 2020 21:54:34 -0400 Subject: tweek documentation --- fpm/src/fpm_command_line.f90 | 488 +++++++++++++++++++++---------------------- 1 file changed, 244 insertions(+), 244 deletions(-) diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index fc76e05..fc08f65 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -74,14 +74,14 @@ contains 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" + 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', & @@ -171,7 +171,7 @@ contains if(size(unnamed).lt.2)then unnamed=['help', 'fpm '] endif - widest=256 + widest=256 allocate(character(len=widest) :: help_text(0)) do i=2,size(unnamed) select case(unnamed(i)) @@ -265,16 +265,16 @@ contains 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 ', & + ' ', & + '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', & + 'NAME ', & + ' fpm(1) - A Fortran package manager and build system ', & 'OS TYPE' ] help_fpm=[character(len=80) :: help_fpm, & 'SYNOPSIS ', & @@ -292,7 +292,7 @@ contains ' 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. ', & + ' for a listing of registered projects. ', & ' ', & ' All output goes into the directory "build/". ', & ' ', & @@ -301,7 +301,7 @@ contains ' ', & ' build [--release] [--list] ', & ' Compile the packages into the "build/" directory. ', & - ' new NAME [--lib] [--app] [--test] ', & + ' new NAME [--lib] [--app] [--test] [--backfill] ', & ' Create a new Fortran package directory ', & ' with sample files ', & ' run [NAME(s)] [--release] [--list] [-- ARGS] ', & @@ -325,251 +325,251 @@ contains 'EXAMPLES ', & ' sample commands: ', & ' ', & + ' fpm new mypackage --app --test ', & ' 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 ', & - ' run(1) - the fpm(1) subcommand to run project applications ', & - ' ', & - 'SYNOPSIS ', & - ' fpm run [NAME(s)] [--release] [-- ARGS] ', & - ' ', & - ' fpm run --help|--version ', & - ' ', & - 'DESCRIPTION ', & - ' Run applications you have built in your fpm(1) project. ', & - ' ', & - 'OPTIONS ', & - ' NAME(s) optional list of specific names to execute. ', & - ' The default is to run all the applications in app/ ', & - ' or the programs listed in the "fpm.toml" file. ', & - ' --release selects the optimized build instead of the debug ', & - ' build. ', & - ' --list list candidates instead of building or running them', & - ' -- ARGS optional arguments to pass to the program(s). ', & - ' The same arguments are passed to all names ', & - ' specified. ', & - ' ', & - 'EXAMPLES ', & - 'run fpm(1) project applications ', & - ' ', & - ' # run default programs in /app or as specified in "fpm.toml" ', & - ' fpm run ', & - ' ', & - ' # run a specific program and pass arguments to the command ', & - ' fpm run mytest -- -x 10 -y 20 --title "my title line" ', & - ' ', & - ' # production version of two applications ', & - ' fpm run tst1 tst2 --release ', & - 'SEE ALSO ', & - ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & + 'NAME ', & + ' run(1) - the fpm(1) subcommand to run project applications ', & + ' ', & + 'SYNOPSIS ', & + ' fpm run [NAME(s)] [--release] [-- ARGS] ', & + ' ', & + ' fpm run --help|--version ', & + ' ', & + 'DESCRIPTION ', & + ' Run applications you have built in your fpm(1) project. ', & + ' ', & + 'OPTIONS ', & + ' NAME(s) optional list of specific names to execute. ', & + ' The default is to run all the applications in app/ ', & + ' or the programs listed in the "fpm.toml" file. ', & + ' --release selects the optimized build instead of the debug ', & + ' build. ', & + ' --list list candidates instead of building or running them ', & + ' -- ARGS optional arguments to pass to the program(s). ', & + ' The same arguments are passed to all names ', & + ' specified. ', & + ' ', & + 'EXAMPLES ', & + ' run fpm(1) project applications ', & + ' ', & + ' # run default programs in /app or as specified in "fpm.toml" ', & + ' fpm run ', & + ' ', & + ' # run a specific program and pass arguments to the command ', & + ' fpm run mytest -- -x 10 -y 20 --title "my title line" ', & + ' ', & + ' # production version of two applications ', & + ' fpm run tst1 tst2 --release ', & + 'SEE ALSO ', & + ' 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 ', & - ' The "fpm build" command ', & - ' o Fetches any dependencies ', & - ' o Scans your sources ', & - ' o Builds them in the proper order ', & - ' ', & - ' The Fortran source files are assumed to be in app/, test/, and src/ ', & - ' by default. The changed or new files found are rebuilt. ', & - ' The results are placed in the build/ directory. ', & - ' ', & - ' Non-default pathnames and remote dependencies are used if ', & - ' specified in the "fpm.toml" file. ', & - ' ', & - 'OPTIONS ', & - ' --release build in build/*_release instead of build/*_debug with ', & - ' high optimization instead of full debug options. ', & - ' --list list candidates instead of building or running them ', & - ' --help print this help and exit ', & - ' --version print program version information and exit ', & - ' ', & - 'EXAMPLES ', & - ' Sample commands: ', & - ' ', & - ' fpm build # build with debug options ', & - ' fpm build --release # build with high optimization ', & - 'SEE ALSO ', & - ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & + 'NAME ', & + ' build(1) - the fpm(1) subcommand to build a project ', & + 'SYNOPSIS ', & + ' fpm build [--release]|[-list] ', & + ' ', & + ' fpm build --help|--version ', & + ' ', & + 'DESCRIPTION ', & + ' The "fpm build" command ', & + ' o Fetches any dependencies ', & + ' o Scans your sources ', & + ' o Builds them in the proper order ', & + ' ', & + ' The Fortran source files are assumed to be in app/, test/, and src/ ', & + ' by default. The changed or new files found are rebuilt. ', & + ' The results are placed in the build/ directory. ', & + ' ', & + ' Non-default pathnames and remote dependencies are used if ', & + ' specified in the "fpm.toml" file. ', & + ' ', & + 'OPTIONS ', & + ' --release build in build/*_release instead of build/*_debug with ', & + ' high optimization instead of full debug options. ', & + ' --list list candidates instead of building or running them ', & + ' --help print this help and exit ', & + ' --version print program version information and exit ', & + ' ', & + 'EXAMPLES ', & + ' Sample commands: ', & + ' ', & + ' fpm build # build with debug options ', & + ' fpm build --release # build with high optimization ', & + 'SEE ALSO ', & + ' 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 ', & - ' ', & - 'SYNOPSIS ', & - ' 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. ', & - ' ', & - 'OPTIONS ', & - ' 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 ', & - ' ', & - 'SEE ALSO ', & - ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & + 'NAME ', & + ' help(1) - the fpm(1) subcommand to display help ', & + ' ', & + 'SYNOPSIS ', & + ' fpm help [fpm] [new] [build] [run] [test] [help] [version] [manual] ', & + ' ', & + ' fpm help [fortran|fortran_manual][FORTRAN_INTRINSIC_NAME] ', & + ' ', & + 'DESCRIPTION ', & + ' 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. 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. "fortran_manual" 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 fortran_manual # all Fortran documentation ', & + ' ', & + 'SEE ALSO ', & + ' 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 [--lib] [--app] [--test] [--backfill] ', & - ' ', & - ' fpm new --help|--version ', & - ' ', & - 'DESCRIPTION ', & - ' "fpm new" creates a new programming project in a new directory.', & - ' ', & - ' 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. ', & - ' ', & - 'OPTIONS ', & - ' NAME the name of the project directory to create. The name ', & - ' must be a valid Fortran name composed of 1 to 63 ', & - ' ASCII alphanumeric characters and underscores, ', & - ' starting with a letter. ', & - ' ', & - ' 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 ', & - ' ', & - ' fpm new myproject # create new project directory and seed it', & - ' cd myproject # Enter the new directory ', & - ' # and run commands such as ', & - ' fpm build ', & - ' fpm run # run example application program ', & - ' fpm test # run example test program ', & - 'SEE ALSO ', & - ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & - ' ', & - ' Registered packages are at https://fortran-lang.org/packages ', & + help_new=[character(len=80) :: & + 'NAME ', & + ' new(1) - the fpm(1) subcommand to initialize a new project ', & + 'SYNOPSIS ', & + ' fpm new NAME [--lib] [--app] [--test] [--backfill] ', & + ' ', & + ' fpm new --help|--version ', & + ' ', & + 'DESCRIPTION ', & + ' "fpm new" creates a new programming project in a new directory .', & + ' ', & + ' 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 your name and e-mail address. ', & + ' ', & + 'OPTIONS ', & + ' NAME the name of the project directory to create. The name ', & + ' must be a valid Fortran name composed of 1 to 63 ', & + ' ASCII alphanumeric characters and underscores, ', & + ' starting with a letter. ', & + ' ', & + ' 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 programs. ', & + ' ', & + ' --help print this help and exit ', & + ' --version print program version information and exit ', & + ' ', & + 'EXAMPLES ', & + ' Sample use ', & + ' ', & + ' fpm new myproject # create new project directory and seed it ', & + ' cd myproject # Enter the new directory ', & + ' # and run commands such as ', & + ' fpm build ', & + ' fpm run # run example application program ', & + ' fpm test # run example test program ', & + 'SEE ALSO ', & + ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & + ' ', & + ' Registered packages are at https://fortran-lang.org/packages ', & '' ] help_test=[character(len=80) :: & - 'NAME ', & - ' test(1) - the fpm(1) subcommand to run project tests ', & - ' ', & - 'SYNOPSIS ', & - ' fpm test [NAME(s)] [--release] [--list] [-- ARGS] ', & - ' ', & - ' fpm test --help|--version ', & - ' ', & - 'DESCRIPTION ', & - ' Run applications you have built to test your project. ', & - ' ', & - 'OPTIONS ', & - ' NAME(s) optional list of specific test names to execute. ', & - ' The default is to run all the tests in test/ ', & - ' or the tests listed in the "fpm.toml" file. ', & - ' --release selects the optimized build instead of the debug ', & - ' build. ', & - ' --list list candidates instead of building or running them', & - ' -- ARGS optional arguments to pass to the test program(s). ', & - ' The same arguments are passed to all test names ', & - ' specified. ', & - ' ', & - 'EXAMPLES ', & - 'run tests ', & - ' ', & - ' # run default tests in /test or as specified in "fpm.toml" ', & - ' fpm test ', & - ' ', & - ' # run a specific test and pass arguments to the command ', & - ' fpm test mytest -- -x 10 -y 20 --title "my title line" ', & - ' ', & - ' fpm test tst1 tst2 --release # production version of two tests', & - 'SEE ALSO ', & - ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & + 'NAME ', & + ' test(1) - the fpm(1) subcommand to run project tests ', & + ' ', & + 'SYNOPSIS ', & + ' fpm test [NAME(s)] [--release] [--list] [-- ARGS] ', & + ' ', & + ' fpm test --help|--version ', & + ' ', & + 'DESCRIPTION ', & + ' Run applications you have built to test your project. ', & + ' ', & + 'OPTIONS ', & + ' NAME(s) optional list of specific test names to execute. ', & + ' The default is to run all the tests in test/ ', & + ' or the tests listed in the "fpm.toml" file. ', & + ' --release selects the optimized build instead of the debug ', & + ' build. ', & + ' --list list candidates instead of building or running them ', & + ' -- ARGS optional arguments to pass to the test program(s). ', & + ' The same arguments are passed to all test names ', & + ' specified. ', & + ' ', & + 'EXAMPLES ', & + 'run tests ', & + ' ', & + ' # run default tests in /test or as specified in "fpm.toml" ', & + ' fpm test ', & + ' ', & + ' # run a specific test and pass arguments to the command ', & + ' fpm test mytest -- -x 10 -y 20 --title "my title line" ', & + ' ', & + ' fpm test tst1 tst2 --release # production version of two tests ', & + 'SEE ALSO ', & + ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & '' ] help_install=[character(len=80) :: & - ' fpm(1) subcommand "install" ', & - ' ', & - ' Usage: fpm install NAME ', & + ' fpm(1) subcommand "install" ', & + ' ', & + ' Usage: fpm install NAME ', & '' ] end subroutine set_help -- cgit v1.2.3 From 141058116c807cccbcebadde53034a439a33c9be Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Fri, 9 Oct 2020 22:16:38 -0400 Subject: whitespace --- fpm/src/fpm_command_line.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index fc08f65..4f45cb3 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -463,7 +463,7 @@ contains ' fpm new --help|--version ', & ' ', & 'DESCRIPTION ', & - ' "fpm new" creates 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 with the specified ', & ' name and runs the command "git init" in that directory and ', & -- cgit v1.2.3 From a7c1a9c5c1623e45dc26648d584d513553d38617 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sat, 10 Oct 2020 14:56:52 -0400 Subject: second pass at in-line documentation After installing the rust package manager cargo(1) made a second pass at the in-line documentation and added the "line" subcommand, which like "help" is processed entirely within the fpm_command_line.f90 file. --- fpm/src/fpm_command_line.f90 | 127 +++++++++++++++++++++++++++++++++---------- 1 file changed, 98 insertions(+), 29 deletions(-) diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 4f45cb3..59c7d5a 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -5,7 +5,7 @@ use fpm_environment, only : get_os_type, & 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 fpm_filesystem, only : basename, canon_path use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, & & stdout=>output_unit, & & stderr=>error_unit @@ -60,8 +60,9 @@ character(len=ibug),allocatable :: names(:) character(len=:), allocatable :: version_text(:) character(len=:), allocatable :: help_new(:), help_fpm(:), help_run(:), & - & help_test(:), help_build(:), help_usage(:), & - & help_text(:), help_install(:), help_help(:) + & help_test(:), help_build(:), help_usage(:), & + & help_text(:), help_install(:), help_help(:), & + & help_list(:), help_list_dash(:), help_list_nodash(:) contains subroutine get_command_line_settings(cmd_settings) @@ -139,7 +140,8 @@ contains & 'usage: fpm new NAME [--lib] [--app] [--test] [--backfill]' stop 2 end select - + !! canon_path is not converting ".", etc. + name=canon_path(name) if( .not.is_fortran_name(basename(name)) )then write(stderr,'(g0)') [ character(len=72) :: & & 'ERROR: the new directory basename must be an allowed ', & @@ -187,6 +189,8 @@ contains help_text=[character(len=widest) :: help_text, help_new] case('fpm ' ) help_text=[character(len=widest) :: help_text, help_fpm] + case('list ' ) + help_text=[character(len=widest) :: help_text, help_list] case('version' ) help_text=[character(len=widest) :: help_text, version_text] case('manual ' ) @@ -198,21 +202,28 @@ contains help_text=[character(len=widest) :: help_text, help_help] help_text=[character(len=widest) :: help_text, version_text] case default - ! note help_intrinsics is returning a fixed-length array to avoid compiler issues - help_text=[character(len=widest) :: help_text, help_intrinsics( lower( unnamed(i) ) ) ] + ! note help_intrinsics is returning a fixed-length array + ! to avoid compiler issues + 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) ) + call printhelp(help_text) case('install') call set_args('--release F ', help_install, version_text) allocate(fpm_install_settings :: cmd_settings) - + case('list') + call set_args(' --list F', help_list, version_text) + call printhelp(help_list_nodash) + if(lget('list'))then + call printhelp(help_list_dash) + endif case('test') call set_args('--list F --release F --',help_test,version_text) @@ -228,18 +239,27 @@ contains case default - call set_args(' ', help_fpm, version_text) + call set_args(' --list F', help_fpm, version_text) ! 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' + help_text=help_usage + if(lget('list'))then + help_text=help_list_dash + elseif(len_trim(cmdarg).eq.0)then + write(stderr,'(*(a))')'ERROR: missing subcommand. Must be one of' + call printhelp(help_list_nodash) else write(stderr,'(*(a))')'ERROR: unknown subcommand [', & & trim(cmdarg), ']' endif - write(stderr,'(g0)')(trim(help_usage(i)), i=1, size(help_usage) ) + call printhelp(help_text) end select + contains + subroutine printhelp(lines) + character(len=:),intent(in),allocatable :: lines(:) + write(stdout,'(g0)')(trim(lines(i)), i=1, size(lines) ) + end subroutine printhelp end subroutine get_command_line_settings function is_fortran_name(line) result (lout) @@ -264,13 +284,32 @@ contains end function is_fortran_name subroutine set_help() + help_list_nodash=[character(len=80) :: & + ' ', & + ' build Compile the package placing results in the "build" directory', & + ' help Display help ', & + ' list Display this list of subcommand descriptions ', & + ' new Create a new Fortran package directory with sample files ', & + ' run Run the local package application programs ', & + ' test Run the test programs ', & + ' '] + help_list_dash = [character(len=80) :: & + ' ', & + ' build [--release] [--list] ', & + ' help [NAME(s)] ', & + ' new NAME [--lib] [--app] [--test] [--backfill] ', & + ' list [--list] ', & + ' run [NAME(s)] [--release] [--list] [-- ARGS] ', & + ' test [NAME(s)] [--release] [--list] [-- ARGS] ', & + ' '] help_usage=[character(len=80) :: & ' ', & - 'USAGE: fpm [ SUBCOMMAND [SUBCOMMAND_OPTIONS] ] | [|--help|--version] ', & + 'USAGE: fpm [ SUBCOMMAND [SUBCOMMAND_OPTIONS] ] | [--help|--version] ', & + ' where SUBCOMMAND is commonly new|build|run|test ', & ' ', & - ' where SUBCOMMAND is commonly new|build|run|test|install|help ', & - ' Enter "fpm --help" or "fpm SUBCOMMAND --help" for more ', & - ' information.', & + ' Enter "fpm list " or "fpm --list" for a full list of ', & + ' subcommands. Enter "fpm --help" or "fpm SUBCOMMAND --help" ', & + ' for detailed command information. ', & '' ] help_fpm=[character(len=80) :: & 'NAME ', & @@ -294,7 +333,9 @@ contains ' See the fpm(1) repository at https://fortran-lang.org/packages ', & ' for a listing of registered projects. ', & ' ', & - ' All output goes into the directory "build/". ', & + ' All output goes into the directory "build/" which can generally be ', & + ' removed and rebuilt if required. Note that if external packages are ', & + ' being used you need network connectivity to rebuild from scratch. ', & ' ', & 'SUBCOMMANDS ', & ' Valid fpm subcommands are: ', & @@ -310,13 +351,14 @@ contains ' test [NAME(s)] [--release] [--list] [-- ARGS] ', & ' Run the tests ', & ' help [NAME(s)] Alternate method for displaying subcommand help ', & + ' list [--list] Display brief descriptions of all subcommands. ', & ' ', & '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. ', & + ' in "build/*_debug/". When this flag is present build ', & + ' output goes into "build/*_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. ', & @@ -334,9 +376,33 @@ contains 'SEE ALSO ', & ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & ''] + help_list=[character(len=80) :: & + 'NAME ', & + ' list(1) - list summary of fpm(1) subcommands ', & + ' ', & + 'SYNOPSIS ', & + ' fpm list [-list] ', & + ' ', & + ' fpm run --help|--version ', & + ' ', & + 'DESCRIPTION ', & + ' Display a short description for each fpm(1) subcommand. ', & + ' ', & + 'OPTIONS ', & + ' --list display a list of command options as well. This is the ', & + ' same output as generated by "fpm --list". ', & + ' ', & + 'EXAMPLES ', & + ' display a short list of fpm(1) subcommands ', & + ' ', & + ' fpm list ', & + ' fpm --list ', & + 'SEE ALSO ', & + ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & + '' ] help_run=[character(len=80) :: & 'NAME ', & - ' run(1) - the fpm(1) subcommand to run project applications ', & + ' run(1) - the fpm(1) subcommand to run project applications ', & ' ', & 'SYNOPSIS ', & ' fpm run [NAME(s)] [--release] [-- ARGS] ', & @@ -366,14 +432,14 @@ contains ' # run a specific program and pass arguments to the command ', & ' fpm run mytest -- -x 10 -y 20 --title "my title line" ', & ' ', & - ' # production version of two applications ', & - ' fpm run tst1 tst2 --release ', & + ' # run production version of two applications ', & + ' fpm run prg1 prg2 --release ', & 'SEE ALSO ', & ' 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 ', & + ' build(1) - the fpm(1) subcommand to build a project ', & 'SYNOPSIS ', & ' fpm build [--release]|[-list] ', & ' ', & @@ -385,9 +451,12 @@ contains ' o Scans your sources ', & ' o Builds them in the proper order ', & ' ', & - ' The Fortran source files are assumed to be in app/, test/, and src/ ', & - ' by default. The changed or new files found are rebuilt. ', & - ' The results are placed in the build/ directory. ', & + ' The Fortran source files are assumed by default to be in ', & + ' o src/ for modules and procedure source ', & + ' o app/ main program(s) for applications ', & + ' o test/ main program(s) and support files for project tests ', & + ' Changed or new files found are rebuilt. The results are placed in ', & + ' the build/ directory. ', & ' ', & ' Non-default pathnames and remote dependencies are used if ', & ' specified in the "fpm.toml" file. ', & @@ -456,7 +525,7 @@ contains '' ] help_new=[character(len=80) :: & 'NAME ', & - ' new(1) - the fpm(1) subcommand to initialize a new project ', & + ' new(1) - the fpm(1) subcommand to initialize a new project ', & 'SYNOPSIS ', & ' fpm new NAME [--lib] [--app] [--test] [--backfill] ', & ' ', & @@ -532,7 +601,7 @@ contains '' ] help_test=[character(len=80) :: & 'NAME ', & - ' test(1) - the fpm(1) subcommand to run project tests ', & + ' test(1) - the fpm(1) subcommand to run project tests ', & ' ', & 'SYNOPSIS ', & ' fpm test [NAME(s)] [--release] [--list] [-- ARGS] ', & -- cgit v1.2.3 From c2e6a119719d6e6be485b3fe864b3fd896262316 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sat, 10 Oct 2020 23:31:13 -0400 Subject: beta test of new subcommand --- fpm/fpm.toml | 5 + fpm/src/fpm_command_line.f90 | 70 ++++++----- fpm/test/new_test/new_test.f90 | 277 +++++++++++++++++++++++++++++++++++++++++ 3 files changed, 322 insertions(+), 30 deletions(-) create mode 100644 fpm/test/new_test/new_test.f90 diff --git a/fpm/fpm.toml b/fpm/fpm.toml index 532e010..8b4d8a3 100644 --- a/fpm/fpm.toml +++ b/fpm/fpm.toml @@ -22,6 +22,11 @@ name = "cli-test" source-dir = "test/cli_test" main = "cli_test.f90" +[[test]] +name = "new-test" +source-dir = "test/new_test" +main = "new_test.f90" + [[test]] name = "fpm-test" source-dir = "test/fpm_test" diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 59c7d5a..671d17f 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -124,20 +124,20 @@ contains & list=lget('list') ) case('new') - call set_args(' --lib F --app F --test F --backfill F', & + call set_args(' --src F --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,'(*(7x,g0,/))') & - & 'usage: fpm new NAME [--lib] [--app] [--test] [--backfill]' + & 'usage: fpm new NAME [--lib|--src] [--app] [--test] [--backfill]' stop 1 case(2) name=trim(unnamed(2)) case default write(stderr,'(g0)')'ERROR: only one directory name allowed' write(stderr,'(7x,g0)') & - & 'usage: fpm new NAME [--lib] [--app] [--test] [--backfill]' + & 'usage: fpm new NAME [--lib|--src] [--app] [--test] [--backfill]' stop 2 end select !! canon_path is not converting ".", etc. @@ -154,11 +154,11 @@ contains allocate(fpm_new_settings :: cmd_settings) - if (any( specified(['lib ','app ','test']) ) )then - cmd_settings=fpm_new_settings(name=name, & - & with_executable=lget('app'), & - & with_test=lget('test'), & - & with_lib=lget('lib'), & + if (any( specified(['src ','lib ','app ','test']) ) )then + cmd_settings=fpm_new_settings(name=name, & + & with_executable=lget('app'), & + & with_test=lget('test'), & + & with_lib=any([lget('lib'),lget('src')]), & & backfill=lget('backfill') ) else cmd_settings=fpm_new_settings(name=name, & @@ -246,7 +246,9 @@ contains if(lget('list'))then help_text=help_list_dash elseif(len_trim(cmdarg).eq.0)then - write(stderr,'(*(a))')'ERROR: missing subcommand. Must be one of' + write(stdout,'(*(a))')'Fortran Package Manager:' + write(stdout,'(*(a))')' ' + write(stdout,'(*(a))')' subcommand may be one of' call printhelp(help_list_nodash) else write(stderr,'(*(a))')'ERROR: unknown subcommand [', & @@ -297,7 +299,7 @@ contains ' ', & ' build [--release] [--list] ', & ' help [NAME(s)] ', & - ' new NAME [--lib] [--app] [--test] [--backfill] ', & + ' new NAME [--lib|--src] [--app] [--test] [--backfill] ', & ' list [--list] ', & ' run [NAME(s)] [--release] [--list] [-- ARGS] ', & ' test [NAME(s)] [--release] [--list] [-- ARGS] ', & @@ -314,8 +316,7 @@ contains help_fpm=[character(len=80) :: & 'NAME ', & ' fpm(1) - A Fortran package manager and build system ', & - 'OS TYPE' ] - help_fpm=[character(len=80) :: help_fpm, & + ' ', & 'SYNOPSIS ', & ' fpm SUBCOMMAND [SUBCOMMAND_OPTIONS] ', & ' ', & @@ -342,7 +343,7 @@ contains ' ', & ' build [--release] [--list] ', & ' Compile the packages into the "build/" directory. ', & - ' new NAME [--lib] [--app] [--test] [--backfill] ', & + ' new NAME [--lib|--src] [--app] [--test] [--backfill] ', & ' Create a new Fortran package directory ', & ' with sample files ', & ' run [NAME(s)] [--release] [--list] [-- ARGS] ', & @@ -364,6 +365,7 @@ contains ' --help Show help text and exit. Valid for all subcommands. ', & ' --version Show version information and exit. Valid for all ', & ' subcommands. ', & + ' ', & 'EXAMPLES ', & ' sample commands: ', & ' ', & @@ -373,6 +375,7 @@ contains ' fpm run ', & ' fpm new --help ', & ' 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 ', & ''] @@ -397,6 +400,7 @@ contains ' ', & ' fpm list ', & ' fpm --list ', & + ' ', & 'SEE ALSO ', & ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & '' ] @@ -434,12 +438,14 @@ contains ' ', & ' # run production version of two applications ', & ' fpm run prg1 prg2 --release ', & + ' ', & 'SEE ALSO ', & ' 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] ', & ' ', & @@ -473,6 +479,7 @@ contains ' ', & ' fpm build # build with debug options ', & ' fpm build --release # build with high optimization ', & + ' ', & 'SEE ALSO ', & ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & '' ] @@ -505,6 +512,7 @@ contains ' 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: ', & ' ', & @@ -527,7 +535,7 @@ contains 'NAME ', & ' new(1) - the fpm(1) subcommand to initialize a new project ', & 'SYNOPSIS ', & - ' fpm new NAME [--lib] [--app] [--test] [--backfill] ', & + ' fpm new NAME [--lib|--src] [--app] [--test] [--backfill] ', & ' ', & ' fpm new --help|--version ', & ' ', & @@ -564,26 +572,26 @@ contains ' 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. ', & + ' --lib,--src 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 programs. ', & + ' --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 programs. ', & ' ', & - ' --help print this help and exit ', & - ' --version print program version information and exit ', & + ' --help print this help and exit ', & + ' --version print program version information and exit ', & ' ', & 'EXAMPLES ', & ' Sample use ', & @@ -594,6 +602,7 @@ contains ' fpm build ', & ' fpm run # run example application program ', & ' fpm test # run example test program ', & + ' ', & 'SEE ALSO ', & ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & ' ', & @@ -632,6 +641,7 @@ contains ' fpm test mytest -- -x 10 -y 20 --title "my title line" ', & ' ', & ' fpm test tst1 tst2 --release # production version of two tests ', & + ' ', & 'SEE ALSO ', & ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & '' ] diff --git a/fpm/test/new_test/new_test.f90 b/fpm/test/new_test/new_test.f90 new file mode 100644 index 0000000..3fdf159 --- /dev/null +++ b/fpm/test/new_test/new_test.f90 @@ -0,0 +1,277 @@ +program new_test +use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit +use fpm_filesystem, only : is_dir, list_files, exists +use fpm_strings, only : string_t +use fpm_environment, only : run, get_os_type +use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_WINDOWS +type(string_t), allocatable :: file_names(:) +character(len=:), allocatable :: directory +integer :: i, j, k +character(len=*),parameter :: cmdpath = 'build/gfortran_debug/app/fpm' +character(len=:),allocatable :: path +character(len=*),parameter :: cmds(*) = [character(len=80) :: & +' new', & +' new no-no', & +' new A', & +' new B --lib', & +' new C --app', & +' new D --test', & +' new E --lib --test ', & +' new F --lib --app', & +' new G --test --app', & +' new BB --lib', & +' new BB --test ', & +' new BB --backfill --test', & +' new CC --test --src --app', & +' new --version', & +' new --help'] +integer :: estat, cstat +character(len=256) :: message +character(len=:),allocatable :: directories(:) +character(len=:),allocatable :: expected(:) +logical,allocatable :: tally(:) + write(*,'(g0:,1x)')'TEST new SUBCOMMAND (draft):' + allocate(tally(0)) + directories=[character(len=80) :: 'A','B','C','D','E','F','G','BB','CC'] + + do i=1,size(directories) + if( is_dir(trim(directories(i))) ) then + write(*,*)'ERROR:',trim( directories(i) ),' already exists' + write(*,*)' you must remove scratch directories before performing this test' + write(*,'(*(g0:,1x))')'directories:',(trim(directories(j)),j=1,size(directories)),'no-no' + stop + endif + enddo + + !! SEE IF EXPECTED FILES ARE GENERATED + !! DOS versus POSIX filenames + ! assuming fpm command is in path and the new version + select case (get_os_type()) + case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD) + path=cmdpath + case (OS_WINDOWS) + path=u2d(cmdpath) + case default + write(*,*)'ERROR: unknown OS. Stopping test' + stop 2 + end select + + + do i=1,size(cmds) + message='' + call execute_command_line(cmdpath//''//cmds(i),exitstat=estat,cmdstat=cstat,cmdmsg=message) + write(*,'(*(g0))')'CMD=',trim(cmds(i)),' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message) + enddo + + if( is_dir('no-no') ) then + tally=[tally,.false.] + write(*,*)'ERROR: directory no-no/ exists' + else + tally=[tally,.true.] + endif + + ! assuming hidden files in .git and .gitignore are ignored for now + TESTS: do i=1,size(directories) + ! test if expected directory exists + if( .not. is_dir(trim(directories(i))) ) then + tally=[tally,.false.] + write(*,*)'ERROR:',trim( directories(i) ),' is not a directory' + else + select case(directories(i)) + case('A') + expected=[ character(len=80)::& + &'A/app','A/fpm.toml','A/README.md','A/src','A/test','A/app/main.f90','A/src/A.f90','A/test/main.f90'] + case('B') + expected=[ character(len=80)::& + &'B/fpm.toml','B/README.md','B/src','B/src/B.f90'] + case('C') + expected=[ character(len=80)::& + &'C/app','C/fpm.toml','C/README.md','C/app/main.f90'] + case('D') + expected=[ character(len=80)::& + &'D/fpm.toml','D/README.md','D/test','D/test/main.f90'] + case('E') + expected=[ character(len=80)::& + &'E/fpm.toml','E/README.md','E/src','E/test','E/src/E.f90','E/test/main.f90'] + case('F') + expected=[ character(len=80)::& + &'F/app','F/fpm.toml','F/README.md','F/src','F/app/main.f90','F/src/F.f90'] + case('G') + expected=[ character(len=80)::& + &'G/app','G/fpm.toml','G/README.md','G/test','G/app/main.f90','G/test/main.f90'] + case('BB') + expected=[ character(len=80)::& + &'BB/fpm.toml','BB/README.md','BB/src','BB/test','BB/src/BB.f90','BB/test/main.f90'] + case('CC') + expected=[ character(len=80)::& + &'CC/app','CC/fpm.toml','CC/README.md','CC/src','CC/test','CC/app/main.f90','CC/src/CC.f90','CC/test/main.f90'] + case default + write(*,*)'ERROR: internal error. unknown directory name ',trim(directories(i)) + stop 4 + end select + call list_files(trim(directories(i)), file_names,recurse=.true.) + write(*,'(*(g0))',advance='no')'>>>DIRECTORY ',trim(directories(i)),': ' + write(*,'(*(g0:,", "))')( file_names(j)%s, j=1,size(file_names) ) + if(size(expected).ne.size(file_names))then + write(*,*)'unexpected number of files in file list=',size(file_names),' expected ',size(directories) + tally=[tally,.false.] + cycle TESTS + else + select case (get_os_type()) + case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD) + case (OS_WINDOWS) + do j=1,size(expected) + expected(j)=u2d(expected(j)) + enddo + case default + write(*,*)'ERROR: unknown OS. Stopping test' + stop 3 + end select + do j=1,size(expected) + if( .not.any(file_names(j)%s==expected) )then + tally=[tally,.false.] + write(*,'("ERROR: EXPECTED ",*(g0:,", "))')( trim(expected(k)), k=1,size(expected) ) + write(*,'(*(g0))')' NO MATCH FOR ',file_names(j)%s + cycle TESTS + endif + enddo + tally=[tally,.true.] + endif + endif + enddo TESTS + write(*,'("TALLY=",*(g0))')tally + if(all(tally))then + write(*,'(*(g0))')'PASSED: all ',count(tally),' tests passed ' + else + write(*,*)'FAILED: PASSED=',count(tally),' FAILED=',count(.not.tally) + stop 5 + endif +!----------------------------------------------------------------------------------------------------------------------------------- +contains +!----------------------------------------------------------------------------------------------------------------------------------- +function u2d(pathname) result(dos) +! simplistically replace / with \ to make posix pathname DOS pathname +character(len=*),intent(in) :: pathname +character(len=:),allocatable :: dos +integer :: i +dos=pathname +do i=1,len(pathname) + if(pathname(i:i).eq.'/')dos(i:i)='\' +enddo +end function u2d +!----------------------------------------------------------------------------------------------------------------------------------- +function djb2_hash_arr(chars,continue) result(hash_128) +use,intrinsic :: ISO_FORTRAN_ENV, only : int8,int16,int32,int64 +implicit none + +!$@(#) djb2_hash(3fp): DJB2 hash of array (algorithm by Daniel J. Bernstein ) for character array + +character(len=1),intent(in) :: chars(:) +logical,intent(in),optional :: continue +integer :: i +integer(kind=int64) :: hash_128 +integer(kind=int64),save :: hash_64=5381 + + if(present(continue))then + hash_64 = hash_64 + else + hash_64 = 5381_int64 + endif + do i=1,size(chars) + hash_64 = (ishft(hash_64,5) + hash_64) + ichar(chars(i),kind=int64) + enddo + hash_128=transfer([hash_64,0_int64],hash_128) + DEBUG : block + integer :: ios + write(6,'("*djb2_hash* hashing string=",*(a))',advance='no')chars + write(6,'(1x,"hash=",i0,1x,"hex hash=",z32.32)')hash_128,hash_128 + flush(6,iostat=ios) + endblock DEBUG +end function djb2_hash_arr +!----------------------------------------------------------------------------------------------------------------------------------- +subroutine slurp(filename,text,length,lines) +use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit +implicit none + +!$@(#) M_io::slurp(3f): allocate text array and read file filename into it + +class(*),intent(in) :: filename ! filename to shlep +character(len=1),allocatable,intent(out) :: text(:) ! array to hold file +integer,intent(out),optional :: length ! length of longest line +integer,intent(out),optional :: lines ! number of lines + +integer :: nchars=0 ! holds size of file +integer :: igetunit ! use newunit=igetunit in f08 +integer :: ios=0 ! used for I/O error status +integer :: length_local +integer :: lines_local +integer :: i +integer :: icount +character(len=256) :: message +character(len=4096) :: local_filename + + length_local=0 + lines_local=0 + + message='' + select type(FILENAME) + type is (character(len=*)) + open(newunit=igetunit, file=trim(filename), action="read", iomsg=message,& + &form="unformatted", access="stream",status='old',iostat=ios) + local_filename=filename + type is (integer) + rewind(unit=filename,iostat=ios,iomsg=message) + write(local_filename,'("unit ",i0)')filename + igetunit=filename + end select + + if(ios.eq.0)then ! if file was successfully opened + + inquire(unit=igetunit, size=nchars) + + if(nchars.le.0)then + call stderr_local( '*slurp* empty file '//trim(local_filename) ) + return + endif + ! read file into text array + ! + if(allocated(text))deallocate(text) ! make sure text array not allocated + allocate ( text(nchars) ) ! make enough storage to hold file + read(igetunit,iostat=ios,iomsg=message) text ! load input file -> text array + if(ios.ne.0)then + call stderr_local( '*slurp* bad read of '//trim(local_filename)//':'//trim(message) ) + endif + else + call stderr_local('*slurp* '//message) + allocate ( text(0) ) ! make enough storage to hold file + endif + + close(iostat=ios,unit=igetunit) ! close if opened successfully or not + + if(present(lines).or.present(length))then ! get length of longest line and number of lines + icount=0 + do i=1,nchars + if(text(i).eq.NEW_LINE('A'))then + lines_local=lines_local+1 + length_local=max(length_local,icount) + icount=0 + endif + icount=icount+1 + enddo + if(nchars.ne.0)then + if(text(nchars).ne.NEW_LINE('A'))then + lines_local=lines_local+1 + length_local=max(length_local,icount) + endif + endif + if(present(lines))lines=lines_local + if(present(length))length=length_local + endif +end subroutine slurp +!----------------------------------------------------------------------------------------------------------------------------------- +subroutine stderr_local(message) +character(len=*) :: message + write(stderr,'(a)')trim(message) ! write message to standard error +end subroutine stderr_local +!----------------------------------------------------------------------------------------------------------------------------------- +end program new_test -- cgit v1.2.3 From fd0df5f7910a6ecfb674ce3e0395a7b3f208cdbb Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 11 Oct 2020 02:52:50 -0400 Subject: DOS pathname for executable --- fpm/test/new_test/new_test.f90 | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/fpm/test/new_test/new_test.f90 b/fpm/test/new_test/new_test.f90 index 3fdf159..5d7f9de 100644 --- a/fpm/test/new_test/new_test.f90 +++ b/fpm/test/new_test/new_test.f90 @@ -59,7 +59,8 @@ logical,allocatable :: tally(:) do i=1,size(cmds) message='' - call execute_command_line(cmdpath//''//cmds(i),exitstat=estat,cmdstat=cstat,cmdmsg=message) + write(*,*)path//' '//cmds(i) + call execute_command_line(path//' '//cmds(i),exitstat=estat,cmdstat=cstat,cmdmsg=message) write(*,'(*(g0))')'CMD=',trim(cmds(i)),' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message) enddo -- cgit v1.2.3 From ffc515af907f7c090f035d5f2d251c6fb88f74c4 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 11 Oct 2020 03:47:20 -0400 Subject: correct for DOS differences --- fpm/test/new_test/new_test.f90 | 16 ++++++++++++---- 1 file changed, 12 insertions(+), 4 deletions(-) diff --git a/fpm/test/new_test/new_test.f90 b/fpm/test/new_test/new_test.f90 index 5d7f9de..2a4d3fe 100644 --- a/fpm/test/new_test/new_test.f90 +++ b/fpm/test/new_test/new_test.f90 @@ -5,6 +5,7 @@ use fpm_strings, only : string_t use fpm_environment, only : run, get_os_type use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_WINDOWS type(string_t), allocatable :: file_names(:) +character(len=:), allocatable :: fnames(:) character(len=:), allocatable :: directory integer :: i, j, k character(len=*),parameter :: cmdpath = 'build/gfortran_debug/app/fpm' @@ -110,11 +111,18 @@ logical,allocatable :: tally(:) write(*,*)'ERROR: internal error. unknown directory name ',trim(directories(i)) stop 4 end select + !! MSwindows has hidden files in it call list_files(trim(directories(i)), file_names,recurse=.true.) + if(allocated(fnames))deallocate(fnames) + allocate(character(len=0) :: fnames(0)) + do j=1,size(file_names) + if(file_names(j)%s(1:1).eq.'.')cycle + fnames=[character(len=max(len(fnames),len(file_names(j)%s))) :: fnames,file_names(j)%s] + enddo write(*,'(*(g0))',advance='no')'>>>DIRECTORY ',trim(directories(i)),': ' write(*,'(*(g0:,", "))')( file_names(j)%s, j=1,size(file_names) ) - if(size(expected).ne.size(file_names))then - write(*,*)'unexpected number of files in file list=',size(file_names),' expected ',size(directories) + if(size(expected).ne.size(fnames))then + write(*,*)'unexpected number of files in file list=',size(fnames),' expected ',size(expected) tally=[tally,.false.] cycle TESTS else @@ -129,10 +137,10 @@ logical,allocatable :: tally(:) stop 3 end select do j=1,size(expected) - if( .not.any(file_names(j)%s==expected) )then + if( .not.any(fnames(j)==expected) )then tally=[tally,.false.] write(*,'("ERROR: EXPECTED ",*(g0:,", "))')( trim(expected(k)), k=1,size(expected) ) - write(*,'(*(g0))')' NO MATCH FOR ',file_names(j)%s + write(*,'(*(g0))')' NO MATCH FOR ',fnames(j) cycle TESTS endif enddo -- cgit v1.2.3 From ad653051402d93544efda095a39372fd922e83b2 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 11 Oct 2020 03:58:43 -0400 Subject: what is cwd? --- fpm/src/fpm/cmd/new.f90 | 20 ++++++++++++++++++++ 1 file changed, 20 insertions(+) diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 index 0293033..a8a8876 100644 --- a/fpm/src/fpm/cmd/new.f90 +++ b/fpm/src/fpm/cmd/new.f90 @@ -23,7 +23,9 @@ character(len=:),allocatable :: littlefile(:) else call mkdir(settings%name) ! make new directory endif + call showcwd('before test') call run('cd '//settings%name) ! change to new directory as a test. System dependent potentially + call showcwd('after test') !! NOTE: need some system routines to handle filenames like "." like realpath() or getcwd(). bname=basename(settings%name) @@ -116,9 +118,27 @@ character(len=:),allocatable :: littlefile(:) endif call warnwrite(join_path(settings%name, 'fpm.toml'), message) ! now that built it write NAME/fpm.toml + call showcwd('before init') call run('cd ' // settings%name // ';git init') ! assumes these commands work on all systems and git(1) is installed + call showcwd('after init') contains +subroutine showcwd(msg) +use fpm_environment, only : run, get_os_type +use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_WINDOWS +character(len=*),intent(in) :: msg + write(*,'(a,1x)',advance='no')msg + select case (get_os_type()) + case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD) + call run('pwd') + case (OS_WINDOWS) + call run('chdir') + case default + write(*,*)'ERROR: unknown OS. Stopping test' + stop 2 + end select +end subroutine showcwd + subroutine warnwrite(fname,data) character(len=*),intent(in) :: fname character(len=*),intent(in) :: data(:) -- cgit v1.2.3 From e6ee005096650fcbb75d43e2ad08b3515f2f2f42 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 11 Oct 2020 04:24:10 -0400 Subject: DOS Test development --- fpm/test/new_test/new_test.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/fpm/test/new_test/new_test.f90 b/fpm/test/new_test/new_test.f90 index 2a4d3fe..289431e 100644 --- a/fpm/test/new_test/new_test.f90 +++ b/fpm/test/new_test/new_test.f90 @@ -116,7 +116,7 @@ logical,allocatable :: tally(:) if(allocated(fnames))deallocate(fnames) allocate(character(len=0) :: fnames(0)) do j=1,size(file_names) - if(file_names(j)%s(1:1).eq.'.')cycle + if(file_names(j)%s(1:1).eq.'.'.or.index(file_names(j)%s,'/.').ne.0.or.index(file_names(j)%s,'\.').ne.0)cycle fnames=[character(len=max(len(fnames),len(file_names(j)%s))) :: fnames,file_names(j)%s] enddo write(*,'(*(g0))',advance='no')'>>>DIRECTORY ',trim(directories(i)),': ' -- cgit v1.2.3 From 0678a9a8cdd88a2df4764db5b438f4c24dc6beac Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 11 Oct 2020 04:56:15 -0400 Subject: mkdir on dos of existing directory stops program on unix/linux it does not --- fpm/src/fpm/cmd/new.f90 | 22 ++-------------------- 1 file changed, 2 insertions(+), 20 deletions(-) diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 index a8a8876..6435e11 100644 --- a/fpm/src/fpm/cmd/new.f90 +++ b/fpm/src/fpm/cmd/new.f90 @@ -20,12 +20,12 @@ character(len=:),allocatable :: littlefile(:) write(stderr,'(*(g0,1x))')'fpm::new',settings%name,'already exists.' write(stderr,'(*(g0,1x))')' perhaps you wanted to add --backfill ?' return + elseif(exists(settings%name) .and. settings%backfill )then + write(*,'(*(g0))')'backfilling ',settings%name else call mkdir(settings%name) ! make new directory endif - call showcwd('before test') call run('cd '//settings%name) ! change to new directory as a test. System dependent potentially - call showcwd('after test') !! NOTE: need some system routines to handle filenames like "." like realpath() or getcwd(). bname=basename(settings%name) @@ -118,27 +118,9 @@ character(len=:),allocatable :: littlefile(:) endif call warnwrite(join_path(settings%name, 'fpm.toml'), message) ! now that built it write NAME/fpm.toml - call showcwd('before init') call run('cd ' // settings%name // ';git init') ! assumes these commands work on all systems and git(1) is installed - call showcwd('after init') contains -subroutine showcwd(msg) -use fpm_environment, only : run, get_os_type -use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_WINDOWS -character(len=*),intent(in) :: msg - write(*,'(a,1x)',advance='no')msg - select case (get_os_type()) - case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD) - call run('pwd') - case (OS_WINDOWS) - call run('chdir') - case default - write(*,*)'ERROR: unknown OS. Stopping test' - stop 2 - end select -end subroutine showcwd - subroutine warnwrite(fname,data) character(len=*),intent(in) :: fname character(len=*),intent(in) :: data(:) -- cgit v1.2.3 From a5162c09c6f6ff900ae1f23a9946c2e3b19c5e5c Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 11 Oct 2020 05:10:56 -0400 Subject: whitespace --- fpm/src/fpm/cmd/new.f90 | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 index 6435e11..ce00357 100644 --- a/fpm/src/fpm/cmd/new.f90 +++ b/fpm/src/fpm/cmd/new.f90 @@ -17,13 +17,13 @@ character(len=:),allocatable :: message(:) character(len=:),allocatable :: littlefile(:) if(exists(settings%name) .and. .not.settings%backfill )then - write(stderr,'(*(g0,1x))')'fpm::new',settings%name,'already exists.' - write(stderr,'(*(g0,1x))')' perhaps you wanted to add --backfill ?' - return + write(stderr,'(*(g0,1x))')'fpm::new',settings%name,'already exists.' + write(stderr,'(*(g0,1x))')' perhaps you wanted to add --backfill ?' + return elseif(exists(settings%name) .and. settings%backfill )then - write(*,'(*(g0))')'backfilling ',settings%name + write(*,'(*(g0))')'backfilling ',settings%name else - call mkdir(settings%name) ! make new directory + call mkdir(settings%name) ! make new directory endif call run('cd '//settings%name) ! change to new directory as a test. System dependent potentially !! NOTE: need some system routines to handle filenames like "." like realpath() or getcwd(). @@ -126,9 +126,9 @@ character(len=*),intent(in) :: fname character(len=*),intent(in) :: data(:) if(.not.exists(fname))then - call filewrite(fname,data) + call filewrite(fname,data) else - write(stderr,'(*(g0,1x))')'fpm::new',fname,'already exists. Not overwriting' + write(stderr,'(*(g0,1x))')'fpm::new',fname,'already exists. Not overwriting' endif end subroutine warnwrite -- cgit v1.2.3 From 70ae232ecbcfca102babe2b1fbdb08f4b14236b1 Mon Sep 17 00:00:00 2001 From: urbanjost Date: Sun, 11 Oct 2020 05:22:43 -0400 Subject: Update fpm/src/fpm/cmd/new.f90 Co-authored-by: Laurence Kedward --- fpm/src/fpm/cmd/new.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 index ce00357..dce13bc 100644 --- a/fpm/src/fpm/cmd/new.f90 +++ b/fpm/src/fpm/cmd/new.f90 @@ -118,7 +118,7 @@ character(len=:),allocatable :: littlefile(:) endif call warnwrite(join_path(settings%name, 'fpm.toml'), message) ! now that built it write NAME/fpm.toml - call run('cd ' // settings%name // ';git init') ! assumes these commands work on all systems and git(1) is installed + call run('cd ' // settings%name // '&&git init') ! assumes these commands work on all systems and git(1) is installed contains subroutine warnwrite(fname,data) -- cgit v1.2.3 From 79214e63fef965eeb03a5c38226aa55ea22315d9 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 11 Oct 2020 05:25:45 -0400 Subject: change cd NEWNAME;git init to cd NEWNAME &&git init per @LKedward --- fpm/src/fpm/cmd/new.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 index ce00357..dce13bc 100644 --- a/fpm/src/fpm/cmd/new.f90 +++ b/fpm/src/fpm/cmd/new.f90 @@ -118,7 +118,7 @@ character(len=:),allocatable :: littlefile(:) endif call warnwrite(join_path(settings%name, 'fpm.toml'), message) ! now that built it write NAME/fpm.toml - call run('cd ' // settings%name // ';git init') ! assumes these commands work on all systems and git(1) is installed + call run('cd ' // settings%name // '&&git init') ! assumes these commands work on all systems and git(1) is installed contains subroutine warnwrite(fname,data) -- cgit v1.2.3 From 07667934b065ca61a5db38882a1bf8933e96317f Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 11 Oct 2020 06:10:52 -0400 Subject: check if name is a directory on backfill instead of depending on system command --- fpm/src/fpm/cmd/new.f90 | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 index dce13bc..757274e 100644 --- a/fpm/src/fpm/cmd/new.f90 +++ b/fpm/src/fpm/cmd/new.f90 @@ -2,7 +2,7 @@ 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 +use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir use,intrinsic :: iso_fortran_env, only : stderr=>error_unit implicit none private @@ -20,8 +20,11 @@ character(len=:),allocatable :: littlefile(:) write(stderr,'(*(g0,1x))')'fpm::new',settings%name,'already exists.' write(stderr,'(*(g0,1x))')' perhaps you wanted to add --backfill ?' return - elseif(exists(settings%name) .and. settings%backfill )then + elseif(is_dir(settings%name) .and. settings%backfill )then write(*,'(*(g0))')'backfilling ',settings%name + elseif(exists(settings%name) )then + write(stderr,'(*(g0,1x))')'fpm::new',settings%name,'already exists and is not a directory.' + return else call mkdir(settings%name) ! make new directory endif -- cgit v1.2.3 From a1318c35ca35a962852de5ff17a44c76b310946e Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 11 Oct 2020 18:20:50 -0400 Subject: simplify initializing git(1) repository --- fpm/.gitignore | 2 +- fpm/src/fpm/cmd/new.f90 | 104 ++++++++++++++++++++++++++++++------------------ 2 files changed, 67 insertions(+), 39 deletions(-) diff --git a/fpm/.gitignore b/fpm/.gitignore index c602557..7e96036 100644 --- a/fpm/.gitignore +++ b/fpm/.gitignore @@ -1,2 +1,2 @@ build/* -*/FODDER/* +FODDER/* diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 index 757274e..f57b948 100644 --- a/fpm/src/fpm/cmd/new.f90 +++ b/fpm/src/fpm/cmd/new.f90 @@ -10,38 +10,50 @@ public :: cmd_new contains -subroutine cmd_new(settings) ! --with-executable F --with-test F ' +subroutine cmd_new(settings) type(fpm_new_settings), intent(in) :: settings character(len=:),allocatable :: bname ! baeename of NAME character(len=:),allocatable :: message(:) character(len=:),allocatable :: littlefile(:) if(exists(settings%name) .and. .not.settings%backfill )then - write(stderr,'(*(g0,1x))')'fpm::new',settings%name,'already exists.' - write(stderr,'(*(g0,1x))')' perhaps you wanted to add --backfill ?' + write(stderr,'(*(g0,1x))')& + & 'ERROR: ',settings%name,'already exists.' + write(stderr,'(*(g0,1x))')& + & ' perhaps you wanted to add --backfill ?' return elseif(is_dir(settings%name) .and. settings%backfill )then write(*,'(*(g0))')'backfilling ',settings%name elseif(exists(settings%name) )then - write(stderr,'(*(g0,1x))')'fpm::new',settings%name,'already exists and is not a directory.' + write(stderr,'(*(g0,1x))')& + & 'ERROR: ',settings%name,'already exists and is not a directory.' return else - call mkdir(settings%name) ! make new directory + ! make new directory + call mkdir(settings%name) endif - call run('cd '//settings%name) ! change to new directory as a test. System dependent potentially - !! NOTE: need some system routines to handle filenames like "." like realpath() or getcwd(). + + ! change to new directory as a test. System dependent potentially + call run('cd '//settings%name) + !! NOTE: need some system routines to handle filenames like "." + !! like realpath() or getcwd(). bname=basename(settings%name) - !! weird gfortran bug?? lines truncated to concatenated string length, not 80 - !! hit some weird gfortran bug when littlefile data was an argument to warnwrite(3f), ok when a variable + !! weird gfortran bug?? lines truncated to concatenated string length, + !! not 80 + !! hit some weird gfortran bug when littlefile data was an argument + !! to warnwrite(3f), ok when a variable - call warnwrite(join_path(settings%name, '.gitignore'), ['build/*']) ! create NAME/.gitignore file + ! create NAME/.gitignore file + call warnwrite(join_path(settings%name, '.gitignore'), ['build/*']) littlefile=[character(len=80) :: '# '//bname, 'My cool new project!'] - call warnwrite(join_path(settings%name, 'README.md'), littlefile) ! create NAME/README.md + ! create NAME/README.md + call warnwrite(join_path(settings%name, 'README.md'), littlefile) - message=[character(len=80) :: & ! start building NAME/fpm.toml + ! start building NAME/fpm.toml + message=[character(len=80) :: & &'name = "'//bname//'" ', & &'version = "0.1.0" ', & &'license = "license" ', & @@ -53,11 +65,13 @@ character(len=:),allocatable :: littlefile(:) if(settings%with_lib)then call mkdir(join_path(settings%name,'src') ) - message=[character(len=80) :: message, & ! create next section of fpm.toml + ! create next section of fpm.toml + message=[character(len=80) :: message, & &'[library] ', & &'source-dir="src" ', & &''] - littlefile=[character(len=80) :: & ! create placeholder module src/bname.f90 + ! create placeholder module src/bname.f90 + littlefile=[character(len=80) :: & &'module '//bname, & &' implicit none', & &' private', & @@ -68,39 +82,44 @@ character(len=:),allocatable :: littlefile(:) &' print *, "Hello, '//bname//'!"', & &' end subroutine say_hello', & &'end module '//bname] - ! a proposed alternative default - call warnwrite(join_path(settings%name, 'src', bname//'.f90'), littlefile) ! create NAME/src/NAME.f90 + ! create NAME/src/NAME.f90 + call warnwrite(join_path(settings%name, 'src', bname//'.f90'),& + & littlefile) endif if(settings%with_test)then - call mkdir(join_path(settings%name, 'test')) ! create NAME/test or stop - message=[character(len=80) :: message, & ! create next section of fpm.toml + + ! create NAME/test or stop + call mkdir(join_path(settings%name, 'test')) + ! create next section of fpm.toml + message=[character(len=80) :: message, & &'[[test]] ', & &'name="runTests" ', & &'source-dir="test" ', & &'main="main.f90" ', & &''] - littlefile=[character(len=80) :: & + littlefile=[character(len=80) :: & &'program main', & &'implicit none', & &'', & &'print *, "Put some tests in here!"', & &'end program main'] - ! a proposed alternative default a little more substantive - call warnwrite(join_path(settings%name, 'test/main.f90'), littlefile) ! create NAME/test/main.f90 + ! create NAME/test/main.f90 + call warnwrite(join_path(settings%name, 'test/main.f90'), littlefile) endif if(settings%with_executable)then - call mkdir(join_path(settings%name, 'app')) ! create NAME/app or stop - message=[character(len=80) :: message, & ! create next section of fpm.toml + ! create next section of fpm.toml + call mkdir(join_path(settings%name, 'app')) + ! create NAME/app or stop + message=[character(len=80) :: message, & &'[[executable]] ', & &'name="'//bname//'" ', & &'source-dir="app" ', & &'main="main.f90" ', & &''] - if(exists(bname//'/src/'))then littlefile=[character(len=80) :: & &'program main', & @@ -119,9 +138,11 @@ character(len=:),allocatable :: littlefile(:) endif call warnwrite(join_path(settings%name, 'app/main.f90'), littlefile) endif - call warnwrite(join_path(settings%name, 'fpm.toml'), message) ! now that built it write NAME/fpm.toml - call run('cd ' // settings%name // '&&git init') ! assumes these commands work on all systems and git(1) is installed + ! now that built it write NAME/fpm.toml + call warnwrite(join_path(settings%name, 'fpm.toml'), message) + ! assumes git(1) is installed and in path + call run('git init ' // settings%name) contains subroutine warnwrite(fname,data) @@ -131,14 +152,17 @@ character(len=*),intent(in) :: data(:) if(.not.exists(fname))then call filewrite(fname,data) else - write(stderr,'(*(g0,1x))')'fpm::new',fname,'already exists. Not overwriting' + write(stderr,'(*(g0,1x))')'INFO: ',fname,& + & 'already exists. Not overwriting' endif end subroutine warnwrite subroutine filewrite(filename,filedata) -use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit -! write filedata to file filename +! procedure to write filedata to file filename +use,intrinsic :: iso_fortran_env, only : & + & stdin=>input_unit, stdout=>output_unit, stderr=>error_unit + character(len=*),intent(in) :: filename character(len=*),intent(in) :: filedata(:) integer :: lun, i, ios @@ -149,11 +173,11 @@ character(len=256) :: message if(filename.ne.' ')then open(file=filename, & & newunit=lun, & - & form='formatted', & ! FORM = FORMATTED | UNFORMATTED - & access='sequential', & ! ACCESS = SEQUENTIAL | DIRECT | STREAM - & action='write', & ! ACTION = READ|WRITE | READWRITE - & position='rewind', & ! POSITION = ASIS | REWIND | APPEND - & status='new', & ! STATUS = NEW | REPLACE | OLD | SCRATCH | UNKNOWN + & form='formatted', & ! FORM = FORMATTED | UNFORMATTED + & access='sequential', & ! ACCESS = SEQUENTIAL| DIRECT | STREAM + & action='write', & ! ACTION = READ|WRITE| READWRITE + & position='rewind', & ! POSITION= ASIS | REWIND | APPEND + & status='new', & ! STATUS = NEW| REPLACE| OLD| SCRATCH| UNKNOWN & iostat=ios, & & iomsg=message) else @@ -161,17 +185,21 @@ character(len=256) :: message ios=0 endif if(ios.ne.0)then - write(stderr,'(*(a:,1x))')'*filewrite* error:',filename,trim(message) + write(stderr,'(*(a:,1x))')& + & '*filewrite* error:',filename,trim(message) error stop 1 endif - do i=1,size(filedata) ! write file + ! write file + do i=1,size(filedata) write(lun,'(a)',iostat=ios,iomsg=message)trim(filedata(i)) if(ios.ne.0)then - write(stderr,'(*(a:,1x))')'*filewrite* error:',filename,trim(message) + write(stderr,'(*(a:,1x))')& + & '*filewrite* error:',filename,trim(message) error stop 4 endif enddo - close(unit=lun,iostat=ios,iomsg=message) ! close file + ! close file + close(unit=lun,iostat=ios,iomsg=message) if(ios.ne.0)then write(stderr,'(*(a:,1x))')'*filewrite* error:',trim(message) error stop 2 -- cgit v1.2.3 From 51180c0d964415b3168c1cdd1fed9f29e3507858 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 11 Oct 2020 06:10:52 -0400 Subject: check if name is a directory on backfill instead of depending on system command --- fpm/src/fpm/cmd/new.f90 | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 index dce13bc..757274e 100644 --- a/fpm/src/fpm/cmd/new.f90 +++ b/fpm/src/fpm/cmd/new.f90 @@ -2,7 +2,7 @@ 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 +use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir use,intrinsic :: iso_fortran_env, only : stderr=>error_unit implicit none private @@ -20,8 +20,11 @@ character(len=:),allocatable :: littlefile(:) write(stderr,'(*(g0,1x))')'fpm::new',settings%name,'already exists.' write(stderr,'(*(g0,1x))')' perhaps you wanted to add --backfill ?' return - elseif(exists(settings%name) .and. settings%backfill )then + elseif(is_dir(settings%name) .and. settings%backfill )then write(*,'(*(g0))')'backfilling ',settings%name + elseif(exists(settings%name) )then + write(stderr,'(*(g0,1x))')'fpm::new',settings%name,'already exists and is not a directory.' + return else call mkdir(settings%name) ! make new directory endif -- cgit v1.2.3 From 48a79214686ba2da0f84fc520a4f80a0ba389f08 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 11 Oct 2020 18:20:50 -0400 Subject: simplify initializing git(1) repository --- fpm/.gitignore | 2 +- fpm/src/fpm/cmd/new.f90 | 104 ++++++++++++++++++++++++++++++------------------ 2 files changed, 67 insertions(+), 39 deletions(-) diff --git a/fpm/.gitignore b/fpm/.gitignore index c602557..7e96036 100644 --- a/fpm/.gitignore +++ b/fpm/.gitignore @@ -1,2 +1,2 @@ build/* -*/FODDER/* +FODDER/* diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 index 757274e..f57b948 100644 --- a/fpm/src/fpm/cmd/new.f90 +++ b/fpm/src/fpm/cmd/new.f90 @@ -10,38 +10,50 @@ public :: cmd_new contains -subroutine cmd_new(settings) ! --with-executable F --with-test F ' +subroutine cmd_new(settings) type(fpm_new_settings), intent(in) :: settings character(len=:),allocatable :: bname ! baeename of NAME character(len=:),allocatable :: message(:) character(len=:),allocatable :: littlefile(:) if(exists(settings%name) .and. .not.settings%backfill )then - write(stderr,'(*(g0,1x))')'fpm::new',settings%name,'already exists.' - write(stderr,'(*(g0,1x))')' perhaps you wanted to add --backfill ?' + write(stderr,'(*(g0,1x))')& + & 'ERROR: ',settings%name,'already exists.' + write(stderr,'(*(g0,1x))')& + & ' perhaps you wanted to add --backfill ?' return elseif(is_dir(settings%name) .and. settings%backfill )then write(*,'(*(g0))')'backfilling ',settings%name elseif(exists(settings%name) )then - write(stderr,'(*(g0,1x))')'fpm::new',settings%name,'already exists and is not a directory.' + write(stderr,'(*(g0,1x))')& + & 'ERROR: ',settings%name,'already exists and is not a directory.' return else - call mkdir(settings%name) ! make new directory + ! make new directory + call mkdir(settings%name) endif - call run('cd '//settings%name) ! change to new directory as a test. System dependent potentially - !! NOTE: need some system routines to handle filenames like "." like realpath() or getcwd(). + + ! change to new directory as a test. System dependent potentially + call run('cd '//settings%name) + !! NOTE: need some system routines to handle filenames like "." + !! like realpath() or getcwd(). bname=basename(settings%name) - !! weird gfortran bug?? lines truncated to concatenated string length, not 80 - !! hit some weird gfortran bug when littlefile data was an argument to warnwrite(3f), ok when a variable + !! weird gfortran bug?? lines truncated to concatenated string length, + !! not 80 + !! hit some weird gfortran bug when littlefile data was an argument + !! to warnwrite(3f), ok when a variable - call warnwrite(join_path(settings%name, '.gitignore'), ['build/*']) ! create NAME/.gitignore file + ! create NAME/.gitignore file + call warnwrite(join_path(settings%name, '.gitignore'), ['build/*']) littlefile=[character(len=80) :: '# '//bname, 'My cool new project!'] - call warnwrite(join_path(settings%name, 'README.md'), littlefile) ! create NAME/README.md + ! create NAME/README.md + call warnwrite(join_path(settings%name, 'README.md'), littlefile) - message=[character(len=80) :: & ! start building NAME/fpm.toml + ! start building NAME/fpm.toml + message=[character(len=80) :: & &'name = "'//bname//'" ', & &'version = "0.1.0" ', & &'license = "license" ', & @@ -53,11 +65,13 @@ character(len=:),allocatable :: littlefile(:) if(settings%with_lib)then call mkdir(join_path(settings%name,'src') ) - message=[character(len=80) :: message, & ! create next section of fpm.toml + ! create next section of fpm.toml + message=[character(len=80) :: message, & &'[library] ', & &'source-dir="src" ', & &''] - littlefile=[character(len=80) :: & ! create placeholder module src/bname.f90 + ! create placeholder module src/bname.f90 + littlefile=[character(len=80) :: & &'module '//bname, & &' implicit none', & &' private', & @@ -68,39 +82,44 @@ character(len=:),allocatable :: littlefile(:) &' print *, "Hello, '//bname//'!"', & &' end subroutine say_hello', & &'end module '//bname] - ! a proposed alternative default - call warnwrite(join_path(settings%name, 'src', bname//'.f90'), littlefile) ! create NAME/src/NAME.f90 + ! create NAME/src/NAME.f90 + call warnwrite(join_path(settings%name, 'src', bname//'.f90'),& + & littlefile) endif if(settings%with_test)then - call mkdir(join_path(settings%name, 'test')) ! create NAME/test or stop - message=[character(len=80) :: message, & ! create next section of fpm.toml + + ! create NAME/test or stop + call mkdir(join_path(settings%name, 'test')) + ! create next section of fpm.toml + message=[character(len=80) :: message, & &'[[test]] ', & &'name="runTests" ', & &'source-dir="test" ', & &'main="main.f90" ', & &''] - littlefile=[character(len=80) :: & + littlefile=[character(len=80) :: & &'program main', & &'implicit none', & &'', & &'print *, "Put some tests in here!"', & &'end program main'] - ! a proposed alternative default a little more substantive - call warnwrite(join_path(settings%name, 'test/main.f90'), littlefile) ! create NAME/test/main.f90 + ! create NAME/test/main.f90 + call warnwrite(join_path(settings%name, 'test/main.f90'), littlefile) endif if(settings%with_executable)then - call mkdir(join_path(settings%name, 'app')) ! create NAME/app or stop - message=[character(len=80) :: message, & ! create next section of fpm.toml + ! create next section of fpm.toml + call mkdir(join_path(settings%name, 'app')) + ! create NAME/app or stop + message=[character(len=80) :: message, & &'[[executable]] ', & &'name="'//bname//'" ', & &'source-dir="app" ', & &'main="main.f90" ', & &''] - if(exists(bname//'/src/'))then littlefile=[character(len=80) :: & &'program main', & @@ -119,9 +138,11 @@ character(len=:),allocatable :: littlefile(:) endif call warnwrite(join_path(settings%name, 'app/main.f90'), littlefile) endif - call warnwrite(join_path(settings%name, 'fpm.toml'), message) ! now that built it write NAME/fpm.toml - call run('cd ' // settings%name // '&&git init') ! assumes these commands work on all systems and git(1) is installed + ! now that built it write NAME/fpm.toml + call warnwrite(join_path(settings%name, 'fpm.toml'), message) + ! assumes git(1) is installed and in path + call run('git init ' // settings%name) contains subroutine warnwrite(fname,data) @@ -131,14 +152,17 @@ character(len=*),intent(in) :: data(:) if(.not.exists(fname))then call filewrite(fname,data) else - write(stderr,'(*(g0,1x))')'fpm::new',fname,'already exists. Not overwriting' + write(stderr,'(*(g0,1x))')'INFO: ',fname,& + & 'already exists. Not overwriting' endif end subroutine warnwrite subroutine filewrite(filename,filedata) -use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit -! write filedata to file filename +! procedure to write filedata to file filename +use,intrinsic :: iso_fortran_env, only : & + & stdin=>input_unit, stdout=>output_unit, stderr=>error_unit + character(len=*),intent(in) :: filename character(len=*),intent(in) :: filedata(:) integer :: lun, i, ios @@ -149,11 +173,11 @@ character(len=256) :: message if(filename.ne.' ')then open(file=filename, & & newunit=lun, & - & form='formatted', & ! FORM = FORMATTED | UNFORMATTED - & access='sequential', & ! ACCESS = SEQUENTIAL | DIRECT | STREAM - & action='write', & ! ACTION = READ|WRITE | READWRITE - & position='rewind', & ! POSITION = ASIS | REWIND | APPEND - & status='new', & ! STATUS = NEW | REPLACE | OLD | SCRATCH | UNKNOWN + & form='formatted', & ! FORM = FORMATTED | UNFORMATTED + & access='sequential', & ! ACCESS = SEQUENTIAL| DIRECT | STREAM + & action='write', & ! ACTION = READ|WRITE| READWRITE + & position='rewind', & ! POSITION= ASIS | REWIND | APPEND + & status='new', & ! STATUS = NEW| REPLACE| OLD| SCRATCH| UNKNOWN & iostat=ios, & & iomsg=message) else @@ -161,17 +185,21 @@ character(len=256) :: message ios=0 endif if(ios.ne.0)then - write(stderr,'(*(a:,1x))')'*filewrite* error:',filename,trim(message) + write(stderr,'(*(a:,1x))')& + & '*filewrite* error:',filename,trim(message) error stop 1 endif - do i=1,size(filedata) ! write file + ! write file + do i=1,size(filedata) write(lun,'(a)',iostat=ios,iomsg=message)trim(filedata(i)) if(ios.ne.0)then - write(stderr,'(*(a:,1x))')'*filewrite* error:',filename,trim(message) + write(stderr,'(*(a:,1x))')& + & '*filewrite* error:',filename,trim(message) error stop 4 endif enddo - close(unit=lun,iostat=ios,iomsg=message) ! close file + ! close file + close(unit=lun,iostat=ios,iomsg=message) if(ios.ne.0)then write(stderr,'(*(a:,1x))')'*filewrite* error:',trim(message) error stop 2 -- cgit v1.2.3 From d2857ab27f27de933680e56fd7ae85c9b0021577 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Thu, 15 Oct 2020 19:04:36 -0400 Subject: restore .gitignore --- fpm/.gitignore | 1 - 1 file changed, 1 deletion(-) diff --git a/fpm/.gitignore b/fpm/.gitignore index 7e96036..a007fea 100644 --- a/fpm/.gitignore +++ b/fpm/.gitignore @@ -1,2 +1 @@ build/* -FODDER/* -- cgit v1.2.3 From d2c63b39109b4fc658839124abfd9c704b39e1e7 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Thu, 15 Oct 2020 19:06:04 -0400 Subject: restore .gitignore --- fpm/.gitignore | 1 - 1 file changed, 1 deletion(-) diff --git a/fpm/.gitignore b/fpm/.gitignore index 7e96036..a007fea 100644 --- a/fpm/.gitignore +++ b/fpm/.gitignore @@ -1,2 +1 @@ build/* -FODDER/* -- cgit v1.2.3 From aa04c3f8046620c2919127051f8557bf42d902c8 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Thu, 15 Oct 2020 19:04:36 -0400 Subject: restore .gitignore --- fpm/.gitignore | 1 - 1 file changed, 1 deletion(-) diff --git a/fpm/.gitignore b/fpm/.gitignore index 7e96036..a007fea 100644 --- a/fpm/.gitignore +++ b/fpm/.gitignore @@ -1,2 +1 @@ build/* -FODDER/* -- cgit v1.2.3 From 07d36eb6a546116f2088bdbcdd526f7cce39ea0e Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Fri, 16 Oct 2020 14:52:09 -0400 Subject: better help per @LKedward --- fpm/src/fpm_command_line.f90 | 34 +++++++++++++++++----------------- 1 file changed, 17 insertions(+), 17 deletions(-) diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 671d17f..6d4abee 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -248,11 +248,11 @@ contains elseif(len_trim(cmdarg).eq.0)then write(stdout,'(*(a))')'Fortran Package Manager:' write(stdout,'(*(a))')' ' - write(stdout,'(*(a))')' subcommand may be one of' call printhelp(help_list_nodash) else write(stderr,'(*(a))')'ERROR: unknown subcommand [', & & trim(cmdarg), ']' + call printhelp(help_list_dash) endif call printhelp(help_text) @@ -286,14 +286,21 @@ contains end function is_fortran_name subroutine set_help() - help_list_nodash=[character(len=80) :: & - ' ', & - ' build Compile the package placing results in the "build" directory', & - ' help Display help ', & - ' list Display this list of subcommand descriptions ', & - ' new Create a new Fortran package directory with sample files ', & - ' run Run the local package application programs ', & - ' test Run the test programs ', & + help_list_nodash=[character(len=80) :: & + 'USAGE: fpm [ SUBCOMMAND [SUBCOMMAND_OPTIONS] ] | [--help|--version] ', & + ' where SUBCOMMAND is commonly new|build|run|test ', & + ' ', & + ' subcommand may be one of ', & + ' ', & + ' build Compile the package placing results in the "build" directory', & + ' help Display help ', & + ' list Display this list of subcommand descriptions ', & + ' new Create a new Fortran package directory with sample files ', & + ' run Run the local package application programs ', & + ' test Run the test programs ', & + ' ', & + ' Enter "fpm --list" for a brief list of subcommand options. Enter ', & + ' "fpm --help" or "fpm SUBCOMMAND --help" for detailed descriptions. ', & ' '] help_list_dash = [character(len=80) :: & ' ', & @@ -305,13 +312,6 @@ contains ' test [NAME(s)] [--release] [--list] [-- ARGS] ', & ' '] help_usage=[character(len=80) :: & - ' ', & - 'USAGE: fpm [ SUBCOMMAND [SUBCOMMAND_OPTIONS] ] | [--help|--version] ', & - ' where SUBCOMMAND is commonly new|build|run|test ', & - ' ', & - ' Enter "fpm list " or "fpm --list" for a full list of ', & - ' subcommands. Enter "fpm --help" or "fpm SUBCOMMAND --help" ', & - ' for detailed command information. ', & '' ] help_fpm=[character(len=80) :: & 'NAME ', & @@ -386,7 +386,7 @@ contains 'SYNOPSIS ', & ' fpm list [-list] ', & ' ', & - ' fpm run --help|--version ', & + ' fpm list --help|--version ', & ' ', & 'DESCRIPTION ', & ' Display a short description for each fpm(1) subcommand. ', & -- cgit v1.2.3 From 1cd0d03b60c6a41c79a132606aa6fc2425b5c988 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Fri, 16 Oct 2020 21:25:58 -0400 Subject: simplify new_test.f90 using functions already existing in fpm(1) source --- fpm/src/fpm_command_line.f90 | 6 +- fpm/test/new_test/new_test.f90 | 225 +++++++---------------------------------- 2 files changed, 42 insertions(+), 189 deletions(-) diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 6d4abee..1ea170e 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -130,14 +130,14 @@ contains case(1) write(stderr,'(*(g0,/))')'ERROR: directory name required' write(stderr,'(*(7x,g0,/))') & - & 'usage: fpm new NAME [--lib|--src] [--app] [--test] [--backfill]' + & 'USAGE: fpm new NAME [--lib|--src] [--app] [--test] [--backfill]' stop 1 case(2) name=trim(unnamed(2)) case default write(stderr,'(g0)')'ERROR: only one directory name allowed' write(stderr,'(7x,g0)') & - & 'usage: fpm new NAME [--lib|--src] [--app] [--test] [--backfill]' + & 'USAGE: fpm new NAME [--lib|--src] [--app] [--test] [--backfill]' stop 2 end select !! canon_path is not converting ".", etc. @@ -648,7 +648,7 @@ contains help_install=[character(len=80) :: & ' fpm(1) subcommand "install" ', & ' ', & - ' Usage: fpm install NAME ', & + ' USAGE: fpm install NAME ', & '' ] end subroutine set_help diff --git a/fpm/test/new_test/new_test.f90 b/fpm/test/new_test/new_test.f90 index 289431e..06f0c8a 100644 --- a/fpm/test/new_test/new_test.f90 +++ b/fpm/test/new_test/new_test.f90 @@ -1,12 +1,10 @@ program new_test use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit -use fpm_filesystem, only : is_dir, list_files, exists -use fpm_strings, only : string_t +use fpm_filesystem, only : is_dir, list_files, exists, windows_path +use fpm_strings, only : string_t, operator(.in.) use fpm_environment, only : run, get_os_type use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_WINDOWS type(string_t), allocatable :: file_names(:) -character(len=:), allocatable :: fnames(:) -character(len=:), allocatable :: directory integer :: i, j, k character(len=*),parameter :: cmdpath = 'build/gfortran_debug/app/fpm' character(len=:),allocatable :: path @@ -31,6 +29,7 @@ character(len=256) :: message character(len=:),allocatable :: directories(:) character(len=:),allocatable :: expected(:) logical,allocatable :: tally(:) +logical :: IS_OS_WINDOWS write(*,'(g0:,1x)')'TEST new SUBCOMMAND (draft):' allocate(tally(0)) directories=[character(len=80) :: 'A','B','C','D','E','F','G','BB','CC'] @@ -45,19 +44,21 @@ logical,allocatable :: tally(:) enddo !! SEE IF EXPECTED FILES ARE GENERATED - !! DOS versus POSIX filenames - ! assuming fpm command is in path and the new version + !! Issues: + !! o assuming fpm command is in expected path and the new version + !! o DOS versus POSIX filenames + is_os_windows=.false. select case (get_os_type()) case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD) path=cmdpath case (OS_WINDOWS) - path=u2d(cmdpath) + path=windows_path(path) + is_os_windows=.true. case default write(*,*)'ERROR: unknown OS. Stopping test' stop 2 end select - - + ! execute the fpm(1) commands do i=1,size(cmds) message='' write(*,*)path//' '//cmds(i) @@ -80,74 +81,53 @@ logical,allocatable :: tally(:) write(*,*)'ERROR:',trim( directories(i) ),' is not a directory' else select case(directories(i)) - case('A') - expected=[ character(len=80)::& + case('A'); expected=[ character(len=80)::& &'A/app','A/fpm.toml','A/README.md','A/src','A/test','A/app/main.f90','A/src/A.f90','A/test/main.f90'] - case('B') - expected=[ character(len=80)::& + case('B'); expected=[ character(len=80)::& &'B/fpm.toml','B/README.md','B/src','B/src/B.f90'] - case('C') - expected=[ character(len=80)::& + case('C'); expected=[ character(len=80)::& &'C/app','C/fpm.toml','C/README.md','C/app/main.f90'] - case('D') - expected=[ character(len=80)::& + case('D'); expected=[ character(len=80)::& &'D/fpm.toml','D/README.md','D/test','D/test/main.f90'] - case('E') - expected=[ character(len=80)::& + case('E'); expected=[ character(len=80)::& &'E/fpm.toml','E/README.md','E/src','E/test','E/src/E.f90','E/test/main.f90'] - case('F') - expected=[ character(len=80)::& + case('F'); expected=[ character(len=80)::& &'F/app','F/fpm.toml','F/README.md','F/src','F/app/main.f90','F/src/F.f90'] - case('G') - expected=[ character(len=80)::& + case('G'); expected=[ character(len=80)::& &'G/app','G/fpm.toml','G/README.md','G/test','G/app/main.f90','G/test/main.f90'] - case('BB') - expected=[ character(len=80)::& + case('BB'); expected=[ character(len=80)::& &'BB/fpm.toml','BB/README.md','BB/src','BB/test','BB/src/BB.f90','BB/test/main.f90'] - case('CC') - expected=[ character(len=80)::& + case('CC'); expected=[ character(len=80)::& &'CC/app','CC/fpm.toml','CC/README.md','CC/src','CC/test','CC/app/main.f90','CC/src/CC.f90','CC/test/main.f90'] case default write(*,*)'ERROR: internal error. unknown directory name ',trim(directories(i)) stop 4 end select !! MSwindows has hidden files in it + !! Warning: This only looks for expected files. If there are more files than expected it does not fail call list_files(trim(directories(i)), file_names,recurse=.true.) - if(allocated(fnames))deallocate(fnames) - allocate(character(len=0) :: fnames(0)) - do j=1,size(file_names) - if(file_names(j)%s(1:1).eq.'.'.or.index(file_names(j)%s,'/.').ne.0.or.index(file_names(j)%s,'\.').ne.0)cycle - fnames=[character(len=max(len(fnames),len(file_names(j)%s))) :: fnames,file_names(j)%s] - enddo - write(*,'(*(g0))',advance='no')'>>>DIRECTORY ',trim(directories(i)),': ' - write(*,'(*(g0:,", "))')( file_names(j)%s, j=1,size(file_names) ) - if(size(expected).ne.size(fnames))then - write(*,*)'unexpected number of files in file list=',size(fnames),' expected ',size(expected) - tally=[tally,.false.] - cycle TESTS - else - select case (get_os_type()) - case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD) - case (OS_WINDOWS) - do j=1,size(expected) - expected(j)=u2d(expected(j)) - enddo - case default - write(*,*)'ERROR: unknown OS. Stopping test' - stop 3 - end select - do j=1,size(expected) - if( .not.any(fnames(j)==expected) )then - tally=[tally,.false.] - write(*,'("ERROR: EXPECTED ",*(g0:,", "))')( trim(expected(k)), k=1,size(expected) ) - write(*,'(*(g0))')' NO MATCH FOR ',fnames(j) - cycle TESTS - endif - enddo - tally=[tally,.true.] + + if(size(expected).ne.size(file_names))then + write(*,*)'WARNING: unexpected number of files in file list=',size(file_names),' expected ',size(expected) + write(*,'("EXPECTED: ",*(g0:,","))')(trim(expected(j)),j=1,size(expected)) + write(*,'("FOUND: ",*(g0:,","))')(trim(file_names(j)%s),j=1,size(file_names)) endif + + do j=1,size(expected) + + if(is_os_windows) expected(j)=windows_path(expected(j)) + if( .not.(trim(expected(j)).in.file_names) )then + tally=[tally,.false.] + write(*,'("ERROR: FOUND ",*(g0:,", "))')( trim(file_names(k)%s), k=1,size(file_names) ) + write(*,'(*(g0))')' BUT NO MATCH FOR ',expected(j) + tally=[tally,.false.] + cycle TESTS + endif + enddo + tally=[tally,.true.] endif enddo TESTS + write(*,'("TALLY=",*(g0))')tally if(all(tally))then write(*,'(*(g0))')'PASSED: all ',count(tally),' tests passed ' @@ -155,132 +135,5 @@ logical,allocatable :: tally(:) write(*,*)'FAILED: PASSED=',count(tally),' FAILED=',count(.not.tally) stop 5 endif -!----------------------------------------------------------------------------------------------------------------------------------- -contains -!----------------------------------------------------------------------------------------------------------------------------------- -function u2d(pathname) result(dos) -! simplistically replace / with \ to make posix pathname DOS pathname -character(len=*),intent(in) :: pathname -character(len=:),allocatable :: dos -integer :: i -dos=pathname -do i=1,len(pathname) - if(pathname(i:i).eq.'/')dos(i:i)='\' -enddo -end function u2d -!----------------------------------------------------------------------------------------------------------------------------------- -function djb2_hash_arr(chars,continue) result(hash_128) -use,intrinsic :: ISO_FORTRAN_ENV, only : int8,int16,int32,int64 -implicit none - -!$@(#) djb2_hash(3fp): DJB2 hash of array (algorithm by Daniel J. Bernstein ) for character array - -character(len=1),intent(in) :: chars(:) -logical,intent(in),optional :: continue -integer :: i -integer(kind=int64) :: hash_128 -integer(kind=int64),save :: hash_64=5381 - - if(present(continue))then - hash_64 = hash_64 - else - hash_64 = 5381_int64 - endif - do i=1,size(chars) - hash_64 = (ishft(hash_64,5) + hash_64) + ichar(chars(i),kind=int64) - enddo - hash_128=transfer([hash_64,0_int64],hash_128) - DEBUG : block - integer :: ios - write(6,'("*djb2_hash* hashing string=",*(a))',advance='no')chars - write(6,'(1x,"hash=",i0,1x,"hex hash=",z32.32)')hash_128,hash_128 - flush(6,iostat=ios) - endblock DEBUG -end function djb2_hash_arr -!----------------------------------------------------------------------------------------------------------------------------------- -subroutine slurp(filename,text,length,lines) -use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit -implicit none - -!$@(#) M_io::slurp(3f): allocate text array and read file filename into it - -class(*),intent(in) :: filename ! filename to shlep -character(len=1),allocatable,intent(out) :: text(:) ! array to hold file -integer,intent(out),optional :: length ! length of longest line -integer,intent(out),optional :: lines ! number of lines -integer :: nchars=0 ! holds size of file -integer :: igetunit ! use newunit=igetunit in f08 -integer :: ios=0 ! used for I/O error status -integer :: length_local -integer :: lines_local -integer :: i -integer :: icount -character(len=256) :: message -character(len=4096) :: local_filename - - length_local=0 - lines_local=0 - - message='' - select type(FILENAME) - type is (character(len=*)) - open(newunit=igetunit, file=trim(filename), action="read", iomsg=message,& - &form="unformatted", access="stream",status='old',iostat=ios) - local_filename=filename - type is (integer) - rewind(unit=filename,iostat=ios,iomsg=message) - write(local_filename,'("unit ",i0)')filename - igetunit=filename - end select - - if(ios.eq.0)then ! if file was successfully opened - - inquire(unit=igetunit, size=nchars) - - if(nchars.le.0)then - call stderr_local( '*slurp* empty file '//trim(local_filename) ) - return - endif - ! read file into text array - ! - if(allocated(text))deallocate(text) ! make sure text array not allocated - allocate ( text(nchars) ) ! make enough storage to hold file - read(igetunit,iostat=ios,iomsg=message) text ! load input file -> text array - if(ios.ne.0)then - call stderr_local( '*slurp* bad read of '//trim(local_filename)//':'//trim(message) ) - endif - else - call stderr_local('*slurp* '//message) - allocate ( text(0) ) ! make enough storage to hold file - endif - - close(iostat=ios,unit=igetunit) ! close if opened successfully or not - - if(present(lines).or.present(length))then ! get length of longest line and number of lines - icount=0 - do i=1,nchars - if(text(i).eq.NEW_LINE('A'))then - lines_local=lines_local+1 - length_local=max(length_local,icount) - icount=0 - endif - icount=icount+1 - enddo - if(nchars.ne.0)then - if(text(nchars).ne.NEW_LINE('A'))then - lines_local=lines_local+1 - length_local=max(length_local,icount) - endif - endif - if(present(lines))lines=lines_local - if(present(length))length=length_local - endif -end subroutine slurp -!----------------------------------------------------------------------------------------------------------------------------------- -subroutine stderr_local(message) -character(len=*) :: message - write(stderr,'(a)')trim(message) ! write message to standard error -end subroutine stderr_local -!----------------------------------------------------------------------------------------------------------------------------------- end program new_test -- cgit v1.2.3 From 814302fe074a04368a57f9252f966f2c6a20ebab Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Fri, 16 Oct 2020 22:15:09 -0400 Subject: dos revised new_test.f90 --- fpm/test/new_test/new_test.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/fpm/test/new_test/new_test.f90 b/fpm/test/new_test/new_test.f90 index 06f0c8a..cafcaf2 100644 --- a/fpm/test/new_test/new_test.f90 +++ b/fpm/test/new_test/new_test.f90 @@ -52,7 +52,7 @@ logical :: IS_OS_WINDOWS case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD) path=cmdpath case (OS_WINDOWS) - path=windows_path(path) + path=windows_path(cmdpath) is_os_windows=.true. case default write(*,*)'ERROR: unknown OS. Stopping test' -- cgit v1.2.3 From fea59a2162eb471defc4099a98c7a996181c3d6a Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Fri, 16 Oct 2020 22:42:33 -0400 Subject: mention --list option on main command --- fpm/src/fpm_command_line.f90 | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 1ea170e..d67cd41 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -287,7 +287,7 @@ contains subroutine set_help() help_list_nodash=[character(len=80) :: & - 'USAGE: fpm [ SUBCOMMAND [SUBCOMMAND_OPTIONS] ] | [--help|--version] ', & + 'USAGE: fpm [ SUBCOMMAND [SUBCOMMAND_OPTIONS] ]|[--list|--help|--version]', & ' where SUBCOMMAND is commonly new|build|run|test ', & ' ', & ' subcommand may be one of ', & @@ -320,7 +320,7 @@ contains 'SYNOPSIS ', & ' fpm SUBCOMMAND [SUBCOMMAND_OPTIONS] ', & ' ', & - ' fpm --help|--version ', & + ' fpm --help|--version|--list ', & ' ', & 'DESCRIPTION ', & ' fpm(1) is a package manager that helps you create Fortran projects ', & @@ -360,7 +360,8 @@ contains ' in "build/*_debug/". When this flag is present build ', & ' output goes into "build/*_release/" and common compiler ', & ' optimization flags are used. ', & - ' --list list candidates instead of building or running them ', & + ' --list List candidates instead of building or running them. ', & + ' On the fpm command this shows a brief list of subcommands.', & ' -- 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 ', & -- cgit v1.2.3 From 0673b35ecb827835eca50136e52a3be03ae24c6b Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sat, 17 Oct 2020 00:01:09 -0400 Subject: snapshot of help as html --- docs/index.html | 721 +++++++++++++++++++++++++++++++++++++++++++ fpm/src/fpm_command_line.f90 | 2 +- 2 files changed, 722 insertions(+), 1 deletion(-) create mode 100644 docs/index.html diff --git a/docs/index.html b/docs/index.html new file mode 100644 index 0000000..3df031b --- /dev/null +++ b/docs/index.html @@ -0,0 +1,721 @@ + + + + + + +
[UP]
+
+
+
+


Manual Reference Pages  - untitled ()

+
+ + +

NAME

+ +
+
+fpm(1) - A Fortran package manager and build system +

+

+ +

SYNOPSIS

+ + +
+fpm SUBCOMMAND [SUBCOMMAND_OPTIONS] +

+fpm --help|--version|--list +

+ + +

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 registered projects. +

+All output goes into the directory "build/" which can generally be +removed and rebuilt if required. Note that if external packages are +being used you need network connectivity to rebuild from scratch. +

+ + +

SUBCOMMANDS

+ +
+
+Valid fpm subcommands are: +

+

+     build [--release] [--list]
+                     Compile the packages into the "build/" directory.
+     new NAME [--lib|--src] [--app] [--test] [--backfill]
+                     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
+     list [--list]   Display brief descriptions of all subcommands.
+

+

+
+ + +

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/*_debug/". When this flag is present build +output goes into "build/*_release/" and common compiler +optimization flags are used. +
+--list +List candidates instead of building or running them. +On the fpm command this shows a brief list of subcommands. +
+-- 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 new mypackage --app --test
+    fpm build
+    fpm test
+    fpm run
+    fpm new --help
+    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 +
+ + +

NAME

+ +
+
+new(1) - the fpm(1) subcommand to initialize a new project +
+ + +

SYNOPSIS

+ +
+
+fpm new NAME [--lib|--src] [--app] [--test] [--backfill] +

+fpm new --help|--version +

+ + +

DESCRIPTION

+ +
+
+"fpm new" creates a new programming project in a new directory. +

+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 your name and e-mail address. +
+ + +

OPTIONS

+ +
+
+ + + + + + + + + + +
+NAME +the name of the project directory to create. The name +must be a valid Fortran name composed of 1 to 63 +ASCII alphanumeric characters and underscores, +starting with a letter. +
+The default is to create all of the src/, app/, and test/ +directories. If any of the following options are specified +then only selected subdirectories are generated: +
+--lib,--src
  +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 programs. +
+--help +print this help and exit +
+--version
  +print program version information and exit +
+ + +

EXAMPLES

+ +
+
+Sample use +

+

+   fpm new myproject  # create new project directory and seed it
+   cd myproject       # Enter the new directory
+   # and run commands such as
+   fpm build
+   fpm run            # run example application program
+   fpm test           # run example test program
+

+

+
+ + +

SEE ALSO

+ +
+
+The fpm(1) home page at https://github.com/fortran-lang/fpm +

+Registered packages are at https://fortran-lang.org/packages +

+ + +

NAME

+ +
+
+build(1) - the fpm(1) subcommand to build a project +

+

+ + +

SYNOPSIS

+ +
+
+fpm build [--release]|[-list] +

+fpm build --help|--version +

+ + +

DESCRIPTION

+ +
+
+The "fpm build" command +
+ + + + + +
+o + +Fetches any dependencies +
+o + +Scans your sources +
+o + +Builds them in the proper order +
+

+The Fortran source files are assumed by default to be in +

+ + + + + +
+o + +src/ for modules and procedure source +
+o + +app/ main program(s) for applications +
+o + +test/ main program(s) and support files for project tests +Changed or new files found are rebuilt. The results are placed in +the build/ directory. +
+

+Non-default pathnames and remote dependencies are used if +specified in the "fpm.toml" file. +

+ + +

OPTIONS

+ +
+
+ + + + + +
+--release
  +build in build/*_release instead of build/*_debug with +high optimization instead of full debug options. +
+--list +list candidates instead of building or running them +
+--help +print this help and exit +
+--version
  +print program version information and exit +
+ + +

EXAMPLES

+ +
+
+Sample commands: +

+

+  fpm build           # build with debug options
+  fpm build --release # build with high optimization
+

+

+
+ + +

SEE ALSO

+ +
+
+The fpm(1) home page at https://github.com/fortran-lang/fpm +
+ + +

NAME

+ +
+
+run(1) - the fpm(1) subcommand to run project applications +

+

+ + +

SYNOPSIS

+ +
+
+fpm run [NAME(s)] [--release] [-- ARGS] +

+fpm run --help|--version +

+ + +

DESCRIPTION

+ +
+
+Run applications you have built in your fpm(1) project. +
+ + +

OPTIONS

+ +
+
+ + + + + +
+NAME(s) +optional list of specific names to execute. +The default is to run all the applications in app/ +or the programs listed in the "fpm.toml" file. +
+--release
  +selects the optimized build instead of the debug +build. +
+--list +list candidates instead of building or running them +
+-- ARGS
  +optional arguments to pass to the program(s). +The same arguments are passed to all names +specified. +
+ + +

EXAMPLES

+ +
+
+run fpm(1) project applications +

+

+  # run default programs in /app or as specified in "fpm.toml"
+  fpm run
+

+ # run a specific program and pass arguments to the command + fpm run mytest -- -x 10 -y 20 --title "my title line" +

+ # run production version of two applications + fpm run prg1 prg2 --release +

+

+
+ + +

SEE ALSO

+ +
+
+The fpm(1) home page at https://github.com/fortran-lang/fpm +
+ + +

NAME

+ +
+
+test(1) - the fpm(1) subcommand to run project tests +

+

+ + +

SYNOPSIS

+ +
+
+fpm test [NAME(s)] [--release] [--list] [-- ARGS] +

+fpm test --help|--version +

+ + +

DESCRIPTION

+ +
+
+Run applications you have built to test your project. +
+ + +

OPTIONS

+ +
+
+ + + + + +
+NAME(s) +optional list of specific test names to execute. +The default is to run all the tests in test/ +or the tests listed in the "fpm.toml" file. +
+--release
  +selects the optimized build instead of the debug +build. +
+--list +list candidates instead of building or running them +
+-- ARGS
  +optional arguments to pass to the test program(s). +The same arguments are passed to all test names +specified. +
+ + +

EXAMPLES

+ +
+
+run tests +

+

+ # run default tests in /test or as specified in "fpm.toml"
+ fpm test
+

+ # run a specific test and pass arguments to the command + fpm test mytest -- -x 10 -y 20 --title "my title line" +

+ fpm test tst1 tst2 --release # production version of two tests +

+

+
+ + +

SEE ALSO

+ +
+
+The fpm(1) home page at https://github.com/fortran-lang/fpm +
+ + +

NAME

+ +
+
+help(1) - the fpm(1) subcommand to display help +

+

+ + +

SYNOPSIS

+ +
+
+fpm help [fpm] [new] [build] [run] [test] [help] [version] [manual] +

+fpm help [fortran|fortran_manual][FORTRAN_INTRINSIC_NAME] +

+ + +

DESCRIPTION

+ +
+
+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. 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. "fortran_manual" 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 fortran_manual # all Fortran documentation
+

+

+
+ + +

SEE ALSO

+ +
+
+The fpm(1) home page at https://github.com/fortran-lang/fpm + + + + + + + + +
+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:
  +Linux +
+


+
untitled () October 16, 2020
Generated by manServer 1.08 from x.1 using man macros. +

+
+
+ + diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index d67cd41..3cb6203 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -571,7 +571,7 @@ contains ' ', & ' 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: ', & + ' then only selected subdirectories are generated: ', & ' ', & ' --lib,--src create directory src/ and a placeholder module ', & ' named "NAME.f90" for use with subcommand "build". ', & -- cgit v1.2.3 From aa93e1b0618ef9b6086f515e40c9f45be26e03ff Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sat, 17 Oct 2020 00:34:42 -0400 Subject: add list subcommand to manual output --- fpm/src/fpm_command_line.f90 | 1 + 1 file changed, 1 insertion(+) diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 3cb6203..0efc076 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -200,6 +200,7 @@ contains 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, help_list] help_text=[character(len=widest) :: help_text, version_text] case default ! note help_intrinsics is returning a fixed-length array -- cgit v1.2.3 From 8692a9aeceac6314d62844be3e644a2a28605ec8 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sat, 17 Oct 2020 00:40:41 -0400 Subject: update HTML sample manual --- docs/index.html | 171 +++++++++++++++++++++++++++++++++++--------------------- 1 file changed, 108 insertions(+), 63 deletions(-) diff --git a/docs/index.html b/docs/index.html index 3df031b..f351396 100644 --- a/docs/index.html +++ b/docs/index.html @@ -47,7 +47,7 @@ a.existingWikiWord[title]{ //border: 1px dashed #BBB; }


Manual Reference Pages  - untitled ()

- +

NAME

@@ -56,6 +56,7 @@ a.existingWikiWord[title]{ //border: 1px dashed #BBB; } fpm(1) - A Fortran package manager and build system

+

SYNOPSIS

@@ -65,7 +66,7 @@ a.existingWikiWord[title]{ //border: 1px dashed #BBB; }

fpm --help|--version|--list - +

DESCRIPTION

@@ -144,7 +145,7 @@ Show version information and exit. Valid for all subcommands. - +

EXAMPLES

@@ -162,7 +163,7 @@ sample commands:

- +

SEE ALSO

@@ -170,7 +171,7 @@ sample commands:
The fpm(1) home page at https://github.com/fortran-lang/fpm
-
+

NAME

@@ -178,17 +179,17 @@ The fpm(1) home page at https://github.com/fortran-lang/fpm
new(1) - the fpm(1) subcommand to initialize a new project
-
+

SYNOPSIS

-fpm new NAME [--lib|--src] [--app] [--test] [--backfill] +fpm new NAME [--lib|--src] [--app] [--test] [--backfill]

fpm new --help|--version

- +

DESCRIPTION

@@ -218,7 +219,7 @@ and a ".gitignore" file for ignoring the build/ directory Remember to update the information in the sample "fpm.toml" file with your name and e-mail address. -
+

OPTIONS

@@ -254,7 +255,7 @@ 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". +So the default is equivalent to "fpm NAME --lib --app --test". --backfill   @@ -275,7 +276,7 @@ print this help and exit print program version information and exit - +

EXAMPLES

@@ -293,7 +294,7 @@ Sample use

- +

SEE ALSO

@@ -303,7 +304,7 @@ The fpm(1) home page at https://github.com/fortran-lang/fpm

Registered packages are at https://fortran-lang.org/packages - +

NAME

@@ -312,7 +313,7 @@ Registered packages are at https://fortran-lang.org/packages build(1) - the fpm(1) subcommand to build a project

- +

SYNOPSIS

@@ -322,7 +323,7 @@ Registered packages are at https://fortran-lang.org/packages

fpm build --help|--version - +

DESCRIPTION

@@ -377,7 +378,7 @@ the build/ directory. Non-default pathnames and remote dependencies are used if specified in the "fpm.toml" file. - +

OPTIONS

@@ -402,7 +403,7 @@ print this help and exit print program version information and exit -
+

EXAMPLES

@@ -416,7 +417,7 @@ Sample commands:

- +

SEE ALSO

@@ -424,7 +425,7 @@ Sample commands:
The fpm(1) home page at https://github.com/fortran-lang/fpm
-
+

NAME

@@ -433,7 +434,7 @@ The fpm(1) home page at https://github.com/fortran-lang/fpm run(1) - the fpm(1) subcommand to run project applications

- +

SYNOPSIS

@@ -443,7 +444,7 @@ The fpm(1) home page at https://github.com/fortran-lang/fpm

fpm run --help|--version - +

DESCRIPTION

@@ -451,7 +452,7 @@ The fpm(1) home page at https://github.com/fortran-lang/fpm
Run applications you have built in your fpm(1) project.
-
+

OPTIONS

@@ -480,7 +481,7 @@ The same arguments are passed to all names specified. -
+

EXAMPLES

@@ -500,7 +501,7 @@ run fpm(1) project applications

- +

SEE ALSO

@@ -508,7 +509,7 @@ run fpm(1) project applications
The fpm(1) home page at https://github.com/fortran-lang/fpm
-
+

NAME

@@ -517,7 +518,7 @@ The fpm(1) home page at https://github.com/fortran-lang/fpm test(1) - the fpm(1) subcommand to run project tests

- +

SYNOPSIS

@@ -527,7 +528,7 @@ The fpm(1) home page at https://github.com/fortran-lang/fpm

fpm test --help|--version - +

DESCRIPTION

@@ -535,7 +536,7 @@ The fpm(1) home page at https://github.com/fortran-lang/fpm
Run applications you have built to test your project.
-
+

OPTIONS

@@ -564,7 +565,7 @@ The same arguments are passed to all test names specified. -
+

EXAMPLES

@@ -583,7 +584,7 @@ run tests

- +

SEE ALSO

@@ -591,7 +592,7 @@ run tests
The fpm(1) home page at https://github.com/fortran-lang/fpm
-
+

NAME

@@ -600,7 +601,7 @@ The fpm(1) home page at https://github.com/fortran-lang/fpm help(1) - the fpm(1) subcommand to display help

- +

SYNOPSIS

@@ -610,7 +611,7 @@ The fpm(1) home page at https://github.com/fortran-lang/fpm

fpm help [fortran|fortran_manual][FORTRAN_INTRINSIC_NAME] - +

DESCRIPTION

@@ -619,7 +620,7 @@ The fpm(1) home page at https://github.com/fortran-lang/fpm The "fpm help" command is an alternative to the --help parameter on the fpm(1) command and its subcommands. - +

OPTIONS

@@ -647,7 +648,7 @@ uppercase to avoid conflicts with fpm(1) topics; but can be in lowercase if there is no conflict. -
+

EXAMPLES

@@ -677,43 +678,87 @@ Additional general Fortran documentation

- +

SEE ALSO

The fpm(1) home page at https://github.com/fortran-lang/fpm - - - - - - - -
-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:
  -Linux + + + +

NAME

+ +
+
+list(1) - list summary of fpm(1) subcommands +

+

+ + +

SYNOPSIS

+ +
+
+fpm list [-list] +

+fpm list --help|--version +

+ + +

DESCRIPTION

+ +
+
+Display a short description for each fpm(1) subcommand. +
+ + +

OPTIONS

+ +
+
+ +
+--list +display a list of command options as well. This is the +same output as generated by "fpm --list".
+ + +

EXAMPLES

+ +
+
+display a short list of fpm(1) subcommands +

+

+  fpm list
+  fpm --list
+

+

+
+ + +

SEE ALSO

+ +
+
+The fpm(1) home page at https://github.com/fortran-lang/fpm +

+

+   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:     Linux
+
+


-
untitled () October 16, 2020
Generated by manServer 1.08 from x.1 using man macros. +
untitled () October 17, 2020
Generated by manServer 1.08 from x.1 using man macros.

-- cgit v1.2.3 From 3726ca3eeed20c6ad7699141fb6ed4fc64d541a0 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sat, 17 Oct 2020 21:02:22 -0400 Subject: change test scripts in ci/ to remove scratch directories for new-test --- ci/run_tests.bat | 4 +++- ci/run_tests.sh | 2 ++ fpm/fpm.toml | 3 +++ fpm/src/fpm/cmd/new.f90 | 19 +++++++++------- fpm/test/new_test/new_test.f90 | 50 +++++++++++++++++++++++------------------- 5 files changed, 47 insertions(+), 31 deletions(-) diff --git a/ci/run_tests.bat b/ci/run_tests.bat index 76e5349..5f455b3 100755 --- a/ci/run_tests.bat +++ b/ci/run_tests.bat @@ -9,8 +9,10 @@ if errorlevel 1 exit 1 fpm run if errorlevel 1 exit 1 +rmdir fpm_scratch_* /s /q fpm test if errorlevel 1 exit 1 +rmdir fpm_scratch_* /s /q build\gfortran_debug\app\fpm if errorlevel 1 exit 1 @@ -103,4 +105,4 @@ if errorlevel 1 exit 1 if errorlevel 1 exit 1 .\build\gfortran_debug\app\Program_with_module -if errorlevel 1 exit 1 \ No newline at end of file +if errorlevel 1 exit 1 diff --git a/ci/run_tests.sh b/ci/run_tests.sh index adff2b3..7568b46 100755 --- a/ci/run_tests.sh +++ b/ci/run_tests.sh @@ -5,7 +5,9 @@ set -ex cd fpm fpm build fpm run +rm -rf fpm_scratch_*/ fpm test +rm -rf fpm_scratch_*/ build/gfortran_debug/app/fpm cd ../test/example_packages/hello_world diff --git a/fpm/fpm.toml b/fpm/fpm.toml index 8b4d8a3..f5fd443 100644 --- a/fpm/fpm.toml +++ b/fpm/fpm.toml @@ -16,6 +16,7 @@ rev = "649075aceb97f997665a1a4656514fd2e9b4becc" [dependencies.fortran-intrinsic-manpages] git = "https://github.com/urbanjost/M_intrinsics.git" +rev = "a758ebdd0487e8cab5b4894fbf375f87147c44b5" [[test]] name = "cli-test" @@ -31,3 +32,5 @@ main = "new_test.f90" name = "fpm-test" source-dir = "test/fpm_test" main = "main.f90" + + diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 index f57b948..eb1a532 100644 --- a/fpm/src/fpm/cmd/new.f90 +++ b/fpm/src/fpm/cmd/new.f90 @@ -15,6 +15,9 @@ type(fpm_new_settings), intent(in) :: settings character(len=:),allocatable :: bname ! baeename of NAME character(len=:),allocatable :: message(:) character(len=:),allocatable :: littlefile(:) +character(len=8) :: date + + call date_and_time(DATE=date) if(exists(settings%name) .and. .not.settings%backfill )then write(stderr,'(*(g0,1x))')& @@ -53,14 +56,14 @@ character(len=:),allocatable :: littlefile(:) call warnwrite(join_path(settings%name, 'README.md'), littlefile) ! start building NAME/fpm.toml - message=[character(len=80) :: & - &'name = "'//bname//'" ', & - &'version = "0.1.0" ', & - &'license = "license" ', & - &'author = "Jane Doe" ', & - &'maintainer = "jane.doe@example.com" ', & - &'copyright = "2020 Jane Doe" ', & - &' ', & + message=[character(len=80) :: & + &'name = "'//bname//'" ', & + &'version = "0.1.0" ', & + &'license = "license" ', & + &'author = "Jane Doe" ', & + &'maintainer = "jane.doe@example.com" ', & + &'copyright = "'//date(1:4)//' Jane Doe" ', & + &' ', & &''] if(settings%with_lib)then diff --git a/fpm/test/new_test/new_test.f90 b/fpm/test/new_test/new_test.f90 index cafcaf2..17e269a 100644 --- a/fpm/test/new_test/new_test.f90 +++ b/fpm/test/new_test/new_test.f90 @@ -4,37 +4,42 @@ use fpm_filesystem, only : is_dir, list_files, exists, windows_path use fpm_strings, only : string_t, operator(.in.) use fpm_environment, only : run, get_os_type use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_WINDOWS +implicit none type(string_t), allocatable :: file_names(:) integer :: i, j, k character(len=*),parameter :: cmdpath = 'build/gfortran_debug/app/fpm' character(len=:),allocatable :: path +character(len=*),parameter :: scr = 'fpm_scratch_' character(len=*),parameter :: cmds(*) = [character(len=80) :: & ' new', & ' new no-no', & -' new A', & -' new B --lib', & -' new C --app', & -' new D --test', & -' new E --lib --test ', & -' new F --lib --app', & -' new G --test --app', & -' new BB --lib', & -' new BB --test ', & -' new BB --backfill --test', & -' new CC --test --src --app', & +' new '//scr//'A', & +' new '//scr//'B --lib', & +' new '//scr//'C --app', & +' new '//scr//'D --test', & +' new '//scr//'E --lib --test ', & +' new '//scr//'F --lib --app', & +' new '//scr//'G --test --app', & +' new '//scr//'BB --lib', & +' new '//scr//'BB --test ', & +' new '//scr//'BB --backfill --test', & +' new '//scr//'CC --test --src --app', & ' new --version', & ' new --help'] integer :: estat, cstat character(len=256) :: message character(len=:),allocatable :: directories(:) +character(len=:),allocatable :: shortdirs(:) character(len=:),allocatable :: expected(:) logical,allocatable :: tally(:) logical :: IS_OS_WINDOWS write(*,'(g0:,1x)')'TEST new SUBCOMMAND (draft):' allocate(tally(0)) - directories=[character(len=80) :: 'A','B','C','D','E','F','G','BB','CC'] + shortdirs=[character(len=80) :: 'A','B','C','D','E','F','G','BB','CC'] + allocate(character(len=80) :: directories(size(shortdirs))) do i=1,size(directories) + directories(i)=scr//trim(shortdirs(i)) if( is_dir(trim(directories(i))) ) then write(*,*)'ERROR:',trim( directories(i) ),' already exists' write(*,*)' you must remove scratch directories before performing this test' @@ -76,31 +81,31 @@ logical :: IS_OS_WINDOWS ! assuming hidden files in .git and .gitignore are ignored for now TESTS: do i=1,size(directories) ! test if expected directory exists - if( .not. is_dir(trim(directories(i))) ) then + if( .not. is_dir(trim( directories(i))) ) then tally=[tally,.false.] write(*,*)'ERROR:',trim( directories(i) ),' is not a directory' else - select case(directories(i)) + select case(shortdirs(i)) case('A'); expected=[ character(len=80)::& - &'A/app','A/fpm.toml','A/README.md','A/src','A/test','A/app/main.f90','A/src/A.f90','A/test/main.f90'] + &'A/app','A/fpm.toml','A/README.md','A/src','A/test','A/app/main.f90','A/src/'//scr//'A.f90','A/test/main.f90'] case('B'); expected=[ character(len=80)::& - &'B/fpm.toml','B/README.md','B/src','B/src/B.f90'] + &'B/fpm.toml','B/README.md','B/src','B/src/'//scr//'B.f90'] case('C'); expected=[ character(len=80)::& &'C/app','C/fpm.toml','C/README.md','C/app/main.f90'] case('D'); expected=[ character(len=80)::& &'D/fpm.toml','D/README.md','D/test','D/test/main.f90'] case('E'); expected=[ character(len=80)::& - &'E/fpm.toml','E/README.md','E/src','E/test','E/src/E.f90','E/test/main.f90'] + &'E/fpm.toml','E/README.md','E/src','E/test','E/src/'//scr//'E.f90','E/test/main.f90'] case('F'); expected=[ character(len=80)::& - &'F/app','F/fpm.toml','F/README.md','F/src','F/app/main.f90','F/src/F.f90'] + &'F/app','F/fpm.toml','F/README.md','F/src','F/app/main.f90','F/src/'//scr//'F.f90'] case('G'); expected=[ character(len=80)::& &'G/app','G/fpm.toml','G/README.md','G/test','G/app/main.f90','G/test/main.f90'] case('BB'); expected=[ character(len=80)::& - &'BB/fpm.toml','BB/README.md','BB/src','BB/test','BB/src/BB.f90','BB/test/main.f90'] + &'BB/fpm.toml','BB/README.md','BB/src','BB/test','BB/src/'//scr//'BB.f90','BB/test/main.f90'] case('CC'); expected=[ character(len=80)::& - &'CC/app','CC/fpm.toml','CC/README.md','CC/src','CC/test','CC/app/main.f90','CC/src/CC.f90','CC/test/main.f90'] + &'CC/app','CC/fpm.toml','CC/README.md','CC/src','CC/test','CC/app/main.f90','CC/src/'//scr//'CC.f90','CC/test/main.f90'] case default - write(*,*)'ERROR: internal error. unknown directory name ',trim(directories(i)) + write(*,*)'ERROR: internal error. unknown directory name ',trim(shortdirs(i)) stop 4 end select !! MSwindows has hidden files in it @@ -109,12 +114,13 @@ logical :: IS_OS_WINDOWS if(size(expected).ne.size(file_names))then write(*,*)'WARNING: unexpected number of files in file list=',size(file_names),' expected ',size(expected) - write(*,'("EXPECTED: ",*(g0:,","))')(trim(expected(j)),j=1,size(expected)) + write(*,'("EXPECTED: ",*(g0:,","))')(scr//trim(expected(j)),j=1,size(expected)) write(*,'("FOUND: ",*(g0:,","))')(trim(file_names(j)%s),j=1,size(file_names)) endif do j=1,size(expected) + expected(j)=scr//expected(j) if(is_os_windows) expected(j)=windows_path(expected(j)) if( .not.(trim(expected(j)).in.file_names) )then tally=[tally,.false.] -- cgit v1.2.3 From 401efe6555d8ebbe6ffa63e8bda43cc8ba42546b Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 18 Oct 2020 09:37:18 -0400 Subject: have new_test.f90 clean up scratch directories --- fpm/test/new_test/new_test.f90 | 30 ++++++++++++++++++++---------- 1 file changed, 20 insertions(+), 10 deletions(-) diff --git a/fpm/test/new_test/new_test.f90 b/fpm/test/new_test/new_test.f90 index 17e269a..8007f7a 100644 --- a/fpm/test/new_test/new_test.f90 +++ b/fpm/test/new_test/new_test.f90 @@ -11,6 +11,7 @@ character(len=*),parameter :: cmdpath = 'build/gfortran_debug/app/fpm' character(len=:),allocatable :: path character(len=*),parameter :: scr = 'fpm_scratch_' character(len=*),parameter :: cmds(*) = [character(len=80) :: & +! run a variety of "fpm new" variations and verify expected files are generated ' new', & ' new no-no', & ' new '//scr//'A', & @@ -38,16 +39,6 @@ logical :: IS_OS_WINDOWS shortdirs=[character(len=80) :: 'A','B','C','D','E','F','G','BB','CC'] allocate(character(len=80) :: directories(size(shortdirs))) - do i=1,size(directories) - directories(i)=scr//trim(shortdirs(i)) - if( is_dir(trim(directories(i))) ) then - write(*,*)'ERROR:',trim( directories(i) ),' already exists' - write(*,*)' you must remove scratch directories before performing this test' - write(*,'(*(g0:,1x))')'directories:',(trim(directories(j)),j=1,size(directories)),'no-no' - stop - endif - enddo - !! SEE IF EXPECTED FILES ARE GENERATED !! Issues: !! o assuming fpm command is in expected path and the new version @@ -55,14 +46,25 @@ logical :: IS_OS_WINDOWS is_os_windows=.false. select case (get_os_type()) case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD) + call execute_command_line('rm -rf fpm_scratch_*',exitstat=estat,cmdstat=cstat,cmdmsg=message) path=cmdpath case (OS_WINDOWS) path=windows_path(cmdpath) is_os_windows=.true. + call execute_command_line('rmdir fpm_scratch_* /s /q',exitstat=estat,cmdstat=cstat,cmdmsg=message) case default write(*,*)'ERROR: unknown OS. Stopping test' stop 2 end select + do i=1,size(directories) + directories(i)=scr//trim(shortdirs(i)) + if( is_dir(trim(directories(i))) ) then + write(*,*)'ERROR:',trim( directories(i) ),' already exists' + write(*,*)' you must remove scratch directories before performing this test' + write(*,'(*(g0:,1x))')'directories:',(trim(directories(j)),j=1,size(directories)),'no-no' + stop + endif + enddo ! execute the fpm(1) commands do i=1,size(cmds) message='' @@ -134,6 +136,14 @@ logical :: IS_OS_WINDOWS endif enddo TESTS + ! clean up scratch files; might want an option to leave them for inspection + select case (get_os_type()) + case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD) + call execute_command_line('rm -rf fpm_scratch_*',exitstat=estat,cmdstat=cstat,cmdmsg=message) + case (OS_WINDOWS) + call execute_command_line('rmdir fpm_scratch_* /s /q',exitstat=estat,cmdstat=cstat,cmdmsg=message) + end select + write(*,'("TALLY=",*(g0))')tally if(all(tally))then write(*,'(*(g0))')'PASSED: all ',count(tally),' tests passed ' -- cgit v1.2.3 From aa2ed841bedd6940a34e425f04857c2fce65ab6c Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 18 Oct 2020 11:45:38 -0400 Subject: suggested help text changes --- docs/index.html | 111 ++++++++++++++++++++++++++++++------------- fpm/src/fpm_command_line.f90 | 48 ++++++++++--------- 2 files changed, 103 insertions(+), 56 deletions(-) diff --git a/docs/index.html b/docs/index.html index f351396..edd199c 100644 --- a/docs/index.html +++ b/docs/index.html @@ -75,7 +75,7 @@ a.existingWikiWord[title]{ //border: 1px dashed #BBB; } 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 +Most significantly fpm(1) lets you draw 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. @@ -93,7 +93,7 @@ being used you need network connectivity to rebuild from scratch.

-Valid fpm subcommands are: +Valid fpm(1) subcommands are:

      build [--release] [--list]
@@ -128,12 +128,12 @@ optimization flags are used.
 
--list -List candidates instead of building or running them. -On the fpm command this shows a brief list of subcommands. +List candidates instead of building or running them. On +the fpm(1) command this shows a brief list of subcommands.
-- ARGS
  -Arguments to pass to executables/tests +Arguments to pass to executables.
--help @@ -195,25 +195,52 @@ The fpm(1) home page at https://github.com/fortran-lang/fpm
-"fpm new" creates a new programming project in a new directory. +"fpm new" creates and populates a new programming project directory. +It +
+ + + + + + + +
+o + +creates a directory with the specified name +
+o + +runs the command "git init" in that directory +
+o + +populates the directory with the default project directories +
+o + +adds sample Fortran source files +
+o + +adds a ".gitignore" file for ignoring the build/ directory +(where fpm-generated output will be placed) +

-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): +The basic default file structure is

-    NAME/
-      fpm.toml
-      .gitignore
-      src/
-          NAME.f90
-      app/
-          main.f90
-      test/
-          main.f90
+     NAME/
+       fpm.toml
+       .gitignore
+       src/
+           NAME.f90
+       app/
+           main.f90
+       test/
+           main.f90
 

Remember to update the information in the sample "fpm.toml" @@ -747,19 +774,37 @@ display a short list of fpm(1) subcommands
The fpm(1) home page at https://github.com/fortran-lang/fpm -

-

-   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:     Linux
-
-


-
untitled () October 17, 2020
Generated by manServer 1.08 from x.1 using man macros. -

+ + + +
+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:
  +Linux +


+
untitled () October 18, 2020
Generated by manServer 1.08 from d68c10d7-7027-443c-9855-663219ca410d using man macros. +

diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 0efc076..1975602 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -327,7 +327,7 @@ contains ' 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 ', & + ' Most significantly fpm(1) lets you draw 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. ', & @@ -340,7 +340,7 @@ contains ' being used you need network connectivity to rebuild from scratch. ', & ' ', & 'SUBCOMMANDS ', & - ' Valid fpm subcommands are: ', & + ' Valid fpm(1) subcommands are: ', & ' ', & ' build [--release] [--list] ', & ' Compile the packages into the "build/" directory. ', & @@ -361,9 +361,9 @@ contains ' in "build/*_debug/". When this flag is present build ', & ' output goes into "build/*_release/" and common compiler ', & ' optimization flags are used. ', & - ' --list List candidates instead of building or running them. ', & - ' On the fpm command this shows a brief list of subcommands.', & - ' -- ARGS Arguments to pass to executables/tests ', & + ' --list List candidates instead of building or running them. On ', & + ' the fpm(1) command this shows a brief list of subcommands.', & + ' -- ARGS Arguments to pass to executables. ', & ' --help Show help text and exit. Valid for all subcommands. ', & ' --version Show version information and exit. Valid for all ', & ' subcommands. ', & @@ -542,24 +542,26 @@ contains ' fpm new --help|--version ', & ' ', & 'DESCRIPTION ', & - ' "fpm new" creates a new programming project in a new directory. ', & - ' ', & - ' 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 ', & + ' "fpm new" creates and populates a new programming project directory. ', & + ' It ', & + ' o creates a directory with the specified name ', & + ' o runs the command "git init" in that directory ', & + ' o populates the directory with the default project directories ', & + ' o adds sample Fortran source files ', & + ' o adds a ".gitignore" file for ignoring the build/ directory ', & + ' (where fpm-generated output will be placed) ', & + ' ', & + ' The basic default file structure is ', & + ' ', & + ' 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 your name and e-mail address. ', & -- cgit v1.2.3 From e6c086df2a8a8db08e2fc6ad6bbee4bf6ee27a35 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Sun, 18 Oct 2020 11:55:04 -0400 Subject: delete HTML version of help text, change/remove use of !! --- docs/index.html | 811 ------------------------------------------- fpm/src/fpm.f90 | 26 +- fpm/src/fpm/cmd/new.f90 | 9 +- fpm/src/fpm_command_line.f90 | 2 +- 4 files changed, 13 insertions(+), 835 deletions(-) delete mode 100644 docs/index.html diff --git a/docs/index.html b/docs/index.html deleted file mode 100644 index edd199c..0000000 --- a/docs/index.html +++ /dev/null @@ -1,811 +0,0 @@ - - - - - - -
[UP]
-
-
-
-


Manual Reference Pages  - untitled ()

-
- - -

NAME

- -
-
-fpm(1) - A Fortran package manager and build system -

-

- - -

SYNOPSIS

- -
-
-fpm SUBCOMMAND [SUBCOMMAND_OPTIONS] -

-fpm --help|--version|--list -

- - -

DESCRIPTION

- -
-
-fpm(1) is a package manager that helps you create Fortran projects -from source. -

-Most significantly fpm(1) lets you draw 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 registered projects. -

-All output goes into the directory "build/" which can generally be -removed and rebuilt if required. Note that if external packages are -being used you need network connectivity to rebuild from scratch. -

- - -

SUBCOMMANDS

- -
-
-Valid fpm(1) subcommands are: -

-

-     build [--release] [--list]
-                     Compile the packages into the "build/" directory.
-     new NAME [--lib|--src] [--app] [--test] [--backfill]
-                     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
-     list [--list]   Display brief descriptions of all subcommands.
-

-

-
- - -

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/*_debug/". When this flag is present build -output goes into "build/*_release/" and common compiler -optimization flags are used. -
---list -List candidates instead of building or running them. On -the fpm(1) command this shows a brief list of subcommands. -
--- ARGS
  -Arguments to pass to executables. -
---help -Show help text and exit. Valid for all subcommands. -
---version
  -Show version information and exit. Valid for all -subcommands. -
- - -

EXAMPLES

- -
-
-sample commands: -

-

-    fpm new mypackage --app --test
-    fpm build
-    fpm test
-    fpm run
-    fpm new --help
-    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 -
- - -

NAME

- -
-
-new(1) - the fpm(1) subcommand to initialize a new project -
- - -

SYNOPSIS

- -
-
-fpm new NAME [--lib|--src] [--app] [--test] [--backfill] -

-fpm new --help|--version -

- - -

DESCRIPTION

- -
-
-"fpm new" creates and populates a new programming project directory. -It -
- - - - - - - -
-o - -creates a directory with the specified name -
-o - -runs the command "git init" in that directory -
-o - -populates the directory with the default project directories -
-o - -adds sample Fortran source files -
-o - -adds a ".gitignore" file for ignoring the build/ directory -(where fpm-generated output will be placed) -
-

-The basic default file structure is -

-

-     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 your name and e-mail address. -
- - -

OPTIONS

- -
-
- - - - - - - - - - -
-NAME -the name of the project directory to create. The name -must be a valid Fortran name composed of 1 to 63 -ASCII alphanumeric characters and underscores, -starting with a letter. -
-The default is to create all of the src/, app/, and test/ -directories. If any of the following options are specified -then only selected subdirectories are generated: -
---lib,--src
  -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 programs. -
---help -print this help and exit -
---version
  -print program version information and exit -
- - -

EXAMPLES

- -
-
-Sample use -

-

-   fpm new myproject  # create new project directory and seed it
-   cd myproject       # Enter the new directory
-   # and run commands such as
-   fpm build
-   fpm run            # run example application program
-   fpm test           # run example test program
-

-

-
- - -

SEE ALSO

- -
-
-The fpm(1) home page at https://github.com/fortran-lang/fpm -

-Registered packages are at https://fortran-lang.org/packages -

- - -

NAME

- -
-
-build(1) - the fpm(1) subcommand to build a project -

-

- - -

SYNOPSIS

- -
-
-fpm build [--release]|[-list] -

-fpm build --help|--version -

- - -

DESCRIPTION

- -
-
-The "fpm build" command -
- - - - - -
-o - -Fetches any dependencies -
-o - -Scans your sources -
-o - -Builds them in the proper order -
-

-The Fortran source files are assumed by default to be in -

- - - - - -
-o - -src/ for modules and procedure source -
-o - -app/ main program(s) for applications -
-o - -test/ main program(s) and support files for project tests -Changed or new files found are rebuilt. The results are placed in -the build/ directory. -
-

-Non-default pathnames and remote dependencies are used if -specified in the "fpm.toml" file. -

- - -

OPTIONS

- -
-
- - - - - -
---release
  -build in build/*_release instead of build/*_debug with -high optimization instead of full debug options. -
---list -list candidates instead of building or running them -
---help -print this help and exit -
---version
  -print program version information and exit -
- - -

EXAMPLES

- -
-
-Sample commands: -

-

-  fpm build           # build with debug options
-  fpm build --release # build with high optimization
-

-

-
- - -

SEE ALSO

- -
-
-The fpm(1) home page at https://github.com/fortran-lang/fpm -
- - -

NAME

- -
-
-run(1) - the fpm(1) subcommand to run project applications -

-

- - -

SYNOPSIS

- -
-
-fpm run [NAME(s)] [--release] [-- ARGS] -

-fpm run --help|--version -

- - -

DESCRIPTION

- -
-
-Run applications you have built in your fpm(1) project. -
- - -

OPTIONS

- -
-
- - - - - -
-NAME(s) -optional list of specific names to execute. -The default is to run all the applications in app/ -or the programs listed in the "fpm.toml" file. -
---release
  -selects the optimized build instead of the debug -build. -
---list -list candidates instead of building or running them -
--- ARGS
  -optional arguments to pass to the program(s). -The same arguments are passed to all names -specified. -
- - -

EXAMPLES

- -
-
-run fpm(1) project applications -

-

-  # run default programs in /app or as specified in "fpm.toml"
-  fpm run
-

- # run a specific program and pass arguments to the command - fpm run mytest -- -x 10 -y 20 --title "my title line" -

- # run production version of two applications - fpm run prg1 prg2 --release -

-

-
- - -

SEE ALSO

- -
-
-The fpm(1) home page at https://github.com/fortran-lang/fpm -
- - -

NAME

- -
-
-test(1) - the fpm(1) subcommand to run project tests -

-

- - -

SYNOPSIS

- -
-
-fpm test [NAME(s)] [--release] [--list] [-- ARGS] -

-fpm test --help|--version -

- - -

DESCRIPTION

- -
-
-Run applications you have built to test your project. -
- - -

OPTIONS

- -
-
- - - - - -
-NAME(s) -optional list of specific test names to execute. -The default is to run all the tests in test/ -or the tests listed in the "fpm.toml" file. -
---release
  -selects the optimized build instead of the debug -build. -
---list -list candidates instead of building or running them -
--- ARGS
  -optional arguments to pass to the test program(s). -The same arguments are passed to all test names -specified. -
- - -

EXAMPLES

- -
-
-run tests -

-

- # run default tests in /test or as specified in "fpm.toml"
- fpm test
-

- # run a specific test and pass arguments to the command - fpm test mytest -- -x 10 -y 20 --title "my title line" -

- fpm test tst1 tst2 --release # production version of two tests -

-

-
- - -

SEE ALSO

- -
-
-The fpm(1) home page at https://github.com/fortran-lang/fpm -
- - -

NAME

- -
-
-help(1) - the fpm(1) subcommand to display help -

-

- - -

SYNOPSIS

- -
-
-fpm help [fpm] [new] [build] [run] [test] [help] [version] [manual] -

-fpm help [fortran|fortran_manual][FORTRAN_INTRINSIC_NAME] -

- - -

DESCRIPTION

- -
-
-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. 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. "fortran_manual" 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 fortran_manual # all Fortran documentation
-

-

-
- - -

SEE ALSO

- -
-
-The fpm(1) home page at https://github.com/fortran-lang/fpm -
- - -

NAME

- -
-
-list(1) - list summary of fpm(1) subcommands -

-

- - -

SYNOPSIS

- -
-
-fpm list [-list] -

-fpm list --help|--version -

- - -

DESCRIPTION

- -
-
-Display a short description for each fpm(1) subcommand. -
- - -

OPTIONS

- -
-
- - -
---list -display a list of command options as well. This is the -same output as generated by "fpm --list". -
- - -

EXAMPLES

- -
-
-display a short list of fpm(1) subcommands -

-

-  fpm list
-  fpm --list
-

-

-
- - -

SEE ALSO

- -
-
-The fpm(1) home page at https://github.com/fortran-lang/fpm -
- - - -
-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:
  -Linux -


-
untitled () October 18, 2020
Generated by manServer 1.08 from d68c10d7-7027-443c-9855-663219ca410d using man macros. -

-
-
- - diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index 4442923..7ab28df 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -202,7 +202,7 @@ logical :: list stop endif else - !! expand names, duplicates are a problem?? + !*! expand names, duplicates are a problem?? allocate(foundit(size(settings%name))) foundit=.false. FINDIT: do i=1,size(package%executable) @@ -217,18 +217,15 @@ logical :: list do i=1,size(settings%name) if(.not.foundit(i))then write(stderr,'(*(g0,1x))')'fpm::run:executable',trim(settings%name(i)),'not located' - !!elseif(settings%debug)then - !! write(stderr,'(*(g0,1x))')'fpm::run:executable',trim(settings%name(i)),'located at',newwords(i),& - !! & merge('exists ','does not exist',exists(trim(settings%name(i)))) endif enddo if(allocated(foundit))deallocate(foundit) endif do i=1,size(newwords) - !! list is a new option for use with xargs, to move files to production area, valgrind, gdb, ls -l, .... - !! maybe add as --mask and could do --mask 'echo %xx' or --mask 'cp %XX /usr/local/bin/' an so on - !! default if blank would be filename uptodate|needs|updated|doesnotexist creation_date, ... - !! or maybe just list filenames so can pipe through xargs, and so on + !*! list is a new option for use with xargs, to move files to production area, valgrind, gdb, ls -l, .... + !*! maybe add as --mask and could do --mask 'echo %xx' or --mask 'cp %XX /usr/local/bin/' an so on + !*! default if blank would be filename uptodate|needs|updated|doesnotexist creation_date, ... + !*! or maybe just list filenames so can pipe through xargs, and so on if(settings%list)then write(stderr,'(*(g0,1x))')'fpm::run:executable expected at',newwords(i),& & merge('exists ','does not exist',exists(newwords(i))) @@ -287,7 +284,7 @@ logical :: list stop endif else - !! expand names, duplicates are a problem?? + !*! expand names, duplicates are a problem?? allocate(foundit(size(settings%name))) foundit=.false. FINDIT: do i=1,size(package%test) @@ -302,18 +299,15 @@ logical :: list do i=1,size(settings%name) if(.not.foundit(i))then write(stderr,'(*(g0,1x))')'fpm::run:test',trim(settings%name(i)),'not located' - !!elseif(settings%debug)then - !! write(stderr,'(*(g0,1x))')'fpm::run:test',trim(settings%name(i)),'located at',newwords(i),& - !! & merge('exists ','does not exist',exists(trim(settings%name(i)))) endif enddo if(allocated(foundit))deallocate(foundit) endif do i=1,size(newwords) - !! list is a new option for use with xargs, to move files to production area, valgrind, gdb, ls -l, .... - !! maybe add as --mask and could do --mask 'echo %xx' or --mask 'cp %XX /usr/local/bin/' an so on - !! default if blank would be filename uptodate|needs|updated|doesnotexist creation_date, ... - !! or maybe just list filenames so can pipe through xargs, and so on + !*! list is a new option for use with xargs, to move files to production area, valgrind, gdb, ls -l, .... + !*! maybe add as --mask and could do --mask 'echo %xx' or --mask 'cp %XX /usr/local/bin/' an so on + !*! default if blank would be filename uptodate|needs|updated|doesnotexist creation_date, ... + !*! or maybe just list filenames so can pipe through xargs, and so on if(settings%list)then write(stderr,'(*(g0,1x))')'fpm::run:test expected at',newwords(i),& & merge('exists ','does not exist',exists(newwords(i))) diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 index eb1a532..91145d8 100644 --- a/fpm/src/fpm/cmd/new.f90 +++ b/fpm/src/fpm/cmd/new.f90 @@ -38,15 +38,10 @@ character(len=8) :: date ! change to new directory as a test. System dependent potentially call run('cd '//settings%name) - !! NOTE: need some system routines to handle filenames like "." - !! like realpath() or getcwd(). + !*! NOTE: need some system routines to handle filenames like "." + !*! like realpath() or getcwd(). bname=basename(settings%name) - !! weird gfortran bug?? lines truncated to concatenated string length, - !! not 80 - !! hit some weird gfortran bug when littlefile data was an argument - !! to warnwrite(3f), ok when a variable - ! create NAME/.gitignore file call warnwrite(join_path(settings%name, '.gitignore'), ['build/*']) diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 1975602..f8d6f4a 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -140,7 +140,7 @@ contains & 'USAGE: fpm new NAME [--lib|--src] [--app] [--test] [--backfill]' stop 2 end select - !! canon_path is not converting ".", etc. + !*! canon_path is not converting ".", etc. name=canon_path(name) if( .not.is_fortran_name(basename(name)) )then write(stderr,'(g0)') [ character(len=72) :: & -- cgit v1.2.3 From 9d5b03d192e50831e2046c7843174dff5ca2a37a Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Tue, 20 Oct 2020 08:16:05 -0400 Subject: remove intrinsics documentation --- fpm/fpm.toml | 4 ---- fpm/src/fpm_command_line.f90 | 26 ++------------------------ 2 files changed, 2 insertions(+), 28 deletions(-) diff --git a/fpm/fpm.toml b/fpm/fpm.toml index f5fd443..fc3a381 100644 --- a/fpm/fpm.toml +++ b/fpm/fpm.toml @@ -14,10 +14,6 @@ tag = "v0.2" git = "https://github.com/urbanjost/M_CLI2.git" rev = "649075aceb97f997665a1a4656514fd2e9b4becc" -[dependencies.fortran-intrinsic-manpages] -git = "https://github.com/urbanjost/M_intrinsics.git" -rev = "a758ebdd0487e8cab5b4894fbf375f87147c44b5" - [[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 f8d6f4a..cf7c761 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -3,7 +3,6 @@ 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, canon_path use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, & @@ -203,14 +202,8 @@ contains help_text=[character(len=widest) :: help_text, help_list] help_text=[character(len=widest) :: help_text, version_text] case default - ! note help_intrinsics is returning a fixed-length array - ! to avoid compiler issues 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 + & 'ERROR: unknown help topic "'//trim(unnamed(i))//'"'] end select enddo call printhelp(help_text) @@ -332,7 +325,7 @@ contains ' 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 ', & + ' See the fpm(1) repository at https://fortran-lang.org/packages/fpm ', & ' for a listing of registered projects. ', & ' ', & ' All output goes into the directory "build/" which can generally be ', & @@ -493,8 +486,6 @@ contains 'SYNOPSIS ', & ' fpm help [fpm] [new] [build] [run] [test] [help] [version] [manual] ', & ' ', & - ' fpm help [fortran|fortran_manual][FORTRAN_INTRINSIC_NAME] ', & - ' ', & 'DESCRIPTION ', & ' The "fpm help" command is an alternative to the --help parameter ', & ' on the fpm(1) command and its subcommands. ', & @@ -508,12 +499,6 @@ contains ' ', & ' 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. "fortran_manual" 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: ', & @@ -523,13 +508,6 @@ contains ' 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 fortran_manual # all Fortran documentation ', & - ' ', & 'SEE ALSO ', & ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', & '' ] -- cgit v1.2.3