/[MITgcm]/MITgcm/pkg/rbcs/rbcs_add_tendency.F
ViewVC logotype

Diff of /MITgcm/pkg/rbcs/rbcs_add_tendency.F

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

revision 1.1 by stephd, Mon Dec 19 19:13:43 2005 UTC revision 1.6 by jmc, Sat May 14 19:52:12 2011 UTC
# Line 1  Line 1 
1    C $Header$
2    C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "RBCS_OPTIONS.h"
 #include "PACKAGES_CONFIG.h"  
5    
6  CBOP  CBOP
7  C !ROUTINE: RBCS_ADD_TSTENDENCY  C !ROUTINE: RBCS_ADD_TSTENDENCY
8    
9  C !INTERFACE: ==========================================================  C !INTERFACE: ==========================================================
10        SUBROUTINE RBCS_ADD_TENDENCY(bi,bj,k, tracernum,        SUBROUTINE RBCS_ADD_TENDENCY(
11       &                            myTime, myThid )       I                    bi, bj, k, tracerNum,
12         I                    myTime, myThid )
13    
14  C !DESCRIPTION:  C !DESCRIPTION:
15  C     Will update tendencies with terms to relax to 3-D field  C     Will update tendencies with terms to relax to 3-D field
# Line 15  C     Will update tendencies with terms Line 17  C     Will update tendencies with terms
17  C !USES: ===============================================================  C !USES: ===============================================================
18        IMPLICIT NONE        IMPLICIT NONE
19  #include "SIZE.h"  #include "SIZE.h"
 #include "GRID.h"  
 #include "DYNVARS.h"  
20  #include "EEPARAMS.h"  #include "EEPARAMS.h"
21  #include "PARAMS.h"  #include "PARAMS.h"
22    c#include "GRID.h"
23    #include "DYNVARS.h"
24  #ifdef ALLOW_PTRACERS  #ifdef ALLOW_PTRACERS
25  #include "PTRACERS_SIZE.h"  #include "PTRACERS_SIZE.h"
26  #include "PTRACERS.h"  #include "PTRACERS_FIELDS.h"
27  #endif  #endif
28  #include "RBCS.h"  #include "RBCS_SIZE.h"
29    #include "RBCS_PARAMS.h"
30    #include "RBCS_FIELDS.h"
31    
32  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
33  C  myThid               :: thread number  C  bi,bj          :: tile indices
34  C  myIter               :: current timestep  C  k              :: vertical level index
35  C  myTime               :: current time  C  tracerNum      :: tracer number (1=Temp, 2=Salt, >2 : ptracer)
36  C  iTracer              :: ptracer number  C  myTime         :: current time
37  C  bi,bj                :: tile indices  C  myIter         :: current timestep
38  C  k                    :: vertical level  C  myThid         :: my Thread Id number
39        INTEGER myThid, myIter        INTEGER bi, bj, k
40          INTEGER tracerNum
41        _RL myTime        _RL myTime
42        INTEGER bi,bj,k  c     INTEGER myIter
43        INTEGER tracernum        INTEGER myThid
44    
45  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
46  C  i,j                  :: loop indices  C  i,j            :: loop indices
47        INTEGER i,j        INTEGER i,j
48    #ifdef ALLOW_PTRACERS
49        INTEGER iTracer        INTEGER iTracer
50        INTEGER irbc        INTEGER irbc
51    #endif
52  CEOP  CEOP
53    
54  #ifdef ALLOW_RBCS  #ifdef ALLOW_RBCS
55    
56        if (tracernum.eq.1) then  #ifndef DISABLE_RBCS_MOM
57         if (useRBCtemp) then        IF ( tracerNum.EQ.-1 .AND. useRBCuVel ) THEN
58          DO j=1,sNy          DO j=0,sNy+1
59          DO i=1,sNx           DO i=0,sNx+1
60           gT(I,J,K,bi,bj) = gT(I,J,K,bi,bj)            gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)
61       &       - maskC(I,J,K,bi,bj)*       &       - RBC_maskU(i,j,k,bi,bj)/tauRelaxU
62       &      RBC_mask(I,J,K,bi,bj,1)/tauRelaxT*       &        *( uVel(i,j,k,bi,bj)- RBCuVel(i,j,k,bi,bj) )
63       &      (theta(I,J,K,bi,bj)-  c    &        *maskW(i,j,k,bi,bj)
64       &             RBCtemp(I,J,K,bi,bj))           ENDDO
65          ENDDO          ENDDO
66          ENDIF
67          IF ( tracerNum.EQ.-2 .AND. useRBCvVel ) THEN
68            DO j=0,sNy+1
69             DO i=0,sNx+1
70              gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)
71         &       - RBC_maskV(i,j,k,bi,bj)/tauRelaxV
72         &        *( vVel(i,j,k,bi,bj)- RBCvVel(i,j,k,bi,bj) )
73    c    &        *maskS(i,j,k,bi,bj)
74             ENDDO
75          ENDDO          ENDDO
76         endif        ENDIF
77        endif  #endif /* DISABLE_RBCS_MOM */
78    
79        if (tracernum.eq.2) then        IF ( tracerNum.EQ.1 .AND. useRBCtemp ) THEN
        if (useRBCsalt) then  
80          DO j=1,sNy          DO j=1,sNy
81          DO i=1,sNx           DO i=1,sNx
82           gS(I,J,K,bi,bj) = gS(I,J,K,bi,bj)            gT(i,j,k,bi,bj) = gT(i,j,k,bi,bj)
83       &       - maskC(I,J,K,bi,bj)*       &       - RBC_mask(i,j,k,bi,bj,1)/tauRelaxT
84       &      RBC_mask(I,J,K,bi,bj,2)/tauRelaxS*       &        *( theta(i,j,k,bi,bj)- RBCtemp(i,j,k,bi,bj) )
85       &      (salt(I,J,K,bi,bj)-  c    &        *maskC(i,j,k,bi,bj)
86       &             RBCsalt(I,J,K,bi,bj))           ENDDO
87          ENDDO          ENDDO
88          ENDIF
89    
90          IF ( tracerNum.EQ.2 .AND. useRBCsalt ) THEN
91            DO j=1,sNy
92             DO i=1,sNx
93              gS(i,j,k,bi,bj) = gS(i,j,k,bi,bj)
94         &       - RBC_mask(i,j,k,bi,bj,2)/tauRelaxS
95         &        *( salt(i,j,k,bi,bj)- RBCsalt(i,j,k,bi,bj) )
96    c    &        *maskC(i,j,k,bi,bj)
97             ENDDO
98          ENDDO          ENDDO
99         endif        ENDIF
       endif  
100    
101  #ifdef ALLOW_PTRACERS  #ifdef ALLOW_PTRACERS
102        if (tracernum.gt.2) then        IF ( usePTRACERS .AND. tracerNum.GT.2 ) THEN
103         iTracer=tracernum-2         iTracer = tracerNum-2
104         irbc=max(maskLEN,tracernum)         irbc = MIN(maskLEN,tracerNum)
105         if (useRBCptracers) then         IF ( useRBCptrnum(iTracer) ) THEN
106          if (useRBCptrnum(iTracer)) then          DO j=1,sNy
          DO j=1,sNy  
107           DO i=1,sNx           DO i=1,sNx
108             gPtr(I,J,K,bi,bj,iTracer) = gPtr(I,J,K,bi,bj,iTracer)            gPtr(i,j,k,bi,bj,iTracer) = gPtr(i,j,k,bi,bj,iTracer)
109       &       - maskC(I,J,K,bi,bj)*       &       - RBC_mask(i,j,k,bi,bj,irbc)/tauRelaxPTR(iTracer)
110       &      RBC_mask(I,J,K,bi,bj,irbc)/tauRelaxPTR(iTracer)*       &        *( pTracer(i,j,k,bi,bj,iTracer)
111       &      (pTracer(I,J,K,bi,bj,iTracer)-       &           - RBC_ptracers(i,j,k,bi,bj,iTracer) )
112       &             RBC_ptracers(I,J,K,bi,bj,iTracer))  c    &        *maskC(i,j,k,bi,bj)
          ENDDO  
113           ENDDO           ENDDO
114          endif          ENDDO
115         endif         ENDIF
116        endif        ENDIF
117  #endif  #endif /* ALLOW_PTRACERS */
118    
119  #endif /* ALLOW_RBCS */  #endif /* ALLOW_RBCS */
120    

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.6

  ViewVC Help
Powered by ViewVC 1.1.22