Skip to content

Commit

Permalink
remove unused variables
Browse files Browse the repository at this point in the history
  • Loading branch information
ncrescenzio committed Nov 18, 2024
1 parent 3af4bce commit bcc1245
Show file tree
Hide file tree
Showing 6 changed files with 12 additions and 22 deletions.
3 changes: 2 additions & 1 deletion libsrcs/00modGlobals.f90
Original file line number Diff line number Diff line change
Expand Up @@ -352,6 +352,7 @@ function avg_scal(avg_type, A, B, C) result (res_avg)
real(kind=double) :: res_avg
! local vars

res_avg = zero
if (present(C)) then
! cell average
select case(avg_type)
Expand Down Expand Up @@ -1150,7 +1151,7 @@ function get_dirname(str_file) result(str_dir)
character(len=*), intent(in) :: str_file
character(len=len_trim(adjustl(str_file))) :: str_dir
!local
integer :: bar_pos,nstr,pbar
integer :: nstr, pbar

str_dir(:) = ' '

Expand Down
3 changes: 2 additions & 1 deletion libsrcs/01modNorms.f90
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,8 @@ function eval_dir_norm(this,nvec,vec,scr) result (resnorm)
integer :: i
real(kind=double) :: dnrm2

if ( .not. present(scr) ) then
resnorm = zero
if (.not.present(scr)) then
rc = IOerr(stderr, err_val, 'eval_dir_norm', &
'scratch array not passed' )
else
Expand Down
5 changes: 0 additions & 5 deletions libsrcs/04modDataSequence.f90
Original file line number Diff line number Diff line change
Expand Up @@ -128,9 +128,6 @@ subroutine fill_dataseq(this, data, time)
class(dataseq), intent(inout) :: this
real(kind=double), intent(in ) :: data(this%ndata)
real(kind=double), intent(in ) :: time
!local
integer :: res
logical :: rc

! count number of data stored
this%nstored = this%nstored + 1
Expand Down Expand Up @@ -162,8 +159,6 @@ subroutine lagrange_interpolation(this, time, interpolation, info)
real(kind=double), intent(inout) :: interpolation(this%ndata)
integer, intent(inout) :: info
!local
logical :: rc
integer :: res
integer :: i, idata, nsequence
real(kind=double) :: coeff_langrange

Expand Down
14 changes: 5 additions & 9 deletions libsrcs/05modTimeInputs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -280,7 +280,7 @@ subroutine init_TD(this, stderr, InputFdescr, dimdata, ndata, default_data)
this%TDtime(1) = -huge
this%TDtime(2) = huge
else
if(res .ne. 0) rc = IOerr(stderr, err_inp, 'read_TD', &
rc = IOerr(stderr, err_inp, 'read_TD', &
' file '//etb(InputFdescr%fn)//' does not esxits'//&
' and default not assigned ')
end if
Expand Down Expand Up @@ -550,11 +550,9 @@ subroutine write_steady(stderr, lun, ndata, data, fname)
real(kind=double), intent(in ) :: data(ndata)
character(len=*), intent(in ), optional :: fname
! local vars
integer :: res, u_number
integer :: NInput
integer :: res
integer :: i
logical :: rc
character(len=15) :: scratch
character(len=15) :: filename

if (present(fname)) then
Expand Down Expand Up @@ -630,8 +628,7 @@ subroutine write2file(lun_err, head_body_tail_whole,&
real(kind=double), intent(in ) :: data(dimdata,ndata)
type(file), intent(in ) :: fileout
! local vars
integer :: res, u_number
integer :: NInput
integer :: res
integer :: i,j,k,lun,nnz
integer, allocatable :: indeces_nonzeros(:)
logical :: rc
Expand Down Expand Up @@ -771,9 +768,8 @@ subroutine writearray2file(lun_err, head_body_tail_whole,&
integer, intent(in ) :: lun
character(len=*), intent(in ) :: fn
! local vars
integer :: res, u_number
integer :: NInput
integer :: i,j,k,nnz
integer :: res
integer :: i,j,nnz
integer, allocatable :: indeces_nonzeros(:)
logical :: rc
character(len=15) :: scratch
Expand Down
7 changes: 2 additions & 5 deletions libsrcs/06modTimeOutputs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -98,8 +98,8 @@ subroutine kill_TD(this, lun)
logical :: rc

this%built = .false.
deallocate(this%TDactual)
if (res.ne.0) rc=IOerr(lun, err_dealloc, 'kill_TD', &
deallocate(this%TDactual,stat=res)
if (res.ne.0) rc = IOerr(lun, err_dealloc, 'kill_TD', &
'type TDOut var TDactual')

end subroutine kill_TD
Expand Down Expand Up @@ -191,9 +191,6 @@ subroutine write_end_time(this,lun)
implicit none
class(TDOut), intent(inout) :: this
integer, intent(in ) :: lun
!local
integer :: i,k,ninput
real(kind=double) :: dnrm2

write(lun,'(a4,1pe15.6)') 'time', this%time

Expand Down
2 changes: 1 addition & 1 deletion libsrcs/08modGaussQuadrature.f90
Original file line number Diff line number Diff line change
Expand Up @@ -102,7 +102,7 @@ subroutine gaussquad(lun_err,ngauss,coefcoord,weight)
real(kind=double), intent(out) :: coefcoord(ngauss)
real(kind=double), intent(out) :: weight(ngauss)
! local
integer :: info,lwork,i,j
integer :: info,lwork,j
logical :: rc
integer :: res
real(kind=double), allocatable :: u(:)
Expand Down

0 comments on commit bcc1245

Please sign in to comment.