diff options
author | Laurence Kedward <laurence.kedward@bristol.ac.uk> | 2020-10-16 16:19:29 +0100 |
---|---|---|
committer | GitHub <noreply@github.com> | 2020-10-16 16:19:29 +0100 |
commit | 49de89e8608da15a04bed388e2d1774e1737acd8 (patch) | |
tree | 023e99c07b2c08fd9d4301fb82e5b18708a1f96d | |
parent | d3a65e36b28808c2c51ae41fc107f1179e27a08c (diff) | |
parent | 9d16e5d7292109efb036697224c08faf28de2d2c (diff) | |
download | fpm-49de89e8608da15a04bed388e2d1774e1737acd8.tar.gz fpm-49de89e8608da15a04bed388e2d1774e1737acd8.zip |
Merge pull request #203 from urbanjost/urbanjs
refactor fpm.f90 to separate subcommand new into fpm_new_subcommand.f90
-rw-r--r-- | fpm/app/main.f90 | 3 | ||||
-rw-r--r-- | fpm/src/fpm.f90 | 164 | ||||
-rw-r--r-- | fpm/src/fpm/cmd/new.f90 | 164 | ||||
-rw-r--r-- | fpm/src/fpm_command_line.f90 | 5 | ||||
-rw-r--r-- | fpm/test/cli_test/cli_test.f90 | 3 |
5 files changed, 175 insertions, 164 deletions
diff --git a/fpm/app/main.f90 b/fpm/app/main.f90 index be9b805..9982028 100644 --- a/fpm/app/main.f90 +++ b/fpm/app/main.f90 @@ -7,7 +7,8 @@ use fpm_command_line, only: & fpm_test_settings, & fpm_install_settings, & get_command_line_settings -use fpm, only: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test +use fpm, only: cmd_build, cmd_install, cmd_run, cmd_test +use fpm_cmd_new, only: cmd_new implicit none diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index 4db35ba..4442923 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -4,8 +4,8 @@ use fpm_strings, only: string_t, str_ends_with use fpm_backend, only: build_package use fpm_command_line, only: fpm_build_settings, fpm_new_settings, & fpm_run_settings, fpm_install_settings, fpm_test_settings -use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS -use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename, mkdir +use fpm_environment, only: run +use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, & FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, & FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST @@ -16,12 +16,10 @@ use fpm_manifest, only : get_package_data, default_executable, & default_library, package_t, default_test use fpm_error, only : error_t use fpm_manifest_test, only : test_t -use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, & - & stdout=>output_unit, & - & stderr=>error_unit +use,intrinsic :: iso_fortran_env, only : stderr=>error_unit implicit none private -public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test +public :: cmd_build, cmd_install, cmd_run, cmd_test contains @@ -168,160 +166,6 @@ type(fpm_install_settings), intent(in) :: settings error stop 8 end subroutine cmd_install - -subroutine cmd_new(settings) ! --with-executable F --with-test F ' -type(fpm_new_settings), intent(in) :: settings -integer :: ierr -character(len=:),allocatable :: bname ! baeename of NAME -character(len=:),allocatable :: message(:) -character(len=:),allocatable :: littlefile(:) - - call mkdir(settings%name) ! make new directory - call run('cd '//settings%name) ! change to new directory as a test. New OS routines to improve this; system dependent potentially - !! 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 - - call warnwrite(join_path(settings%name, '.gitignore'), ['build/*']) ! create NAME/.gitignore file - - littlefile=[character(len=80) :: '# '//bname, 'My cool new project!'] - - call warnwrite(join_path(settings%name, 'README.md'), littlefile) ! create NAME/README.md - - message=[character(len=80) :: & ! start building NAME/fpm.toml - &'name = "'//bname//'" ', & - &'version = "0.1.0" ', & - &'license = "license" ', & - &'author = "Jane Doe" ', & - &'maintainer = "jane.doe@example.com" ', & - &'copyright = "2020 Jane Doe" ', & - &' ', & - &''] - - if(settings%with_lib)then - call mkdir(join_path(settings%name,'src') ) - message=[character(len=80) :: message, & ! create next section of fpm.toml - &'[library] ', & - &'source-dir="src" ', & - &''] - littlefile=[character(len=80) :: & ! create placeholder module src/bname.f90 - &'module '//bname, & - &' implicit none', & - &' private', & - &'', & - &' public :: say_hello', & - &'contains', & - &' subroutine say_hello', & - &' 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 - 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 - &'[[test]] ', & - &'name="runTests" ', & - &'source-dir="test" ', & - &'main="main.f90" ', & - &''] - - 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 - 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 - &'[[executable]] ', & - &'name="'//bname//'" ', & - &'source-dir="app" ', & - &'main="main.f90" ', & - &''] - - littlefile=[character(len=80) :: & - &'program main', & - &' use '//bname//', only: say_hello', & - &'', & - &' implicit none', & - &'', & - &' call say_hello', & - &'end program main'] - 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 -contains - -subroutine warnwrite(fname,data) -character(len=*),intent(in) :: fname -character(len=*),intent(in) :: data(:) - - if(.not.exists(fname))then - call filewrite(fname,data) - else - write(stderr,'(*(g0,1x))')'fpm::new<WARNING>',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 -character(len=*),intent(in) :: filename -character(len=*),intent(in) :: filedata(:) -integer :: lun, i, ios -character(len=256) :: message - - message=' ' - ios=0 - 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 - & iostat=ios, & - & iomsg=message) - else - lun=stdout - ios=0 - endif - if(ios.ne.0)then - write(stderr,'(*(a:,1x))')'*filewrite* error:',filename,trim(message) - error stop 1 - endif - do i=1,size(filedata) ! write file - write(lun,'(a)',iostat=ios,iomsg=message)trim(filedata(i)) - if(ios.ne.0)then - write(stderr,'(*(a:,1x))')'*filewrite* error:',filename,trim(message) - error stop 4 - endif - enddo - close(unit=lun,iostat=ios,iomsg=message) ! close file - if(ios.ne.0)then - write(stderr,'(*(a:,1x))')'*filewrite* error:',trim(message) - error stop 2 - endif -end subroutine filewrite - -end subroutine cmd_new - - subroutine cmd_run(settings) type(fpm_run_settings), intent(in) :: settings character(len=:),allocatable :: release_name, cmd, fname diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90 new file mode 100644 index 0000000..fc4c93e --- /dev/null +++ b/fpm/src/fpm/cmd/new.f90 @@ -0,0 +1,164 @@ +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,intrinsic :: iso_fortran_env, only : stderr=>error_unit +implicit none +private +public :: cmd_new + +contains + +subroutine cmd_new(settings) ! --with-executable F --with-test F ' +type(fpm_new_settings), intent(in) :: settings +character(len=:),allocatable :: bname ! baeename of NAME +character(len=:),allocatable :: message(:) +character(len=:),allocatable :: littlefile(:) + + call mkdir(settings%name) ! make new directory + 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) + + !! 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 + + littlefile=[character(len=80) :: '# '//bname, 'My cool new project!'] + + call warnwrite(join_path(settings%name, 'README.md'), littlefile) ! create NAME/README.md + + message=[character(len=80) :: & ! start building NAME/fpm.toml + &'name = "'//bname//'" ', & + &'version = "0.1.0" ', & + &'license = "license" ', & + &'author = "Jane Doe" ', & + &'maintainer = "jane.doe@example.com" ', & + &'copyright = "2020 Jane Doe" ', & + &' ', & + &''] + + if(settings%with_lib)then + call mkdir(join_path(settings%name,'src') ) + message=[character(len=80) :: message, & ! create next section of fpm.toml + &'[library] ', & + &'source-dir="src" ', & + &''] + littlefile=[character(len=80) :: & ! create placeholder module src/bname.f90 + &'module '//bname, & + &' implicit none', & + &' private', & + &'', & + &' public :: say_hello', & + &'contains', & + &' subroutine say_hello', & + &' 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 + 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 + &'[[test]] ', & + &'name="runTests" ', & + &'source-dir="test" ', & + &'main="main.f90" ', & + &''] + + 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 + 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 + &'[[executable]] ', & + &'name="'//bname//'" ', & + &'source-dir="app" ', & + &'main="main.f90" ', & + &''] + + littlefile=[character(len=80) :: & + &'program main', & + &' use '//bname//', only: say_hello', & + &'', & + &' implicit none', & + &'', & + &' call say_hello', & + &'end program main'] + 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 +contains + +subroutine warnwrite(fname,data) +character(len=*),intent(in) :: fname +character(len=*),intent(in) :: data(:) + + if(.not.exists(fname))then + call filewrite(fname,data) + else + write(stderr,'(*(g0,1x))')'fpm::new<WARNING>',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 +character(len=*),intent(in) :: filename +character(len=*),intent(in) :: filedata(:) +integer :: lun, i, ios +character(len=256) :: message + + message=' ' + ios=0 + 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 + & iostat=ios, & + & iomsg=message) + else + lun=stdout + ios=0 + endif + if(ios.ne.0)then + write(stderr,'(*(a:,1x))')'*filewrite* error:',filename,trim(message) + error stop 1 + endif + do i=1,size(filedata) ! write file + write(lun,'(a)',iostat=ios,iomsg=message)trim(filedata(i)) + if(ios.ne.0)then + write(stderr,'(*(a:,1x))')'*filewrite* error:',filename,trim(message) + error stop 4 + endif + enddo + close(unit=lun,iostat=ios,iomsg=message) ! close file + if(ios.ne.0)then + write(stderr,'(*(a:,1x))')'*filewrite* error:',trim(message) + error stop 2 + endif +end subroutine filewrite + +end subroutine cmd_new + +end module fpm_cmd_new diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 5b9d93a..1a7e4ab 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -416,8 +416,9 @@ contains ' ', & ' The "new" subcommand creates a directory and runs the command ', & ' "git init" in that directory and makes an example "fpm.toml" ', & - ' file, a src/ directory, and optionally a test/ and app/ ', & - ' directory with trivial example Fortran source files. ', & + ' file. and src/ directory and a sample module file. It ', & + ' optionally also creates a test/ and app/ directory with ', & + ' trivial example Fortran program sources. ', & ' ', & ' Remember to update the information in the sample "fpm.toml" ', & ' file with such information as your name and e-mail address. ', & diff --git a/fpm/test/cli_test/cli_test.f90 b/fpm/test/cli_test/cli_test.f90 index fac49e8..b0140e1 100644 --- a/fpm/test/cli_test/cli_test.f90 +++ b/fpm/test/cli_test/cli_test.f90 @@ -193,7 +193,8 @@ use fpm_command_line, only: & fpm_test_settings, & fpm_install_settings, & get_command_line_settings -use fpm, only: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test +use fpm, only: cmd_build, cmd_install, cmd_run, cmd_test +use fpm_cmd_new, only: cmd_new class(fpm_cmd_settings), allocatable :: cmd_settings ! duplicates the calls as seen in the main program for fpm call get_command_line_settings(cmd_settings) |