Skip to content

Commit fcbab5d

Browse files
committed
Merge remote-tracking branch 'upstream/master' into separate-targets
2 parents 4336020 + 32c96e5 commit fcbab5d

File tree

9 files changed

+787
-265
lines changed

9 files changed

+787
-265
lines changed

README.md

Lines changed: 9 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -72,32 +72,26 @@ $ cd fpm/
7272

7373
#### Build a bootstrap version of fpm
7474

75-
You can use the install script to perform the build of the Haskell version of *fpm* with:
75+
You can use the install script to bootstrap and install *fpm*:
7676

7777
```bash
7878
$ ./install.sh
7979
```
8080

81-
On Linux, the above command installs `fpm` to `${HOME}/.local/bin/`.
82-
83-
Now you can build the Fortran *fpm* version with
81+
By default, the above command installs `fpm` to `${HOME}/.local/bin/`.
82+
To specify an alternative destination use the `--prefix=` flag, for example:
8483

8584
```bash
86-
$ cd fpm/
87-
$ fpm build
85+
$ ./install.sh --prefix=/usr/local
8886
```
8987

90-
Test that everything is working as expected
88+
which will install *fpm* to `/usr/local/bin`.
9189

92-
```bash
93-
$ fpm test
94-
```
95-
96-
Finally, install the Fortran *fpm* version with
90+
To test that everything is working as expected you can now build *fpm*
91+
with itself and run the tests with:
9792

9893
```bash
99-
$ fpm run --runner mv -- ~/.local/bin
94+
$ cd fpm
95+
$ fpm test
10096
```
10197

102-
Or choose another location if you do not want to overwrite the bootstrapping version.
103-
From now on you can rebuild *fpm* with your Fortran *fpm* version.

fpm/src/fpm.f90

Lines changed: 75 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
module fpm
2-
use fpm_strings, only: string_t, operator(.in.)
2+
use fpm_strings, only: string_t, operator(.in.), glob, join
33
use fpm_backend, only: build_package
44
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
55
fpm_run_settings, fpm_install_settings, fpm_test_settings
@@ -65,6 +65,9 @@ subroutine build_model(model, settings, package, error)
6565
model%output_directory = join_path('build',basename(model%fortran_compiler)//'_'//settings%build_name)
6666

6767
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
6871

6972
allocate(model%packages(model%deps%ndep))
7073

@@ -197,8 +200,7 @@ subroutine cmd_run(settings,test)
197200
class(fpm_run_settings), intent(in) :: settings
198201
logical, intent(in) :: test
199202

200-
integer, parameter :: LINE_WIDTH = 80
201-
integer :: i, j, col_width, nCol
203+
integer :: i, j, col_width
202204
logical :: found(size(settings%name))
203205
type(error_t), allocatable :: error
204206
type(package_config_t) :: package
@@ -209,6 +211,8 @@ subroutine cmd_run(settings,test)
209211
type(build_target_t), pointer :: exe_target
210212
type(srcfile_t), pointer :: exe_source
211213
integer :: run_scope
214+
character(len=:),allocatable :: line
215+
logical :: toomany
212216

213217
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
214218
if (allocated(error)) then
@@ -260,7 +264,7 @@ subroutine cmd_run(settings,test)
260264

261265
do j=1,size(settings%name)
262266

263-
if (trim(settings%name(j))==exe_source%exe_name) then
267+
if (glob(trim(exe_source%exe_name),trim(settings%name(j)))) then
264268

265269
found(j) = .true.
266270
exe_cmd%s = exe_target%output_file
@@ -289,15 +293,61 @@ subroutine cmd_run(settings,test)
289293
end if
290294

291295
! 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
293317

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)
300329

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
301351
j = 1
302352
nCol = LINE_WIDTH/col_width
303353
write(stderr,*) 'Available names:'
@@ -317,36 +367,24 @@ subroutine cmd_run(settings,test)
317367
j = j + 1
318368

319369
end if
320-
321370
end if
322-
323371
end do
324-
325372
write(stderr,*)
326-
stop 1
373+
end subroutine compact_list_all
327374

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
350388

351389
end subroutine cmd_run
352390

0 commit comments

Comments
 (0)