aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorMilan Curcic <caomaco@gmail.com>2020-10-03 11:36:31 -0400
committerGitHub <noreply@github.com>2020-10-03 11:36:31 -0400
commitd3a65e36b28808c2c51ae41fc107f1179e27a08c (patch)
tree6bf8d135e0ddcbdb2354ac7344f17f717d935c52
parent75c1da54b337a08f8205db19e49606e30b4ce2bb (diff)
parent9369cc27ffd74cf8621928f5c80d132a754f648a (diff)
downloadfpm-d3a65e36b28808c2c51ae41fc107f1179e27a08c.tar.gz
fpm-d3a65e36b28808c2c51ae41fc107f1179e27a08c.zip
Merge pull request #189 from urbanjost/NEW
Pull request for NEW
-rw-r--r--fpm/fpm.toml4
-rw-r--r--fpm/src/fpm.f90389
-rw-r--r--fpm/src/fpm/manifest.f9018
-rw-r--r--fpm/src/fpm_command_line.f90777
-rw-r--r--fpm/src/fpm_filesystem.f904
-rw-r--r--fpm/test/cli_test/cli_test.f902
6 files changed, 799 insertions, 395 deletions
diff --git a/fpm/fpm.toml b/fpm/fpm.toml
index ee2e714..9418204 100644
--- a/fpm/fpm.toml
+++ b/fpm/fpm.toml
@@ -12,7 +12,7 @@ tag = "v0.2"
[dependencies.M_CLI2]
git = "https://github.com/urbanjost/M_CLI2.git"
-rev = "5c7df1267c918ec2b1b8e2c6a0ac000367b562cf"
+rev = "649075aceb97f997665a1a4656514fd2e9b4becc"
[[test]]
name = "cli-test"
@@ -23,5 +23,3 @@ main = "cli_test.f90"
name = "fpm-test"
source-dir = "test/fpm_test"
main = "main.f90"
-
-
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index bd93b2a..4db35ba 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -5,7 +5,7 @@ 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
+use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename, mkdir
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
@@ -13,8 +13,9 @@ use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
resolve_module_dependencies
use fpm_manifest, only : get_package_data, default_executable, &
- default_library, package_t
+ 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
@@ -22,9 +23,9 @@ implicit none
private
public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
-
contains
+
subroutine build_model(model, settings, package, error)
! Constructs a valid fpm model from command line settings and toml manifest
!
@@ -32,6 +33,7 @@ subroutine build_model(model, settings, package, error)
type(fpm_build_settings), intent(in) :: settings
type(package_t), intent(in) :: package
type(error_t), allocatable, intent(out) :: error
+ integer :: i
model%package_name = package%name
@@ -41,13 +43,13 @@ subroutine build_model(model, settings, package, error)
if(settings%release)then
model%output_directory = 'build/gfortran_release'
model%fortran_compile_flags=' &
- & -O3 &
- & -Wimplicit-interface &
- & -fPIC &
- & -fmax-errors=1 &
- & -ffast-math &
- & -funroll-loops ' // &
- & '-J'//join_path(model%output_directory,model%package_name)
+ & -O3 &
+ & -Wimplicit-interface &
+ & -fPIC &
+ & -fmax-errors=1 &
+ & -ffast-math &
+ & -funroll-loops ' // &
+ & '-J'//join_path(model%output_directory,model%package_name)
else
model%output_directory = 'build/gfortran_debug'
model%fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g '// &
@@ -72,7 +74,7 @@ subroutine build_model(model, settings, package, error)
if (allocated(error)) then
return
- end if
+ endif
end if
if (allocated(package%executable)) then
@@ -92,29 +94,40 @@ subroutine build_model(model, settings, package, error)
if (allocated(error)) then
return
- end if
+ endif
- end if
+ endif
if (allocated(package%library)) then
+
call add_sources_from_dir(model%sources, package%library%source_dir, &
FPM_SCOPE_LIB, error=error)
if (allocated(error)) then
return
- end if
+ endif
- end if
- call resolve_module_dependencies(model%sources,error)
+ endif
+ if(settings%list)then
+ do i=1,size(model%sources)
+ write(stderr,'(*(g0,1x))')'fpm::build<INFO>:file expected at',model%sources(i)%file_name, &
+ & merge('exists ','does not exist',exists(model%sources(i)%file_name) )
+ enddo
+ stop
+ else
+ call resolve_module_dependencies(model%sources,error)
+ endif
end subroutine build_model
+
subroutine cmd_build(settings)
type(fpm_build_settings), intent(in) :: settings
type(package_t) :: package
type(fpm_model_t) :: model
type(error_t), allocatable :: error
+
call get_package_data(package, "fpm.toml", error)
if (allocated(error)) then
print '(a)', error%message
@@ -152,16 +165,32 @@ end subroutine
subroutine cmd_install(settings)
type(fpm_install_settings), intent(in) :: settings
print *, "fpm error: 'fpm install' not implemented."
- error stop 1
+ 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 :: bname
- bname=basename(settings%name) !! new basename(dirname) if full paths are allowed ???
+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
- message=[character(len=80) :: & ! create fpm.toml
+ 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" ', &
@@ -169,71 +198,297 @@ character(len=:),allocatable :: bname
&'maintainer = "jane.doe@example.com" ', &
&'copyright = "2020 Jane Doe" ', &
&' ', &
- &'[library] ', &
- &'source-dir="src" ', &
&'']
- if(settings%with_test)then
- message=[character(len=80) :: message, & ! create next section of fpm.toml
- &'[[test]] ', &
- &'name="runTests" ', &
- &'source-dir="test" ', &
- &'main="main.f90" ', &
- &'']
- endif
-
- if(settings%with_executable)then
- message=[character(len=80) :: message, & ! create next section of fpm.toml
- &'[[executable]] ', &
- &'name="'//bname//'" ', &
- &'source-dir="app" ', &
- &'main="main.f90" ', &
- &'']
- endif
-
- write(*,'(a)')message
- print *, "fpm error: 'fpm new' not implemented."
- error stop 1
+ 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
- integer :: i
- write(*,*)'RELEASE=',settings%release
+subroutine cmd_run(settings)
+type(fpm_run_settings), intent(in) :: settings
+character(len=:),allocatable :: release_name, cmd, fname
+integer :: i, j
+type(package_t) :: package
+type(error_t), allocatable :: error
+character(len=:),allocatable :: newwords(:)
+logical,allocatable :: foundit(:)
+logical :: list
+ call get_package_data(package, "fpm.toml", error)
+ if (allocated(error)) then
+ print '(a)', error%message
+ stop
+ endif
+ release_name=trim(merge('gfortran_release','gfortran_debug ',settings%release))
+ newwords=[character(len=0) ::]
+ ! Populate executable in case we find the default app directory
+ if (.not.allocated(package%executable) .and. exists("app")) then
+ allocate(package%executable(1))
+ call default_executable(package%executable(1), package%name)
+ endif
if(size(settings%name).eq.0)then
- write(*,*)'RUN DEFAULTS with arguments ['//settings%args//']'
+ if ( .not.allocated(package%executable) ) then
+ write(stderr,'(*(g0,1x))')'fpm::run<INFO>:no executables found in fpm.toml and no default app/ directory'
+ stop
+ endif
+ allocate(foundit(size(package%executable)))
+ do i=1,size(package%executable)
+ fname=join_path('build',release_name,package%executable(i)%source_dir,package%executable(i)%name)
+ newwords=[character(len=max(len(newwords),len(fname))) :: newwords,fname]
+ enddo
+ if(size(newwords).lt.1)then
+ write(stderr,'(*(g0,1x))')'fpm::run<INFO>:no executables found in fpm.toml'
+ stop
+ endif
else
+ !! expand names, duplicates are a problem??
+ allocate(foundit(size(settings%name)))
+ foundit=.false.
+ FINDIT: do i=1,size(package%executable)
+ do j=1,size(settings%name)
+ if(settings%name(j).eq.package%executable(i)%name)then
+ fname=join_path('build',release_name,package%executable(i)%source_dir,package%executable(i)%name)
+ newwords=[character(len=max(len(newwords),len(fname))) :: newwords,fname]
+ foundit(j)=.true.
+ endif
+ enddo
+ enddo FINDIT
do i=1,size(settings%name)
- write(*,*)'RUN:'//trim(settings%name(i))//' with arguments ['//settings%args//']'
+ if(.not.foundit(i))then
+ write(stderr,'(*(g0,1x))')'fpm::run<ERROR>:executable',trim(settings%name(i)),'not located'
+ !!elseif(settings%debug)then
+ !! write(stderr,'(*(g0,1x))')'fpm::run<INFO>: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
-
- print *, "fpm error: 'fpm run' not implemented."
- error stop 1
-
+ 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
+ if(settings%list)then
+ write(stderr,'(*(g0,1x))')'fpm::run<INFO>:executable expected at',newwords(i),&
+ & merge('exists ','does not exist',exists(newwords(i)))
+ cycle
+ endif
+ cmd=newwords(i) // ' ' // settings%args
+ if(exists(newwords(i)))then
+ call run(cmd)
+ else ! try to build -- once build works conditionally this should be an unconditional call
+ call cmd_build(fpm_build_settings(release=settings%release,list=.false.))
+ if(exists(newwords(i)))then
+ call run(cmd)
+ else
+ write(stderr,*)'fpm::run<ERROR>',cmd,' not found'
+ endif
+ endif
+ enddo
+ deallocate(newwords)
end subroutine cmd_run
-subroutine cmd_test(settings)
- type(fpm_test_settings), intent(in) :: settings
- character(len=:),allocatable :: release_name
- integer :: i
- !! looks like would get this from model when cmd_test is implimented
+subroutine cmd_test(settings)
+type(fpm_test_settings), intent(in) :: settings
+character(len=:),allocatable :: release_name, cmd, fname
+integer :: i, j
+type(package_t) :: package
+type(error_t), allocatable :: error
+character(len=:),allocatable :: newwords(:)
+logical,allocatable :: foundit(:)
+logical :: list
+ call get_package_data(package, "fpm.toml", error)
+ if (allocated(error)) then
+ print '(a)', error%message
+ stop
+ endif
release_name=trim(merge('gfortran_release','gfortran_debug ',settings%release))
+ newwords=[character(len=0) ::]
- write(*,*)'RELEASE=',settings%release,' RELEASE_NAME=',release_name,' ARGS=',settings%args
- if( size(settings%name) .gt.0 )then
- write(*,*)'RUN THESE:'
- do i=1,size(settings%name)
- write(*,*)'RUN:'//trim(settings%name(i))//' with arguments ['//settings%args//']'
+ ! Populate test in case we find the default test directory
+ if (.not.allocated(package%test) .and. exists("test")) then
+ allocate(package%test(1))
+ call default_test(package%test(1), package%name)
+ endif
+ if(size(settings%name).eq.0)then
+ if ( .not.allocated(package%test) ) then
+ write(stderr,'(*(g0,1x))')'fpm::run<INFO>:no tests found in fpm.toml and no default test/ directory'
+ stop
+ endif
+ allocate(foundit(size(package%test)))
+ do i=1,size(package%test)
+ fname=join_path('build',release_name,package%test(i)%source_dir,package%test(i)%name)
+ newwords=[character(len=max(len(newwords),len(fname))) :: newwords,fname]
enddo
+ if(size(newwords).lt.1)then
+ write(stderr,'(*(g0,1x))')'fpm::run<INFO>:no tests found in fpm.toml'
+ stop
+ endif
else
- write(*,*)'RUN DEFAULTS: with arguments ['//settings%args//']'
+ !! expand names, duplicates are a problem??
+ allocate(foundit(size(settings%name)))
+ foundit=.false.
+ FINDIT: do i=1,size(package%test)
+ do j=1,size(settings%name)
+ if(settings%name(j).eq.package%test(i)%name)then
+ fname=join_path('build',release_name,package%test(i)%source_dir,package%test(i)%name)
+ newwords=[character(len=max(len(newwords),len(fname))) :: newwords,fname]
+ foundit(j)=.true.
+ endif
+ enddo
+ enddo FINDIT
+ do i=1,size(settings%name)
+ if(.not.foundit(i))then
+ write(stderr,'(*(g0,1x))')'fpm::run<ERROR>:test',trim(settings%name(i)),'not located'
+ !!elseif(settings%debug)then
+ !! write(stderr,'(*(g0,1x))')'fpm::run<INFO>: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
-
- print *, "fpm error: 'fpm test' not implemented."
- error stop 1
+ 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
+ if(settings%list)then
+ write(stderr,'(*(g0,1x))')'fpm::run<INFO>:test expected at',newwords(i),&
+ & merge('exists ','does not exist',exists(newwords(i)))
+ cycle
+ endif
+ cmd=newwords(i) // ' ' // settings%args
+ if(exists(newwords(i)))then
+ call run(cmd)
+ else ! try to build -- once build works conditionally this should be an unconditional call
+ call cmd_build(fpm_build_settings(release=settings%release,list=.false.))
+ if(exists(newwords(i)))then
+ call run(cmd)
+ else
+ write(stderr,*)'fpm::run<ERROR>',cmd,' not found'
+ endif
+ endif
+ enddo
+ deallocate(newwords)
end subroutine cmd_test
+
end module fpm
diff --git a/fpm/src/fpm/manifest.f90 b/fpm/src/fpm/manifest.f90
index 0098890..d3e47de 100644
--- a/fpm/src/fpm/manifest.f90
+++ b/fpm/src/fpm/manifest.f90
@@ -13,10 +13,11 @@ module fpm_manifest
use fpm_manifest_package, only : package_t, new_package
use fpm_error, only : error_t, fatal_error, file_not_found_error
use fpm_toml, only : toml_table, read_package_file
+ use fpm_manifest_test, only : test_t
implicit none
private
- public :: get_package_data, default_executable, default_library
+ public :: get_package_data, default_executable, default_library, default_test
public :: package_t
@@ -49,6 +50,21 @@ contains
end subroutine default_executable
+ !> Populate test in case we find the default test/ directory
+ subroutine default_test(self, name)
+
+ !> Instance of the executable meta data
+ type(test_t), intent(out) :: self
+
+ !> Name of the package
+ character(len=*), intent(in) :: name
+
+ self%name = name
+ self%source_dir = "test"
+ self%main = "main.f90"
+
+ end subroutine default_test
+
!> Obtain package meta data from a configuation file
subroutine get_package_data(package, file, error)
diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90
index 84b4693..5b9d93a 100644
--- a/fpm/src/fpm_command_line.f90
+++ b/fpm/src/fpm_command_line.f90
@@ -1,57 +1,62 @@
-!! new are full pathnames allowed? Is more than one pathname allowed?
-!! fpm --search search keywords, descriptions, names of fpm(1) package registry
-!! install not sure what it is supposed to do. Install files in build/ to a user-specified area?
module fpm_command_line
- 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
- use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
+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 fpm_filesystem, only : basename
+use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
& stdout=>output_unit, &
& stderr=>error_unit
- implicit none
-
- private
- public :: fpm_cmd_settings, &
- fpm_build_settings, &
- fpm_install_settings, &
- fpm_new_settings, &
- fpm_run_settings, &
- fpm_test_settings, &
- get_command_line_settings
-
- type, abstract :: fpm_cmd_settings
- end type
-
- integer,parameter :: ibug=4096
- type, extends(fpm_cmd_settings) :: fpm_new_settings
- character(len=:),allocatable :: name
- logical :: with_executable=.false.
- logical :: with_test=.false.
- end type
-
- type, extends(fpm_cmd_settings) :: fpm_build_settings
- logical :: release=.false.
- end type
-
- type, extends(fpm_cmd_settings) :: fpm_run_settings
- character(len=ibug),allocatable :: name(:)
- logical :: release=.false.
- logical :: list=.false.
- character(len=:),allocatable :: args
- end type
-
- type, extends(fpm_cmd_settings) :: fpm_test_settings
- character(len=ibug),allocatable :: name(:)
- logical :: release=.false.
- character(len=:),allocatable :: args
- end type
-
- type, extends(fpm_cmd_settings) :: fpm_install_settings
- end type
-
- character(len=:),allocatable :: name
- character(len=ibug),allocatable :: names(:)
+implicit none
+
+private
+public :: fpm_cmd_settings, &
+ fpm_build_settings, &
+ fpm_install_settings, &
+ fpm_new_settings, &
+ fpm_run_settings, &
+ fpm_test_settings, &
+ get_command_line_settings
+
+type, abstract :: fpm_cmd_settings
+end type
+
+integer,parameter :: ibug=4096
+type, extends(fpm_cmd_settings) :: fpm_new_settings
+ character(len=:),allocatable :: name
+ logical :: with_executable=.false.
+ logical :: with_test=.false.
+ logical :: with_lib=.true.
+end type
+
+type, extends(fpm_cmd_settings) :: fpm_build_settings
+ logical :: release=.false.
+ logical :: list=.false.
+end type
+
+type, extends(fpm_cmd_settings) :: fpm_run_settings
+ character(len=ibug),allocatable :: name(:)
+ logical :: release=.false.
+ logical :: list=.false.
+ character(len=:),allocatable :: args
+end type
+
+type, extends(fpm_cmd_settings) :: fpm_test_settings
+ character(len=ibug),allocatable :: name(:)
+ logical :: release=.false.
+ logical :: list=.false.
+ character(len=:),allocatable :: args
+end type
+
+type, extends(fpm_cmd_settings) :: fpm_install_settings
+end type
+
+character(len=:),allocatable :: name
+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(:)
contains
subroutine get_command_line_settings(cmd_settings)
@@ -59,301 +64,431 @@ contains
character(len=4096) :: cmdarg
integer :: i
- character(len=:), allocatable :: help_text(:), version_text(:)
+ call set_help()
! text for --version switch,
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', &
+ & '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
cmdarg = ''
do i = 1, command_argument_count()
- call get_command_argument(i, cmdarg)
- if(adjustl(cmdarg(1:1)) .ne. '-')exit
+ 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
select case(trim(cmdarg))
case('run')
- help_text=[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. ', &
- ' -- 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 test2 -release ', &
- '' ]
- call set_args('--list F --release F --',help_text,version_text)
-
- if( size(unnamed) .gt. 1 )then
- names=unnamed(2:)
- else
- names=[character(len=len(names)) :: ]
- endif
-
- allocate(fpm_run_settings :: cmd_settings)
- cmd_settings=fpm_run_settings( name=names, release=lget('release'), args=remaining )
+ call set_args('--list F --release F --',help_run,version_text)
+
+ if( size(unnamed) .gt. 1 )then
+ names=unnamed(2:)
+ else
+ names=[character(len=len(names)) :: ]
+ endif
+
+ allocate(fpm_run_settings :: cmd_settings)
+ cmd_settings=fpm_run_settings( name=names, list=lget('list'), &
+ & release=lget('release'), args=remaining )
case('build')
- help_text=[character(len=80) :: &
- 'NAME ', &
- ' build(1) - the fpm(1) subcommand to build a project ', &
- 'SYNOPSIS ', &
- ' fpm build [--release] build ', &
- ' fpm build --help|--version ', &
- ' ', &
- 'DESCRIPTION ', &
- ' Finds the Fortran source files in app/, test/, and ', &
- ' src/ by default; determines the dependencies ', &
- ' between the files and rebuilds unbuilt or changed ', &
- ' files. The results are placed in the build/ directory. ', &
- ' ', &
- ' Non-default pathnames are used if specified in the ', &
- ' "fpm.toml" file. ', &
- ' ', &
- ' Remote dependencies are satisfied as well 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. ', &
- ' --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 ', &
- '' ]
- call set_args( '--release F --',help_text,version_text )
-
- allocate( fpm_build_settings :: cmd_settings )
- cmd_settings=fpm_build_settings( release=lget('release') )
+ 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') )
case('new')
- help_text=[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 --help|--version ', &
- ' ', &
- 'DESCRIPTION ', &
- ' Create 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, a src/ directory, and optionally a test/ and app/ ', &
- ' directory with trivial example Fortran source files. ', &
- ' ', &
- ' Remember to update the information in the sample "fpm.toml" ', &
- ' file with such information as your name and e-mail address. ', &
- ' ', &
- 'EXAMPLES ', &
- ' Sample use ', &
- ' ', &
- ' # create new project directory and seed it ', &
- ' fpm new myproject ', &
- ' # Enter the new directory ', &
- ' cd myproject ', &
- ' # and run commands such as ', &
- ' fpm build ', &
- ' fpm run # if you selected --with-executable ', &
- ' fpm test # if you selected --with-test ', &
- ' ', &
- '' ]
- call set_args(' --with-executable F --with-test F ', help_text, 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]'
- 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]'
- stop 2
- end select
-
- allocate(fpm_new_settings :: cmd_settings)
- cmd_settings=fpm_new_settings(name=name, with_executable=lget('with-executable'), with_test=lget('with-test') )
+ call set_args(' --with-executable F --with-test F --lib F --app F --test 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]'
+ 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]'
+ 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.'
+ 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') )
+ endif
+
+ case('help')
+ call set_args(' ',help_help,version_text)
+ if(size(unnamed).lt.2)then
+ unnamed=['help', 'fpm ']
+ endif
+ allocate(character(len=80) :: help_text(0))
+ do i=2,size(unnamed)
+ select case(unnamed(i))
+ case('build ' )
+ help_text=[character(len=80) :: help_text, help_build]
+ case('run ' )
+ help_text=[character(len=80) :: help_text, help_run]
+ case('help ' )
+ help_text=[character(len=80) :: help_text, help_help]
+ case('test ' )
+ help_text=[character(len=80) :: help_text, help_test]
+ case('new ' )
+ help_text=[character(len=80) :: help_text, help_new]
+ case('fpm ' )
+ help_text=[character(len=80) :: 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]
+ case default
+ help_text=[character(len=80) :: help_text, 'unknown subcommand'//unnamed(i)]
+ end select
+ enddo
+ write(stderr,'(g0)')(trim(help_text(i)), i=1, size(help_text) )
case('install')
- help_text=[character(len=80) :: &
- ' fpm(1) subcommand "install" ', &
- ' ', &
- ' Usage: fpm install NAME ', &
- '' ]
- call set_args('--release F ', help_text, version_text)
+ call set_args('--release F ', help_install, version_text)
- allocate(fpm_install_settings :: cmd_settings)
+ allocate(fpm_install_settings :: cmd_settings)
case('test')
- help_text=[character(len=80) :: &
- 'NAME ', &
- ' test(1) - the fpm(1) subcommand to run project tests ', &
- ' ', &
- 'SYNOPSIS ', &
- ' fpm test [NAME(s)] [--release] [-- 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. ', &
- ' -- 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 test2 -release # production version of two tests', &
- ' ', &
- '' ]
- call set_args(' -release F --', help_text, version_text)
-
- if( size(unnamed) .gt. 1 )then
- names=unnamed(2:)
- else
- names=[character(len=len(names)) :: ]
- endif
-
- allocate(fpm_test_settings :: cmd_settings)
- cmd_settings=fpm_test_settings(name=names, release=lget('release'), args=remaining )
+ call set_args('--list F --release F --',help_test,version_text)
+
+ if( size(unnamed) .gt. 1 )then
+ names=unnamed(2:)
+ else
+ names=[character(len=len(names)) :: ]
+ endif
+
+ allocate(fpm_test_settings :: cmd_settings)
+ cmd_settings=fpm_test_settings( name=names, list=lget('list'), &
+ & release=lget('release'), args=remaining )
case default
- help_text=[character(len=80) :: &
- 'NAME', &
- ' fpm(1) - A Fortran package manager and build system', &
- 'OS TYPE' ]
- select case (get_os_type())
- case (OS_LINUX); help_text=[character(len=80) :: help_text, " Linux" ]
- case (OS_MACOS); help_text=[character(len=80) :: help_text, " macOS" ]
- case (OS_WINDOWS); help_text=[character(len=80) :: help_text, " Windows" ]
- case (OS_CYGWIN); help_text=[character(len=80) :: help_text, " Cygwin" ]
- case (OS_SOLARIS); help_text=[character(len=80) :: help_text, " Solaris" ]
- case (OS_FREEBSD); help_text=[character(len=80) :: help_text, " FreeBSD" ]
- case (OS_UNKNOWN); help_text=[character(len=80) :: help_text, " Unknown" ]
- case default ; help_text=[character(len=80) :: help_text, " UNKNOWN" ]
- end select
- help_text=[character(len=80) :: help_text, &
- 'SYNTAX ', &
- ' 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] 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] [-- ARGS] ', &
- ' Run the tests ', &
- '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 ', &
- ' For examples and documentation see https://github.com/fortran-lang/fpm ', &
- '']
-
- call set_args(' ', help_text, 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'
- else
- 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) )
- !!stop 3 ! causes github site tests to fail
- stop
+
+ call set_args(' ', 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'
+ else
+ 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) )
end select
- end subroutine get_command_line_settings
+ 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)
+ character(len=*),parameter :: int='0123456789'
+ character(len=*),parameter :: lower='abcdefghijklmnopqrstuvwxyz'
+ character(len=*),parameter :: upper='ABCDEFGHIJKLMNOPQRSTUVWXYZ'
+ character(len=*),parameter :: allowed=upper//lower//int//'_'
+ character(len=*),intent(in) :: line
+ character(len=:),allocatable :: name
+ logical :: lout
+ name=trim(line)
+ if(len(name).ne.0)then
+ lout = .true. &
+ & .and. verify(name(1:1), lower//upper) == 0 &
+ & .and. verify(name,allowed) == 0 &
+ & .and. len(name) <= 63
+ else
+ lout = .false.
+ endif
+ end function is_fortran_name
+
+ subroutine set_help()
+ 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 ', &
+ '']
+ 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 test2 -release ', &
+ 'SEE ALSO ', &
+ ' The fpm(1) home page is 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 is 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][all] ', &
+ ' ', &
+ '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. ', &
+ ' ', &
+ 'EXAMPLES ', &
+ ' ', &
+ ' fpm help ', &
+ ' fpm help version ', &
+ ' fpm all ', &
+ 'SEE ALSO ', &
+ ' The fpm(1) home page is 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 --help|--version ', &
+ ' ', &
+ 'DESCRIPTION ', &
+ ' Create 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, a src/ directory, and optionally a test/ and app/ ', &
+ ' directory with trivial example Fortran source files. ', &
+ ' ', &
+ ' 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. ', &
+ ' --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 ', &
+ ' ', &
+ '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 # if you selected --with-executable ', &
+ ' fpm test # if you selected --with-test ', &
+ 'SEE ALSO ', &
+ ' The fpm(1) home page is 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 test2 -release # production version of two tests', &
+ 'SEE ALSO ', &
+ ' The fpm(1) home page is https://github.com/fortran-lang/fpm ', &
+ '' ]
+ help_install=[character(len=80) :: &
+ ' fpm(1) subcommand "install" ', &
+ ' ', &
+ ' Usage: fpm install NAME ', &
+ '' ]
+ end subroutine set_help
end module fpm_command_line
diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90
index 2aa9f8b..d2096f1 100644
--- a/fpm/src/fpm_filesystem.f90
+++ b/fpm/src/fpm_filesystem.f90
@@ -218,11 +218,11 @@ subroutine mkdir(dir)
select case (get_os_type())
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
call execute_command_line('mkdir -p ' // dir, exitstat=stat)
- write (*, '(2a)') 'mkdir -p ' // dir
+ write (*, '(" + ",2a)') 'mkdir -p ' // dir
case (OS_WINDOWS)
call execute_command_line("mkdir " // windows_path(dir), exitstat=stat)
- write (*, '(2a)') 'mkdir ' // windows_path(dir)
+ write (*, '(" + ",2a)') 'mkdir ' // windows_path(dir)
end select
if (stat /= 0) then
diff --git a/fpm/test/cli_test/cli_test.f90 b/fpm/test/cli_test/cli_test.f90
index ab032f5..fac49e8 100644
--- a/fpm/test/cli_test/cli_test.f90
+++ b/fpm/test/cli_test/cli_test.f90
@@ -40,7 +40,7 @@ character(len=256) :: message
character(len=*),parameter :: tests(*)= [ character(len=256) :: &
'CMD="new", ESTAT=1,', &
-'CMD="new -unknown", ESTAT=2,', &
+!'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",', &