Skip to content

Commit 5aa571c

Browse files
committed
Fix: add message and listing when run name not found
1 parent c7cb062 commit 5aa571c

File tree

1 file changed

+42
-0
lines changed

1 file changed

+42
-0
lines changed

fpm/src/fpm.f90

Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -305,6 +305,7 @@ subroutine cmd_run(settings,test)
305305
logical, intent(in) :: test
306306

307307
integer :: i, j
308+
logical :: found(size(settings%name))
308309
type(error_t), allocatable :: error
309310
type(package_t) :: package
310311
type(fpm_model_t) :: model
@@ -328,6 +329,7 @@ subroutine cmd_run(settings,test)
328329
end if
329330

330331
! Enumerate executable targets to run
332+
found(:) = .false.
331333
allocate(executables(0))
332334
do i=1,size(model%targets)
333335

@@ -352,6 +354,7 @@ subroutine cmd_run(settings,test)
352354

353355
if (trim(settings%name(j))==exe_source%exe_name) then
354356

357+
found(j) = .true.
355358
exe_cmd%s = exe_target%output_file
356359
executables = [executables, exe_cmd]
357360

@@ -367,6 +370,45 @@ subroutine cmd_run(settings,test)
367370

368371
end do
369372

373+
! Check all names are valid
374+
if (any(.not.found)) then
375+
376+
write(stderr,'(A)',advance="no")'fpm::run<ERROR> specified names '
377+
do j=1,size(settings%name)
378+
if (.not.found(j)) write(stderr,'(A)',advance="no") '"'//trim(settings%name(j))//'" '
379+
end do
380+
write(stderr,'(A)') 'not found.'
381+
write(stderr,*)
382+
383+
j = 1
384+
write(stderr,*) 'Available names:'
385+
do i=1,size(model%targets)
386+
387+
exe_target => model%targets(i)%ptr
388+
389+
if (exe_target%target_type == FPM_TARGET_EXECUTABLE .and. &
390+
allocated(exe_target%dependencies)) then
391+
392+
exe_source => exe_target%dependencies(1)%ptr%source
393+
394+
if (exe_source%unit_scope == &
395+
merge(FPM_SCOPE_TEST,FPM_SCOPE_APP,test)) then
396+
397+
write(stderr,'(A17)',advance=(merge("yes","no ",modulo(j,4)==0))) basename(exe_target%output_file)
398+
399+
j = j + 1
400+
401+
end if
402+
403+
end if
404+
405+
end do
406+
407+
write(stderr,*)
408+
stop 1
409+
410+
end if
411+
370412
! NB. To be replaced after incremental rebuild is implemented
371413
if (.not.settings%list .and. &
372414
any([(.not.exists(executables(i)%s),i=1,size(executables))])) then

0 commit comments

Comments
 (0)