Skip to content

Commit

Permalink
Remove some unused variables.
Browse files Browse the repository at this point in the history
  • Loading branch information
GeorgeGayno-NOAA committed Aug 24, 2023
1 parent 42ab7cd commit e67a305
Show file tree
Hide file tree
Showing 2 changed files with 11 additions and 21 deletions.
20 changes: 8 additions & 12 deletions sorc/global_cycle.fd/cycle.f90
Original file line number Diff line number Diff line change
Expand Up @@ -724,7 +724,7 @@ SUBROUTINE SFCDRV(LUGB, IDIM,JDIM,LENSFC,LSOIL,DELTSFC, &
! update foundation & surface temperature for NSST
!
CALL ADJUST_NSST(RLA,RLO,SLIFCS,SLIFCS_FG,TSFFCS,SITFCS,SICFCS,STCFCS, &
NSST,LENSFC,LSOIL,IDIM,JDIM,ZSEA1,ZSEA2,IM,ID,DELTSFC, &
NSST,LENSFC,LSOIL,IDIM,JDIM,ZSEA1,ZSEA2, &
tf_clm_tile,tf_trd_tile,sal_clm_tile)
ENDIF
ENDIF
Expand Down Expand Up @@ -910,9 +910,6 @@ END SUBROUTINE SFCDRV
!! depth of sea temperature. In whole mm.
!! @param[in] ZSEA2 When running nsst model, this is the upper bound of
!! depth of sea temperature. In whole mm.
!! @param[in] MON Month
!! @param[in] DAY Day
!! @param[in] DELTSFC Cycling frequency in hours
!! @param[in] tf_clm_tile Climatological reference temperature on the
!! cubed-sphere tile.
!! @param[in] tf_trd_tile Climatolocial reference temperature trend on the
Expand All @@ -922,7 +919,7 @@ END SUBROUTINE SFCDRV
!! @author Xu Li, George Gayno
SUBROUTINE ADJUST_NSST(RLA,RLO,SLMSK_TILE,SLMSK_FG_TILE,SKINT_TILE,&
SICET_TILE,sice_tile,SOILT_TILE,NSST,LENSFC,LSOIL, &
IDIM,JDIM,ZSEA1,ZSEA2,MON,DAY,DELTSFC, &
IDIM,JDIM,ZSEA1,ZSEA2, &
tf_clm_tile,tf_trd_tile,sal_clm_tile)

USE UTILS
Expand All @@ -935,11 +932,11 @@ SUBROUTINE ADJUST_NSST(RLA,RLO,SLMSK_TILE,SLMSK_FG_TILE,SKINT_TILE,&

IMPLICIT NONE

INTEGER, INTENT(IN) :: LENSFC, LSOIL, IDIM, JDIM, MON, DAY
INTEGER, INTENT(IN) :: LENSFC, LSOIL, IDIM, JDIM

REAL, INTENT(IN) :: SLMSK_TILE(LENSFC), SLMSK_FG_TILE(LENSFC)
real, intent(in) :: tf_clm_tile(lensfc),tf_trd_tile(lensfc),sal_clm_tile(lensfc)
REAL, INTENT(IN) :: ZSEA1, ZSEA2, DELTSFC
REAL, INTENT(IN) :: ZSEA1, ZSEA2
REAL, INTENT(INOUT) :: RLA(LENSFC), RLO(LENSFC), SKINT_TILE(LENSFC)
REAL, INTENT(INOUT) :: SICET_TILE(LENSFC),sice_tile(lensfc),SOILT_TILE(LENSFC,LSOIL)

Expand Down Expand Up @@ -1710,7 +1707,7 @@ subroutine get_tf_clm(xlats_ij,xlons_ij,ny,nx,iy,im,id,ih,tf_clm,tf_trd)
real, dimension(nx*ny) :: tf_clm_ij ! sst climatology at target grids (nx*ny)
real, dimension(nx*ny) :: tf_trd_ij ! 6-hourly sst climatology tendency
real :: wei1,wei2
integer :: nxc,nyc,mon1,mon2,i,j
integer :: nxc,nyc,mon1,mon2
character (len=6), parameter :: fin_tf_clm='sstclm' ! sst climatology file name
!
! get which two months used and their weights from atime
Expand Down Expand Up @@ -1823,7 +1820,7 @@ subroutine get_sal_clm(xlats_ij,xlons_ij,ny,nx,iy,im,id,ih,sal_clm)

real, dimension(nx*ny) :: sal_clm_ij ! salinity climatology at target grids (nx*ny)
real :: wei1,wei2
integer :: nxc,nyc,mon1,mon2,i,j
integer :: nxc,nyc,mon1,mon2
character (len=6), parameter :: fin_sal_clm='salclm' ! salinity climatology file name
!
! get which two months used and their weights from atime
Expand Down Expand Up @@ -1933,11 +1930,10 @@ subroutine intp_tile(tf_lalo,dlats_lalo,dlons_lalo,jdim_lalo,idim_lalo, &
real, parameter :: deg2rad=3.1415926/180.0
real, dimension(jdim_lalo) :: xlats_lalo
real, dimension(idim_lalo) :: xlons_lalo
real :: tf,wsum,res_km
real :: wsum
integer :: itile,jtile
integer :: ii,jj,ij,iii,jjj
integer :: ij
integer :: ilalo,jlalo,ilalop1,jlalop1
integer :: istart,iend,jstart,jend,krad

integer, allocatable, dimension(:,:) :: id1,id2,jdc
real, allocatable, dimension(:,:,:) :: agrid,s2c
Expand Down
12 changes: 3 additions & 9 deletions sorc/global_cycle.fd/read_write_data.f90
Original file line number Diff line number Diff line change
Expand Up @@ -872,7 +872,7 @@ SUBROUTINE READ_GSI_DATA(GSI_FILE, FILE_TYPE, LSOIL)
CHARACTER(LEN=1) :: K_CH
CHARACTER(LEN=10) :: INCVAR
CHARACTER(LEN=80) :: err_msg
INTEGER :: K, I
INTEGER :: K

PRINT*
PRINT*, "READ INPUT GSI DATA FROM: "//TRIM(GSI_FILE)
Expand Down Expand Up @@ -1705,7 +1705,6 @@ subroutine get_tf_clm_dim(file_sst,mlat_sst,mlon_sst)
integer,parameter:: lu_sst = 21 ! fortran unit number of grib sst file

integer :: iret
integer :: mscan,kb1
integer :: kf,kg,k,j,ierr
integer, dimension(22):: jgds,kgds
integer, dimension(25):: jpds,kpds
Expand Down Expand Up @@ -1763,15 +1762,14 @@ subroutine read_salclm_gfs_nc(filename,sal,xlats,xlons,nlat,nlon,itime)
real, dimension(nlon), intent(out) :: xlons
real, dimension(nlon,nlat), intent(out) :: sal
! Local variables
integer :: ncid,ntime
integer :: ncid

integer, parameter :: ndims = 3
character (len = *), parameter :: lat_name = "latitude"
character (len = *), parameter :: lon_name = "longitude"
character (len = *), parameter :: t_name = "time"
character (len = *), parameter :: sal_name="sal"
integer :: no_fill,fill_value
integer :: time_varid,lon_varid, lat_varid, z_varid, sal_varid
integer :: time_varid,lon_varid, lat_varid, sal_varid

! The start and count arrays will tell the netCDF library where to read our data.
integer, dimension(ndims) :: start, count
Expand All @@ -1783,10 +1781,6 @@ subroutine read_salclm_gfs_nc(filename,sal,xlats,xlons,nlat,nlon,itime)
character (len = *), parameter :: lat_units = "degrees_north"
character (len = *), parameter :: lon_units = "degrees_east"

integer :: missv
! Loop indices
integer :: i,j

! Open the file.
call nc_check( nf90_open(filename, nf90_nowrite, ncid) )

Expand Down

0 comments on commit e67a305

Please sign in to comment.