diff options
author | init current directory[i] <urbanjost@comcast.net> | 2020-12-18 12:01:44 -0500 |
---|---|---|
committer | init current directory[i] <urbanjost@comcast.net> | 2020-12-18 12:01:44 -0500 |
commit | 4e5dc0d49cbd66785c42d938458cf982cf3ecaf3 (patch) | |
tree | 80426c77fce00cddebd3a5c80384adeaab2c96dc | |
parent | 483f23b56e8806cfcd2664449030a389ddf7b560 (diff) | |
download | fpm-4e5dc0d49cbd66785c42d938458cf982cf3ecaf3.tar.gz fpm-4e5dc0d49cbd66785c42d938458cf982cf3ecaf3.zip |
Update subcommand "new" to reflect the addition of support for the example/ directory
The "new" subcommand was updated with an --example switch in line with the other
standard directories. Corresponding changes were made to the documentation and
the test of the "new" subcommand. This reflexs the addition of --example to the
"run" subcommand and the model changes to automatically build applications found
in the example/ directory.
-rw-r--r-- | fpm/src/fpm/cmd/new.f90 | 22 | ||||
-rw-r--r-- | fpm/src/fpm_command_line.f90 | 48 | ||||
-rw-r--r-- | fpm/test/help_test/help_test.f90 | 19 | ||||
-rw-r--r-- | fpm/test/new_test/new_test.f90 | 5 |
4 files changed, 66 insertions, 28 deletions
diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 index 04cd7d5..7e21e92 100644 --- a/fpm/src/fpm/cmd/new.f90 +++ b/fpm/src/fpm/cmd/new.f90 @@ -107,6 +107,28 @@ character(len=8) :: date call warnwrite(join_path(settings%name, 'test/main.f90'), littlefile) endif + if(settings%with_example)then + + ! create NAME/example or stop + call mkdir(join_path(settings%name, 'example')) + ! create next section of fpm.toml + message=[character(len=80) :: message, & + &'[[example]] ', & + &'name="demo" ', & + &'source-dir="example" ', & + &'main="demo.f90" ', & + &''] + + littlefile=[character(len=80) :: & + &'program demo', & + &'implicit none', & + &'', & + &'print *, "Put some examples in here!"', & + &'end program demo'] + ! create NAME/example/demo.f90 + call warnwrite(join_path(settings%name, 'example/demo.f90'), littlefile) + endif + if(settings%with_executable)then ! create next section of fpm.toml call mkdir(join_path(settings%name, 'app')) diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index a733fc2..87b80b9 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -54,6 +54,7 @@ type, extends(fpm_cmd_settings) :: fpm_new_settings logical :: with_executable=.false. logical :: with_test=.false. logical :: with_lib=.true. + logical :: with_example=.false. logical :: backfill=.true. end type @@ -203,6 +204,7 @@ contains & --lib F & & --app F & & --test F & + & --example F & & --backfill F& & --verbose F',& & help_new, version_text) @@ -210,14 +212,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] [--example] [--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] [--example] [--backfill]' stop 2 end select !*! canon_path is not converting ".", etc. @@ -234,13 +236,14 @@ contains allocate(fpm_new_settings :: cmd_settings) - if (any( specified(['src ','lib ','app ','test']) ) )then + if (any( specified([character(len=10) :: 'src','lib','app','test','example']) ) )then cmd_settings=fpm_new_settings(& & backfill=lget('backfill'), & & name=name, & & with_executable=lget('app'), & & with_lib=any([lget('lib'),lget('src')]), & & with_test=lget('test'), & + & with_example=lget('example'), & & verbose=lget('verbose') ) else cmd_settings=fpm_new_settings(& @@ -249,6 +252,7 @@ contains & with_executable=.true., & & with_lib=.true., & & with_test=.true., & + & with_example=.true., & & verbose=lget('verbose') ) endif @@ -476,7 +480,7 @@ contains ' ', & ' build [--compiler COMPILER_NAME] [--release] [--list] ', & ' help [NAME(s)] ', & - ' new NAME [--lib|--src] [--app] [--test] [--backfill] ', & + ' new NAME [--lib|--src] [--app] [--test] [--example] [--backfill] ', & ' update [NAME(s)] [--fetch-only] [--clean] [--verbose] ', & ' list [--list] ', & ' run [[--target] NAME(s)] [--release] [--runner "CMD"] [--list] [--example] ', & @@ -588,14 +592,16 @@ contains ' ', & ' Their syntax is ', & ' ', & - ' build [--release] [--list] [--compiler COMPILER_NAME] ', & - ' new NAME [--lib|--src] [--app] [--test] [--backfill] ', & - ' update [NAME(s)] [--fetch-only] [--clean] ', & - ' run|test [[--target] NAME(s)] [--release] [--list] ', & - ' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', & - ' help [NAME(s)] ', & - ' list [--list] ', & - ' install [--release] [--no-rebuild] [--prefix PATH] [options] ', & + ' build [--release] [--list] [--compiler COMPILER_NAME] ', & + ' new NAME [--lib|--src] [--app] [--test] [--example] [--backfill] ', & + ' update [NAME(s)] [--fetch-only] [--clean] ', & + ' run [[--target] NAME(s)] [--release] [--list] [--example] ', & + ' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', & + ' test [[--target] NAME(s)] [--release] [--list] ', & + ' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', & + ' help [NAME(s)] ', & + ' list [--list] ', & + ' install [--release] [--no-rebuild] [--prefix PATH] [options] ', & ' ', & 'SUBCOMMAND OPTIONS ', & ' --release Builds or runs in release mode (versus debug mode). fpm(1)', & @@ -730,6 +736,7 @@ contains ' 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 ', & + ' o example/ main program(s) for examples and demonstrations ', & ' Changed or new files found are rebuilt. The results are placed in ', & ' the build/ directory. ', & ' ', & @@ -788,7 +795,7 @@ contains 'NAME ', & ' 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] [--example] [--backfill] ', & ' ', & ' fpm new --help|--version ', & ' ', & @@ -813,6 +820,8 @@ contains ' main.f90 ', & ' test/ ', & ' main.f90 ', & + ' example/ ', & + ' demo.f90 ', & ' ', & ' Remember to update the information in the sample "fpm.toml" ', & ' file with your name and e-mail address. ', & @@ -823,7 +832,7 @@ contains ' ASCII alphanumeric characters and underscores, ', & ' starting with a letter. ', & ' ', & - ' The default is to create all of the src/, app/, and test/ ', & + ' The default is to create all of the src/, app/, test/, and example/ ', & ' directories. If any of the following options are specified ', & ' then only selected subdirectories are generated: ', & ' ', & @@ -834,8 +843,10 @@ contains ' --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. ', & + ' --example create directory example/ and a placeholder program ', & + ' for use with the subcommand "run --example". ', & ' ', & - ' So the default is equivalent to "fpm NAME --lib --app --test". ', & + ' So the default is equivalent to "fpm NAME --lib --app --test --example" ', & ' ', & ' --backfill By default the directory must not exist. If this ', & ' option is present the directory may pre-exist and ', & @@ -843,7 +854,7 @@ contains ' 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. ', & + ' app/, test/ and example/ directories and programs. ', & ' ', & ' --help print this help and exit ', & ' --version print program version information and exit ', & @@ -855,8 +866,9 @@ contains ' 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 ', & + ' fpm run # run example application program(s) ', & + ' fpm test # run example test program(s) ', & + ' fpm run --example # run example program(s) ', & '' ] help_test=[character(len=80) :: & 'NAME ', & diff --git a/fpm/test/help_test/help_test.f90 b/fpm/test/help_test/help_test.f90 index b9c1645..a44786c 100644 --- a/fpm/test/help_test/help_test.f90 +++ b/fpm/test/help_test/help_test.f90 @@ -1,5 +1,5 @@ program help_test -! note hardcoded len=512 instead of len=: in this test is a work-around a gfortran bug in old +! note hardcoded len=k1 instead of len=: in this test is a work-around a gfortran bug in old ! pre-v8.3 versions use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit implicit none @@ -7,12 +7,13 @@ integer :: i, j integer :: be, af character(len=:),allocatable :: path integer :: estat, cstat -character(len=512) :: message +integer,parameter :: k1=132 +character(len=k1) :: message logical,allocatable :: tally(:) !intel-bug!character(len=:),allocatable :: book1(:), book2(:) -character(len=512),allocatable :: book1(:), book2(:), book3(:) +character(len=k1),allocatable :: book1(:), book2(:), book3(:) !intel-bug!character(len=:),allocatable :: page1(:) -character(len=512),allocatable :: page1(:) +character(len=k1),allocatable :: page1(:) integer :: lines integer :: chars ! run a variety of "fpm help" variations and verify expected files are generated @@ -185,7 +186,7 @@ subroutine wipe(filename) character(len=*),intent(in) :: filename integer :: ios integer :: lun -character(len=512) :: message +character(len=k1) :: message open(file=filename,newunit=lun,iostat=ios,iomsg=message) if(ios.eq.0)then close(unit=lun,iostat=ios,status='delete',iomsg=message) @@ -203,7 +204,7 @@ implicit none character(*),intent(in) :: filename ! filename to shlep character(len=1),allocatable,intent(out) :: text(:) ! array to hold file integer :: nchars, igetunit, ios -character(len=512) :: message +character(len=k1) :: message character(len=4096) :: local_filename ios=0 nchars=0 @@ -240,7 +241,7 @@ subroutine swallow(FILENAME,pageout) implicit none character(len=*),intent(in) :: FILENAME ! file to read !intel-bug!character(len=:),allocatable,intent(out) :: pageout(:) ! page to hold file in memory -character(len=512),allocatable,intent(out) :: pageout(:) ! page to hold file in memory +character(len=k1),allocatable,intent(out) :: pageout(:) ! page to hold file in memory character(len=1),allocatable :: text(:) ! array to hold file in memory call slurp(FILENAME,text) ! allocate character array and copy file into it @@ -259,7 +260,7 @@ function page(array) result (table) character(len=1),intent(in) :: array(:) !intel-bug!character(len=:),allocatable :: table(:) -character(len=512),allocatable :: table(:) +character(len=k1),allocatable :: table(:) integer :: i integer :: linelength integer :: length @@ -291,7 +292,7 @@ character(len=1),parameter :: cr=char(13) if(allocated(table))deallocate(table) !intel-bug!allocate(character(len=linelength) :: table(lines)) - allocate(character(len=512) :: table(lines)) + allocate(character(len=k1) :: table(lines)) table=' ' linecount=1 position=1 diff --git a/fpm/test/new_test/new_test.f90 b/fpm/test/new_test/new_test.f90 index 2220b43..2dfc11e 100644 --- a/fpm/test/new_test/new_test.f90 +++ b/fpm/test/new_test/new_test.f90 @@ -21,6 +21,7 @@ character(len=*),parameter :: cmds(*) = [character(len=80) :: & ' new '//scr//'E --lib --test ', & ' new '//scr//'F --lib --app', & ' new '//scr//'G --test --app', & +' new '//scr//'H --example', & ' new '//scr//'BB --lib', & ' new '//scr//'BB --test ', & ' new '//scr//'BB --backfill --test', & @@ -38,7 +39,7 @@ logical :: IS_OS_WINDOWS cmdpath = get_command_path() allocate(tally(0)) - shortdirs=[character(len=80) :: 'A','B','C','D','E','F','G','BB','CC'] + shortdirs=[character(len=80) :: 'A','B','C','D','E','F','G','H','BB','CC'] allocate(character(len=80) :: directories(size(shortdirs))) !! SEE IF EXPECTED FILES ARE GENERATED @@ -104,6 +105,8 @@ logical :: IS_OS_WINDOWS &'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('H'); expected=[ character(len=80)::& + &'H/example','H/fpm.toml','H/README.md','H/example/demo.f90'] case('BB'); expected=[ character(len=80)::& &'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)::& |