Skip to content

Commit

Permalink
more bug fix ( out of bound fix)
Browse files Browse the repository at this point in the history
  • Loading branch information
weiyuan-jiang committed Jul 1, 2022
1 parent 0660206 commit cbae185
Show file tree
Hide file tree
Showing 2 changed files with 14 additions and 13 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -1401,7 +1401,7 @@ SUBROUTINE modis_scale_para_high (ease_grid,MA,gfile)
integer :: yy,j,month
integer, allocatable, dimension (:) :: vegcls
real, allocatable, dimension (:) :: &
modisvf, modisnf,albvf,albnf, lat,lon, &
modisvf, modisnf,albvf,albnf, &
green,lai,lai_before,lai_after,grn_before,grn_after
real, allocatable, dimension (:) :: &
calbvf,calbnf, zero_array, one_array, albvr,albnr
Expand Down Expand Up @@ -1435,8 +1435,8 @@ SUBROUTINE modis_scale_para_high (ease_grid,MA,gfile)
close (10,status='keep')

fname=trim(gfile)//'.til'

open (10,file=fname,status='old',action='read',form='formatted')

fname='clsm/mosaic_veg_typs_fracs'
open (20,file=fname,status='old',action='read',form='formatted')

Expand All @@ -1451,9 +1451,9 @@ SUBROUTINE modis_scale_para_high (ease_grid,MA,gfile)

do n = 1,ip
if (ease_grid) then
read(10,*,IOSTAT=ierr) typ,pfs,lon,lat,ig,jg,fr_gcm
read(10,*,IOSTAT=ierr) typ !,pfs,lont,latt,ig,jg,fr_gcm
else
read(10,'(I10,3E20.12,9(2I10,E20.12,I10))',IOSTAT=ierr) &
read(10,'(I10,3E20.12,9(2I10,E20.12,I10))',IOSTAT=ierr) &

This comment has been minimized.

Copy link
@gmao-rreichle

gmao-rreichle Jul 1, 2022

Contributor

@weiyuan-jiang, shouldn't lines 1456-1457 be edited similar to the change in line 1454? That is:
read(10,'(I10))',IOSTAT=ierr) typ ! ,tarea, lont, latt, ig, jg, fr_gcm, indx_dum, pfs, j_dum, fr_cat, j_dum
Note the change in the format string.
Also, I think the following variables are still declared but are not needed anymore:
ig, jg, lont, latt, pfs, indx_dum, fr_cat, tarea
Note that j_dum is still used above.
Please double-check what I'm proposing here.

typ,tarea,lont,latt,ig,jg,fr_gcm,indx_dum,pfs,j_dum,fr_cat,j_dum
endif

This comment has been minimized.

Copy link
@gmao-rreichle

gmao-rreichle Jul 1, 2022

Contributor

I think we can also simplify lines 1461-1462 as follows:
read (20,*) indr1, indr1, vegcls(ip2) ! ,indr1,fr_gcm,fr_gcm
I think the only info needed here is vegcls
Then the declaration of fr_gcm can also be removed.

if (typ == 100) then
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2728,7 +2728,7 @@ SUBROUTINE cti_stat_file (ease_grid,gfile, MaskFile)
if (ease_grid) then
read(10,*,IOSTAT=ierr) typ,pfs,lon,lat,ig,jg,fr_gcm,i_dum
else
read(10,'(I10,3E20.12,9(2I10,E20.12,I10))',IOSTAT=ierr) &
read(10,'(I10,3E20.12,9(2I10,E20.12,I10))',IOSTAT=ierr) &
typ,tarea,lon,lat,ig,jg,fr_gcm,indx_dum,pfs,i_dum,fr_cat,j_dum
endif

Expand Down Expand Up @@ -6215,9 +6215,9 @@ SUBROUTINE FUNCIDEP( &
endif
enddo
locmax=MAX(3,indimax10)

endif ! if (nmax .ge. shift+1)
! add protection here in case nmax <3 . why 3 ?
if (locmax > nmax) locmax = nmax
endif ! if (nmax .ge. shift+1)
30 densmax=denstest(idep,locmax)
aa(idep)=exp(1.)*densmax

Expand Down Expand Up @@ -6441,10 +6441,10 @@ SUBROUTINE FUNCZBAR( &
densaux(n) .gt. densaux(n-11) .and. &
densaux(n) .gt. densaux(n-12) .and. &
densaux(n) .gt. densaux(n-13) .and. &
densaux(n) .gt. densaux(n-14) .and. &
densaux(n) .gt. densaux(n-15)) then
locmax=n
goto 30
densaux(n) .gt. densaux(n-14)) then ! .and. &
!densaux(n) .gt. densaux(n-15)) then
locmax=n
goto 30
endif
enddo

Expand All @@ -6459,7 +6459,8 @@ SUBROUTINE FUNCZBAR( &
endif
enddo
locmax=MAX(3,indimax10)

! in case nmax < 3. why hard coded 3?
if(locmax > nmax) locmax = nmax
endif ! if (nmax .ge. shift+1)

30 densmax=denstest(locmax)
Expand Down

0 comments on commit cbae185

Please sign in to comment.