Skip to content

Commit 61edac7

Browse files
committed
Refactor: run command to use model targets
1 parent 6a2d6e7 commit 61edac7

File tree

4 files changed

+129
-192
lines changed

4 files changed

+129
-192
lines changed

fpm/app/main.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ program main
77
fpm_test_settings, &
88
fpm_install_settings, &
99
get_command_line_settings
10-
use fpm, only: cmd_build, cmd_install, cmd_run, cmd_test
10+
use fpm, only: cmd_build, cmd_install, cmd_run
1111
use fpm_cmd_new, only: cmd_new
1212

1313
implicit none
@@ -22,9 +22,9 @@ program main
2222
type is (fpm_build_settings)
2323
call cmd_build(settings)
2424
type is (fpm_run_settings)
25-
call cmd_run(settings)
25+
call cmd_run(settings,test=.false.)
2626
type is (fpm_test_settings)
27-
call cmd_test(settings)
27+
call cmd_run(settings,test=.true.)
2828
type is (fpm_install_settings)
2929
call cmd_install(settings)
3030
end select

fpm/src/fpm.f90

Lines changed: 123 additions & 180 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,8 @@ module fpm
77
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
88
use fpm_model, only: fpm_model_t, srcfile_t, build_target_t, &
99
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
10-
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
10+
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST, &
11+
FPM_TARGET_EXECUTABLE
1112

1213
use fpm_sources, only: add_executable_sources, add_sources_from_dir
1314
use fpm_targets, only: targets_from_sources, resolve_module_dependencies
@@ -21,7 +22,7 @@ module fpm
2122
use fpm_manifest_dependency, only: dependency_t
2223
implicit none
2324
private
24-
public :: cmd_build, cmd_install, cmd_run, cmd_test
25+
public :: cmd_build, cmd_install, cmd_run
2526

2627
contains
2728

@@ -148,7 +149,6 @@ subroutine build_model(model, settings, package, error)
148149
type(fpm_build_settings), intent(in) :: settings
149150
type(package_t), intent(in) :: package
150151
type(error_t), allocatable, intent(out) :: error
151-
integer :: i
152152

153153
type(string_t), allocatable :: package_list(:)
154154

@@ -227,55 +227,69 @@ subroutine build_model(model, settings, package, error)
227227

228228
call targets_from_sources(model,model%sources)
229229

230-
if(settings%list)then
231-
do i=1,size(model%targets)
232-
write(stderr,*) model%targets(i)%ptr%output_file
233-
enddo
234-
stop
235-
endif
236-
237230
call resolve_module_dependencies(model%targets,error)
238231

239232
end subroutine build_model
240233

234+
!> Apply package defaults
235+
subroutine package_defaults(package)
236+
type(package_t), intent(inout) :: package
237+
238+
! Populate library in case we find the default src directory
239+
if (.not.allocated(package%library) .and. exists("src")) then
240+
allocate(package%library)
241+
call default_library(package%library)
242+
end if
243+
244+
! Populate executable in case we find the default app
245+
if (.not.allocated(package%executable) .and. &
246+
exists(join_path('app',"main.f90"))) then
247+
allocate(package%executable(1))
248+
call default_executable(package%executable(1), package%name)
249+
end if
250+
251+
! Populate test in case we find the default test directory
252+
if (.not.allocated(package%test) .and. exists("test")) then
253+
allocate(package%test(1))
254+
call default_test(package%test(1), package%name)
255+
endif
256+
257+
if (.not.(allocated(package%library) .or. allocated(package%executable))) then
258+
print '(a)', "Neither library nor executable found, there is nothing to do"
259+
error stop 1
260+
end if
261+
262+
end subroutine
241263

242264
subroutine cmd_build(settings)
243265
type(fpm_build_settings), intent(in) :: settings
244266
type(package_t) :: package
245267
type(fpm_model_t) :: model
246268
type(error_t), allocatable :: error
247269

270+
integer :: i
271+
248272
call get_package_data(package, "fpm.toml", error)
249273
if (allocated(error)) then
250274
print '(a)', error%message
251275
error stop 1
252276
end if
253277

254-
! Populate library in case we find the default src directory
255-
if (.not.allocated(package%library) .and. exists("src")) then
256-
allocate(package%library)
257-
call default_library(package%library)
258-
end if
259-
260-
! Populate executable in case we find the default app
261-
if (.not.allocated(package%executable) .and. &
262-
exists(join_path('app',"main.f90"))) then
263-
allocate(package%executable(1))
264-
call default_executable(package%executable(1), package%name)
265-
end if
266-
267-
if (.not.(allocated(package%library) .or. allocated(package%executable))) then
268-
print '(a)', "Neither library nor executable found, there is nothing to do"
269-
error stop 1
270-
end if
278+
call package_defaults(package)
271279

272280
call build_model(model, settings, package, error)
273281
if (allocated(error)) then
274282
print '(a)', error%message
275283
error stop 1
276284
end if
277285

278-
call build_package(model)
286+
if(settings%list)then
287+
do i=1,size(model%targets)
288+
write(stderr,*) model%targets(i)%ptr%output_file
289+
enddo
290+
else
291+
call build_package(model)
292+
endif
279293

280294
end subroutine
281295

@@ -285,167 +299,96 @@ subroutine cmd_install(settings)
285299
error stop 8
286300
end subroutine cmd_install
287301

288-
subroutine cmd_run(settings)
289-
type(fpm_run_settings), intent(in) :: settings
290-
character(len=:),allocatable :: release_name, cmd, fname
291-
integer :: i, j
292-
type(package_t) :: package
293-
type(error_t), allocatable :: error
294-
character(len=:),allocatable :: newwords(:)
295-
logical,allocatable :: foundit(:)
296-
logical :: list
302+
subroutine cmd_run(settings,test)
303+
class(fpm_run_settings), intent(in) :: settings
304+
logical, intent(in) :: test
305+
306+
integer :: i, j
307+
type(error_t), allocatable :: error
308+
type(package_t) :: package
309+
type(fpm_model_t) :: model
310+
type(string_t) :: exe_cmd
311+
type(string_t), allocatable :: executables(:)
312+
type(build_target_t), pointer :: exe_target
313+
type(srcfile_t), pointer :: exe_source
314+
297315
call get_package_data(package, "fpm.toml", error)
298316
if (allocated(error)) then
299317
print '(a)', error%message
300-
stop
301-
endif
302-
release_name=trim(merge('gfortran_release','gfortran_debug ',settings%release))
303-
newwords=[character(len=0) ::]
304-
! Populate executable in case we find the default app directory
305-
if (.not.allocated(package%executable) .and. exists("app")) then
306-
allocate(package%executable(1))
307-
call default_executable(package%executable(1), package%name)
308-
endif
309-
if(size(settings%name).eq.0)then
310-
if ( .not.allocated(package%executable) ) then
311-
write(stderr,'(*(g0,1x))')'fpm::run<INFO>:no executables found in fpm.toml and no default app/ directory'
312-
stop
313-
endif
314-
allocate(foundit(size(package%executable)))
315-
do i=1,size(package%executable)
316-
fname=join_path('build',release_name,package%executable(i)%source_dir,package%executable(i)%name)
317-
newwords=[character(len=max(len(newwords),len(fname))) :: newwords,fname]
318-
enddo
319-
if(size(newwords).lt.1)then
320-
write(stderr,'(*(g0,1x))')'fpm::run<INFO>:no executables found in fpm.toml'
321-
stop
322-
endif
323-
else
324-
!*! expand names, duplicates are a problem??
325-
allocate(foundit(size(settings%name)))
326-
foundit=.false.
327-
FINDIT: do i=1,size(package%executable)
328-
do j=1,size(settings%name)
329-
if(settings%name(j).eq.package%executable(i)%name)then
330-
fname=join_path('build',release_name,package%executable(i)%source_dir,package%executable(i)%name)
331-
newwords=[character(len=max(len(newwords),len(fname))) :: newwords,fname]
332-
foundit(j)=.true.
333-
endif
334-
enddo
335-
enddo FINDIT
336-
do i=1,size(settings%name)
337-
if(.not.foundit(i))then
338-
write(stderr,'(*(g0,1x))')'fpm::run<ERROR>:executable',trim(settings%name(i)),'not located'
339-
endif
340-
enddo
341-
if(allocated(foundit))deallocate(foundit)
342-
endif
343-
do i=1,size(newwords)
344-
!*! list is a new option for use with xargs, to move files to production area, valgrind, gdb, ls -l, ....
345-
!*! maybe add as --mask and could do --mask 'echo %xx' or --mask 'cp %XX /usr/local/bin/' an so on
346-
!*! default if blank would be filename uptodate|needs|updated|doesnotexist creation_date, ...
347-
!*! or maybe just list filenames so can pipe through xargs, and so on
348-
if(settings%list)then
349-
write(stderr,'(*(g0,1x))')'fpm::run<INFO>:executable expected at',newwords(i),&
350-
& merge('exists ','does not exist',exists(newwords(i)))
351-
cycle
352-
endif
353-
cmd=newwords(i) // ' ' // settings%args
354-
if(exists(newwords(i)))then
355-
call run(cmd)
356-
else ! try to build -- once build works conditionally this should be an unconditional call
357-
call cmd_build(fpm_build_settings(release=settings%release,list=.false.))
358-
if(exists(newwords(i)))then
359-
call run(cmd)
360-
else
361-
write(stderr,*)'fpm::run<ERROR>',cmd,' not found'
362-
endif
363-
endif
364-
enddo
365-
deallocate(newwords)
366-
end subroutine cmd_run
318+
error stop 1
319+
end if
367320

321+
call package_defaults(package)
368322

369-
subroutine cmd_test(settings)
370-
type(fpm_test_settings), intent(in) :: settings
371-
character(len=:),allocatable :: release_name, cmd, fname
372-
integer :: i, j
373-
type(package_t) :: package
374-
type(error_t), allocatable :: error
375-
character(len=:),allocatable :: newwords(:)
376-
logical,allocatable :: foundit(:)
377-
logical :: list
378-
call get_package_data(package, "fpm.toml", error)
323+
call build_model(model, settings%fpm_build_settings, package, error)
379324
if (allocated(error)) then
380325
print '(a)', error%message
381-
stop
382-
endif
383-
release_name=trim(merge('gfortran_release','gfortran_debug ',settings%release))
384-
newwords=[character(len=0) ::]
326+
error stop 1
327+
end if
385328

386-
! Populate test in case we find the default test directory
387-
if (.not.allocated(package%test) .and. exists("test")) then
388-
allocate(package%test(1))
389-
call default_test(package%test(1), package%name)
390-
endif
391-
if(size(settings%name).eq.0)then
392-
if ( .not.allocated(package%test) ) then
393-
write(stderr,'(*(g0,1x))')'fpm::run<INFO>:no tests found in fpm.toml and no default test/ directory'
394-
stop
395-
endif
396-
allocate(foundit(size(package%test)))
397-
do i=1,size(package%test)
398-
fname=join_path('build',release_name,package%test(i)%source_dir,package%test(i)%name)
399-
newwords=[character(len=max(len(newwords),len(fname))) :: newwords,fname]
400-
enddo
401-
if(size(newwords).lt.1)then
402-
write(stderr,'(*(g0,1x))')'fpm::run<INFO>:no tests found in fpm.toml'
403-
stop
404-
endif
405-
else
406-
!*! expand names, duplicates are a problem??
407-
allocate(foundit(size(settings%name)))
408-
foundit=.false.
409-
FINDIT: do i=1,size(package%test)
410-
do j=1,size(settings%name)
411-
if(settings%name(j).eq.package%test(i)%name)then
412-
fname=join_path('build',release_name,package%test(i)%source_dir,package%test(i)%name)
413-
newwords=[character(len=max(len(newwords),len(fname))) :: newwords,fname]
414-
foundit(j)=.true.
415-
endif
416-
enddo
417-
enddo FINDIT
418-
do i=1,size(settings%name)
419-
if(.not.foundit(i))then
420-
write(stderr,'(*(g0,1x))')'fpm::run<ERROR>:test',trim(settings%name(i)),'not located'
421-
endif
422-
enddo
423-
if(allocated(foundit))deallocate(foundit)
424-
endif
425-
do i=1,size(newwords)
426-
!*! list is a new option for use with xargs, to move files to production area, valgrind, gdb, ls -l, ....
427-
!*! maybe add as --mask and could do --mask 'echo %xx' or --mask 'cp %XX /usr/local/bin/' an so on
428-
!*! default if blank would be filename uptodate|needs|updated|doesnotexist creation_date, ...
429-
!*! or maybe just list filenames so can pipe through xargs, and so on
430-
if(settings%list)then
431-
write(stderr,'(*(g0,1x))')'fpm::run<INFO>:test expected at',newwords(i),&
432-
& merge('exists ','does not exist',exists(newwords(i)))
433-
cycle
434-
endif
435-
cmd=newwords(i) // ' ' // settings%args
436-
if(exists(newwords(i)))then
437-
call run(cmd)
438-
else ! try to build -- once build works conditionally this should be an unconditional call
439-
call cmd_build(fpm_build_settings(release=settings%release,list=.false.))
440-
if(exists(newwords(i)))then
441-
call run(cmd)
329+
! Enumerate executable targets to run
330+
allocate(executables(0))
331+
do i=1,size(model%targets)
332+
333+
exe_target => model%targets(i)%ptr
334+
335+
if (exe_target%target_type == FPM_TARGET_EXECUTABLE .and. &
336+
allocated(exe_target%dependencies)) then
337+
338+
exe_source => exe_target%dependencies(1)%ptr%source
339+
340+
if (exe_source%unit_scope == &
341+
merge(FPM_SCOPE_TEST,FPM_SCOPE_APP,test)) then
342+
343+
if (size(settings%name) == 0) then
344+
345+
exe_cmd%s = exe_target%output_file
346+
executables = [executables, exe_cmd]
347+
348+
else
349+
350+
do j=1,size(settings%name)
351+
352+
if (trim(settings%name(j))==exe_source%exe_name) then
353+
354+
exe_cmd%s = exe_target%output_file
355+
executables = [executables, exe_cmd]
356+
357+
end if
358+
359+
end do
360+
361+
end if
362+
363+
end if
364+
365+
end if
366+
367+
end do
368+
369+
! NB. To be replaced after incremental rebuild is implemented
370+
if (.not.settings%list .and. &
371+
any([(.not.exists(executables(i)%s),i=1,size(executables))])) then
372+
373+
call build_package(model)
374+
375+
end if
376+
377+
do i=1,size(executables)
378+
if (settings%list) then
379+
write(stderr,*) executables(i)%s
380+
else
381+
382+
if (exists(executables(i)%s)) then
383+
call run(executables(i)%s//" "//settings%args)
442384
else
443-
write(stderr,*)'fpm::run<ERROR>',cmd,' not found'
444-
endif
445-
endif
446-
enddo
447-
deallocate(newwords)
448-
end subroutine cmd_test
385+
write(stderr,*)'fpm::run<ERROR>',executables(i)%s,' not found'
386+
stop 1
387+
end if
449388

389+
end if
390+
end do
391+
392+
end subroutine cmd_run
450393

451394
end module fpm

0 commit comments

Comments
 (0)