/[MITgcm]/MITgcm_contrib/rpa_layers/layers/layers_calc.F
ViewVC logotype

Contents of /MITgcm_contrib/rpa_layers/layers/layers_calc.F

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


Revision 1.1 - (show annotations) (download)
Tue Sep 15 19:16:53 2009 UTC (14 years, 9 months ago) by rpa
Branch: MAIN
importing layers package

1 #include "LAYERS_OPTIONS.h"
2
3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
4
5 SUBROUTINE LAYERS_CALC(
6 I myTime, myIter, myThid )
7
8 C ===================================================================
9 C Calculate the transport in isopycnal layers.
10 C This is the meat of the LAYERS package.
11 C ===================================================================
12
13 IMPLICIT NONE
14 #include "SIZE.h"
15 #include "GRID.h"
16 #include "DYNVARS.h"
17 #include "EEPARAMS.h"
18 #include "PARAMS.h"
19 #include "LAYERS_SIZE.h"
20 #include "LAYERS.h"
21
22 C INPUT PARAMETERS:
23 C bi, bj - array indices on which to apply calculations
24 C myTime - Current time in simulati
25 C myThid :: my Thread Id number
26 INTEGER bi, bj, myTime, myIter, myThid
27
28 #ifdef ALLOW_LAYERS
29
30 C === Local variables ===
31 C i,j :: horizontal indices
32 C k :: vertical index for model grid
33 C kci :: index from CellIndex
34 C kg :: index for looping though layers_G
35 C kk :: vertical index for ZZ (fine) grid
36 C kgu,kgv :: vertical index for isopycnal grid
37 C TatV :: temperature at U point
38 C TatV :: temperature at V point
39
40 INTEGER i,j,k,kk,kg,kci
41 INTEGER kgu(sNx+1,sNy+1), kgv(sNx+1,sNy+1)
42 _RL TatU, TatV
43 CHARACTER*(MAX_LEN_MBUF) msgBuf
44
45 C --- The thread loop
46 DO bj=myByLo(myThid),myByHi(myThid)
47 DO bi=myBxLo(myThid),myBxHi(myThid)
48
49 C Initialize the serach indices
50 DO j = 1,sNy+1
51 DO i = 1,sNx+1
52 C The temperature index (layer_G) goes from cold to warm.
53 C The water column goes from warm (k=1) to cold (k=Nr).
54 C So initialize the search with the warmest value.
55 kgu(i,j) = Nlayers
56 kgv(i,j) = Nlayers
57 ENDDO
58 ENDDO
59
60 C Reset the arrays
61 DO kg=1,Nlayers
62 DO j = 1,sNy+1
63 DO i = 1,sNx+1
64 #ifdef LAYERS_UFLUX
65 layers_UFlux(i,j,kg,bi,bj) = 0. _d 0
66 #ifdef LAYERS_THICKNESS
67 layers_HU(i,j,kg,bi,bj) = 0. _d 0
68 #endif /* LAYERS_THICKNESS */
69 #endif /* LAYERS_UFLUX */
70 #ifdef LAYERS_VFLUX
71 layers_VFlux(i,j,kg,bi,bj) = 0. _d 0
72 #ifdef LAYERS_THICKNESS
73 layers_HV(i,j,kg,bi,bj) = 0. _d 0
74 #endif /* LAYERS_THICKNESS */
75 #endif /* LAYERS_VFLUX */
76 ENDDO
77 ENDDO
78 ENDDO
79
80 C _RL theta(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
81 C Sometimes it is done this way
82 C DO j=1-Oly+1,sNy+Oly-1
83 C DO i=1-Olx+1,sNx+Olx-1
84 DO kk=1,NZZ
85 k = MapIndex(kk)
86 kci = CellIndex(kk)
87 DO j = 1,sNy+1
88 DO i = 1,sNx+1
89
90 #ifdef LAYERS_UFLUX
91 C ------ Find theta at the U point (west) on the fine Z grid
92 TatU = MapFact(kk) *
93 & 0.5 _d 0 * (theta(i-1,j,k,bi,bj)+theta(i,j,k,bi,bj)) +
94 & (1-MapFact(kk)) *
95 & 0.5 _d 0 * (theta(i-1,j,k+1,bi,bj)+theta(i,j,k+1,bi,bj))
96
97 C ------ Now that we know T everywhere, determine the binning.
98
99 IF (TatU .GE. layers_G(Nlayers)) THEN
100 C the point is in the hottest bin or hotter
101 kgu(i,j) = Nlayers
102 ELSE IF (TatU .LT. layers_G(2)) THEN
103 C the point is in the coldest bin or colder
104 kgu(i,j) = 1
105 ELSE IF ( (TatU .GE. layers_G(kgu(i,j)))
106 & .AND. (TatU .LT. layers_G(kgu(i,j)+1)) ) THEN
107 C already on the right bin -- do nothing
108 ELSE IF (TatU .GE. layers_G(kgu(i,j))) THEN
109 C have to hunt for the right bin by getting hotter
110 DO WHILE (TatU .GE. layers_G(kgu(i,j)+1))
111 kgu(i,j) = kgu(i,j) + 1
112 ENDDO
113 C now layers_G(kgu(i,j)+1) < TatU <= layers_G(kgu(i,j)+1)
114 ELSE IF (TatU .LT. layers_G(kgu(i,j)+1)) THEN
115 C have to hunt for the right bin by getting colder
116 DO WHILE (TatU .LT. layers_G(kgu(i,j)))
117 kgu(i,j) = kgu(i,j) - 1
118 ENDDO
119 C now layers_G(kgu(i,j)+1) <= TatU < layers_G(kgu(i,j)+1)
120 ELSE
121 C that should have covered all the options
122 WRITE(msgBuf,'(A,1E14.6)')
123 & 'S/R LAYERS_CALC: Couldnt find a bin in layers_G for TatU=',
124 & TatU
125 CALL PRINT_ERROR( msgBuf, myThid )
126 STOP 'ABNORMAL END: S/R LAYERS_INIT_FIXED'
127 END IF
128
129 C ------ Augment the bin values
130 layers_UFlux(i,j,kgu(i,j),bi,bj) =
131 & layers_UFlux(i,j,kgu(i,j),bi,bj) +
132 & dZZ * uVel(i,j,kci,bi,bj) * hFacW(i,j,kci,bi,bj)
133
134 #ifdef LAYERS_THICKNESS
135 layers_HU(i,j,kgu(i,j),bi,bj) = layers_HU(i,j,kgu(i,j),bi,bj)
136 & + dZZ * hFacW(i,j,kci,bi,bj)
137 #endif /* LAYERS_THICKNESS */
138
139 #endif /* LAYERS_UFLUX */
140
141 #ifdef LAYERS_VFLUX
142 C ------ Find theta at the V point (south) on the fine Z grid
143 TatV = MapFact(kk) *
144 & 0.5 _d 0 * (theta(i,j-1,k,bi,bj)+theta(i,j,k,bi,bj)) +
145 & (1-MapFact(kk)) *
146 & 0.5 _d 0 * (theta(i,j-1,k+1,bi,bj)+theta(i,j,k+1,bi,bj))
147
148 C ------ Now that we know T everywhere, determine the binning
149 IF (TatV .GE. layers_G(Nlayers)) THEN
150 C the point is in the hottest bin or hotter
151 kgv(i,j) = Nlayers
152 ELSE IF (TatV .LT. layers_G(2)) THEN
153 C the point is in the coldest bin or colder
154 kgv(i,j) = 1
155 ELSE IF ( (TatV .GE. layers_G(kgv(i,j)))
156 & .AND. (TatV .LT. layers_G(kgv(i,j)+1)) ) THEN
157 C already on the right bin -- do nothing
158 ELSE IF (TatV .GE. layers_G(kgv(i,j))) THEN
159 C have to hunt for the right bin by getting hotter
160 DO WHILE (TatV .GE. layers_G(kgv(i,j)+1))
161 kgv(i,j) = kgv(i,j) + 1
162 ENDDO
163 C now layers_G(kgv(i,j)+1) < TatV <= layers_G(kgv(i,j)+1)
164 ELSE IF (TatV .LT. layers_G(kgv(i,j)+1)) THEN
165 C have to hunt for the right bin by getting colder
166 DO WHILE (TatV .LT. layers_G(kgv(i,j)))
167 kgv(i,j) = kgv(i,j) - 1
168 ENDDO
169 C now layers_G(kgv(i,j)+1) <= TatV < layers_G(kgv(i,j)+1)
170 ELSE
171 C that should have covered all the options
172 WRITE(msgBuf,'(A,1E14.6)')
173 & 'S/R LAYERS_CALC: Couldnt find a bin in layers_G for TatV=',
174 & TatV
175 CALL PRINT_ERROR( msgBuf, myThid )
176 STOP 'ABNORMAL END: S/R LAYERS_INIT_FIXED'
177 END IF
178
179 C ------ Augment the bin values
180 layers_VFlux(i,j,kgv(i,j),bi,bj) =
181 & layers_VFlux(i,j,kgv(i,j),bi,bj)
182 & + dZZ * vVel(i,j,kci,bi,bj) * hFacS(i,j,kci,bi,bj)
183
184 #ifdef LAYERS_THICKNESS
185 layers_HV(i,j,kgv(i,j),bi,bj) = layers_HV(i,j,kgv(i,j),bi,bj)
186 & + dZZ * hFacS(i,j,kci,bi,bj)
187 #endif /* LAYERS_THICKNESS */
188
189 #endif /* LAYERS_VFLUX */
190
191 C k loop
192 ENDDO
193
194 ENDDO
195 ENDDO
196
197 #ifdef ALLOW_TIMEAVE
198 C-- Time-average
199 IF ( taveFreq.GT.0. ) THEN
200
201 #ifdef LAYERS_UFLUX
202 CALL TIMEAVE_CUMULATE( layers_UFlux_T, layers_UFlux, Nlayers,
203 & deltaTclock, bi, bj, myThid )
204 #ifdef LAYERS_THICKNESS
205 CALL TIMEAVE_CUMULATE( layers_HU_T, layers_HU, Nlayers,
206 & deltaTclock, bi, bj, myThid )
207 #endif /* LAYERS_THICKNESS */
208 #endif /* LAYERS_UFLUX */
209 #ifdef LAYERS_VFLUX
210 CALL TIMEAVE_CUMULATE( layers_VFlux_T, layers_VFlux, Nlayers,
211 & deltaTclock, bi, bj, myThid )
212 #ifdef LAYERS_THICKNESS
213 CALL TIMEAVE_CUMULATE( layers_HV_T, layers_HV, Nlayers,
214 & deltaTclock, bi, bj, myThid )
215 #endif /* LAYERS_THICKNESS */
216 #endif /* LAYERS_VFLUX */
217
218 DO kg=1,Nlayers
219 layers_TimeAve(kg,bi,bj)=layers_TimeAve(kg,bi,bj)+deltaTclock
220 ENDDO
221
222 ENDIF
223 #endif /* ALLOW_TIMEAVE */
224
225 C --- End bi,bj loop
226 ENDDO
227 ENDDO
228
229 #endif /* ALLOW_LAYERS */
230
231 RETURN
232 END

  ViewVC Help
Powered by ViewVC 1.1.22