Skip to content

Commit

Permalink
Cleaning up more TS_MPDATA, TS_HSIMT stuff.
Browse files Browse the repository at this point in the history
- also a fix to get_state for COBALT extra variables.
  • Loading branch information
kshedstrom committed Feb 4, 2020
1 parent 1b46d81 commit cc6205a
Show file tree
Hide file tree
Showing 7 changed files with 11 additions and 87 deletions.
1 change: 0 additions & 1 deletion ROMS/Include/lake_signell.h
Expand Up @@ -19,7 +19,6 @@
#define DJ_GRADPS
#define SPLINES_VDIFF
#define SPLINES_VVISC
#define TS_MPDATA
#define SALINITY
#define SOLVE3D
#define MASKING
Expand Down
7 changes: 0 additions & 7 deletions ROMS/Nonlinear/Biology/umaine.h
Expand Up @@ -2140,13 +2140,6 @@
& (Bio(i,k,indx)-Bio_bak(i,k,indx))* &
& Hz(i,j,k), &
& Minval)
!#ifdef TS_MPDATA
! t(i,j,k,3,indx)=t(i,j,k,nnew,indx)*Hz_inv(i,k)
!#endif
!
! t(i,j,k,nnew,indx)=t(i,j,k,nnew,indx)+ &
! & (Bio(i,k,indx)-Bio_bak(i,k,indx))* Hz(i,j,k)

END DO
END DO
END DO
Expand Down
38 changes: 0 additions & 38 deletions ROMS/Nonlinear/pre_step3d.F
Expand Up @@ -82,14 +82,6 @@ SUBROUTINE pre_step3d (ng, tile)
& GRID(ng) % Hvom, &
& GRID(ng) % z_r, &
& GRID(ng) % z_w, &
# ifdef TS_HSIMT
& GRID(ng) % omn, &
& GRID(ng) % om_u, &
& GRID(ng) % om_v, &
& GRID(ng) % on_u, &
& GRID(ng) % on_v, &

# endif
& FORCES(ng) % btflx, &
& FORCES(ng) % bustr, &
& FORCES(ng) % bvstr, &
Expand Down Expand Up @@ -146,9 +138,6 @@ SUBROUTINE pre_step3d_tile (ng, tile, &
& pm, pn, &
& Hz, Huon, Hvom, &
& z_r, z_w, &
# ifdef TS_HSIMT
& omn,om_u,om_v,on_u,on_v, &
# endif
& btflx, bustr, bvstr, &
& stflx, sustr, svstr, &
# ifdef SOLAR_SOURCE
Expand Down Expand Up @@ -198,9 +187,6 @@ SUBROUTINE pre_step3d_tile (ng, tile, &
# ifdef T_PASSIVE
USE pt3dbc_mod, ONLY : pt3dbc_tile
# endif
# ifdef TS_HSIMT
USE hsimt_tvd_mod
# endif
!
! Imported variable declarations.
!
Expand All @@ -225,13 +211,6 @@ SUBROUTINE pre_step3d_tile (ng, tile, &
real(r8), intent(in) :: Hvom(LBi:,LBj:,:)
real(r8), intent(in) :: z_r(LBi:,LBj:,:)
real(r8), intent(in) :: z_w(LBi:,LBj:,0:)
# ifdef TS_HSIMT
real(r8), intent(in) :: omn(LBi:,LBj:)
real(r8), intent(in) :: om_u(LBi:,LBj:)
real(r8), intent(in) :: om_v(LBi:,LBj:)
real(r8), intent(in) :: on_u(LBi:,LBj:)
real(r8), intent(in) :: on_v(LBi:,LBj:)
# endif
real(r8), intent(in) :: btflx(LBi:,LBj:,:)
real(r8), intent(in) :: bustr(LBi:,LBj:)
real(r8), intent(in) :: bvstr(LBi:,LBj:)
Expand Down Expand Up @@ -293,13 +272,6 @@ SUBROUTINE pre_step3d_tile (ng, tile, &
real(r8), intent(in) :: Hvom(LBi:UBi,LBj:UBj,N(ng))
real(r8), intent(in) :: z_r(LBi:UBi,LBj:UBj,N(ng))
real(r8), intent(in) :: z_w(LBi:UBi,LBj:UBj,0:N(ng))
# ifdef TS_HSIMT
real(r8), intent(in) :: omn(LBi:,LBj:)
real(r8), intent(in) :: om_u(LBi:,LBj:)
real(r8), intent(in) :: om_v(LBi:,LBj:)
real(r8), intent(in) :: on_u(LBi:,LBj:)
real(r8), intent(in) :: on_v(LBi:,LBj:)
# endif
real(r8), intent(in) :: btflx(LBi:UBi,LBj:UBj,NT(ng))
real(r8), intent(in) :: bustr(LBi:UBi,LBj:UBj)
real(r8), intent(in) :: bvstr(LBi:UBi,LBj:UBj)
Expand Down Expand Up @@ -347,11 +319,6 @@ SUBROUTINE pre_step3d_tile (ng, tile, &
# endif
# if defined DIAGNOSTICS_TS || defined DIAGNOSTICS_UV
integer :: idiag
# endif
# if defined TS_MPDATA || defined TS_HSIMT
real(r8), parameter :: Gamma = 0.5_r8
# else
real(r8), parameter :: Gamma = 1.0_r8/6.0_r8
# endif
real(r8), parameter :: eps = 1.0E-16_r8

Expand All @@ -370,11 +337,6 @@ SUBROUTINE pre_step3d_tile (ng, tile, &
real(r8), dimension(IminS:ImaxS,JminS:JmaxS) :: curv
real(r8), dimension(IminS:ImaxS,JminS:JmaxS) :: grad

# ifdef TS_HSIMT
real(r8), dimension(IminS:ImaxS,JminS:JmaxS,0:N(ng)) :: kaz
real(r8):: rd,rkad,a1,b1,betad,sw,rru,rkau,betau,epson,cc1,cc2,cc3
# endif

# include "set_bounds.h"

# ifndef TS_FIXED
Expand Down
11 changes: 1 addition & 10 deletions ROMS/Nonlinear/step3d_t.F
Expand Up @@ -373,13 +373,6 @@ SUBROUTINE step3d_t_tile (ng, tile, &
real(r8), allocatable :: Va(:,:,:)
real(r8), allocatable :: Wa(:,:,:)

# ifdef TS_HSIMT
real(r8), dimension(IminS:ImaxS,JminS:JmaxS,0:N(ng)) :: kaz
real(r8):: rd,rkad,a1,b1,betad,sw,ru,rkau,betau,epson,cc1,cc2,cc3
real(r8):: u_k(LBi:UBi,LBj:UBj)
real(r8):: v_k(LBi:UBi,LBj:UBj)
# endif

# ifdef AGE_DISTRIBUTION
real(r8) :: fac
# endif
Expand Down Expand Up @@ -1741,9 +1734,7 @@ SUBROUTINE step3d_t_tile (ng, tile, &
END DO
END DO
# endif
# if !defined TS_MPDATA && !defined TS_HSIMT
# define SALT_LIMIT
# endif
# define SALT_LIMIT
# ifdef SALT_LIMIT
!
! Apply limiter to salt - and maybe other tracers
Expand Down
19 changes: 0 additions & 19 deletions ROMS/Utility/checkdefs.F
Expand Up @@ -2999,7 +2999,6 @@ SUBROUTINE checkdefs
& 'Further limiter in upwind corrector fluxes for stability'
is=LEN_TRIM(Coptions)+1
Coptions(is:is+17)=' TS_MPDATA_LIMIT,'
# endif
# endif
#endif
#if defined TS_DIF2 && defined SOLVE3D
Expand Down Expand Up @@ -3592,24 +3591,6 @@ SUBROUTINE checkdefs
exit_flag=5
END IF
#endif
#if !defined DISTRIBUTE && defined TS_MPDATA
!
! Stop if activating MPDATA in serial with partitions or shared-
! memory.
!
IF (Master) THEN
DO ng=1,Ngrids
IF (NtileX(ng)*NtileE(ng).gt.1) THEN
WRITE (stdout,210) uppercase('ts_mpdata')
exit_flag=5
EXIT
END IF
END DO
210 FORMAT (/,' CHECKDEFS - cannot activate option: ',a, &
& /,13x,'in serial with partitions or shared-memory...', &
& /,13x,'Use distributed-memory (MPI) in parallel runs.')
END IF
#endif
#ifdef Q_PSOURCE
!
! Stop if activating obsolete mass point Sources/Sinks option. This
Expand Down
20 changes: 10 additions & 10 deletions ROMS/Utility/get_state.F
Expand Up @@ -2337,16 +2337,16 @@ SUBROUTINE get_state (ng, model, msg, ncname, IniRec, Tindex)
& Fmin, Fmax
END IF
END IF
END IF
ELSE
IF (Master) THEN
WRITE (stdout,80) string, TRIM(Vname(1,iDobgc(itrc))), &
& TRIM(ncname)
END IF
exit_flag=4
IF (FoundError(exit_flag, nf90_noerr, __LINE__, &
& __FILE__)) THEN
RETURN
ELSE
IF (Master) THEN
WRITE (stdout,80) string, TRIM(Vname(1,iDobgc(itrc))), &
& TRIM(ncname)
END IF
exit_flag=4
IF (FoundError(exit_flag, nf90_noerr, __LINE__, &
& __FILE__)) THEN
RETURN
END IF
END IF
END IF
END DO
Expand Down
2 changes: 0 additions & 2 deletions ROMS/Utility/read_phypar.F
Expand Up @@ -3479,8 +3479,6 @@ SUBROUTINE read_PhyPar (model, inp, out, Lwrite)
& Ngrids, Nfiles, FLEET)
# endif
#endif
=======
>>>>>>> kate_svn
CASE ('GRDNAME')
label='GRD - application grid'
Npts=load_s1d(Nval, Cval, Cdim, line, label, igrid, &
Expand Down

0 comments on commit cc6205a

Please sign in to comment.