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

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

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


Revision 1.4 - (hide annotations) (download)
Mon Nov 5 19:08:51 2007 UTC (16 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59k, checkpoint59j, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62d, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.3: +2 -2 lines
split PTRACERS.h in 2 header files: PTRACERS_FIELDS.h & PTRACERS_PARAMS.h

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/pkg/rbcs/rbcs_add_tendency.F,v 1.3 2007/10/09 00:09:25 jmc Exp $
2 jmc 1.3 C $Name: $
3 stephd 1.1
4     #include "CPP_OPTIONS.h"
5     #include "PACKAGES_CONFIG.h"
6    
7     CBOP
8     C !ROUTINE: RBCS_ADD_TSTENDENCY
9    
10     C !INTERFACE: ==========================================================
11     SUBROUTINE RBCS_ADD_TENDENCY(bi,bj,k, tracernum,
12     & myTime, myThid )
13    
14     C !DESCRIPTION:
15     C Will update tendencies with terms to relax to 3-D field
16    
17     C !USES: ===============================================================
18     IMPLICIT NONE
19     #include "SIZE.h"
20     #include "GRID.h"
21     #include "DYNVARS.h"
22     #include "EEPARAMS.h"
23     #include "PARAMS.h"
24     #ifdef ALLOW_PTRACERS
25     #include "PTRACERS_SIZE.h"
26 jmc 1.4 #include "PTRACERS_FIELDS.h"
27 stephd 1.1 #endif
28     #include "RBCS.h"
29    
30     C !INPUT PARAMETERS: ===================================================
31     C myThid :: thread number
32     C myIter :: current timestep
33     C myTime :: current time
34     C iTracer :: ptracer number
35     C bi,bj :: tile indices
36     C k :: vertical level
37     INTEGER myThid, myIter
38     _RL myTime
39     INTEGER bi,bj,k
40     INTEGER tracernum
41    
42     C !LOCAL VARIABLES: ====================================================
43     C i,j :: loop indices
44     INTEGER i,j
45     INTEGER iTracer
46     INTEGER irbc
47     CEOP
48    
49     #ifdef ALLOW_RBCS
50    
51     if (tracernum.eq.1) then
52     if (useRBCtemp) then
53     DO j=1,sNy
54     DO i=1,sNx
55     gT(I,J,K,bi,bj) = gT(I,J,K,bi,bj)
56     & - maskC(I,J,K,bi,bj)*
57     & RBC_mask(I,J,K,bi,bj,1)/tauRelaxT*
58     & (theta(I,J,K,bi,bj)-
59     & RBCtemp(I,J,K,bi,bj))
60     ENDDO
61     ENDDO
62     endif
63     endif
64    
65     if (tracernum.eq.2) then
66     if (useRBCsalt) then
67     DO j=1,sNy
68     DO i=1,sNx
69     gS(I,J,K,bi,bj) = gS(I,J,K,bi,bj)
70     & - maskC(I,J,K,bi,bj)*
71     & RBC_mask(I,J,K,bi,bj,2)/tauRelaxS*
72     & (salt(I,J,K,bi,bj)-
73     & RBCsalt(I,J,K,bi,bj))
74     ENDDO
75     ENDDO
76     endif
77     endif
78    
79     #ifdef ALLOW_PTRACERS
80     if (tracernum.gt.2) then
81     iTracer=tracernum-2
82 stephd 1.2 irbc=min(maskLEN,tracernum)
83 stephd 1.1 if (useRBCptracers) then
84     if (useRBCptrnum(iTracer)) then
85     DO j=1,sNy
86     DO i=1,sNx
87     gPtr(I,J,K,bi,bj,iTracer) = gPtr(I,J,K,bi,bj,iTracer)
88     & - maskC(I,J,K,bi,bj)*
89     & RBC_mask(I,J,K,bi,bj,irbc)/tauRelaxPTR(iTracer)*
90     & (pTracer(I,J,K,bi,bj,iTracer)-
91     & RBC_ptracers(I,J,K,bi,bj,iTracer))
92     ENDDO
93     ENDDO
94     endif
95     endif
96     endif
97     #endif
98    
99     #endif /* ALLOW_RBCS */
100    
101     RETURN
102     END

  ViewVC Help
Powered by ViewVC 1.1.22