Skip to content

Commit 2d19620

Browse files
committed
.eq. -> ==
1 parent b8439d4 commit 2d19620

File tree

8 files changed

+50
-50
lines changed

8 files changed

+50
-50
lines changed

src/fpm.f90

Lines changed: 2 additions & 2 deletions
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).eq.0 .and. size(executables).gt.1
393+
toomany= size(settings%name)==0 .and. size(executables).gt.1
394394
if ( any(.not.found) &
395395
& .or. &
396396
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
@@ -413,7 +413,7 @@ subroutine cmd_run(settings,test)
413413

414414
call compact_list_all()
415415

416-
if(line.eq.'.' .or. line.eq.' ')then ! do not report these special strings
416+
if(line=='.' .or. line==' ')then ! do not report these special strings
417417
call fpm_stop(0,'')
418418
else
419419
call fpm_stop(1,'')

src/fpm_command_line.f90

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -271,14 +271,14 @@ subroutine get_command_line_settings(cmd_settings)
271271
! convert special string '..' to equivalent (shorter) '*'
272272
! to allow for a string that does not require shift-key and quoting
273273
do i=1,size(names)
274-
if(names(i).eq.'..')names(i)='*'
274+
if(names(i)=='..')names(i)='*'
275275
enddo
276276

277277
c_compiler = sget('c-compiler')
278278
archiver = sget('archiver')
279279
allocate(fpm_run_settings :: cmd_settings)
280280
val_runner=sget('runner')
281-
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
281+
if(specified('runner') .and. val_runner=='')val_runner='echo'
282282
cmd_settings=fpm_run_settings(&
283283
& args=remaining,&
284284
& profile=val_profile,&
@@ -348,7 +348,7 @@ subroutine get_command_line_settings(cmd_settings)
348348
call fpm_stop(2,'only one directory name allowed')
349349
end select
350350
!*! canon_path is not converting ".", etc.
351-
if(name.eq.'.')then
351+
if(name=='.')then
352352
call get_current_directory(name, error)
353353
if (allocated(error)) then
354354
write(stderr, '("[Error]", 1x, a)') error%message
@@ -402,12 +402,12 @@ subroutine get_command_line_settings(cmd_settings)
402402
case('help','manual')
403403
call set_args(common_args, help_help,version_text)
404404
if(size(unnamed).lt.2)then
405-
if(unnamed(1).eq.'help')then
405+
if(unnamed(1)=='help')then
406406
unnamed=[' ', 'fpm']
407407
else
408408
unnamed=manual
409409
endif
410-
elseif(unnamed(2).eq.'manual')then
410+
elseif(unnamed(2)=='manual')then
411411
unnamed=manual
412412
endif
413413
widest=256
@@ -505,14 +505,14 @@ subroutine get_command_line_settings(cmd_settings)
505505
! convert special string '..' to equivalent (shorter) '*'
506506
! to allow for a string that does not require shift-key and quoting
507507
do i=1,size(names)
508-
if(names(i).eq.'..')names(i)='*'
508+
if(names(i)=='..')names(i)='*'
509509
enddo
510510

511511
c_compiler = sget('c-compiler')
512512
archiver = sget('archiver')
513513
allocate(fpm_test_settings :: cmd_settings)
514514
val_runner=sget('runner')
515-
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
515+
if(specified('runner') .and. val_runner=='')val_runner='echo'
516516
cmd_settings=fpm_test_settings(&
517517
& args=remaining, &
518518
& profile=val_profile, &
@@ -570,7 +570,7 @@ subroutine get_command_line_settings(cmd_settings)
570570
help_text=help_usage
571571
if(lget('list'))then
572572
help_text=help_list_dash
573-
elseif(len_trim(cmdarg).eq.0)then
573+
elseif(len_trim(cmdarg)==0)then
574574
write(stdout,'(*(a))')'Fortran Package Manager:'
575575
write(stdout,'(*(a))')' '
576576
call printhelp(help_list_nodash)
@@ -595,7 +595,7 @@ subroutine check_build_vals()
595595
character(len=:), allocatable :: flags
596596

597597
val_compiler=sget('compiler')
598-
if(val_compiler.eq.'') then
598+
if(val_compiler=='') then
599599
val_compiler='gfortran'
600600
endif
601601

src/fpm_environment.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -190,7 +190,7 @@ function get_env(NAME,DEFAULT) result(VALUE)
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

src/fpm_filesystem.F90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -419,7 +419,7 @@ recursive subroutine list_files(dir, files, recurse)
419419
type(string_t) :: files_tmp(N_MAX)
420420
integer(kind=c_int) :: r
421421

422-
if (c_is_dir(dir(1:len_trim(dir))//c_null_char) .eq. 0) then
422+
if (c_is_dir(dir(1:len_trim(dir))//c_null_char) == 0) then
423423
allocate (files(0))
424424
return
425425
end if
@@ -440,7 +440,7 @@ recursive subroutine list_files(dir, files, recurse)
440440
else
441441
string_fortran = f_string(c_get_d_name(dir_entry_c))
442442

443-
if ((string_fortran .eq. '.' .or. string_fortran .eq. '..')) then
443+
if ((string_fortran == '.' .or. string_fortran == '..')) then
444444
cycle
445445
end if
446446

@@ -827,7 +827,7 @@ function which(command) result(pathname)
827827
character(len=:),allocatable :: pathname, checkon, paths(:), exts(:)
828828
integer :: i, j
829829
pathname=''
830-
call split(get_env('PATH'),paths,delimiters=merge(';',':',separator().eq.'\'))
830+
call split(get_env('PATH'),paths,delimiters=merge(';',':',separator()=='\'))
831831
SEARCH: do i=1,size(paths)
832832
checkon=trim(join_path(trim(paths(i)),command))
833833
select case(separator())

src/fpm_strings.f90

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -380,7 +380,7 @@ subroutine split(input_line,array,delimiters,order,nulls)
380380
icol=1 ! initialize pointer into input line
381381
INFINITE: do i30=1,ilen,1 ! store into each array element
382382
ibegin(i30)=icol ! assume start new token on the character
383-
if(index(dlim(1:idlim),input_line(icol:icol)).eq.0)then ! if current character is not a delimiter
383+
if(index(dlim(1:idlim),input_line(icol:icol))==0)then ! if current character is not a delimiter
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))
@@ -574,7 +574,7 @@ pure function join(str,sep,trm,left,right,start,end) result (string)
574574
if(present(left))then ; left_local=left ; else ; left_local='' ; endif
575575
if(present(right))then ; right_local=right ; else ; right_local='' ; endif
576576
string=''
577-
if(size(str).eq.0)then
577+
if(size(str)==0)then
578578
string=string//left_local//right_local
579579
else
580580
do i = 1,size(str)-1
@@ -851,21 +851,21 @@ function glob(tame,wild)
851851
do ! Walk the text strings one character at a time.
852852
if(wildtext(wi:wi) == '*')then ! How do you match a unique text string?
853853
do i=wi,wlen ! Easy: unique up on it!
854-
if(wildtext(wi:wi).eq.'*')then
854+
if(wildtext(wi:wi)=='*')then
855855
wi=wi+1
856856
else
857857
exit
858858
endif
859859
enddo
860-
if(wildtext(wi:wi).eq.NULL) then ! "x" matches "*"
860+
if(wildtext(wi:wi)==NULL) then ! "x" matches "*"
861861
glob=.true.
862862
return
863863
endif
864864
if(wildtext(wi:wi) .ne. '?') then
865865
! Fast-forward to next possible match.
866866
do while (tametext(ti:ti) .ne. wildtext(wi:wi))
867867
ti=ti+1
868-
if (tametext(ti:ti).eq.NULL)then
868+
if (tametext(ti:ti)==NULL)then
869869
glob=.false.
870870
return ! "x" doesn't match "*y*"
871871
endif
@@ -900,14 +900,14 @@ function glob(tame,wild)
900900
endif
901901
ti=ti+1
902902
wi=wi+1
903-
if (tametext(ti:ti).eq.NULL) then ! How do you match a tame text string?
903+
if (tametext(ti:ti)==NULL) then ! How do you match a tame text string?
904904
if(wildtext(wi:wi).ne.NULL)then
905905
do while (wildtext(wi:wi) == '*') ! The tame way: unique up on it!
906906
wi=wi+1 ! "x" matches "x*"
907-
if(wildtext(wi:wi).eq.NULL)exit
907+
if(wildtext(wi:wi)==NULL)exit
908908
enddo
909909
endif
910-
if (wildtext(wi:wi).eq.NULL)then
910+
if (wildtext(wi:wi)==NULL)then
911911
glob=.true.
912912
return ! "x" matches "x"
913913
endif

test/cli_test/cli_test.f90

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -78,7 +78,7 @@ program main
7878
readme(3)=' /'
7979
tally=[logical ::] ! an array that tabulates the command test results as pass or fail.
8080

81-
if(command_argument_count().eq.0)then ! assume if called with no arguments to do the tests. This means you cannot
81+
if(command_argument_count()==0)then ! assume if called with no arguments to do the tests. This means you cannot
8282
! have a test of no parameters. Could improve on this.
8383
! if called with parameters assume this is a test and call the routine to
8484
! parse the resulting values after calling the CLI command line parser
@@ -91,7 +91,7 @@ program main
9191
write(*,*)'command=',command
9292

9393
do i=1,size(tests)
94-
if(tests(i).eq.' ')then
94+
if(tests(i)==' ')then
9595
open(file='_test_cli',newunit=lun,delim='quote')
9696
close(unit=lun,status='delete')
9797
exit
@@ -113,8 +113,8 @@ program main
113113
write(*,'(*(g0))')'START: TEST ',i,' CMD=',trim(cmd)
114114
! call this program which will crack command line and write results to scratch file _test_cli
115115
call execute_command_line(command//' '//trim(cmd),cmdstat=act_cstat,exitstat=act_estat)
116-
if(cstat.eq.act_cstat.and.estat.eq.act_estat)then
117-
if(estat.eq.0)then
116+
if(cstat==act_cstat.and.estat==act_estat)then
117+
if(estat==0)then
118118
open(file='_test_cli',newunit=lun,delim='quote')
119119
act_name=[(repeat(' ',len(act_name)),i=1,max_names)]
120120
act_profile=''
@@ -130,12 +130,12 @@ program main
130130
close(unit=lun)
131131
! compare results to expected values
132132
subtally=[logical ::]
133-
call test_test('NAME',all(act_name.eq.name))
134-
call test_test('PROFILE',act_profile.eq.profile)
133+
call test_test('NAME',all(act_name==name))
134+
call test_test('PROFILE',act_profile==profile)
135135
call test_test('WITH_EXPECTED',act_w_e.eqv.w_e)
136136
call test_test('WITH_TESTED',act_w_t.eqv.w_t)
137137
call test_test('WITH_TEST',act_w_t.eqv.w_t)
138-
call test_test('ARGS',act_args.eq.args)
138+
call test_test('ARGS',act_args==args)
139139
if(all(subtally))then
140140
write(*,'(*(g0))')'PASSED: TEST ',i,' STATUS: expected ',cstat,' ',estat,' actual ',act_cstat,' ',act_estat,&
141141
& ' for [',trim(cmd),']'

test/fpm_test/test_versioning.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -74,12 +74,12 @@ subroutine test_valid_equals(error)
7474
call new_version(v1, [0, 9, 0])
7575
call new_version(v2, [0, 9])
7676

77-
if (.not. v1.eq.v2) then
77+
if (.not. v1==v2) then
7878
call test_failed(error, "Version comparison failed")
7979
return
8080
end if
8181

82-
if (.not. v2.eq.v1) then
82+
if (.not. v2==v1) then
8383
call test_failed(error, "Version comparison failed")
8484
return
8585
end if

test/help_test/help_test.f90

Lines changed: 17 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -77,25 +77,25 @@ program help_test
7777
message=''
7878
call execute_command_line(path,exitstat=estat,cmdstat=cstat,cmdmsg=message)
7979
write(*,'(*(g0))')'<INFO>CMD=',path,' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message)
80-
tally=[tally,all([estat.eq.0,cstat.eq.0])]
80+
tally=[tally,all([estat==0,cstat==0])]
8181
call swallow('fpm_scratch_help.txt',page1)
8282
if(size(page1).lt.3)then
8383
write(*,*)'<ERROR>help for '//names(i)//' ridiculiously small'
8484
tally=[tally,.false.]
8585
exit
8686
endif
87-
!!write(*,*)findloc(page1,'NAME').eq.1
87+
!!write(*,*)findloc(page1,'NAME')==1
8888
be=count(.not.tally)
89-
tally=[tally,count(page1.eq.'NAME').eq.1]
90-
tally=[tally,count(page1.eq.'SYNOPSIS').eq.1]
91-
tally=[tally,count(page1.eq.'DESCRIPTION').eq.1]
89+
tally=[tally,count(page1=='NAME')==1]
90+
tally=[tally,count(page1=='SYNOPSIS')==1]
91+
tally=[tally,count(page1=='DESCRIPTION')==1]
9292
af=count(.not.tally)
9393
if(be.ne.af)then
9494
write(*,*)'<ERROR>missing expected sections in ',names(i)
9595
write(*,*)page1(1) ! assuming at least size 1 for debugging mingw
96-
write(*,*)count(page1.eq.'NAME')
97-
write(*,*)count(page1.eq.'SYNOPSIS')
98-
write(*,*)count(page1.eq.'DESCRIPTION')
96+
write(*,*)count(page1=='NAME')
97+
write(*,*)count(page1=='SYNOPSIS')
98+
write(*,*)count(page1=='DESCRIPTION')
9999
write(*,'(a)')page1
100100
endif
101101
write(*,*)'<INFO>have completed ',count(tally),' tests'
@@ -109,15 +109,15 @@ program help_test
109109
path= prog // cmds(i)
110110
call execute_command_line(path,exitstat=estat,cmdstat=cstat,cmdmsg=message)
111111
write(*,'(*(g0))')'<INFO>CMD=',path,' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message)
112-
tally=[tally,all([estat.eq.0,cstat.eq.0])]
112+
tally=[tally,all([estat==0,cstat==0])]
113113
enddo
114114

115115
! compare book written in fragments with manual
116116
call swallow('fpm_scratch_help.txt',book1)
117117
call swallow('fpm_scratch_manual.txt',book2)
118118
! get rid of lines from run() which is not on stderr at the moment
119-
book1=pack(book1,index(book1,' + build/').eq.0)
120-
book2=pack(book1,index(book2,' + build/').eq.0)
119+
book1=pack(book1,index(book1,' + build/')==0)
120+
book2=pack(book1,index(book2,' + build/')==0)
121121
write(*,*)'<INFO>book1 ',size(book1), len(book1)
122122
write(*,*)'<INFO>book2 ',size(book2), len(book2)
123123
if(size(book1).ne.size(book2))then
@@ -135,7 +135,7 @@ program help_test
135135

136136
! overall size of manual
137137
!chars=size(book2)
138-
!lines=max(count(char(10).eq.book2),count(char(13).eq.book2))
138+
!lines=max(count(char(10)==book2),count(char(13)==book2))
139139
chars=sum(len_trim(book2)) ! SUM TRIMMED LENGTH
140140
lines=size(book2)
141141
if( (chars.lt.12000) .or. (lines.lt.350) )then
@@ -164,7 +164,7 @@ subroutine wipe(filename)
164164
integer :: lun
165165
character(len=k1) :: message
166166
open(file=filename,newunit=lun,iostat=ios,iomsg=message)
167-
if(ios.eq.0)then
167+
if(ios==0)then
168168
close(unit=lun,iostat=ios,status='delete',iomsg=message)
169169
if(ios.ne.0)then
170170
write(*,*)'<ERROR>'//trim(message)
@@ -188,7 +188,7 @@ subroutine slurp(filename,text)
188188
open(newunit=igetunit, file=trim(filename), action="read", iomsg=message,&
189189
&form="unformatted", access="stream",status='old',iostat=ios)
190190
local_filename=filename
191-
if(ios.eq.0)then ! if file was successfully opened
191+
if(ios==0)then ! if file was successfully opened
192192
inquire(unit=igetunit, size=nchars)
193193
if(nchars.le.0)then
194194
call stderr_local( '*slurp* empty file '//trim(local_filename) )
@@ -252,7 +252,7 @@ function page(array) result (table)
252252
length=0
253253
sz=size(array)
254254
do i=1,sz
255-
if(array(i).eq.nl)then
255+
if(array(i)==nl)then
256256
linelength=max(linelength,length)
257257
lines=lines+1
258258
length=0
@@ -273,10 +273,10 @@ function page(array) result (table)
273273
linecount=1
274274
position=1
275275
do i=1,sz
276-
if(array(i).eq.nl)then
276+
if(array(i)==nl)then
277277
linecount=linecount+1
278278
position=1
279-
elseif(array(i).eq.cr)then
279+
elseif(array(i)==cr)then
280280
elseif(linelength.ne.0)then
281281
if(position.gt.len(table))then
282282
write(*,*)'<ERROR> adding character past edge of text',table(linecount),array(i)

0 commit comments

Comments
 (0)