diff options
author | init current directory[i] <urbanjost@comcast.net> | 2020-09-29 21:40:11 -0400 |
---|---|---|
committer | init current directory[i] <urbanjost@comcast.net> | 2020-10-01 01:01:19 -0400 |
commit | 61235265d7eed55655ca8756e252c31c1fe2dbde (patch) | |
tree | 8e8e61dbe206ef59b381e90c501eede5a98b0eac | |
parent | 3ad659412e52a00cfc6e47270689deb34e26520e (diff) | |
download | fpm-61235265d7eed55655ca8756e252c31c1fe2dbde.tar.gz fpm-61235265d7eed55655ca8756e252c31c1fe2dbde.zip |
consistent indenting
-rw-r--r-- | fpm/src/fpm.f90 | 682 | ||||
-rw-r--r-- | fpm/src/fpm_command_line.f90 | 744 |
2 files changed, 707 insertions, 719 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index 7061d6d..7e96456 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -1,17 +1,17 @@ module fpm -use fpm_strings, only : string_t, str_ends_with -use fpm_backend, only : build_package +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 : join_path, number_of_rows, list_files, exists, basename, mkdir -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_test -use fpm_error, only : error_t + 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 : join_path, number_of_rows, list_files, exists, basename, mkdir +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_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, & @@ -21,9 +21,8 @@ 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 ! @@ -41,13 +40,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 '// & @@ -60,123 +59,122 @@ subroutine build_model(model, settings, package, error) if (allocated(package%executable)) then call add_executable_sources(model%sources, package%executable, & - is_test=.false., error=error) + is_test=.false., error=error) if (allocated(error)) then return - end if + endif - end if + endif if (allocated(package%test)) then call add_executable_sources(model%sources, package%test, & - is_test=.true., error=error) + is_test=.true., error=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, & - error=error) + error=error) if (allocated(error)) then return - end if + endif - end if + endif if(settings%list)then - do i=1,size(model%sources) + 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 + & merge('exists ','does not exist',exists(model%sources(i)%file_name) ) + enddo + stop else - call resolve_module_dependencies(model%sources) + call resolve_module_dependencies(model%sources) 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 - error stop 1 -end if - -! Populate library in case we find the default src directory -if (.not.allocated(package%library) .and. exists("src")) then - allocate(package%library) - call default_library(package%library) -end if - -! 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) -end if - -! 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) -end if - -if (.not.(allocated(package%library) .or. allocated(package%executable) .or. allocated(package%test) )) then - print '(a)', "Neither library nor executable found, there is nothing to do" - error stop 1 -end if - -call build_model(model, settings, package, error) -if (allocated(error)) then - print '(a)', error%message - error stop 1 -end if - -call build_package(model) + + call get_package_data(package, "fpm.toml", error) + if (allocated(error)) then + print '(a)', error%message + error stop 5 + endif + + ! Populate library in case we find the default src directory + if (.not.allocated(package%library) .and. exists("src")) then + allocate(package%library) + call default_library(package%library) + endif + + ! 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 + + ! 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 (.not.(allocated(package%library) .or. allocated(package%executable) .or. allocated(package%test) )) then + print '(a)', "Neither library nor executable found, there is nothing to do" + error stop 6 + endif + + call build_model(model, settings, package, error) + if (allocated(error)) then + print '(a)', error%message + error stop 7 + endif + + call build_package(model) end subroutine cmd_build -!=================================================================================================================================== -!()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()()! -!=================================================================================================================================== + + 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 :: 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 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!'] + littlefile=[character(len=80) :: '# '//bname, 'My cool new project!'] - call warnwrite(join_path(settings%name, 'README.md'), littlefile) ! create NAME/README.md + call warnwrite(join_path(settings%name, 'README.md'), littlefile) ! create NAME/README.md - message=[character(len=80) :: & ! start building NAME/fpm.toml + message=[character(len=80) :: & ! start building NAME/fpm.toml &'name = "'//bname//'" ', & &'version = "0.1.0" ', & &'license = "license" ', & @@ -186,81 +184,83 @@ 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 - &'[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 + 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 + + 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 @@ -268,44 +268,44 @@ 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) - 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 + + 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 @@ -315,82 +315,81 @@ 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 - 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. + 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 + 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) + 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 - enddo FINDIT - do i=1,size(settings%name) - 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 - 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 + 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 + 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 - write(stderr,*)'fpm::run<ERROR>',cmd,' not found' - endif - endif - enddo - deallocate(newwords) + 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, cmd, fname @@ -400,81 +399,80 @@ 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 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 - !! 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. + 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 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 + !! 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 - 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 - 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 + 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 + 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 - write(stderr,*)'fpm::run<ERROR>',cmd,' not found' - endif - endif - enddo - deallocate(newwords) + 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_command_line.f90 b/fpm/src/fpm_command_line.f90 index d1714bf..76bdca6 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -1,68 +1,58 @@ -!! 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? -!! should test always write to build/test.log ? -!! -list |xargs -iXX valgrind -options XX options? -!! or maybe --mask "valgrind --options %XX --options" -!! might be useful for valgrind, gdb, time, ... -!! better to have commands in fpm.toml instead or in addition? -!! what about profiling? -!! note run and test are not currently doing an automatic build 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, specified - use fpm_filesystem, only : basename - 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 +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 +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 +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 +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_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_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_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 +type, extends(fpm_cmd_settings) :: fpm_install_settings +end type - character(len=:),allocatable :: name - character(len=ibug),allocatable :: names(:) +character(len=:),allocatable :: name +character(len=ibug),allocatable :: names(:) contains subroutine get_command_line_settings(cmd_settings) @@ -83,359 +73,359 @@ contains ! 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. ', & - ' --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 ', & - '' ] - call set_args('--list F --release F --',help_text,version_text) + 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. ', & + ' --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 ', & + '' ] + 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 + 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 ) + 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]|[-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 ', & - '' ] - call set_args( '--release F --list F --',help_text,version_text ) + help_text=[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 ', & + '' ] + call set_args( '--release F --list F --',help_text,version_text ) - allocate( fpm_build_settings :: cmd_settings ) - cmd_settings=fpm_build_settings( release=lget('release'),list=lget('list') ) + 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. ', & - ' ', & - ' 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 ', & - '' ] - call set_args(' --with-executable F --with-test F --lib F --app F --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 + 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. ', & + ' ', & + ' 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 ', & + '' ] + call set_args(' --with-executable F --with-test F --lib F --app F --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 - if( .not.fortran_name(basename(name)) )then - write(stderr,'(*(g0))')'ERROR: new directory name 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-z] and underscores.' - stop 4 - endif + if( .not.fortran_name(basename(name)) )then + write(stderr,'(*(g0))')'ERROR: new directory name 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-z] 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.) + 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 + ! 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('install') - help_text=[character(len=80) :: & - ' fpm(1) subcommand "install" ', & - ' ', & - ' Usage: fpm install NAME ', & - '' ] - call set_args('--release F ', help_text, version_text) + help_text=[character(len=80) :: & + ' fpm(1) subcommand "install" ', & + ' ', & + ' Usage: fpm install NAME ', & + '' ] + call set_args('--release F ', help_text, 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] [--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 ', & - '' ] - call set_args('--list F --release F --',help_text,version_text) + help_text=[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 ', & + '' ] + 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 + 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 ) + 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' ] + 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" ] + 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, & - '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 ', & - '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_text=[character(len=80) :: help_text, & + '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 ', & + '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 ', & + ''] - 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_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 end select - end subroutine get_command_line_settings + end subroutine get_command_line_settings - function 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 fortran_name + function 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 fortran_name end module fpm_command_line |