Skip to content

Commit

Permalink
Remove more unused variables.
Browse files Browse the repository at this point in the history
Fixes #886.
  • Loading branch information
GeorgeGayno-NOAA committed Jan 24, 2024
1 parent 1fcd99c commit 615ad2b
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 20 deletions.
26 changes: 11 additions & 15 deletions sorc/orog_mask_tools.fd/orog.fd/mtnlm7_oclsm.F
Original file line number Diff line number Diff line change
Expand Up @@ -64,9 +64,9 @@
character(len=256) :: INPUTOROG = "none"
character(len=256) :: merge_file = "none"
logical :: mask_only = .false.
integer :: MTNRES,IM,JM,NM,NR,EFAC,BLAT,NW
integer :: MTNRES,IM,JM,EFAC,BLAT
fsize=65536
READ(5,*) MTNRES,IM,JM,NM,NR,EFAC,BLAT
READ(5,*) MTNRES,IM,JM,EFAC,BLAT
READ(5,*) OUTGRID
READ(5,*) INPUTOROG
READ(5,*) mask_only
Expand All @@ -83,8 +83,7 @@
! --- other possibilities are =8 for 4' and =4 for 2' see
! HJ for T1000 test. Must set to 1 for now.
MTNRES=1
print*, MTNRES,IM,JM,NM,NR,EFAC,BLAT
NW=(NM+1)*((NR+1)*NM+2)
print*, MTNRES,IM,JM,EFAC,BLAT
IMN = 360*120/MTNRES
JMN = 180*120/MTNRES
print *, ' Starting terr12 mtnlm7_slm30.f IMN,JMN:',IMN,JMN
Expand Down Expand Up @@ -141,7 +140,7 @@
endif READ_GRID_FILE
CALL TERSUB(IMN,JMN,IM,JM,NR,NW,EFAC,BLAT,
CALL TERSUB(IMN,JMN,IM,JM,EFAC,BLAT,
& OUTGRID,INPUTOROG,MASK_ONLY,MERGE_FILE)
STOP
END
Expand All @@ -152,8 +151,6 @@
!! @param[in] JMN "j" dimension of the input terrain dataset.
!! @param[in] IM "i" dimension of the model grid tile.
!! @param[in] JM "j" dimension of the model grid tile.
!! @param[in] NR Rhomboidal flag.
!! @param[in] NW Number of waves.
!! @param[in] EFAC Factor to adjust orography by its variance.
!! @param[in] BLAT When less than zero, reverse latitude/
!! longitude for output.
Expand All @@ -165,12 +162,12 @@
!! @param[in] MASK_ONLY Flag to generate the Land Mask only
!! @param[in] MERGE_FILE Ocean merge file
!! @author Jordan Alpert NOAA/EMC
SUBROUTINE TERSUB(IMN,JMN,IM,JM,NR,NW,EFAC,BLAT,
SUBROUTINE TERSUB(IMN,JMN,IM,JM,EFAC,BLAT,
& OUTGRID,INPUTOROG,MASK_ONLY,MERGE_FILE)
implicit none
include 'netcdf.inc'
C
integer :: IMN,JMN,IM,JM,NR,NW
integer, intent(in) :: IMN,JMN,IM,JM
character(len=*), intent(in) :: OUTGRID
character(len=*), intent(in) :: INPUTOROG
character(len=*), intent(in) :: MERGE_FILE
Expand Down Expand Up @@ -204,7 +201,7 @@ SUBROUTINE TERSUB(IMN,JMN,IM,JM,NR,NW,EFAC,BLAT,
real :: DELXN,RS,RN,slma,oroa,vara,var4a,xn,XS
real, allocatable :: WGTCLT(:),XLAT(:)
real, allocatable :: XLON(:),ORS(:),oaa(:),ola(:),GLAT(:)
real, allocatable :: XLON(:),oaa(:),ola(:),GLAT(:)
real, allocatable :: GEOLON(:,:),GEOLON_C(:,:),DX(:,:)
real, allocatable :: GEOLAT(:,:),GEOLAT_C(:,:),DY(:,:)
Expand Down Expand Up @@ -237,7 +234,7 @@ SUBROUTINE TERSUB(IMN,JMN,IM,JM,NR,NW,EFAC,BLAT,
! reals
allocate (WGTCLT(JM),XLAT(JM))
allocate (XLON(IM),ORS(NW),oaa(4),ola(4),GLAT(JMN))
allocate (XLON(IM),oaa(4),ola(4),GLAT(JMN))
allocate (ZAVG(IMN,JMN))
allocate (ZSLM(IMN,JMN))
Expand Down Expand Up @@ -351,8 +348,8 @@ SUBROUTINE TERSUB(IMN,JMN,IM,JM,NR,NW,EFAC,BLAT,
!
! --- IMN,JMN
print*, ' IM, JM, NR, EFAC, BLAT'
print*, IM,JM,NR,EFAC,BLAT
print*, ' IM, JM, EFAC, BLAT'
print*, IM,JM,EFAC,BLAT
print *,' imn,jmn,glob(imn,jmn)=',imn,jmn,glob(imn,jmn)
print *,' UBOUND ZAVG=',UBOUND(ZAVG)
print *,' UBOUND glob=',UBOUND(glob)
Expand Down Expand Up @@ -1257,7 +1254,6 @@ SUBROUTINE TERSUB(IMN,JMN,IM,JM,NR,NW,EFAC,BLAT,
CALL REVERS(IM, JM, numi, HPRIME(1,1,IMT), WORK1)
ENDDO
ENDIF
ORS=0.
ORF=ORO
deallocate (WORK1)
Expand Down Expand Up @@ -1315,7 +1311,7 @@ SUBROUTINE TERSUB(IMN,JMN,IM,JM,NR,NW,EFAC,BLAT,
! Deallocate 1d vars
deallocate(numi,lonsperlat)
deallocate(WGTCLT,XLAT,XLON,ORS,oaa,ola,GLAT)
deallocate(WGTCLT,XLAT,XLON,oaa,ola,GLAT)
! Deallocate 2d vars
deallocate (OCLSM)
Expand Down
6 changes: 1 addition & 5 deletions ush/fv3gfs_make_orog.sh
Original file line number Diff line number Diff line change
Expand Up @@ -57,13 +57,9 @@ fi
if [ ! -s $workdir ]; then mkdir -p $workdir ;fi
if [ ! -s $outdir ]; then mkdir -p $outdir ;fi

#jcap is for Gaussian grid
#jcap=`expr $latb - 2 `
jcap=0
mtnres=1
efac=0
blat=0
NR=0

if [ $is_latlon -eq 1 ]; then
OUTGRID="none"
Expand Down Expand Up @@ -94,7 +90,7 @@ if [ $is_latlon -eq 0 ]; then
fi
cp $executable .

echo $mtnres $lonb $latb $jcap $NR $efac $blat > INPS
echo $mtnres $lonb $latb $efac $blat > INPS
echo $OUTGRID >> INPS
echo $orogfile >> INPS
if [ -z ${ocn+x} ]; then
Expand Down

0 comments on commit 615ad2b

Please sign in to comment.