Back to home page

MITgcm

 
 

    


File indexing completed on 2022-10-26 05:09:35 UTC

view on githubraw file Latest commit cc9097e5 on 2022-10-26 02:15:19 UTC
fda3710353 Oliv*0001 #include "LONGSTEP_OPTIONS.h"
                0002 
                0003 CBOP
                0004 C !ROUTINE: LONGSTEP_FORCING_SURF
                0005 
                0006 C !INTERFACE: ==========================================================
                0007       SUBROUTINE LONGSTEP_FORCING_SURF(
                0008      I                            bi, bj, iMin, iMax, jMin, jMax,
cc9097e522 Oliv*0009      I                            myTime, myIter, myThid )
fda3710353 Oliv*0010 
                0011 C !DESCRIPTION:
                0012 C     Precomputes surface forcing term for pkg/ptracers.
                0013 C     Precomputation is needed because of non-local KPP transport term,
                0014 C     routine KPP_TRANSPORT_PTR.
                0015 
                0016 C !USES: ===============================================================
                0017       IMPLICIT NONE
                0018 #include "SIZE.h"
                0019 #include "EEPARAMS.h"
                0020 #include "PARAMS.h"
cc9097e522 Oliv*0021 c #include "GRID.h"
                0022 c #include "SURFACE.h"
                0023 c #include "FFIELDS.h"
fda3710353 Oliv*0024 c #include "DYNVARS.h"
                0025 #include "LONGSTEP.h"
cc9097e522 Oliv*0026 #ifdef ALLOW_PTRACERS
                0027 # include "PTRACERS_SIZE.h"
                0028 # include "PTRACERS_PARAMS.h"
                0029 # include "PTRACERS_FIELDS.h"
                0030 #endif
fda3710353 Oliv*0031 
                0032 C !INPUT PARAMETERS: ===================================================
                0033 C  bi,bj                :: tile indices
                0034 C  myTime               :: model time
                0035 C  myIter               :: time-step number
                0036 C  myThid               :: thread number
                0037       INTEGER bi, bj, iMin, iMax, jMin, jMax
                0038       _RL myTime
                0039       INTEGER myIter
                0040       INTEGER myThid
                0041 
                0042 #ifdef ALLOW_LONGSTEP
cc9097e522 Oliv*0043 #ifdef ALLOW_PTRACERS
fda3710353 Oliv*0044 
                0045 C !LOCAL VARIABLES: ====================================================
                0046 C  i,j                  :: loop indices
                0047 C  iTrc                 :: tracer index
                0048 C  ks                   :: surface level index
                0049       INTEGER i, j
                0050       INTEGER iTrc, ks
                0051 CEOP
                0052 
                0053       IF ( usingPCoords ) THEN
                0054         ks = Nr
                0055       ELSE
                0056         ks = 1
                0057       ENDIF
                0058 
                0059 C Example of how to add forcing at the surface
                0060       DO iTrc=1,PTRACERS_numInUse
                0061           DO j = jMin, jMax
                0062            DO i = iMin, iMax
                0063              surfaceForcingPTr(i,j,bi,bj,iTrc) =
                0064      &               0. _d 0
                0065 c    &               surfaceForcingS(i,j,bi,bj)
                0066            ENDDO
                0067           ENDDO
                0068       ENDDO
                0069 
                0070 #ifdef EXACT_CONSERV
                0071       IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
                0072      &     .AND. useRealFreshWaterFlux ) THEN
                0073 
                0074        DO iTrc=1,PTRACERS_numInUse
                0075 
                0076 c-  NonLin_FrSurf and RealFreshWaterFlux : PmEpR effectively changes
                0077 c   the water column height ; temp., salt, (tracer) flux associated
                0078 c   with this input/output of water is added here to the surface tendency.
                0079 c
                0080 c   NB: LS_fwflux is PmEpR
                0081 c
                0082          IF (PTRACERS_EvPrRn(iTrc).NE.UNSET_RL) THEN
                0083           DO j = jMin, jMax
                0084            DO i = iMin, iMax
                0085              surfaceForcingPTr(i,j,bi,bj,iTrc) =
                0086      &          surfaceForcingPTr(i,j,bi,bj,iTrc)
                0087      &        + LS_fwFlux(i,j,bi,bj)
                0088      &          *( PTRACERS_EvPrRn(iTrc) - pTracer(i,j,ks,bi,bj,iTrc) )
                0089      &          *mass2rUnit
                0090            ENDDO
                0091           ENDDO
                0092          ENDIF
                0093 
                0094        ENDDO
                0095 
                0096 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0097       ELSE
                0098 #else /* EXACT_CONSERV */
                0099       IF (.TRUE.) THEN
                0100 #endif /* EXACT_CONSERV */
                0101 
                0102 C--   EmPmR does not really affect the water column height (for tracer budget)
                0103 C     and is converted to a salt tendency.
                0104 
                0105        IF (convertFW2Salt .EQ. -1.) THEN
                0106 C-    use local surface tracer field to calculate forcing term:
                0107 
                0108         DO iTrc=1,PTRACERS_numInUse
                0109 
                0110          IF (PTRACERS_EvPrRn(iTrc).NE.UNSET_RL) THEN
                0111 C        account for Rain/Evap tracer content (PTRACERS_EvPrRn) using
                0112 C        local surface tracer
                0113 c
                0114 c   NB: LS_fwflux is EmPmR
                0115 
                0116           DO j = jMin, jMax
                0117            DO i = iMin, iMax
                0118             surfaceForcingPTr(i,j,bi,bj,iTrc) =
                0119      &          surfaceForcingPTr(i,j,bi,bj,iTrc)
                0120      &        + LS_fwFlux(i,j,bi,bj)
                0121      &          *( pTracer(i,j,ks,bi,bj,iTrc) - PTRACERS_EvPrRn(iTrc) )
                0122      &          *mass2rUnit
                0123            ENDDO
                0124           ENDDO
                0125          ENDIF
                0126 
                0127         ENDDO
                0128 
                0129        ELSE
                0130 C-    use uniform tracer value to calculate forcing term:
                0131 
                0132         DO iTrc=1,PTRACERS_numInUse
                0133 
                0134          IF (PTRACERS_EvPrRn(iTrc).NE.UNSET_RL) THEN
                0135 C     account for Rain/Evap tracer content (PTRACERS_EvPrRn) assuming uniform
                0136 C     surface tracer (=PTRACERS_ref)
                0137 c
                0138 c   NB: LS_fwflux is EmPmR
                0139 
                0140           DO j = jMin, jMax
                0141            DO i = iMin, iMax
                0142             surfaceForcingPTr(i,j,bi,bj,iTrc) =
                0143      &          surfaceForcingPTr(i,j,bi,bj,iTrc)
                0144      &        + LS_fwFlux(i,j,bi,bj)
                0145      &            *( PTRACERS_ref(ks,iTrc) - PTRACERS_EvPrRn(iTrc) )
                0146      &            *mass2rUnit
                0147            ENDDO
                0148           ENDDO
                0149          ENDIF
                0150 
                0151         ENDDO
                0152 
                0153 C-    end local-surface-tracer / uniform-value distinction
                0154        ENDIF
                0155 
                0156       ENDIF
                0157 
                0158 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0159 
cc9097e522 Oliv*0160 #endif /* ALLOW_PTRACERS */
fda3710353 Oliv*0161 #endif /* ALLOW_LONGSTEP */
                0162 
                0163       RETURN
                0164       END