/[MITgcm]/MITgcm/pkg/fizhi/fizhi_init_vars.F
ViewVC logotype

Contents of /MITgcm/pkg/fizhi/fizhi_init_vars.F

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


Revision 1.23 - (show annotations) (download)
Tue Mar 27 15:48:27 2012 UTC (12 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint64, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.22: +34 -28 lines
clean-up turbulence cold-start switch: decided in fizhi_init_vars.F, stored
in common bloc (fizhi_coms.h) and then passed as argument up to S/R TURBIO.

1 C $Header: /u/gcmpack/MITgcm/pkg/fizhi/fizhi_init_vars.F,v 1.22 2009/05/12 19:56:35 jmc Exp $
2 C $Name: $
3
4 #include "FIZHI_OPTIONS.h"
5 SUBROUTINE FIZHI_INIT_VARS (myThid)
6 c-----------------------------------------------------------------------
7 c Routine to initialise the fizhi state.
8 c
9 c Input: myThid - Process number calling this routine
10 c
11 c Notes:
12 c 1) For a Cold Start -
13 c This routine takes the initial condition on the dynamics grid
14 c and interpolates to the physics grid to initialize the state
15 c variables that are on both grids. It initializes the variables
16 c of the turbulence scheme to 0., and the land state from a model
17 c climatology.
18 c 2) For a Restart, read the fizhi pickup file
19 c 3) The velocity component physics fields are on an A-Grid
20 c
21 c Calls: dyn2phys (x4)
22 c-----------------------------------------------------------------------
23 IMPLICIT NONE
24 #include "SIZE.h"
25 #include "fizhi_SIZE.h"
26 #include "fizhi_land_SIZE.h"
27 #include "GRID.h"
28 #include "DYNVARS.h"
29 #include "gridalt_mapping.h"
30 #include "fizhi_coms.h"
31 #include "fizhi_land_coms.h"
32 #include "fizhi_earth_coms.h"
33 #include "EEPARAMS.h"
34 #include "SURFACE.h"
35 #include "PARAMS.h"
36 #include "chronos.h"
37 #ifdef ALLOW_EXCH2
38 #include "W2_EXCH2_SIZE.h"
39 #include "W2_EXCH2_TOPOLOGY.h"
40 #endif /* ALLOW_EXCH2 */
41
42 INTEGER myThid
43
44 INTEGER xySize
45 #if defined(ALLOW_EXCH2)
46 PARAMETER ( xySize = W2_ioBufferSize )
47 #else
48 PARAMETER ( xySize = Nx*Ny )
49 #endif
50 Real*8 globalArr( xySize*8 )
51
52 c pe on dynamics and physics grid refers to bottom edge
53 _RL pephy(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nrphys+1,nSx,nSy)
54 _RL pedyn(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr+1,nSx,nSy)
55 _RL windphy(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nrphys,nSx,nSy)
56 _RL udyntemp(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
57 _RL vdyntemp(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
58 _RL tempphy(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nrphys,nSx,nSy)
59
60 INTEGER i, j, L, bi, bj, Lbotij
61 INTEGER im1, im2, jm1, jm2, idim1, idim2, jdim1, jdim2
62 INTEGER xsize, ysize
63 LOGICAL alarm
64 EXTERNAL alarm
65
66 #if defined(ALLOW_EXCH2)
67 xsize = exch2_global_Nx
68 ysize = exch2_global_Ny
69 #else
70 xsize = Nx
71 ysize = Ny
72 #endif
73 im1 = 1-OLx
74 im2 = sNx+OLx
75 jm1 = 1-OLy
76 jm2 = sNy+OLy
77 idim1 = 1
78 idim2 = sNx
79 jdim1 = 1
80 jdim2 = sNy
81
82 c First Check to see if we can start a fizhi experiment at current time
83 c All Fizhi alarms must be on for the first time step of a segment
84
85 if( .not.alarm('moist') .or. .not.alarm('turb') .or.
86 & .not.alarm('radsw') .or. .not.alarm('radlw') ) then
87 write(15,*) ' Cant Start Fizhi experiment at ',nymd,' ',nhms
88 stop
89 endif
90
91 C Deal Here with Variables that are on a Fizhi Pickup or need Initialization
92
93 IF ( startTime.EQ.baseTime .AND. nIter0.EQ.0 ) THEN
94 print *,' In fizhi_init_vars: Beginning of New Experiment '
95
96 do bj = myByLo(myThid), myByHi(myThid)
97 do bi = myBxLo(myThid), myBxHi(myThid)
98
99 C Build pressures on dynamics grid
100 do j = 1,sNy
101 do i = 1,sNx
102 do L = 1,Nr
103 pedyn(i,j,L,bi,bj) = 0.
104 enddo
105 enddo
106 enddo
107 do j = 1,sNy
108 do i = 1,sNx
109 Lbotij = kSurfC(i,j,bi,bj)
110 if(Lbotij.ne.0.)
111 & pedyn(i,j,Lbotij,bi,bj) = Ro_surf(i,j,bi,bj) + etaH(i,j,bi,bj)
112 enddo
113 enddo
114 do j = 1,sNy
115 do i = 1,sNx
116 Lbotij = kSurfC(i,j,bi,bj)
117 do L = Lbotij+1,Nr+1
118 pedyn(i,j,L,bi,bj) = pedyn(i,j,L-1,bi,bj) -
119 & drF(L-1)*hfacC(i,j,L-1,bi,bj)
120 enddo
121 c Do not use a zero field as the top edge pressure for interpolation
122 if(pedyn(i,j,Nr+1,bi,bj).lt.1.e-5)
123 & pedyn(i,j,Nr+1,bi,bj) = 1.e-5
124 enddo
125 enddo
126 C Build pressures on physics grid
127 do j = 1,sNy
128 do i = 1,sNx
129 pephy(i,j,1,bi,bj)=Ro_surf(i,j,bi,bj) + etaH(i,j,bi,bj)
130 do L = 2,Nrphys+1
131 pephy(i,j,L,bi,bj)=pephy(i,j,L-1,bi,bj)-dpphys0(i,j,L-1,bi,bj)
132 enddo
133 c Do not use a zero field as the top edge pressure for interpolation
134 if(pephy(i,j,Nrphys+1,bi,bj).lt.1.e-5)
135 & pephy(i,j,Nrphys+1,bi,bj) = 1.e-5
136 enddo
137 enddo
138 c
139 c Create an initial wind magnitude field on the physics grid -
140 c Use a log wind law with z0=1cm, u*=1 cm/sec,
141 c do units and get u = .025*ln(dP*10), with dP in pa.
142 do L = 1,Nrphys
143 do j = 1,sNy
144 do i = 1,sNx
145 windphy(i,j,L,bi,bj) = 0.025 *
146 & log((pephy(i,j,1,bi,bj)-pephy(i,j,L+1,bi,bj))*10.)
147 enddo
148 enddo
149 enddo
150
151 enddo
152 enddo
153
154 c Create initial fields on phys. grid - Move Dynamics u and v to A-Grid
155 call CtoA(myThid,uvel,vvel,maskW,maskS,im1,im2,jm1,jm2,Nr,
156 & nSx,nSy,1,sNx,1,sNy,udyntemp,vdyntemp)
157
158 do bj = myByLo(myThid), myByHi(myThid)
159 do bi = myBxLo(myThid), myBxHi(myThid)
160
161 c Create initial fields on phys. grid - interpolate from dyn. grid
162 call dyn2phys(udyntemp,pedyn,im1,im2,jm1,jm2,Nr,nSx,nSy,
163 & 1,sNx,1,sNy,bi,bj,windphy,pephy,kSurfC,Nrphys,nlperdyn,1,tempphy)
164 c Note: Interpolation gives bottom-up arrays (level 1 is bottom),
165 c Physics works top-down. so -> need to flip arrays
166 do L = 1,Nrphys
167 do j = 1,sNy
168 do i = 1,sNx
169 uphy(i,j,Nrphys+1-L,bi,bj) = tempphy(i,j,L,bi,bj)
170 enddo
171 enddo
172 enddo
173 call dyn2phys(vdyntemp,pedyn,im1,im2,jm1,jm2,Nr,nSx,nSy,
174 & 1,sNx,1,sNy,bi,bj,windphy,pephy,kSurfC,Nrphys,nlperdyn,1,tempphy)
175 do L = 1,Nrphys
176 do j = 1,sNy
177 do i = 1,sNx
178 vphy(i,j,Nrphys+1-L,bi,bj) = tempphy(i,j,L,bi,bj)
179 enddo
180 enddo
181 enddo
182 call dyn2phys(theta,pedyn,im1,im2,jm1,jm2,Nr,nSx,nSy,
183 & 1,sNx,1,sNy,bi,bj,windphy,pephy,kSurfC,Nrphys,nlperdyn,2,tempphy)
184 do L = 1,Nrphys
185 do j = 1,sNy
186 do i = 1,sNx
187 thphy(i,j,Nrphys+1-L,bi,bj) = tempphy(i,j,L,bi,bj)
188 enddo
189 enddo
190 enddo
191 call dyn2phys(salt,pedyn,im1,im2,jm1,jm2,Nr,nSx,nSy,
192 & 1,sNx,1,sNy,bi,bj,windphy,pephy,kSurfC,Nrphys,nlperdyn,0,tempphy)
193 do L = 1,Nrphys
194 do j = 1,sNy
195 do i = 1,sNx
196 sphy(i,j,Nrphys+1-L,bi,bj) = tempphy(i,j,L,bi,bj)
197 enddo
198 enddo
199 enddo
200
201 c Zero out fizhi tendency arrays on the fizhi grid
202 do L = 1,Nrphys
203 do j = 1,sNy
204 do i = 1,sNx
205 duphy(i,j,L,bi,bj) = 0.
206 dvphy(i,j,L,bi,bj) = 0.
207 dthphy(i,j,L,bi,bj) = 0.
208 dsphy(i,j,L,bi,bj) = 0.
209 enddo
210 enddo
211 enddo
212
213 c Zero out fizhi tendency arrays on the dynamics grid
214 do L = 1,Nr
215 do j = jm1,jm2
216 do i = im1,im2
217 guphy(i,j,L,bi,bj) = 0.
218 gvphy(i,j,L,bi,bj) = 0.
219 gthphy(i,j,L,bi,bj) = 0.
220 gsphy(i,j,L,bi,bj) = 0.
221 enddo
222 enddo
223 enddo
224
225 c Initialize vegetation tile tke, xlmt, khmt, xxmt, yymt, ctmt, zetamt,
226 if( (nhms.eq.nhms0) .and. (nymd.eq.nymd0) ) then
227 print *,' Cold Start: Zero out Turb second moments '
228 do i = 1,nchp
229 ctmt(i,bi,bj) = 0.
230 xxmt(i,bi,bj) = 0.
231 yymt(i,bi,bj) = 0.
232 zetamt(i,bi,bj) = 0.
233 enddo
234 do L = 1,Nrphys
235 do i = 1,nchp
236 tke(i,L,bi,bj) = 0.
237 xlmt(i,L,bi,bj) = 0.
238 khmt(i,L,bi,bj) = 0.
239 enddo
240 enddo
241 else
242 print *,' Need initial Values for TKE - dont have them! '
243 stop
244 endif
245 turbStart(bi,bj) = .TRUE.
246
247 c Now initialize vegetation tile land state too - tcanopy, etc...
248 call fizhi_init_vegsurftiles( globalArr, xsize, ysize,
249 & nymd,nhms, 'D', myThid )
250
251 c Now initialize fizhi arrays that will be on a pickup
252 print *,' Initialize fizhi arrays that will be on pickup '
253 imstturblw(bi,bj) = 0
254 imstturbsw(bi,bj) = 0
255 iras(bi,bj) = 0
256 nlwcld(bi,bj) = 0
257 nlwlz(bi,bj) = 0
258 nswcld(bi,bj) = 0
259 nswlz(bi,bj) = 0
260 do L = 1,Nrphys
261 do j = 1,sNy
262 do i = 1,sNx
263 swlz(i,j,L,bi,bj) = 0.
264 lwlz(i,j,L,bi,bj) = 0.
265 qliqavesw(i,j,L,bi,bj) = 0.
266 qliqavelw(i,j,L,bi,bj) = 0.
267 fccavesw(i,j,L,bi,bj) = 0.
268 fccavelw(i,j,L,bi,bj) = 0.
269 cldtot_sw(i,j,L,bi,bj) = 0.
270 cldras_sw(i,j,L,bi,bj) = 0.
271 cldlsp_sw(i,j,L,bi,bj) = 0.
272 cldtot_lw(i,j,L,bi,bj) = 0.
273 cldras_lw(i,j,L,bi,bj) = 0.
274 cldlsp_lw(i,j,L,bi,bj) = 0.
275 enddo
276 enddo
277 enddo
278 do j = 1,sNy
279 do i = 1,sNx
280 rainlsp(i,j,bi,bj) = 0.
281 raincon(i,j,bi,bj) = 0.
282 snowfall(i,j,bi,bj) = 0.
283 enddo
284 enddo
285
286 enddo
287 enddo
288
289 ELSE
290 print *,' In fizhi_init_vars: Read from restart '
291
292 C-- Read fizhi package state variables from pickup file
293
294 call fizhi_read_pickup( nIter0, myThid )
295 CALL FIZHI_READ_VEGTILES( nIter0, 'D', myThid )
296 do bj = myByLo(myThid), myByHi(myThid)
297 do bi = myBxLo(myThid), myBxHi(myThid)
298 turbStart(bi,bj) = .FALSE.
299 enddo
300 enddo
301
302 ENDIF
303
304 RETURN
305 END

  ViewVC Help
Powered by ViewVC 1.1.22