/[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.4 by jmc, Mon Nov 5 19:08:51 2007 UTC revision 1.5 by jmc, Tue Apr 6 20:38:18 2010 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  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 28  C !USES: =============================== Line 28  C !USES: ===============================
28  #include "RBCS.h"  #include "RBCS.h"
29    
30  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
31  C  myThid               :: thread number  C  bi,bj          :: tile indices
32  C  myIter               :: current timestep  C  k              :: vertical level index
33  C  myTime               :: current time  C  tracerNum      :: tracer number (1=Temp, 2=Salt, >2 : ptracer)
34  C  iTracer              :: ptracer number  C  myTime         :: current time
35  C  bi,bj                :: tile indices  C  myIter         :: current timestep
36  C  k                    :: vertical level  C  myThid         :: my Thread Id number
37        INTEGER myThid, myIter        INTEGER bi, bj, k
38          INTEGER tracerNum
39        _RL myTime        _RL myTime
40        INTEGER bi,bj,k  c     INTEGER myIter
41        INTEGER tracernum        INTEGER myThid
42    
43  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
44  C  i,j                  :: loop indices  C  i,j            :: loop indices
45        INTEGER i,j        INTEGER i,j
46    #ifdef ALLOW_PTRACERS
47        INTEGER iTracer        INTEGER iTracer
48        INTEGER irbc        INTEGER irbc
49    #endif
50  CEOP  CEOP
51    
52  #ifdef ALLOW_RBCS  #ifdef ALLOW_RBCS
53    
54        if (tracernum.eq.1) then        IF ( tracerNum.EQ.1 .AND. useRBCtemp ) THEN
        if (useRBCtemp) then  
55          DO j=1,sNy          DO j=1,sNy
56          DO i=1,sNx           DO i=1,sNx
57           gT(I,J,K,bi,bj) = gT(I,J,K,bi,bj)            gT(i,j,k,bi,bj) = gT(i,j,k,bi,bj)
58       &       - maskC(I,J,K,bi,bj)*       &       - maskC(i,j,k,bi,bj)
59       &      RBC_mask(I,J,K,bi,bj,1)/tauRelaxT*       &        *RBC_mask(i,j,k,bi,bj,1)/tauRelaxT
60       &      (theta(I,J,K,bi,bj)-       &        *( theta(i,j,k,bi,bj)- RBCtemp(i,j,k,bi,bj) )
61       &             RBCtemp(I,J,K,bi,bj))           ENDDO
         ENDDO  
62          ENDDO          ENDDO
63         endif        ENDIF
       endif  
64    
65        if (tracernum.eq.2) then        IF ( tracerNum.EQ.2 .AND. useRBCsalt ) THEN
        if (useRBCsalt) then  
66          DO j=1,sNy          DO j=1,sNy
67          DO i=1,sNx           DO i=1,sNx
68           gS(I,J,K,bi,bj) = gS(I,J,K,bi,bj)            gS(i,j,k,bi,bj) = gS(i,j,k,bi,bj)
69       &       - maskC(I,J,K,bi,bj)*       &       - maskC(i,j,k,bi,bj)
70       &      RBC_mask(I,J,K,bi,bj,2)/tauRelaxS*       &        *RBC_mask(i,j,k,bi,bj,2)/tauRelaxS
71       &      (salt(I,J,K,bi,bj)-       &        *( salt(i,j,k,bi,bj)- RBCsalt(i,j,k,bi,bj) )
72       &             RBCsalt(I,J,K,bi,bj))           ENDDO
         ENDDO  
73          ENDDO          ENDDO
74         endif        ENDIF
       endif  
75    
76  #ifdef ALLOW_PTRACERS  #ifdef ALLOW_PTRACERS
77        if (tracernum.gt.2) then        IF ( usePTRACERS .AND. tracerNum.GT.2 ) THEN
78         iTracer=tracernum-2         iTracer = tracerNum-2
79         irbc=min(maskLEN,tracernum)         irbc = MIN(maskLEN,tracerNum)
80         if (useRBCptracers) then         IF ( useRBCptrnum(iTracer) ) THEN
81          if (useRBCptrnum(iTracer)) then          DO j=1,sNy
          DO j=1,sNy  
82           DO i=1,sNx           DO i=1,sNx
83             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)
84       &       - maskC(I,J,K,bi,bj)*       &       - maskC(i,j,k,bi,bj)
85       &      RBC_mask(I,J,K,bi,bj,irbc)/tauRelaxPTR(iTracer)*       &        *RBC_mask(i,j,k,bi,bj,irbc)/tauRelaxPTR(iTracer)
86       &      (pTracer(I,J,K,bi,bj,iTracer)-       &        *( pTracer(i,j,k,bi,bj,iTracer)
87       &             RBC_ptracers(I,J,K,bi,bj,iTracer))       &           - RBC_ptracers(i,j,k,bi,bj,iTracer) )
88           ENDDO           ENDDO
89           ENDDO          ENDDO
90          endif         ENDIF
91         endif        ENDIF
92        endif  #endif /* ALLOW_PTRACERS */
 #endif  
93    
94  #endif /* ALLOW_RBCS */  #endif /* ALLOW_RBCS */
95    

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.5

  ViewVC Help
Powered by ViewVC 1.1.22