1
1
module fpm
2
- use fpm_strings, only: string_t, operator (.in .)
2
+ use fpm_strings, only: string_t, operator (.in .), glob, join
3
3
use fpm_backend, only: build_package
4
4
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
5
5
fpm_run_settings, fpm_install_settings, fpm_test_settings
@@ -65,6 +65,9 @@ subroutine build_model(model, settings, package, error)
65
65
model% output_directory = join_path(' build' ,basename(model% fortran_compiler)// ' _' // settings% build_name)
66
66
67
67
call add_compile_flag_defaults(settings% build_name, basename(model% fortran_compiler), model)
68
+ if (settings% verbose)then
69
+ write (* ,* )' <INFO>COMPILER OPTIONS: ' , model% fortran_compile_flags
70
+ endif
68
71
69
72
allocate (model% packages(model% deps% ndep))
70
73
@@ -197,8 +200,7 @@ subroutine cmd_run(settings,test)
197
200
class(fpm_run_settings), intent (in ) :: settings
198
201
logical , intent (in ) :: test
199
202
200
- integer , parameter :: LINE_WIDTH = 80
201
- integer :: i, j, col_width, nCol
203
+ integer :: i, j, col_width
202
204
logical :: found(size (settings% name))
203
205
type (error_t), allocatable :: error
204
206
type (package_config_t) :: package
@@ -209,6 +211,8 @@ subroutine cmd_run(settings,test)
209
211
type (build_target_t), pointer :: exe_target
210
212
type (srcfile_t), pointer :: exe_source
211
213
integer :: run_scope
214
+ character (len= :),allocatable :: line
215
+ logical :: toomany
212
216
213
217
call get_package_data(package, " fpm.toml" , error, apply_defaults= .true. )
214
218
if (allocated (error)) then
@@ -260,7 +264,7 @@ subroutine cmd_run(settings,test)
260
264
261
265
do j= 1 ,size (settings% name)
262
266
263
- if (trim (settings% name (j))==exe_source % exe_name ) then
267
+ if (glob( trim (exe_source % exe_name), trim ( settings% name (j))) ) then
264
268
265
269
found(j) = .true.
266
270
exe_cmd% s = exe_target% output_file
@@ -289,15 +293,61 @@ subroutine cmd_run(settings,test)
289
293
end if
290
294
291
295
! Check all names are valid
292
- if (any (.not. found)) then
296
+ ! or no name and found more than one file
297
+ toomany= size (settings% name).eq. 0 .and. size (executables).gt. 1
298
+ if ( any (.not. found) &
299
+ & .or. &
300
+ & ( (toomany .and. .not. test) .or. (toomany .and. settings% runner .ne. ' ' ) ) &
301
+ & .and. &
302
+ & .not. settings% list) then
303
+ line= join(settings% name)
304
+ if (line.ne. ' .' )then ! do not report these special strings
305
+ if (any (.not. found))then
306
+ write (stderr,' (A)' ,advance= " no" )' fpm::run<ERROR> specified names '
307
+ do j= 1 ,size (settings% name)
308
+ if (.not. found(j)) write (stderr,' (A)' ,advance= " no" ) ' "' // trim (settings% name (j))// ' " '
309
+ end do
310
+ write (stderr,' (A)' ) ' not found.'
311
+ write (stderr,* )
312
+ else if (settings% verbose)then
313
+ write (stderr,' (A)' ,advance= " yes" )' <INFO>when more than one executable is available'
314
+ write (stderr,' (A)' ,advance= " yes" )' program names must be specified.'
315
+ endif
316
+ endif
293
317
294
- write (stderr,' (A)' ,advance= " no" )' fpm::run<ERROR> specified names '
295
- do j= 1 ,size (settings% name)
296
- if (.not. found(j)) write (stderr,' (A)' ,advance= " no" ) ' "' // trim (settings% name (j))// ' " '
297
- end do
298
- write (stderr,' (A)' ) ' not found.'
299
- write (stderr,* )
318
+ call compact_list_all()
319
+
320
+ if (line.eq. ' .' .or. line.eq. ' ' )then ! do not report these special strings
321
+ stop
322
+ else
323
+ stop 1
324
+ endif
325
+
326
+ end if
327
+
328
+ call build_package(targets,model)
300
329
330
+ if (settings% list) then
331
+ call compact_list()
332
+ else
333
+
334
+ do i= 1 ,size (executables)
335
+ if (exists(executables(i)% s)) then
336
+ if (settings% runner .ne. ' ' )then
337
+ call run(settings% runner// ' ' // executables(i)% s// " " // settings% args,echo= settings% verbose)
338
+ else
339
+ call run(executables(i)% s// " " // settings% args,echo= settings% verbose)
340
+ endif
341
+ else
342
+ write (stderr,* )' fpm::run<ERROR>' ,executables(i)% s,' not found'
343
+ stop 1
344
+ end if
345
+ end do
346
+ endif
347
+ contains
348
+ subroutine compact_list_all ()
349
+ integer , parameter :: LINE_WIDTH = 80
350
+ integer :: i, j, nCol
301
351
j = 1
302
352
nCol = LINE_WIDTH/ col_width
303
353
write (stderr,* ) ' Available names:'
@@ -317,36 +367,24 @@ subroutine cmd_run(settings,test)
317
367
j = j + 1
318
368
319
369
end if
320
-
321
370
end if
322
-
323
371
end do
324
-
325
372
write (stderr,* )
326
- stop 1
373
+ end subroutine compact_list_all
327
374
328
- end if
329
-
330
- call build_package(targets,model)
331
-
332
- do i= 1 ,size (executables)
333
- if (settings% list) then
334
- write (stderr,* ) executables(i)% s
335
- else
336
-
337
- if (exists(executables(i)% s)) then
338
- if (settings% runner .ne. ' ' )then
339
- call run(settings% runner// ' ' // executables(i)% s// " " // settings% args)
340
- else
341
- call run(executables(i)% s// " " // settings% args)
342
- endif
343
- else
344
- write (stderr,* )' fpm::run<ERROR>' ,executables(i)% s,' not found'
345
- stop 1
346
- end if
347
-
348
- end if
349
- end do
375
+ subroutine compact_list ()
376
+ integer , parameter :: LINE_WIDTH = 80
377
+ integer :: i, j, nCol
378
+ j = 1
379
+ nCol = LINE_WIDTH/ col_width
380
+ write (stderr,* ) ' Matched names:'
381
+ do i= 1 ,size (executables)
382
+ write (stderr,' (A)' ,advance= (merge (" yes" ," no " ,modulo (j,nCol)==0 ))) &
383
+ & [character (len= col_width) :: basename(executables(i)% s)]
384
+ j = j + 1
385
+ enddo
386
+ write (stderr,* )
387
+ end subroutine compact_list
350
388
351
389
end subroutine cmd_run
352
390
0 commit comments