Skip to content

Commit 3045817

Browse files
authored
Merge pull request #701 from zoziha/package_by_package
Some cleanups and minor fixes
2 parents 97df4cf + c24ea66 commit 3045817

File tree

12 files changed

+143
-137
lines changed

12 files changed

+143
-137
lines changed

src/fpm.f90

Lines changed: 6 additions & 6 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.), glob, join, string_cat, fnv_1a, &
2+
use fpm_strings, only: string_t, operator(.in.), glob, join, string_cat, &
33
lower, str_ends_with
44
use fpm_backend, only: build_package
55
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
@@ -393,14 +393,14 @@ subroutine cmd_run(settings,test)
393393

394394
! Check all names are valid
395395
! or no name and found more than one file
396-
toomany= size(settings%name).eq.0 .and. size(executables).gt.1
396+
toomany= size(settings%name)==0 .and. size(executables)>1
397397
if ( any(.not.found) &
398398
& .or. &
399-
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
399+
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner /= '') ) &
400400
& .and. &
401401
& .not.settings%list) then
402402
line=join(settings%name)
403-
if(line.ne.'.')then ! do not report these special strings
403+
if(line/='.')then ! do not report these special strings
404404
if(any(.not.found))then
405405
write(stderr,'(A)',advance="no")'<ERROR>*cmd_run*:specified names '
406406
do j=1,size(settings%name)
@@ -416,7 +416,7 @@ subroutine cmd_run(settings,test)
416416

417417
call compact_list_all()
418418

419-
if(line.eq.'.' .or. line.eq.' ')then ! do not report these special strings
419+
if(line=='.' .or. line==' ')then ! do not report these special strings
420420
call fpm_stop(0,'')
421421
else
422422
call fpm_stop(1,'')
@@ -433,7 +433,7 @@ subroutine cmd_run(settings,test)
433433
allocate(stat(size(executables)))
434434
do i=1,size(executables)
435435
if (exists(executables(i)%s)) then
436-
if(settings%runner .ne. ' ')then
436+
if(settings%runner /= ' ')then
437437
if(.not.allocated(settings%args))then
438438
call run(settings%runner//' '//executables(i)%s, &
439439
echo=settings%verbose, exitstat=stat(i))

src/fpm/cmd/new.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -573,7 +573,7 @@ subroutine cmd_new(settings)
573573
call create_verified_basic_manifest(join_path(settings%name, 'fpm.toml'))
574574
endif
575575
! assumes git(1) is installed and in path
576-
if(which('git').ne.'')then
576+
if(which('git')/='')then
577577
call run('git init ' // settings%name)
578578
endif
579579
contains

src/fpm/error.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -166,8 +166,8 @@ subroutine fpm_stop(value,message)
166166
integer, intent(in) :: value
167167
!> Error message
168168
character(len=*), intent(in) :: message
169-
if(message.ne.'')then
170-
if(value.gt.0)then
169+
if(message/='')then
170+
if(value>0)then
171171
write(stderr,'("<ERROR>",a)')trim(message)
172172
else
173173
write(stderr,'("<INFO> ",a)')trim(message)

src/fpm_backend_output.f90

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,7 @@ subroutine output_status_compiling(progress, queue_index)
7676

7777
character(:), allocatable :: target_name
7878
character(100) :: output_string
79-
character(100) :: overall_progress
79+
character(7) :: overall_progress
8080

8181
associate(target=>progress%target_queue(queue_index)%ptr)
8282

@@ -86,12 +86,12 @@ subroutine output_status_compiling(progress, queue_index)
8686
target_name = basename(target%output_file)
8787
end if
8888

89-
write(overall_progress,'(A,I4,A)') '[',100*progress%n_complete/progress%n_target,'%]'
89+
write(overall_progress,'(A,I3,A)') '[',100*progress%n_complete/progress%n_target,'%] '
9090

9191
if (progress%plain_mode) then ! Plain output
9292

9393
!$omp critical
94-
write(*,'(A8,A30)') trim(overall_progress),target_name
94+
write(*,'(A7,A30)') overall_progress,target_name
9595
!$omp end critical
9696

9797
else ! Pretty output
@@ -100,7 +100,7 @@ subroutine output_status_compiling(progress, queue_index)
100100

101101
call progress%console%write_line(trim(output_string),progress%output_lines(queue_index))
102102

103-
call progress%console%write_line(trim(overall_progress)//'Compiling...',advance=.false.)
103+
call progress%console%write_line(overall_progress//'Compiling...',advance=.false.)
104104

105105
end if
106106

@@ -119,7 +119,7 @@ subroutine output_status_complete(progress, queue_index, build_stat)
119119

120120
character(:), allocatable :: target_name
121121
character(100) :: output_string
122-
character(100) :: overall_progress
122+
character(7) :: overall_progress
123123

124124
!$omp critical
125125
progress%n_complete = progress%n_complete + 1
@@ -139,19 +139,19 @@ subroutine output_status_complete(progress, queue_index, build_stat)
139139
write(output_string,'(A,T40,A,A)') target_name,COLOR_RED//'failed.'//COLOR_RESET
140140
end if
141141

142-
write(overall_progress,'(A,I4,A)') '[',100*progress%n_complete/progress%n_target,'%] '
142+
write(overall_progress,'(A,I3,A)') '[',100*progress%n_complete/progress%n_target,'%] '
143143

144144
if (progress%plain_mode) then ! Plain output
145145

146146
!$omp critical
147-
write(*,'(A8,A30,A7)') trim(overall_progress),target_name, 'done.'
147+
write(*,'(A7,A30,A7)') overall_progress,target_name, 'done.'
148148
!$omp end critical
149149

150150
else ! Pretty output
151151

152152
call progress%console%update_line(progress%output_lines(queue_index),trim(output_string))
153153

154-
call progress%console%write_line(trim(overall_progress)//'Compiling...',advance=.false.)
154+
call progress%console%write_line(overall_progress//'Compiling...',advance=.false.)
155155

156156
end if
157157

src/fpm_command_line.f90

Lines changed: 15 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ module fpm_command_line
2828
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
2929
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
3030
use M_CLI2, only : get_subcommand, CLI_RESPONSE_FILE
31-
use fpm_strings, only : lower, split, fnv_1a, to_fortran_name, is_fortran_name
31+
use fpm_strings, only : lower, split, to_fortran_name, is_fortran_name
3232
use fpm_filesystem, only : basename, canon_path, which, run
3333
use fpm_environment, only : get_command_arguments_quoted
3434
use fpm_error, only : fpm_stop, error_t
@@ -262,7 +262,7 @@ subroutine get_command_line_settings(cmd_settings)
262262

263263
call check_build_vals()
264264

265-
if( size(unnamed) .gt. 1 )then
265+
if( size(unnamed) > 1 )then
266266
names=unnamed(2:)
267267
else
268268
names=[character(len=len(names)) :: ]
@@ -282,14 +282,14 @@ subroutine get_command_line_settings(cmd_settings)
282282
! convert special string '..' to equivalent (shorter) '*'
283283
! to allow for a string that does not require shift-key and quoting
284284
do i=1,size(names)
285-
if(names(i).eq.'..')names(i)='*'
285+
if(names(i)=='..')names(i)='*'
286286
enddo
287287

288288
c_compiler = sget('c-compiler')
289289
archiver = sget('archiver')
290290
allocate(fpm_run_settings :: cmd_settings)
291291
val_runner=sget('runner')
292-
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
292+
if(specified('runner') .and. val_runner=='')val_runner='echo'
293293
cmd_settings=fpm_run_settings(&
294294
& args=remaining,&
295295
& profile=val_profile,&
@@ -361,7 +361,7 @@ subroutine get_command_line_settings(cmd_settings)
361361
call fpm_stop(2,'only one directory name allowed')
362362
end select
363363
!*! canon_path is not converting ".", etc.
364-
if(name.eq.'.')then
364+
if(name=='.')then
365365
call get_current_directory(name, error)
366366
if (allocated(error)) then
367367
write(stderr, '("[Error]", 1x, a)') error%message
@@ -414,13 +414,13 @@ subroutine get_command_line_settings(cmd_settings)
414414

415415
case('help','manual')
416416
call set_args(common_args, help_help,version_text)
417-
if(size(unnamed).lt.2)then
418-
if(unnamed(1).eq.'help')then
417+
if(size(unnamed)<2)then
418+
if(unnamed(1)=='help')then
419419
unnamed=[' ', 'fpm']
420420
else
421421
unnamed=manual
422422
endif
423-
elseif(unnamed(2).eq.'manual')then
423+
elseif(unnamed(2)=='manual')then
424424
unnamed=manual
425425
endif
426426
widest=256
@@ -505,7 +505,7 @@ subroutine get_command_line_settings(cmd_settings)
505505

506506
call check_build_vals()
507507

508-
if( size(unnamed) .gt. 1 )then
508+
if( size(unnamed) > 1 )then
509509
names=unnamed(2:)
510510
else
511511
names=[character(len=len(names)) :: ]
@@ -519,14 +519,14 @@ subroutine get_command_line_settings(cmd_settings)
519519
! convert special string '..' to equivalent (shorter) '*'
520520
! to allow for a string that does not require shift-key and quoting
521521
do i=1,size(names)
522-
if(names(i).eq.'..')names(i)='*'
522+
if(names(i)=='..')names(i)='*'
523523
enddo
524524

525525
c_compiler = sget('c-compiler')
526526
archiver = sget('archiver')
527527
allocate(fpm_test_settings :: cmd_settings)
528528
val_runner=sget('runner')
529-
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
529+
if(specified('runner') .and. val_runner=='')val_runner='echo'
530530
cmd_settings=fpm_test_settings(&
531531
& args=remaining, &
532532
& profile=val_profile, &
@@ -548,7 +548,7 @@ subroutine get_command_line_settings(cmd_settings)
548548
call set_args(common_args // ' --fetch-only F --clean F', &
549549
help_update, version_text)
550550

551-
if( size(unnamed) .gt. 1 )then
551+
if( size(unnamed) > 1 )then
552552
names=unnamed(2:)
553553
else
554554
names=[character(len=len(names)) :: ]
@@ -575,7 +575,6 @@ subroutine get_command_line_settings(cmd_settings)
575575
case default
576576

577577
if(cmdarg.ne.''.and.which('fpm-'//cmdarg).ne.'')then
578-
579578
call run('fpm-'//trim(cmdarg)//' '// get_command_arguments_quoted(),.false.)
580579
else
581580
call set_args('&
@@ -586,7 +585,7 @@ subroutine get_command_line_settings(cmd_settings)
586585
help_text=help_usage
587586
if(lget('list'))then
588587
help_text=help_list_dash
589-
elseif(len_trim(cmdarg).eq.0)then
588+
elseif(len_trim(cmdarg)==0)then
590589
write(stdout,'(*(a))')'Fortran Package Manager:'
591590
write(stdout,'(*(a))')' '
592591
call printhelp(help_list_nodash)
@@ -611,7 +610,7 @@ subroutine check_build_vals()
611610
character(len=:), allocatable :: flags
612611

613612
val_compiler=sget('compiler')
614-
if(val_compiler.eq.'') then
613+
if(val_compiler=='') then
615614
val_compiler='gfortran'
616615
endif
617616

@@ -627,7 +626,7 @@ subroutine printhelp(lines)
627626
integer :: iii,ii
628627
if(allocated(lines))then
629628
ii=size(lines)
630-
if(ii .gt. 0 .and. len(lines).gt. 0) then
629+
if(ii > 0 .and. len(lines)> 0) then
631630
write(stdout,'(g0)')(trim(lines(iii)), iii=1, ii)
632631
else
633632
write(stdout,'(a)')'<WARNING> *printhelp* output requested is empty'

src/fpm_environment.f90

Lines changed: 13 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -171,7 +171,7 @@ function get_env(NAME,DEFAULT) result(VALUE)
171171
integer :: length
172172
! get length required to hold value
173173
length=0
174-
if(NAME.ne.'')then
174+
if(NAME/='')then
175175
call get_environment_variable(NAME, length=howbig,status=stat,trim_name=.true.)
176176
select case (stat)
177177
case (1)
@@ -185,12 +185,12 @@ function get_env(NAME,DEFAULT) result(VALUE)
185185
allocate(character(len=max(howbig,1)) :: VALUE)
186186
! get value
187187
call get_environment_variable(NAME,VALUE,status=stat,trim_name=.true.)
188-
if(stat.ne.0)VALUE=''
188+
if(stat/=0)VALUE=''
189189
end select
190190
else
191191
VALUE=''
192192
endif
193-
if(VALUE.eq.''.and.present(DEFAULT))VALUE=DEFAULT
193+
if(VALUE==''.and.present(DEFAULT))VALUE=DEFAULT
194194
end function get_env
195195

196196
function get_command_arguments_quoted() result(args)
@@ -200,7 +200,7 @@ function get_command_arguments_quoted() result(args)
200200
integer :: ilength, istatus, i
201201
ilength=0
202202
args=''
203-
quote=merge('"',"'",separator().eq.'\')
203+
quote=merge('"',"'",separator()=='\')
204204
do i=2,command_argument_count() ! look at all arguments after subcommand
205205
call get_command_argument(number=i,length=ilength,status=istatus)
206206
if(istatus /= 0) then
@@ -213,10 +213,10 @@ function get_command_arguments_quoted() result(args)
213213
if(istatus /= 0) then
214214
write(stderr,'(*(g0,1x))')'<ERROR>*get_command_arguments_stack* error obtaining argument ',i
215215
exit
216-
elseif(ilength.gt.0)then
217-
if(index(arg//' ','-').ne.1)then
216+
elseif(ilength>0)then
217+
if(index(arg//' ','-')/=1)then
218218
args=args//quote//arg//quote//' '
219-
elseif(index(arg,' ').ne.0)then
219+
elseif(index(arg,' ')/=0)then
220220
args=args//quote//arg//quote//' '
221221
else
222222
args=args//arg//' '
@@ -273,7 +273,7 @@ function separator() result(sep)
273273
character(len=4096) :: name
274274
character(len=:),allocatable :: fname
275275

276-
!*ifort_bug*! if(sep_cache.ne.' ')then ! use cached value. NOTE: A parallel code might theoretically use multiple OS
276+
!*ifort_bug*! if(sep_cache/=' ')then ! use cached value. NOTE: A parallel code might theoretically use multiple OS
277277
!*ifort_bug*! sep=sep_cache
278278
!*ifort_bug*! return
279279
!*ifort_bug*! endif
@@ -285,18 +285,18 @@ function separator() result(sep)
285285
allocate(character(len=arg0_length) :: arg0)
286286
call get_command_argument(0,arg0,status=istat)
287287
! check argument name
288-
if(index(arg0,'\').ne.0)then
288+
if(index(arg0,'\')/=0)then
289289
sep='\'
290-
elseif(index(arg0,'/').ne.0)then
290+
elseif(index(arg0,'/')/=0)then
291291
sep='/'
292292
else
293293
! try name returned by INQUIRE(3f)
294294
existing=.false.
295295
name=' '
296296
inquire(file=arg0,iostat=istat,exist=existing,name=name)
297-
if(index(name,'\').ne.0)then
297+
if(index(name,'\')/=0)then
298298
sep='\'
299-
elseif(index(name,'/').ne.0)then
299+
elseif(index(name,'/')/=0)then
300300
sep='/'
301301
else
302302
! well, try some common syntax and assume in current directory
@@ -310,7 +310,7 @@ function separator() result(sep)
310310
if(existing)then
311311
sep='/'
312312
else ! check environment variable PATH
313-
sep=merge('\','/',index(get_env('PATH'),'\').ne.0)
313+
sep=merge('\','/',index(get_env('PATH'),'\')/=0)
314314
!*!write(*,*)'<WARNING>unknown system directory path separator'
315315
endif
316316
endif

0 commit comments

Comments
 (0)