/[MITgcm]/MITgcm/model/src/thermodynamics.F
ViewVC logotype

Diff of /MITgcm/model/src/thermodynamics.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.2 by heimbach, Mon Aug 13 18:05:26 2001 UTC revision 1.12 by adcroft, Fri Sep 28 02:26:57 2001 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6    CBOP
7    C     !ROUTINE: THERMODYNAMICS
8    C     !INTERFACE:
9        SUBROUTINE THERMODYNAMICS(myTime, myIter, myThid)        SUBROUTINE THERMODYNAMICS(myTime, myIter, myThid)
10  C     /==========================================================\  C     !DESCRIPTION: \bv
11  C     | SUBROUTINE THERMODYNAMICS                                |  C     *==========================================================*
12  C     | o Controlling routine for the prognostic part of the     |  C     | SUBROUTINE THERMODYNAMICS                                
13  C     |   thermo-dynamics.                                       |  C     | o Controlling routine for the prognostic part of the      
14  C     |==========================================================|  C     |   thermo-dynamics.                                        
15  C     \==========================================================/  C     *===========================================================
16        IMPLICIT NONE  C     | The algorithm...
17    C     |
18    C     | "Correction Step"
19    C     | =================
20    C     | Here we update the horizontal velocities with the surface
21    C     | pressure such that the resulting flow is either consistent
22    C     | with the free-surface evolution or the rigid-lid:
23    C     |   U[n] = U* + dt x d/dx P
24    C     |   V[n] = V* + dt x d/dy P
25    C     |
26    C     | "Calculation of Gs"
27    C     | ===================
28    C     | This is where all the accelerations and tendencies (ie.
29    C     | physics, parameterizations etc...) are calculated
30    C     |   rho = rho ( theta[n], salt[n] )
31    C     |   b   = b(rho, theta)
32    C     |   K31 = K31 ( rho )
33    C     |   Gu[n] = Gu( u[n], v[n], wVel, b, ... )
34    C     |   Gv[n] = Gv( u[n], v[n], wVel, b, ... )
35    C     |   Gt[n] = Gt( theta[n], u[n], v[n], wVel, K31, ... )
36    C     |   Gs[n] = Gs( salt[n], u[n], v[n], wVel, K31, ... )
37    C     |
38    C     | "Time-stepping" or "Prediction"
39    C     | ================================
40    C     | The models variables are stepped forward with the appropriate
41    C     | time-stepping scheme (currently we use Adams-Bashforth II)
42    C     | - For momentum, the result is always *only* a "prediction"
43    C     | in that the flow may be divergent and will be "corrected"
44    C     | later with a surface pressure gradient.
45    C     | - Normally for tracers the result is the new field at time
46    C     | level [n+1} *BUT* in the case of implicit diffusion the result
47    C     | is also *only* a prediction.
48    C     | - We denote "predictors" with an asterisk (*).
49    C     |   U* = U[n] + dt x ( 3/2 Gu[n] - 1/2 Gu[n-1] )
50    C     |   V* = V[n] + dt x ( 3/2 Gv[n] - 1/2 Gv[n-1] )
51    C     |   theta[n+1] = theta[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
52    C     |   salt[n+1] = salt[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
53    C     | With implicit diffusion:
54    C     |   theta* = theta[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
55    C     |   salt* = salt[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
56    C     |   (1 + dt * K * d_zz) theta[n] = theta*
57    C     |   (1 + dt * K * d_zz) salt[n] = salt*
58    C     |
59    C     *==========================================================*
60    C     \ev
61    
62    C     !USES:
63          IMPLICIT NONE
64  C     == Global variables ===  C     == Global variables ===
65  #include "SIZE.h"  #include "SIZE.h"
66  #include "EEPARAMS.h"  #include "EEPARAMS.h"
67  #include "PARAMS.h"  #include "PARAMS.h"
68  #include "DYNVARS.h"  #include "DYNVARS.h"
69  #include "GRID.h"  #include "GRID.h"
70    #include "GAD.h"
71  #ifdef ALLOW_PASSIVE_TRACER  #ifdef ALLOW_PASSIVE_TRACER
72  #include "TR1.h"  #include "TR1.h"
73  #endif  #endif
   
74  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
75  # include "tamc.h"  # include "tamc.h"
76  # include "tamc_keys.h"  # include "tamc_keys.h"
# Line 33  C     == Global variables === Line 82  C     == Global variables ===
82  #  include "GMREDI.h"  #  include "GMREDI.h"
83  # endif  # endif
84  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
   
85  #ifdef ALLOW_TIMEAVE  #ifdef ALLOW_TIMEAVE
86  #include "TIMEAVE_STATV.h"  #include "TIMEAVE_STATV.h"
87  #endif  #endif
88    
89    C     !INPUT/OUTPUT PARAMETERS:
90  C     == Routine arguments ==  C     == Routine arguments ==
91  C     myTime - Current time in simulation  C     myTime - Current time in simulation
92  C     myIter - Current iteration number in simulation  C     myIter - Current iteration number in simulation
# Line 46  C     myThid - Thread number for this in Line 95  C     myThid - Thread number for this in
95        INTEGER myIter        INTEGER myIter
96        INTEGER myThid        INTEGER myThid
97    
98    C     !LOCAL VARIABLES:
99  C     == Local variables  C     == Local variables
100  C     xA, yA                 - Per block temporaries holding face areas  C     xA, yA                 - Per block temporaries holding face areas
101  C     uTrans, vTrans, rTrans - Per block temporaries holding flow  C     uTrans, vTrans, rTrans - Per block temporaries holding flow
# Line 74  C     bi, bj Line 124  C     bi, bj
124  C     k, kup,        - Index for layer above and below. kup and kDown  C     k, kup,        - Index for layer above and below. kup and kDown
125  C     kDown, km1       are switched with layer to be the appropriate  C     kDown, km1       are switched with layer to be the appropriate
126  C                      index into fVerTerm.  C                      index into fVerTerm.
 C     tauAB - Adams-Bashforth timestepping weight: 0=forward ; 1/2=Adams-Bashf.  
127        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
128        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
129        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 94  C     tauAB - Adams-Bashforth timesteppi Line 143  C     tauAB - Adams-Bashforth timesteppi
143        _RL sigmaX  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaX  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
144        _RL sigmaY  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaY  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
145        _RL sigmaR  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaR  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
146        _RL tauAB  C     This is currently used by IVDC and Diagnostics
   
 C This is currently used by IVDC and Diagnostics  
147        _RL ConvectCount (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL ConvectCount (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
   
148        INTEGER iMin, iMax        INTEGER iMin, iMax
149        INTEGER jMin, jMax        INTEGER jMin, jMax
150        INTEGER bi, bj        INTEGER bi, bj
# Line 110  c     CHARACTER*(MAX_LEN_MBUF) suff Line 156  c     CHARACTER*(MAX_LEN_MBUF) suff
156  c     LOGICAL  DIFFERENT_MULTIPLE  c     LOGICAL  DIFFERENT_MULTIPLE
157  c     EXTERNAL DIFFERENT_MULTIPLE  c     EXTERNAL DIFFERENT_MULTIPLE
158  Cjmc(end)  Cjmc(end)
159    CEOP
160    
 C---    The algorithm...  
 C  
 C       "Correction Step"  
 C       =================  
 C       Here we update the horizontal velocities with the surface  
 C       pressure such that the resulting flow is either consistent  
 C       with the free-surface evolution or the rigid-lid:  
 C         U[n] = U* + dt x d/dx P  
 C         V[n] = V* + dt x d/dy P  
 C  
 C       "Calculation of Gs"  
 C       ===================  
 C       This is where all the accelerations and tendencies (ie.  
 C       physics, parameterizations etc...) are calculated  
 C         rho = rho ( theta[n], salt[n] )  
 C         b   = b(rho, theta)  
 C         K31 = K31 ( rho )  
 C         Gu[n] = Gu( u[n], v[n], wVel, b, ... )  
 C         Gv[n] = Gv( u[n], v[n], wVel, b, ... )  
 C         Gt[n] = Gt( theta[n], u[n], v[n], wVel, K31, ... )  
 C         Gs[n] = Gs( salt[n], u[n], v[n], wVel, K31, ... )  
 C  
 C       "Time-stepping" or "Prediction"  
 C       ================================  
 C       The models variables are stepped forward with the appropriate  
 C       time-stepping scheme (currently we use Adams-Bashforth II)  
 C       - For momentum, the result is always *only* a "prediction"  
 C       in that the flow may be divergent and will be "corrected"  
 C       later with a surface pressure gradient.  
 C       - Normally for tracers the result is the new field at time  
 C       level [n+1} *BUT* in the case of implicit diffusion the result  
 C       is also *only* a prediction.  
 C       - We denote "predictors" with an asterisk (*).  
 C         U* = U[n] + dt x ( 3/2 Gu[n] - 1/2 Gu[n-1] )  
 C         V* = V[n] + dt x ( 3/2 Gv[n] - 1/2 Gv[n-1] )  
 C         theta[n+1] = theta[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )  
 C         salt[n+1] = salt[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )  
 C       With implicit diffusion:  
 C         theta* = theta[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )  
 C         salt* = salt[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )  
 C         (1 + dt * K * d_zz) theta[n] = theta*  
 C         (1 + dt * K * d_zz) salt[n] = salt*  
 C---  
   
161  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
162  C--   dummy statement to end declaration part  C--   dummy statement to end declaration part
163        ikey = 1        ikey = 1
# Line 205  CHPF$&                  ) Line 208  CHPF$&                  )
208  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
209            act1 = bi - myBxLo(myThid)            act1 = bi - myBxLo(myThid)
210            max1 = myBxHi(myThid) - myBxLo(myThid) + 1            max1 = myBxHi(myThid) - myBxLo(myThid) + 1
   
211            act2 = bj - myByLo(myThid)            act2 = bj - myByLo(myThid)
212            max2 = myByHi(myThid) - myByLo(myThid) + 1            max2 = myByHi(myThid) - myByLo(myThid) + 1
   
213            act3 = myThid - 1            act3 = myThid - 1
214            max3 = nTx*nTy            max3 = nTx*nTy
   
215            act4 = ikey_dynamics - 1            act4 = ikey_dynamics - 1
   
216            ikey = (act1 + 1) + act2*max1            ikey = (act1 + 1) + act2*max1
217       &                      + act3*max1*max2       &                      + act3*max1*max2
218       &                      + act4*max1*max2*max3       &                      + act4*max1*max2*max3
# Line 239  C This is currently also used by IVDC an Line 238  C This is currently also used by IVDC an
238             ConvectCount(i,j,k) = 0.             ConvectCount(i,j,k) = 0.
239             KappaRT(i,j,k) = 0. _d 0             KappaRT(i,j,k) = 0. _d 0
240             KappaRS(i,j,k) = 0. _d 0             KappaRS(i,j,k) = 0. _d 0
241    #ifdef ALLOW_AUTODIFF_TAMC
242               gT(i,j,k,bi,bj) = 0. _d 0
243               gS(i,j,k,bi,bj) = 0. _d 0
244    #ifdef ALLOW_PASSIVE_TRACER
245               gTr1(i,j,k,bi,bj) = 0. _d 0
246    #endif
247    #endif
248            ENDDO            ENDDO
249           ENDDO           ENDDO
250          ENDDO          ENDDO
# Line 250  C This is currently also used by IVDC an Line 256  C This is currently also used by IVDC an
256    
257    
258  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
259  CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
260  CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
261    #ifdef ALLOW_KPP
262    CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
263    CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
264    #endif
265  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
266    
267  C--     Start of diagnostic loop  C--     Start of diagnostic loop
# Line 328  C--     end of diagnostic k loop (Nr:1) Line 338  C--     end of diagnostic k loop (Nr:1)
338    
339  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
340  cph avoids recomputation of integrate_for_w  cph avoids recomputation of integrate_for_w
341  CADJ STORE wvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  CADJ STORE wvel (:,:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
342  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
343    
344  #ifdef  ALLOW_OBCS  #ifdef  ALLOW_OBCS
# Line 405  C--     Compute KPP mixing coefficients Line 415  C--     Compute KPP mixing coefficients
415    
416  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
417  CADJ STORE KPPghat   (:,:,:,bi,bj)  CADJ STORE KPPghat   (:,:,:,bi,bj)
 CADJ &   , KPPviscAz (:,:,:,bi,bj)  
418  CADJ &   , KPPdiffKzT(:,:,:,bi,bj)  CADJ &   , KPPdiffKzT(:,:,:,bi,bj)
419  CADJ &   , KPPdiffKzS(:,:,:,bi,bj)  CADJ &   , KPPdiffKzS(:,:,:,bi,bj)
420  CADJ &   , KPPfrac   (:,:  ,bi,bj)  CADJ &   , KPPfrac   (:,:  ,bi,bj)
# Line 415  CADJ &                 = comlev1_bibj, k Line 424  CADJ &                 = comlev1_bibj, k
424  #endif  /* ALLOW_KPP */  #endif  /* ALLOW_KPP */
425    
426  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
427  CADJ STORE KappaRT(:,:,:)     = comlev1_bibj, key = ikey, byte = isbyte  CADJ STORE KappaRT(:,:,:)     = comlev1_bibj, key=ikey, byte=isbyte
428  CADJ STORE KappaRS(:,:,:)     = comlev1_bibj, key = ikey, byte = isbyte  CADJ STORE KappaRS(:,:,:)     = comlev1_bibj, key=ikey, byte=isbyte
429  CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
430  CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
431  CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
432  CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
433  #ifdef ALLOW_PASSIVE_TRACER  #ifdef ALLOW_PASSIVE_TRACER
434  CADJ STORE tr1  (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  CADJ STORE tr1  (:,:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
435  #endif  #endif
436  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
437    
# Line 436  C note(jmc) : phiHyd=0 at this point but Line 445  C note(jmc) : phiHyd=0 at this point but
445          ENDIF          ENDIF
446  #endif /* ALLOW_AIM */  #endif /* ALLOW_AIM */
447    
448    #ifndef DISABLE_MULTIDIM_ADVECTION
449    C The CPP flag DISABLE_MULTIDIM_ADVECTION is currently set in GAD_OPTIONS.h
450    C and is currently set only for auto-differentiating. Ideally this would
451    C not be necessary. If you need mutli-dimensional advection in a
452    C differentiated code, it does work but costs more), you can edit
453    C GAD_OPTIONS.h to re-enable it.
454    
455    C--     Some advection schemes are better calculated using a multi-dimensional
456    C       method in the absence of any other terms and, if used, is done here.
457            IF (multiDimAdvection) THEN
458             IF (tempStepping .AND.
459         &       tempAdvScheme.NE.ENUM_CENTERED_2ND .AND.
460         &       tempAdvScheme.NE.ENUM_UPWIND_3RD .AND.
461         &       tempAdvScheme.NE.ENUM_CENTERED_4TH ) THEN
462              CALL GAD_ADVECTION(bi,bj,tempAdvScheme,GAD_TEMPERATURE,
463         U                      theta,gT,
464         I                      myTime,myIter,myThid)
465             ENDIF
466             IF (saltStepping .AND.
467         &       saltAdvScheme.NE.ENUM_CENTERED_2ND .AND.
468         &       saltAdvScheme.NE.ENUM_UPWIND_3RD .AND.
469         &       saltAdvScheme.NE.ENUM_CENTERED_4TH ) THEN
470              CALL GAD_ADVECTION(bi,bj,saltAdvScheme,GAD_SALINITY,
471         U                      salt,gS,
472         I                      myTime,myIter,myThid)
473             ENDIF
474            ENDIF
475    #endif /* DISABLE_MULTIDIM_ADVECTION */
476    
477  C--     Start of thermodynamics loop  C--     Start of thermodynamics loop
478          DO k=Nr,1,-1          DO k=Nr,1,-1
# Line 492  C        and step forward storing result Line 529  C        and step forward storing result
529       I         xA,yA,uTrans,vTrans,rTrans,maskUp,       I         xA,yA,uTrans,vTrans,rTrans,maskUp,
530       I         KappaRT,       I         KappaRT,
531       U         fVerT,       U         fVerT,
532       I         myTime, myThid)       I         myTime,myIter,myThid)
            tauAB = 0.5d0 + abEps  
533             CALL TIMESTEP_TRACER(             CALL TIMESTEP_TRACER(
534       I         bi,bj,iMin,iMax,jMin,jMax,k,tauAB,       I         bi,bj,iMin,iMax,jMin,jMax,k,tempAdvScheme,
535       I         theta, gT,       I         theta, gT,
      U         gTnm1,  
536       I         myIter, myThid)       I         myIter, myThid)
537           ENDIF           ENDIF
538           IF ( saltStepping ) THEN           IF ( saltStepping ) THEN
# Line 506  C        and step forward storing result Line 541  C        and step forward storing result
541       I         xA,yA,uTrans,vTrans,rTrans,maskUp,       I         xA,yA,uTrans,vTrans,rTrans,maskUp,
542       I         KappaRS,       I         KappaRS,
543       U         fVerS,       U         fVerS,
544       I         myTime, myThid)       I         myTime,myIter,myThid)
            tauAB = 0.5d0 + abEps  
545             CALL TIMESTEP_TRACER(             CALL TIMESTEP_TRACER(
546       I         bi,bj,iMin,iMax,jMin,jMax,k,tauAB,       I         bi,bj,iMin,iMax,jMin,jMax,k,saltAdvScheme,
547       I         salt, gS,       I         salt, gS,
      U         gSnm1,  
548       I         myIter, myThid)       I         myIter, myThid)
549           ENDIF           ENDIF
550  #ifdef ALLOW_PASSIVE_TRACER  #ifdef ALLOW_PASSIVE_TRACER
# Line 521  C        and step forward storing result Line 554  C        and step forward storing result
554       I         xA,yA,uTrans,vTrans,rTrans,maskUp,       I         xA,yA,uTrans,vTrans,rTrans,maskUp,
555       I         KappaRT,       I         KappaRT,
556       U         fVerTr1,       U         fVerTr1,
557       I         myTime, myThid)       I         myTime,myIter,myThid)
            tauAB = 0.5d0 + abEps  
558             CALL TIMESTEP_TRACER(             CALL TIMESTEP_TRACER(
559       I         bi,bj,iMin,iMax,jMin,jMax,k,tauAB,       I         bi,bj,iMin,iMax,jMin,jMax,k,tracerAdvScheme,
560       I         Tr1, gTr1,       I         Tr1, gTr1,
561       U         gTr1NM1,       I         myIter,myThid)
      I         myIter, myThid)  
562           ENDIF           ENDIF
563  #endif  #endif
564    
565  #ifdef   ALLOW_OBCS  #ifdef   ALLOW_OBCS
566  C--      Apply open boundary conditions  C--      Apply open boundary conditions
567           IF (useOBCS) THEN           IF (useOBCS) THEN
568             CALL OBCS_APPLY_TS( bi, bj, k, gTnm1, gSnm1, myThid )             CALL OBCS_APPLY_TS( bi, bj, k, gT, gS, myThid )
569           END IF           END IF
570  #endif   /* ALLOW_OBCS */  #endif   /* ALLOW_OBCS */
571    
572  C--      Freeze water  C--      Freeze water
573           IF (allowFreezing) THEN           IF (allowFreezing) THEN
574  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
575  CADJ STORE gTNm1(:,:,k,bi,bj) = comlev1_bibj_k  CADJ STORE gT(:,:,k,bi,bj) = comlev1_bibj_k
576  CADJ &   , key = kkey, byte = isbyte  CADJ &   , key = kkey, byte = isbyte
577  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
578              CALL FREEZE( bi, bj, iMin, iMax, jMin, jMax, k, myThid )              CALL FREEZE( bi, bj, iMin, iMax, jMin, jMax, k, myThid )
# Line 553  C--     end of thermodynamic k loop (Nr: Line 584  C--     end of thermodynamic k loop (Nr:
584    
585  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
586  C? Patrick? What about this one?  C? Patrick? What about this one?
587  cph Keys iikey and idkey don't seem to be needed  cph Keys iikey and idkey dont seem to be needed
588  cph since storing occurs on different tape for each  cph since storing occurs on different tape for each
589  cph impldiff call anyways.  cph impldiff call anyways.
590  cph Thus, common block comlev1_impl isn't needed either.  cph Thus, common block comlev1_impl isnt needed either.
591  cph Storing below needed in the case useGMREDI.  cph Storing below needed in the case useGMREDI.
592          iikey = (ikey-1)*maximpl          iikey = (ikey-1)*maximpl
593  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
# Line 567  C--     Implicit diffusion Line 598  C--     Implicit diffusion
598           IF (tempStepping) THEN           IF (tempStepping) THEN
599  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
600              idkey = iikey + 1              idkey = iikey + 1
601  CADJ STORE gTNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte  CADJ STORE gT(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
602  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
603              CALL IMPLDIFF(              CALL IMPLDIFF(
604       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
605       I         deltaTtracer, KappaRT, recip_HFacC,       I         deltaTtracer, KappaRT, recip_HFacC,
606       U         gTNm1,       U         gT,
607       I         myThid )       I         myThid )
608           ENDIF           ENDIF
609    
610           IF (saltStepping) THEN           IF (saltStepping) THEN
611  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
612           idkey = iikey + 2           idkey = iikey + 2
613  CADJ STORE gSNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte  CADJ STORE gS(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
614  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
615              CALL IMPLDIFF(              CALL IMPLDIFF(
616       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
617       I         deltaTtracer, KappaRS, recip_HFacC,       I         deltaTtracer, KappaRS, recip_HFacC,
618       U         gSNm1,       U         gS,
619       I         myThid )       I         myThid )
620           ENDIF           ENDIF
621    
622  #ifdef ALLOW_PASSIVE_TRACER  #ifdef ALLOW_PASSIVE_TRACER
623           IF (tr1Stepping) THEN           IF (tr1Stepping) THEN
624  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
625  CADJ STORE gTr1Nm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte  CADJ STORE gTr1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
626  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
627            CALL IMPLDIFF(            CALL IMPLDIFF(
628       I      bi, bj, iMin, iMax, jMin, jMax,       I      bi, bj, iMin, iMax, jMin, jMax,
629       I      deltaTtracer, KappaRT, recip_HFacC,       I      deltaTtracer, KappaRT, recip_HFacC,
630       U      gTr1Nm1,       U      gTr1,
631       I      myThid )       I      myThid )
632           ENDIF           ENDIF
633  #endif  #endif
# Line 605  CADJ STORE gTr1Nm1(:,:,:,bi,bj) = comlev Line 636  CADJ STORE gTr1Nm1(:,:,:,bi,bj) = comlev
636  C--      Apply open boundary conditions  C--      Apply open boundary conditions
637           IF (useOBCS) THEN           IF (useOBCS) THEN
638             DO K=1,Nr             DO K=1,Nr
639               CALL OBCS_APPLY_TS( bi, bj, k, gTnm1, gSnm1, myThid )               CALL OBCS_APPLY_TS( bi, bj, k, gT, gS, myThid )
640             ENDDO             ENDDO
641           END IF           END IF
642  #endif   /* ALLOW_OBCS */  #endif   /* ALLOW_OBCS */
# Line 621  Ccs- Line 652  Ccs-
652        IF ( useAIM ) THEN        IF ( useAIM ) THEN
653         CALL AIM_AIM2DYN_EXCHANGES( myTime, myThid )         CALL AIM_AIM2DYN_EXCHANGES( myTime, myThid )
654        ENDIF        ENDIF
655         _EXCH_XYZ_R8(gTnm1,myThid)         _EXCH_XYZ_R8(gT,myThid)
656         _EXCH_XYZ_R8(gSnm1,myThid)         _EXCH_XYZ_R8(gS,myThid)
657  #else  #else
658        IF (staggerTimeStep.AND.useCubedSphereExchange) THEN        IF (staggerTimeStep.AND.useCubedSphereExchange) THEN
659         _EXCH_XYZ_R8(gTnm1,myThid)         _EXCH_XYZ_R8(gT,myThid)
660         _EXCH_XYZ_R8(gSnm1,myThid)         _EXCH_XYZ_R8(gS,myThid)
661        ENDIF        ENDIF
662  #endif /* ALLOW_AIM */  #endif /* ALLOW_AIM */
663    

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.12

  ViewVC Help
Powered by ViewVC 1.1.22