Skip to content

Commit

Permalink
Remove some unused variables from mtnlm7_oclsm.F.
Browse files Browse the repository at this point in the history
  • Loading branch information
George Gayno committed Apr 26, 2024
1 parent 12eec27 commit 3d386be
Showing 1 changed file with 13 additions and 30 deletions.
43 changes: 13 additions & 30 deletions sorc/orog_mask_tools.fd/orog.fd/mtnlm7_oclsm.F
Original file line number Diff line number Diff line change
Expand Up @@ -914,10 +914,10 @@ SUBROUTINE TERSUB(IMN,JMN,IM,JM,NM,NR,NF0,NF1,NW,EFAC,
& //trim(INPUTOROG) )

print*, "calling MAKEOA3 to compute OA, OL"
CALL MAKEOA3(ZAVG,zslm,VAR,GLAT,OA,OL,IWORK,ELVMAX,ORO,SLM,
CALL MAKEOA3(ZAVG,VAR,GLAT,OA,OL,IWORK,ELVMAX,ORO,SLM,
1 WORK1,WORK2,WORK3,WORK4,WORK5,WORK6,
2 IM,JM,IMN,JMN,geolon_c,geolat_c,
3 geolon,geolat,is_south_pole,is_north_pole,nx_in,ny_in,
3 geolon,geolat,nx_in,ny_in,
4 oa_in,ol_in,slm_in,lon_in,lat_in)

deallocate(oa_in,ol_in,slm_in,lon_in,lat_in)
Expand Down Expand Up @@ -1516,9 +1516,7 @@ SUBROUTINE MAKEMT(ZAVG,ZSLM,ORO,SLM,VAR,VAR4,
INTEGER ZAVG(IMN,JMN),ZSLM(IMN,JMN)
DIMENSION ORO(IM,JM),SLM(IM,JM),VAR(IM,JM),VAR4(IM,JM)
DIMENSION IST(IM,jm),IEN(IM,jm),JST(JM),JEN(JM),numi(jm)
LOGICAL FLAG, DEBUG
C==== DATA DEBUG/.TRUE./
DATA DEBUG/.FALSE./
LOGICAL FLAG
C
! ---- OCLSM holds the ocean (im,jm) grid
print *,' _____ SUBROUTINE MAKEMT '
Expand Down Expand Up @@ -3598,7 +3596,6 @@ end subroutine interpolate_mismatch
!! is computed from the high-resolution orography data.
!!
!! @param[in] zavg High-resolution orography data.
!! @param[in] zslm High-resolution land-mask data. Not used.
!! @param[in] var Standard deviation of orography on the model grid.
!! @param[out] glat Latitude of each row of input terrain dataset.
!! @param[out] oa4 Orographic asymmetry on the model grid. Four
Expand All @@ -3625,8 +3622,6 @@ end subroutine interpolate_mismatch
!! @param[in] lat_c Corner point latitudes of the model grid points.
!! @param[in] lon_t Center point longitudes of the model grid points.
!! @param[in] lat_t Center point latitudes of the model grid points.
!! @param[in] is_south_pole Not used.
!! @param[in] is_north_pole Not used.
!! @param[in] imi 'i' dimension of input gfs orography data.
!! @param[in] jmi 'j' dimension of input gfs orography data.
!! @param[in] oa_in Asymmetry on the input gfs orography data.
Expand All @@ -3635,10 +3630,10 @@ end subroutine interpolate_mismatch
!! @param[in] lon_in Longitude on the input gfs orography data.
!! @param[in] lat_in Latitude on the input gfs orography data.
!! @author Jordan Alpert NOAA/EMC
SUBROUTINE MAKEOA3(ZAVG,zslm,VAR,GLAT,OA4,OL,IOA4,ELVMAX,
SUBROUTINE MAKEOA3(ZAVG,VAR,GLAT,OA4,OL,IOA4,ELVMAX,
1 ORO,SLM,oro1,XNSUM,XNSUM1,XNSUM2,XNSUM3,XNSUM4,
2 IM,JM,IMN,JMN,lon_c,lat_c,lon_t,lat_t,
3 is_south_pole,is_north_pole,IMI,JMI,OA_IN,OL_IN,
3 IMI,JMI,OA_IN,OL_IN,
4 slm_in,lon_in,lat_in)
! Required when using iplib v4.0 or higher.
Expand All @@ -3652,7 +3647,7 @@ SUBROUTINE MAKEOA3(ZAVG,zslm,VAR,GLAT,OA4,OL,IOA4,ELVMAX,
real, PARAMETER :: R2D=180./3.14159265358979
integer IM,JM,IMN,JMN,IMI,JMI
real GLAT(JMN)
INTEGER ZAVG(IMN,JMN),ZSLM(IMN,JMN)
INTEGER ZAVG(IMN,JMN)
real SLM(IM,JM)
real ORO(IM,JM),ORO1(IM,JM),ELVMAX(IM,JM),ZMAX(IM,JM)
real OA4(IM,JM,4)
Expand All @@ -3662,26 +3657,16 @@ SUBROUTINE MAKEOA3(ZAVG,zslm,VAR,GLAT,OA4,OL,IOA4,ELVMAX,
real lon_in(IMI,JMI), lat_in(IMI,JMI)
real lon_c(IM+1,JM+1), lat_c(IM+1,JM+1)
real lon_t(IM,JM), lat_t(IM,JM)
logical is_south_pole(IM,JM), is_north_pole(IM,JM)
real XNSUM(IM,JM),XNSUM1(IM,JM),XNSUM2(IM,JM)
real XNSUM3(IM,JM),XNSUM4(IM,JM)
real VAR(IM,JM),OL(IM,JM,4)
LOGICAL FLAG
integer i,j,ilist(IMN),numx,i1,j1,ii1
integer KWD,II,npts
integer KWD
real LONO(4),LATO(4),LONI,LATI
real DELXN,HC,HEIGHT,XNPU,XNPD,T
real DELXN,HC,HEIGHT,T
integer NS0,NS1,NS2,NS3,NS4,NS5,NS6
logical inside_a_polygon
real lon,lat,dlon,dlat,dlat_old
real lon1,lat1,lon2,lat2
real xnsum11,xnsum12,xnsum21,xnsum22,xnsumx
real HC_11, HC_12, HC_21, HC_22
real xnsum1_11,xnsum1_12,xnsum1_21,xnsum1_22
real xnsum2_11,xnsum2_12,xnsum2_21,xnsum2_22
real get_lon_angle, get_lat_angle, get_xnsum
integer ist, ien, jst, jen
real xland,xwatr,xl1,xs1,oroavg
integer jst, jen
integer int_opt, ipopt(20), kgds_input(200), kgds_output(200)
integer count_land_output
integer ij, ijmdl_output, iret, num_mismatch_land, num
Expand Down Expand Up @@ -4272,7 +4257,7 @@ subroutine maxmin(ia,len,tile)
ccmr
integer*2 ia(len)
character*7 tile
integer iaamax, iaamin, len, j, m, ja, kount
integer iaamax, iaamin, len, m, ja, kount
integer(8) sum2,std,mean,isum
integer i_count_notset,kount_9
! --- missing is -9999
Expand Down Expand Up @@ -4655,13 +4640,13 @@ subroutine get_xnsum2(lon1,lat1,lon2,lat2,IMN,JMN,
real, intent(out) :: xnsum1,xnsum2,HC
logical verbose
real lon1,lat1,lon2,lat2,oro,delxn
real lon1,lat1,lon2,lat2,delxn
integer IMN,JMN
real glat(JMN)
integer zavg(IMN,JMN)
integer i, j, ist, ien, jst, jen, i1
real HEIGHT, var
real XW1,XW2,slm,xnsum
real XW1,XW2,xnsum
!---figure out ist,ien,jst,jen
do j = 1, JMN
if( GLAT(J) .GT. lat1 ) then
Expand Down Expand Up @@ -4749,13 +4734,12 @@ subroutine get_xnsum3(lon1,lat1,lon2,lat2,IMN,JMN,
implicit none
real, intent(out) :: xnsum1,xnsum2
real lon1,lat1,lon2,lat2,oro,delxn
real lon1,lat1,lon2,lat2,delxn
integer IMN,JMN
real glat(JMN)
integer zavg(IMN,JMN)
integer i, j, ist, ien, jst, jen, i1
real HEIGHT, HC
real XW1,XW2,slm,xnsum
!---figure out ist,ien,jst,jen
! if lat1 or lat 2 is 90 degree. set jst = JMN
jst = JMN
Expand Down Expand Up @@ -4827,7 +4811,6 @@ subroutine nanc(a,l,c)
data inaq3/x'FFC00000'/
data inaq4/x'FFFFFFFF'/
c
real(kind=8)a(l),rtc,t1,t2
character*(*) c
c t1=rtc()
cgwv print *, ' nanc call ',c
Expand Down

0 comments on commit 3d386be

Please sign in to comment.