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

Annotation of /MITgcm/model/src/tracers_correction_step.F

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


Revision 1.9 - (hide annotations) (download)
Sun Nov 6 22:01:37 2005 UTC (18 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57y_post, checkpoint57y_pre, checkpoint58, checkpoint57x_post, checkpoint58a_post, checkpoint57z_post
Changes since 1.8: +6 -3 lines
add #ifdef ALLOW_GENERIC_ADVDIFF / #endif (as in thermodynamics.F)

1 jmc 1.9 C $Header: /u/gcmpack/MITgcm/model/src/tracers_correction_step.F,v 1.8 2005/10/13 19:43:06 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: TRACERS_CORRECTION_STEP
9     C !INTERFACE:
10     SUBROUTINE TRACERS_CORRECTION_STEP(myTime, myIter, myThid)
11     C !DESCRIPTION: \bv
12     C *==========================================================*
13 jmc 1.8 C | SUBROUTINE TRACERS_CORRECTION_STEP
14 jmc 1.1 C *==========================================================*
15     C |1rst Part : Update T,S.
16     C |
17     C | The arrays used for time stepping are cycled.
18     C | Tracers:
19     C | T(n) = Gt(n)
20     C |
21     C |part1: update T,S
22     C | T* (contained in gT) is copied to T (theta)
23     C | S* (contained in gS) is copied to S (salt)
24     C |
25 jmc 1.8 C |part2: Adjustments & Diagnostics
26 jmc 1.1 C | o Filter T,S (Shapiro Filter, Zonal_Filter)
27     C | o Convective Adjustment
28     C | o Diagmnostic of state variables (Time average)
29     C *==========================================================*
30     C \ev
31    
32     C !USES:
33     IMPLICIT NONE
34     C == Global variables ===
35     #include "SIZE.h"
36     #include "EEPARAMS.h"
37     #include "PARAMS.h"
38     #include "DYNVARS.h"
39    
40     C !INPUT/OUTPUT PARAMETERS:
41     C == Routine arguments ==
42     C myTime - Current time in simulation
43     C myIter - Current iteration number in simulation
44     C myThid - Thread number for this instance of the routine.
45     _RL myTime
46     INTEGER myIter
47     INTEGER myThid
48    
49 jmc 1.9 #ifdef ALLOW_GENERIC_ADVDIFF
50 jmc 1.1 C !LOCAL VARIABLES:
51     C == Local variables
52     INTEGER iMin,iMax
53     INTEGER jMin,jMax
54     INTEGER bi,bj
55 jmc 1.9 INTEGER k
56 jmc 1.1
57     CEOP
58    
59     DO bj=myByLo(myThid),myByHi(myThid)
60     DO bi=myBxLo(myThid),myBxHi(myThid)
61    
62     C-- Loop over all layers, top to bottom
63     DO K=1,Nr
64    
65 jmc 1.6 C- Update tracer fields: T(n) = T**
66 stephd 1.3 #ifndef ALLOW_OFFLINE
67 jmc 1.1 IF (tempStepping)
68     & CALL CYCLE_TRACER(
69 jmc 1.6 I bi,bj,K,
70     U theta,gT,
71     I myTime,myIter,myThid )
72 jmc 1.1 IF (saltStepping)
73     & CALL CYCLE_TRACER(
74 jmc 1.6 I bi,bj,k,
75     U salt,gS,
76     I myTime,myIter,myThid )
77 stephd 1.3 #endif
78 jmc 1.1 #ifdef ALLOW_PTRACERS
79 jmc 1.6 C- Update passive tracer fields: T(n) = T**
80 jmc 1.1 IF (usePTRACERS)
81     & CALL PTRACERS_CYCLE(bi,bj,k,myIter,myTime,myThid)
82     #endif /* ALLOW_PTRACERS */
83    
84     C-- End DO K=1,Nr
85     ENDDO
86    
87     C-- End of 1rst bi,bj loop
88     ENDDO
89     ENDDO
90    
91     C--- 2nd Part : Adjustment.
92     C
93     C Static stability is calculated and the tracers are
94     C convective adjusted where statically unstable.
95    
96     C-- Filter (and exchange)
97     #ifdef ALLOW_SHAP_FILT
98     IF (useSHAP_FILT) THEN
99 jmc 1.8 CALL TIMER_START('SHAP_FILT_TS [TRC_CORR_STEP]',myThid)
100 jmc 1.1 CALL SHAP_FILT_APPLY_TS( theta,salt, myTime, myIter, myThid )
101 jmc 1.8 CALL TIMER_STOP ('SHAP_FILT_TS [TRC_CORR_STEP]',myThid)
102 jmc 1.1 ENDIF
103 jmc 1.8 #endif
104 jmc 1.1 #ifdef ALLOW_ZONAL_FILT
105     IF (useZONAL_FILT) THEN
106 jmc 1.8 CALL TIMER_START('ZONAL_FILT_TS [TRC_CORR_STEP]',myThid)
107     CALL ZONAL_FILT_APPLY_TS( theta, salt, myThid )
108     CALL TIMER_STOP ('ZONAL_FILT_TS [TRC_CORR_STEP]',myThid)
109 jmc 1.1 ENDIF
110 jmc 1.8 #endif
111 jmc 1.1
112 stephd 1.3 #ifndef ALLOW_OFFLINE
113 jmc 1.1 DO bj=myByLo(myThid),myByHi(myThid)
114     DO bi=myBxLo(myThid),myBxHi(myThid)
115    
116     C-- Convectively adjust new fields to be statically stable
117     iMin = 1
118     iMax = sNx
119     jMin = 1
120     jMax = sNy
121 mlosch 1.4 #ifdef ALLOW_OPPS
122     IF ( useOPPS ) THEN
123     CALL OPPS_INTERFACE(
124     I bi, bj, iMin, iMax, jMin, jMax,
125     I myTime, myIter, myThid )
126     ELSE
127     #endif /* ALLOW_OPPS */
128     CALL CONVECTIVE_ADJUSTMENT(
129     I bi, bj, iMin, iMax, jMin, jMax,
130     I myTime, myIter, myThid )
131     #ifdef ALLOW_OPPS
132     ENDIF
133     #endif /* ALLOW_OPPS */
134 jmc 1.1
135 spk 1.7 #ifdef ALLOW_MATRIX
136     IF (useMATRIX)
137     & CALL MATRIX_STORE_TENDENCY_IMP( bi, bj, myTime, myIter, myThid )
138     #endif
139    
140 jmc 1.1 C-- End of 2nd bi,bj loop
141     ENDDO
142     ENDDO
143 jmc 1.9 #endif /* ALLOW_OFFLINE */
144    
145     #endif /* ALLOW_GENERIC_ADVDIFF */
146 jmc 1.1
147     RETURN
148     END

  ViewVC Help
Powered by ViewVC 1.1.22