Skip to content

Commit 358a66a

Browse files
committed
.ne. -> /=
1 parent 2d19620 commit 358a66a

File tree

11 files changed

+45
-45
lines changed

11 files changed

+45
-45
lines changed

src/fpm.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -393,11 +393,11 @@ subroutine cmd_run(settings,test)
393393
toomany= size(settings%name)==0 .and. size(executables).gt.1
394394
if ( any(.not.found) &
395395
& .or. &
396-
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
396+
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner /= '') ) &
397397
& .and. &
398398
& .not.settings%list) then
399399
line=join(settings%name)
400-
if(line.ne.'.')then ! do not report these special strings
400+
if(line/='.')then ! do not report these special strings
401401
if(any(.not.found))then
402402
write(stderr,'(A)',advance="no")'<ERROR>*cmd_run*:specified names '
403403
do j=1,size(settings%name)
@@ -430,7 +430,7 @@ subroutine cmd_run(settings,test)
430430
allocate(stat(size(executables)))
431431
do i=1,size(executables)
432432
if (exists(executables(i)%s)) then
433-
if(settings%runner .ne. ' ')then
433+
if(settings%runner /= ' ')then
434434
if(.not.allocated(settings%args))then
435435
call run(settings%runner//' '//executables(i)%s, &
436436
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: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -166,7 +166,7 @@ subroutine fpm_stop(value,message)
166166
integer, intent(in) :: value
167167
!> Error message
168168
character(len=*), intent(in) :: message
169-
if(message.ne.'')then
169+
if(message/='')then
170170
if(value.gt.0)then
171171
write(stderr,'("<ERROR>",a)')trim(message)
172172
else

src/fpm_command_line.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -559,7 +559,7 @@ subroutine get_command_line_settings(cmd_settings)
559559

560560
case default
561561

562-
if(which('fpm-'//cmdarg).ne.'')then
562+
if(which('fpm-'//cmdarg)/='')then
563563
call run('fpm-'//trim(cmdarg)//' '// get_command_arguments_quoted(),.false.)
564564
else
565565
call set_args('&

src/fpm_environment.f90

Lines changed: 10 additions & 10 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,7 +185,7 @@ 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=''
@@ -214,9 +214,9 @@ function get_command_arguments_quoted() result(args)
214214
write(stderr,'(*(g0,1x))')'<ERROR>*get_command_arguments_stack* error obtaining argument ',i
215215
exit
216216
elseif(ilength.gt.0)then
217-
if(index(arg//' ','-').ne.1)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

src/fpm_filesystem.F90

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -457,7 +457,7 @@ recursive subroutine list_files(dir, files, recurse)
457457

458458
r = c_closedir(dir_handle)
459459

460-
if (r .ne. 0) then
460+
if (r /= 0) then
461461
print *, 'c_closedir() failed'
462462
error stop
463463
end if
@@ -472,7 +472,7 @@ recursive subroutine list_files(dir, files, recurse)
472472
allocate(sub_dir_files(0))
473473

474474
do i=1,size(files)
475-
if (c_is_dir(files(i)%s//c_null_char) .ne. 0) then
475+
if (c_is_dir(files(i)%s//c_null_char) /= 0) then
476476
call list_files(files(i)%s, dir_files, recurse=.true.)
477477
sub_dir_files = [sub_dir_files, dir_files]
478478
end if
@@ -714,7 +714,7 @@ subroutine fileopen(filename,lun,ier)
714714

715715
message=' '
716716
ios=0
717-
if(filename.ne.' ')then
717+
if(filename/=' ')then
718718
open(file=filename, &
719719
& newunit=lun, &
720720
& form='formatted', & ! FORM = FORMATTED | UNFORMATTED
@@ -728,7 +728,7 @@ subroutine fileopen(filename,lun,ier)
728728
lun=stdout
729729
ios=0
730730
endif
731-
if(ios.ne.0)then
731+
if(ios/=0)then
732732
lun=-1
733733
if(present(ier))then
734734
ier=ios
@@ -745,9 +745,9 @@ subroutine fileclose(lun,ier)
745745
integer,intent(out),optional :: ier
746746
character(len=256) :: message
747747
integer :: ios
748-
if(lun.ne.-1)then
748+
if(lun/=-1)then
749749
close(unit=lun,iostat=ios,iomsg=message)
750-
if(ios.ne.0)then
750+
if(ios/=0)then
751751
if(present(ier))then
752752
ier=ios
753753
else
@@ -765,12 +765,12 @@ subroutine filewrite(filename,filedata)
765765
integer :: lun, i, ios
766766
character(len=256) :: message
767767
call fileopen(filename,lun)
768-
if(lun.ne.-1)then ! program currently stops on error on open, but might
768+
if(lun/=-1)then ! program currently stops on error on open, but might
769769
! want it to continue so -1 (unallowed LUN) indicates error
770770
! write file
771771
do i=1,size(filedata)
772772
write(lun,'(a)',iostat=ios,iomsg=message)trim(filedata(i))
773-
if(ios.ne.0)then
773+
if(ios/=0)then
774774
call fpm_stop(5,'*filewrite*:'//filename//':'//trim(message))
775775
endif
776776
enddo

src/fpm_strings.f90

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -348,7 +348,7 @@ subroutine split(input_line,array,delimiters,order,nulls)
348348

349349
! decide on value for optional DELIMITERS parameter
350350
if (present(delimiters)) then ! optional delimiter list was present
351-
if(delimiters.ne.'')then ! if DELIMITERS was specified and not null use it
351+
if(delimiters/='')then ! if DELIMITERS was specified and not null use it
352352
dlim=delimiters
353353
else ! DELIMITERS was specified on call as empty string
354354
dlim=' '//char(9)//char(10)//char(11)//char(12)//char(13)//char(0) ! use default delimiter when not specified
@@ -861,9 +861,9 @@ function glob(tame,wild)
861861
glob=.true.
862862
return
863863
endif
864-
if(wildtext(wi:wi) .ne. '?') then
864+
if(wildtext(wi:wi) /= '?') then
865865
! Fast-forward to next possible match.
866-
do while (tametext(ti:ti) .ne. wildtext(wi:wi))
866+
do while (tametext(ti:ti) /= wildtext(wi:wi))
867867
ti=ti+1
868868
if (tametext(ti:ti)==NULL)then
869869
glob=.false.
@@ -873,15 +873,15 @@ function glob(tame,wild)
873873
endif
874874
wbookmark = wildtext(wi:)
875875
tbookmark = tametext(ti:)
876-
elseif(tametext(ti:ti) .ne. wildtext(wi:wi) .and. wildtext(wi:wi) .ne. '?') then
876+
elseif(tametext(ti:ti) /= wildtext(wi:wi) .and. wildtext(wi:wi) /= '?') then
877877
! Got a non-match. If we've set our bookmarks, back up to one or both of them and retry.
878-
if(wbookmark.ne.NULL) then
879-
if(wildtext(wi:).ne. wbookmark) then
878+
if(wbookmark/=NULL) then
879+
if(wildtext(wi:)/= wbookmark) then
880880
wildtext = wbookmark;
881881
wlen=len_trim(wbookmark)
882882
wi=1
883883
! Don't go this far back again.
884-
if (tametext(ti:ti) .ne. wildtext(wi:wi)) then
884+
if (tametext(ti:ti) /= wildtext(wi:wi)) then
885885
tbookmark=tbookmark(2:)
886886
tametext = tbookmark
887887
ti=1
@@ -890,7 +890,7 @@ function glob(tame,wild)
890890
wi=wi+1
891891
endif
892892
endif
893-
if (tametext(ti:ti).ne.NULL) then
893+
if (tametext(ti:ti)/=NULL) then
894894
ti=ti+1
895895
cycle ! "mississippi" matches "*sip*"
896896
endif
@@ -901,7 +901,7 @@ function glob(tame,wild)
901901
ti=ti+1
902902
wi=wi+1
903903
if (tametext(ti:ti)==NULL) then ! How do you match a tame text string?
904-
if(wildtext(wi:wi).ne.NULL)then
904+
if(wildtext(wi:wi)/=NULL)then
905905
do while (wildtext(wi:wi) == '*') ! The tame way: unique up on it!
906906
wi=wi+1 ! "x" matches "x*"
907907
if(wildtext(wi:wi)==NULL)exit
@@ -995,7 +995,7 @@ function is_fortran_name(line) result (lout)
995995
character(len=:),allocatable :: name
996996
logical :: lout
997997
name=trim(line)
998-
if(len(name).ne.0)then
998+
if(len(name)/=0)then
999999
lout = .true. &
10001000
& .and. verify(name(1:1), lower//upper) == 0 &
10011001
& .and. verify(name,allowed) == 0 &

test/cli_test/cli_test.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -124,7 +124,7 @@ program main
124124
act_c_a=.false.
125125
act_args=repeat(' ',132)
126126
read(lun,nml=act_cli,iostat=ios,iomsg=message)
127-
if(ios.ne.0)then
127+
if(ios/=0)then
128128
write(*,'(a)')'ERROR:',trim(message)
129129
endif
130130
close(unit=lun)

test/fpm_test/test_versioning.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -136,12 +136,12 @@ subroutine test_valid_notequals(error)
136136
call new_version(v1, [0, 9, 1])
137137
call new_version(v2, [0, 9])
138138

139-
if (.not. v1.ne.v2) then
139+
if (.not. v1/=v2) then
140140
call test_failed(error, "Version comparison failed")
141141
return
142142
end if
143143

144-
if (.not. v2.ne.v1) then
144+
if (.not. v2/=v1) then
145145
call test_failed(error, "Version comparison failed")
146146
return
147147
end if

test/help_test/help_test.f90

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -90,7 +90,7 @@ program help_test
9090
tally=[tally,count(page1=='SYNOPSIS')==1]
9191
tally=[tally,count(page1=='DESCRIPTION')==1]
9292
af=count(.not.tally)
93-
if(be.ne.af)then
93+
if(be/=af)then
9494
write(*,*)'<ERROR>missing expected sections in ',names(i)
9595
write(*,*)page1(1) ! assuming at least size 1 for debugging mingw
9696
write(*,*)count(page1=='NAME')
@@ -120,11 +120,11 @@ program help_test
120120
book2=pack(book1,index(book2,' + build/')==0)
121121
write(*,*)'<INFO>book1 ',size(book1), len(book1)
122122
write(*,*)'<INFO>book2 ',size(book2), len(book2)
123-
if(size(book1).ne.size(book2))then
123+
if(size(book1)/=size(book2))then
124124
write(*,*)'<ERROR>manual and "debug" appended pages are not the same size'
125125
tally=[tally,.false.]
126126
else
127-
if(all(book1.ne.book2))then
127+
if(all(book1/=book2))then
128128
tally=[tally,.false.]
129129
write(*,*)'<ERROR>manual and "debug" appended pages are not the same'
130130
else
@@ -166,7 +166,7 @@ subroutine wipe(filename)
166166
open(file=filename,newunit=lun,iostat=ios,iomsg=message)
167167
if(ios==0)then
168168
close(unit=lun,iostat=ios,status='delete',iomsg=message)
169-
if(ios.ne.0)then
169+
if(ios/=0)then
170170
write(*,*)'<ERROR>'//trim(message)
171171
endif
172172
else
@@ -198,7 +198,7 @@ subroutine slurp(filename,text)
198198
if(allocated(text))deallocate(text) ! make sure text array not allocated
199199
allocate ( text(nchars) ) ! make enough storage to hold file
200200
read(igetunit,iostat=ios,iomsg=message) text ! load input file -> text array
201-
if(ios.ne.0)then
201+
if(ios/=0)then
202202
call stderr_local( '*slurp* bad read of '//trim(local_filename)//':'//trim(message) )
203203
endif
204204
else
@@ -261,7 +261,7 @@ function page(array) result (table)
261261
endif
262262
enddo
263263
if(sz.gt.0)then
264-
if(array(sz).ne.nl)then
264+
if(array(sz)/=nl)then
265265
lines=lines+1
266266
endif
267267
endif
@@ -277,7 +277,7 @@ function page(array) result (table)
277277
linecount=linecount+1
278278
position=1
279279
elseif(array(i)==cr)then
280-
elseif(linelength.ne.0)then
280+
elseif(linelength/=0)then
281281
if(position.gt.len(table))then
282282
write(*,*)'<ERROR> adding character past edge of text',table(linecount),array(i)
283283
elseif(linecount.gt.size(table))then

0 commit comments

Comments
 (0)