Skip to content

Commit 72465f4

Browse files
committed
.gt. -> >
1 parent 358a66a commit 72465f4

File tree

8 files changed

+16
-16
lines changed

8 files changed

+16
-16
lines changed

src/fpm.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -390,7 +390,7 @@ subroutine cmd_run(settings,test)
390390

391391
! Check all names are valid
392392
! or no name and found more than one file
393-
toomany= size(settings%name)==0 .and. size(executables).gt.1
393+
toomany= size(settings%name)==0 .and. size(executables)>1
394394
if ( any(.not.found) &
395395
& .or. &
396396
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner /= '') ) &

src/fpm/error.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -167,7 +167,7 @@ subroutine fpm_stop(value,message)
167167
!> Error message
168168
character(len=*), intent(in) :: message
169169
if(message/='')then
170-
if(value.gt.0)then
170+
if(value>0)then
171171
write(stderr,'("<ERROR>",a)')trim(message)
172172
else
173173
write(stderr,'("<INFO> ",a)')trim(message)

src/fpm_command_line.f90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -251,7 +251,7 @@ subroutine get_command_line_settings(cmd_settings)
251251

252252
call check_build_vals()
253253

254-
if( size(unnamed) .gt. 1 )then
254+
if( size(unnamed) > 1 )then
255255
names=unnamed(2:)
256256
else
257257
names=[character(len=len(names)) :: ]
@@ -491,7 +491,7 @@ subroutine get_command_line_settings(cmd_settings)
491491

492492
call check_build_vals()
493493

494-
if( size(unnamed) .gt. 1 )then
494+
if( size(unnamed) > 1 )then
495495
names=unnamed(2:)
496496
else
497497
names=[character(len=len(names)) :: ]
@@ -533,7 +533,7 @@ subroutine get_command_line_settings(cmd_settings)
533533
call set_args(common_args // ' --fetch-only F --clean F', &
534534
help_update, version_text)
535535

536-
if( size(unnamed) .gt. 1 )then
536+
if( size(unnamed) > 1 )then
537537
names=unnamed(2:)
538538
else
539539
names=[character(len=len(names)) :: ]
@@ -611,7 +611,7 @@ subroutine printhelp(lines)
611611
integer :: iii,ii
612612
if(allocated(lines))then
613613
ii=size(lines)
614-
if(ii .gt. 0 .and. len(lines).gt. 0) then
614+
if(ii > 0 .and. len(lines)> 0) then
615615
write(stdout,'(g0)')(trim(lines(iii)), iii=1, ii)
616616
else
617617
write(stdout,'(a)')'<WARNING> *printhelp* output requested is empty'

src/fpm_environment.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -213,7 +213,7 @@ 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
216+
elseif(ilength>0)then
217217
if(index(arg//' ','-')/=1)then
218218
args=args//quote//arg//quote//' '
219219
elseif(index(arg,' ')/=0)then

src/fpm_filesystem.F90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -97,7 +97,7 @@ function basename(path,suffix) result (base)
9797
end if
9898

9999
call split(path,file_parts,delimiters='\/')
100-
if(size(file_parts).gt.0)then
100+
if(size(file_parts)>0)then
101101
base = trim(file_parts(size(file_parts)))
102102
else
103103
base = ''
@@ -446,7 +446,7 @@ recursive subroutine list_files(dir, files, recurse)
446446

447447
i = i + 1
448448

449-
if (i .gt. N_MAX) then
449+
if (i > N_MAX) then
450450
files = [files, files_tmp]
451451
i = 1
452452
end if
@@ -462,7 +462,7 @@ recursive subroutine list_files(dir, files, recurse)
462462
error stop
463463
end if
464464

465-
if (i .gt. 0) then
465+
if (i > 0) then
466466
files = [files, files_tmp(1:i)]
467467
end if
468468

src/fpm_strings.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -384,7 +384,7 @@ subroutine split(input_line,array,delimiters,order,nulls)
384384
iterm(i30)=ilen ! initially assume no more tokens
385385
do i10=1,idlim ! search for next delimiter
386386
ifound=index(input_line(ibegin(i30):ilen),dlim(i10:i10))
387-
IF(ifound.gt.0)then
387+
IF(ifound>0)then
388388
iterm(i30)=min(iterm(i30),ifound+ibegin(i30)-2)
389389
endif
390390
enddo
@@ -396,7 +396,7 @@ subroutine split(input_line,array,delimiters,order,nulls)
396396
endif
397397
imax=max(imax,iterm(i30)-ibegin(i30)+1)
398398
icount=i30 ! increment count of number of tokens found
399-
if(icol.gt.ilen)then ! no text left
399+
if(icol>ilen)then ! no text left
400400
exit INFINITE
401401
endif
402402
enddo INFINITE

test/fpm_test/test_versioning.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -208,7 +208,7 @@ subroutine test_valid_compare(error)
208208
call new_version(v1, [1, 0, 8])
209209
call new_version(v2, [1, 0])
210210

211-
if (.not. v1 .gt. v2) then
211+
if (.not. v1 > v2) then
212212
call test_failed(error, "Version comparison failed (gt)")
213213
return
214214
end if

test/help_test/help_test.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -260,7 +260,7 @@ function page(array) result (table)
260260
length=length+1
261261
endif
262262
enddo
263-
if(sz.gt.0)then
263+
if(sz>0)then
264264
if(array(sz)/=nl)then
265265
lines=lines+1
266266
endif
@@ -278,9 +278,9 @@ function page(array) result (table)
278278
position=1
279279
elseif(array(i)==cr)then
280280
elseif(linelength/=0)then
281-
if(position.gt.len(table))then
281+
if(position>len(table))then
282282
write(*,*)'<ERROR> adding character past edge of text',table(linecount),array(i)
283-
elseif(linecount.gt.size(table))then
283+
elseif(linecount>size(table))then
284284
write(*,*)'<ERROR> adding line past end of text',linecount,size(table)
285285
else
286286
table(linecount)(position:position)=array(i)

0 commit comments

Comments
 (0)