/[MITgcm]/MITgcm/pkg/ctrl/ctrl_init.F
ViewVC logotype

Annotation of /MITgcm/pkg/ctrl/ctrl_init.F

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


Revision 1.39 - (hide annotations) (download)
Tue May 10 07:30:14 2011 UTC (13 years ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint62x
Changes since 1.38: +18 -1 lines
add new control variable xx_shifwflx (fresh water flux underneath ice
shelves). This is almost as tedious as obcs-ctrl, because the
variables needs its own mask.

1 edhill 1.10 C
2 mlosch 1.39 C $Header: /u/gcmpack/MITgcm/pkg/ctrl/ctrl_init.F,v 1.38 2011/04/20 19:13:40 mmazloff Exp $
3 heimbach 1.14 C $Name: $
4 heimbach 1.1
5     #include "CTRL_CPPOPTIONS.h"
6    
7 heimbach 1.5 subroutine ctrl_init( mythid )
8 heimbach 1.1
9     c ==================================================================
10 heimbach 1.5 c SUBROUTINE ctrl_init
11 heimbach 1.1 c ==================================================================
12     c
13     c o Set parts of the vector of control variables and initialize the
14     c rest to zero.
15     c
16     c The vector of control variables is initialized here. The
17     c temperature and salinity contributions are read from file.
18     c Subsequently, the latter are dimensionalized and the tile
19     c edges are updated.
20     c
21     c started: Christian Eckert eckert@mit.edu 30-Jun-1999
22     c
23     c changed: Christian Eckert eckert@mit.edu 23-Feb-2000
24     c - Restructured the code in order to create a package
25     c for the MITgcmUV.
26     c
27     c Patrick Heimbach heimbach@mit.edu 30-May-2000
28     c - diffsec was falsely declared.
29     c
30     c Patrick Heimbach heimbach@mit.edu 06-Jun-2000
31     c - Transferred some filename declarations
32     c from ctrl_pack/ctrl_unpack to here
33     c - Transferred mask-per-tile to here
34     c - computation of control vector length here
35     c
36     c Patrick Heimbach heimbach@mit.edu 16-Jun-2000
37     c - Added call to ctrl_pack
38     c - Alternatively: transfer writing of scale files to
39     c ctrl_unpack
40     c
41 heimbach 1.9 c Dimitris Menemenlis menemenlis@mit.edu 7-Mar-2003
42     c - To be consistent with usage in ctrl_getrec.F,
43     c startrec and endrec need to be referenced to
44     c model time = 0, not to startTime.
45     c Also "- modelstep" -> "+ modelstep/2":
46     c old: startrec = int((modelstart - diffsecs)/
47     c old: & xx_???period) + 1
48     c old: endrec = int((modelend - diffsecs - modelstep)/
49     c old: & xx_???period) + 2
50     c new: startrec = int((modelstart + startTime - diffsecs)/
51     c new: & xx_???period) + 1
52     c new: endrec = int((modelend + startTime - diffsecs + modelstep/2)/
53     c new: & xx_???period) + 2
54     c
55 heimbach 1.11 c heimbach@mit.edu totally restructured 28-Oct-2003
56     c
57 heimbach 1.1 c ==================================================================
58 heimbach 1.5 c SUBROUTINE ctrl_init
59 heimbach 1.1 c ==================================================================
60    
61     implicit none
62    
63     c == global variables ==
64    
65     #include "EEPARAMS.h"
66     #include "SIZE.h"
67     #include "PARAMS.h"
68     #include "GRID.h"
69     #include "ctrl.h"
70 heimbach 1.12 #include "optim.h"
71 heimbach 1.1
72 heimbach 1.11 #ifdef ALLOW_CAL
73 heimbach 1.9 # include "cal.h"
74 heimbach 1.5 #endif
75     #ifdef ALLOW_OBCS_CONTROL
76     # include "OBCS.h"
77     #endif
78 heimbach 1.33 #ifdef ALLOW_DIC_CONTROL
79     # include "DIC_CTRL.h"
80     #endif
81 heimbach 1.5
82 heimbach 1.1 c == routine arguments ==
83    
84     integer mythid
85    
86     c == local variables ==
87    
88 heimbach 1.21 integer bi,bj
89 mlosch 1.36 integer i,j
90 heimbach 1.21 integer itlo,ithi
91     integer jtlo,jthi
92     integer jmin,jmax
93     integer imin,imax
94    
95 heimbach 1.11 integer ivar
96 heimbach 1.1 integer startrec
97     integer endrec
98 heimbach 1.11 integer diffrec
99 heimbach 1.5
100 mmazloff 1.38 #ifdef ALLOW_OBCS_CONTROL_MODES
101     INTEGER k,length_of_rec,dUnit
102     INTEGER MDS_RECLEN
103     EXTERNAL MDS_RECLEN
104     #endif
105    
106 heimbach 1.1 c == external ==
107    
108     integer ilnblnk
109     external ilnblnk
110    
111     c == end of interface ==
112    
113 heimbach 1.21 jtlo = mybylo(mythid)
114     jthi = mybyhi(mythid)
115     itlo = mybxlo(mythid)
116     ithi = mybxhi(mythid)
117     jmin = 1-oly
118     jmax = sny+oly
119     imin = 1-olx
120     imax = snx+olx
121    
122 heimbach 1.1 c-- Set default values.
123 heimbach 1.11 do ivar = 1,maxcvars
124 mlosch 1.36 ncvarindex(ivar) = -1
125     ncvarrecs(ivar) = 0
126     ncvarxmax(ivar) = 0
127     ncvarymax(ivar) = 0
128     ncvarnrmax(ivar) = 0
129     ncvargrd(ivar) = '?'
130 heimbach 1.11 enddo
131 heimbach 1.1
132     _BARRIER
133    
134     c-- =====================
135     c-- Initial state fields.
136     c-- =====================
137    
138 heimbach 1.5 cph(
139     cph index 7-10 reserved for atmos. state,
140     cph index 11-14 reserved for open boundaries,
141     cph index 15-16 reserved for mixing coeff.
142 heimbach 1.18 cph index 17 reserved for passive tracer TR1
143 heimbach 1.5 cph index 18,19 reserved for sst, sss
144     cph index 20 for hFacC
145 heimbach 1.6 cph index 21-22 for efluxy, efluxp
146 heimbach 1.17 cph index 23 for bottom drag
147     cph index 24
148     cph index 25-26 for edtaux, edtauy
149     cph index 27-29 for uvel0, vvel0, etan0
150 heimbach 1.32 cph index 30-31 for generic 2d, 3d field
151 heimbach 1.18 cph index 32 reserved for precip (atmos. state)
152     cph index 33 reserved for swflux (atmos. state)
153 heimbach 1.19 cph index 34 reserved for swdown (atmos. state)
154 heimbach 1.24 cph 35 lwflux
155     cph 36 lwdown
156     cph 37 evap
157     cph 38 snowprecip
158     cph 39 apressure
159     cph 40 runoff
160 heimbach 1.26 cph 41 seaice SIAREA
161     cph 42 seaice SIHEFF
162     cph 43 seaice SIHSNOW
163 mlosch 1.39 cph 44 gmredi kapredi
164     cph 45 shelfice shifwflx
165 heimbach 1.5 cph)
166    
167 heimbach 1.16 c----------------------------------------------------------------------
168 heimbach 1.6 c--
169 heimbach 1.1 #ifdef ALLOW_THETA0_CONTROL
170 heimbach 1.5 c-- Initial state temperature contribution.
171 heimbach 1.11 call ctrl_init_ctrlvar (
172     & xx_theta_file, 1, 101, 1, 1, 1,
173     & snx, sny, nr, 'c', '3d', mythid )
174 heimbach 1.1 #endif /* ALLOW_THETA0_CONTROL */
175    
176 heimbach 1.16 c----------------------------------------------------------------------
177 heimbach 1.6 c--
178 heimbach 1.1 #ifdef ALLOW_SALT0_CONTROL
179 heimbach 1.5 c-- Initial state salinity contribution.
180 heimbach 1.11 call ctrl_init_ctrlvar (
181     & xx_salt_file, 2, 102, 1, 1, 1,
182     & snx, sny, nr, 'c', '3d', mythid )
183 heimbach 1.1 #endif /* ALLOW_SALT0_CONTROL */
184    
185 heimbach 1.5 c-- ===========================
186     c-- Surface flux contributions.
187     c-- ===========================
188    
189 heimbach 1.16 c----------------------------------------------------------------------
190 heimbach 1.6 c--
191 heimbach 1.5 #if (defined (ALLOW_HFLUX_CONTROL))
192     c-- Heat flux.
193 mlosch 1.36 call ctrl_init_rec (
194     I xx_hfluxstartdate1, xx_hfluxstartdate2, xx_hfluxperiod, 1,
195     O xx_hfluxstartdate, diffrec, startrec, endrec,
196     I mythid )
197     call ctrl_init_ctrlvar (
198     & xx_hflux_file, 3, 103, diffrec, startrec, endrec,
199     & snx, sny, 1, 'c', 'xy', mythid )
200 heimbach 1.5
201     #elif (defined (ALLOW_ATEMP_CONTROL))
202     c-- Atmos. temperature
203 mlosch 1.36 call ctrl_init_rec (
204     I xx_atempstartdate1, xx_atempstartdate2, xx_atempperiod, 1,
205     O xx_atempstartdate, diffrec, startrec, endrec,
206     I mythid )
207     call ctrl_init_ctrlvar (
208     & xx_atemp_file, 7, 107, diffrec, startrec, endrec,
209     & snx, sny, 1, 'c', 'xy', mythid )
210    
211 heimbach 1.5 #elif (defined (ALLOW_HFLUX0_CONTROL))
212     c-- initial forcing only
213 mlosch 1.36 call ctrl_init_ctrlvar (
214     & xx_hflux_file, 3, 103, 1, 1, 1,
215     & snx, sny, 1, 'c', 'xy', mythid )
216 heimbach 1.1
217 heimbach 1.5 #endif /* ALLOW_HFLUX_CONTROL */
218    
219 heimbach 1.16 c----------------------------------------------------------------------
220 heimbach 1.6 c--
221 heimbach 1.5 #if (defined (ALLOW_SFLUX_CONTROL))
222     c-- Salt flux.
223 mlosch 1.36 call ctrl_init_rec (
224     I xx_sfluxstartdate1, xx_sfluxstartdate2, xx_sfluxperiod, 1,
225     O xx_sfluxstartdate, diffrec, startrec, endrec,
226     I mythid )
227     call ctrl_init_ctrlvar (
228     & xx_sflux_file, 4, 104, diffrec, startrec, endrec,
229     & snx, sny, 1, 'c', 'xy', mythid )
230 heimbach 1.11
231 heimbach 1.5 #elif (defined (ALLOW_AQH_CONTROL))
232     c-- Atmos. humidity
233 mlosch 1.36 call ctrl_init_rec (
234     I xx_aqhstartdate1, xx_aqhstartdate2, xx_aqhperiod, 1,
235     O xx_aqhstartdate, diffrec, startrec, endrec,
236     I mythid )
237     call ctrl_init_ctrlvar (
238     & xx_aqh_file, 8, 108, diffrec, startrec, endrec,
239     & snx, sny, 1, 'c', 'xy', mythid )
240 heimbach 1.5
241     #elif (defined (ALLOW_SFLUX0_CONTROL))
242     c-- initial forcing only
243 mlosch 1.36 call ctrl_init_ctrlvar (
244     & xx_sflux_file, 4, 104, 1, 1, 1,
245     & snx, sny, 1, 'c', 'xy', mythid )
246 heimbach 1.1
247 heimbach 1.5 #endif /* ALLOW_SFLUX_CONTROL */
248    
249 heimbach 1.16 c----------------------------------------------------------------------
250 heimbach 1.6 c--
251 heimbach 1.5 #if (defined (ALLOW_USTRESS_CONTROL))
252     c-- Zonal wind stress.
253 mlosch 1.36 call ctrl_init_rec (
254     I xx_tauustartdate1, xx_tauustartdate2, xx_tauuperiod, 1,
255     O xx_tauustartdate, diffrec, startrec, endrec,
256     I mythid )
257     call ctrl_init_ctrlvar (
258     & xx_tauu_file, 5, 105, diffrec, startrec, endrec,
259 gforget 1.34 #ifndef ALLOW_ROTATE_UV_CONTROLS
260 mlosch 1.36 & snx, sny, 1, 'w', 'xy', mythid )
261 gforget 1.34 #else
262 mlosch 1.36 & snx, sny, 1, 'c', 'xy', mythid )
263 gforget 1.34 #endif
264 heimbach 1.5
265     #elif (defined (ALLOW_UWIND_CONTROL))
266     c-- Zonal wind speed.
267 mlosch 1.36 call ctrl_init_rec (
268     I xx_uwindstartdate1, xx_uwindstartdate2, xx_uwindperiod, 1,
269     O xx_uwindstartdate, diffrec, startrec, endrec,
270     I mythid )
271     call ctrl_init_ctrlvar (
272     & xx_uwind_file, 9, 109, diffrec, startrec, endrec,
273     & snx, sny, 1, 'c', 'xy', mythid )
274 heimbach 1.5
275     #elif (defined (ALLOW_TAUU0_CONTROL))
276     c-- initial forcing only
277 mlosch 1.36 call ctrl_init_ctrlvar (
278     & xx_tauu_file, 5, 105, 1, 1, 1,
279     & snx, sny, 1, 'w', 'xy', mythid )
280 heimbach 1.1
281 heimbach 1.5 #endif /* ALLOW_USTRESS_CONTROL */
282    
283 heimbach 1.16 c----------------------------------------------------------------------
284 heimbach 1.6 c--
285 heimbach 1.5 #if (defined (ALLOW_VSTRESS_CONTROL))
286     c-- Meridional wind stress.
287 mlosch 1.36 call ctrl_init_rec (
288     I xx_tauvstartdate1, xx_tauvstartdate2, xx_tauvperiod, 1,
289     O xx_tauvstartdate, diffrec, startrec, endrec,
290     I mythid )
291     call ctrl_init_ctrlvar (
292     & xx_tauv_file, 6, 106, diffrec, startrec, endrec,
293 gforget 1.34 #ifndef ALLOW_ROTATE_UV_CONTROLS
294 mlosch 1.36 & snx, sny, 1, 's', 'xy', mythid )
295 gforget 1.34 #else
296 mlosch 1.36 & snx, sny, 1, 'c', 'xy', mythid )
297 gforget 1.34 #endif
298 heimbach 1.5
299     #elif (defined (ALLOW_VWIND_CONTROL))
300     c-- Meridional wind speed.
301 mlosch 1.36 call ctrl_init_rec (
302     I xx_vwindstartdate1, xx_vwindstartdate2, xx_vwindperiod, 1,
303     O xx_vwindstartdate, diffrec, startrec, endrec,
304     I mythid )
305     call ctrl_init_ctrlvar (
306     & xx_vwind_file, 10, 110, diffrec, startrec, endrec,
307     & snx, sny, 1, 'c', 'xy', mythid )
308 heimbach 1.5
309     #elif (defined (ALLOW_TAUV0_CONTROL))
310     c-- initial forcing only
311 mlosch 1.36 call ctrl_init_ctrlvar (
312     & xx_tauv_file, 6, 106, 1, 1, 1,
313     & snx, sny, 1, 's', 'xy', mythid )
314 heimbach 1.1
315 heimbach 1.5 #endif /* ALLOW_VSTRESS_CONTROL */
316    
317 heimbach 1.11 c-- ===========================
318     c-- Open boundary contributions.
319     c-- ===========================
320    
321 heimbach 1.16 c----------------------------------------------------------------------
322 heimbach 1.6 c--
323 heimbach 1.5 #ifdef ALLOW_OBCSN_CONTROL
324     c-- Northern obc.
325 mlosch 1.36 call ctrl_init_rec (
326     I xx_obcsnstartdate1, xx_obcsnstartdate2, xx_obcsnperiod, 4,
327     O xx_obcsnstartdate, diffrec, startrec, endrec,
328     I mythid )
329     call ctrl_init_ctrlvar (
330     & xx_obcsn_file, 11, 111, diffrec, startrec, endrec,
331     & snx, 1, nr, 'm', 'xz', mythid )
332 heimbach 1.5 #endif /* ALLOW_OBCSN_CONTROL */
333    
334 heimbach 1.16 c----------------------------------------------------------------------
335 heimbach 1.11 c--
336 heimbach 1.5 #ifdef ALLOW_OBCSS_CONTROL
337     c-- Southern obc.
338 mlosch 1.36 call ctrl_init_rec (
339     I xx_obcssstartdate1, xx_obcssstartdate2, xx_obcssperiod, 4,
340     O xx_obcssstartdate, diffrec, startrec, endrec,
341     I mythid )
342     call ctrl_init_ctrlvar (
343     & xx_obcss_file, 12, 112, diffrec, startrec, endrec,
344     & snx, 1, nr, 'm', 'xz', mythid )
345 heimbach 1.5 #endif /* ALLOW_OBCSS_CONTROL */
346    
347 heimbach 1.16 c----------------------------------------------------------------------
348 heimbach 1.6 c--
349 heimbach 1.5 #ifdef ALLOW_OBCSW_CONTROL
350     c-- Western obc.
351 mlosch 1.36 call ctrl_init_rec (
352     I xx_obcswstartdate1, xx_obcswstartdate2, xx_obcswperiod, 4,
353     O xx_obcswstartdate, diffrec, startrec, endrec,
354     I mythid )
355     call ctrl_init_ctrlvar (
356     & xx_obcsw_file, 13, 113, diffrec, startrec, endrec,
357     & 1, sny, nr, 'm', 'yz', mythid )
358 heimbach 1.11 #endif /* ALLOW_OBCSW_CONTROL */
359 heimbach 1.5
360 heimbach 1.16 c----------------------------------------------------------------------
361 heimbach 1.6 c--
362 heimbach 1.5 #ifdef ALLOW_OBCSE_CONTROL
363     c-- Eastern obc.
364 mlosch 1.36 call ctrl_init_rec (
365     I xx_obcsestartdate1, xx_obcsestartdate2, xx_obcseperiod, 4,
366     O xx_obcsestartdate, diffrec, startrec, endrec,
367     I mythid )
368     call ctrl_init_ctrlvar (
369     & xx_obcse_file, 14, 114, diffrec, startrec, endrec,
370     & 1, sny, nr, 'm', 'yz', mythid )
371 heimbach 1.5 #endif /* ALLOW_OBCSE_CONTROL */
372 heimbach 1.2
373 heimbach 1.16 c----------------------------------------------------------------------
374 heimbach 1.6 c--
375 mmazloff 1.38 #ifdef ALLOW_OBCS_CONTROL_MODES
376     cih Get matrices for reconstruction from barotropic-barclinic modes
377     CMM To use modes now hardcoded with ECCO_CPPOPTION. Would be good to have
378     c run-time option and also define filename=baro_invmodes.bin
379     CALL MDSFINDUNIT( dUnit, myThid )
380     length_of_rec = MDS_RECLEN( 64, NR*NR, myThid )
381     open(dUnit, file='baro_invmodes.bin', status='old',
382     & access='direct', recl=length_of_rec )
383     do j = 1,Nr
384     read(dUnit,rec=j) ((modesv(k,i,j), k=1,Nr), i=1,Nr)
385     end do
386     CLOSE( dUnit )
387     CMM double precision modesv is size [NR,NR,NR]
388     c dim one is z-space
389     c dim two is mode space
390     c dim three is the total depth for which this set of modes applies
391     c so for example modesv(:,2,nr) will be the second mode
392     c in z-space for the full model depth
393     c The modes are to be orthogonal when weighted by dz.
394     c i.e. if f_i(z) = mode i, sum_j(f_i(z_j)*f_j(z_j)*dz_j = delta_ij
395     c first mode should also be constant in depth...barotropic
396     c For a matlab code example how to construct the orthonormal modes,
397     c which are ideally the solution of planetary vertical mode equation
398     c using model mean dRho/dz, see
399     c MITgcm/verification/obcs_ctrl/input/gendata.m
400     c This code is compatible with partial cells
401     #endif
402    
403     c----------------------------------------------------------------------
404     c--
405 heimbach 1.3 #ifdef ALLOW_DIFFKR_CONTROL
406 mlosch 1.36 call ctrl_init_ctrlvar (
407     & xx_diffkr_file, 15, 115, 1, 1, 1,
408     & snx, sny, nr, 'c', '3d', mythid )
409 heimbach 1.3 #endif /* ALLOW_DIFFKR_CONTROL */
410    
411 heimbach 1.16 c----------------------------------------------------------------------
412 heimbach 1.6 c--
413 heimbach 1.3 #ifdef ALLOW_KAPGM_CONTROL
414 mlosch 1.36 call ctrl_init_ctrlvar (
415     & xx_kapgm_file, 16, 116, 1, 1, 1,
416     & snx, sny, nr, 'c', '3d', mythid )
417 heimbach 1.3 #endif /* ALLOW_KAPGM_CONTROL */
418    
419 heimbach 1.16 c----------------------------------------------------------------------
420 heimbach 1.6 c--
421 heimbach 1.18 #ifdef ALLOW_TR10_CONTROL
422 mlosch 1.36 call ctrl_init_ctrlvar (
423     & xx_tr1_file, 17, 117, 1, 1, 1,
424     & snx, sny, nr, 'c', '3d', mythid )
425 heimbach 1.18 #endif /* ALLOW_TR10_CONTROL */
426 heimbach 1.2
427 heimbach 1.16 c----------------------------------------------------------------------
428 heimbach 1.6 c--
429 heimbach 1.20 #if (defined (ALLOW_SST_CONTROL))
430 mlosch 1.36 call ctrl_init_rec (
431     I xx_sststartdate1, xx_sststartdate2, xx_sstperiod, 1,
432     O xx_sststartdate, diffrec, startrec, endrec,
433     I mythid )
434     call ctrl_init_ctrlvar (
435     & xx_sst_file, 18, 118, diffrec, startrec, endrec,
436     & snx, sny, 1, 'c', 'xy', mythid )
437 heimbach 1.20
438     #elif (defined (ALLOW_SST0_CONTROL))
439 mlosch 1.36 call ctrl_init_ctrlvar (
440     & xx_sst_file, 18, 118, 1, 1, 1,
441     & snx, sny, 1, 'c', 'xy', mythid )
442 heimbach 1.20
443     #endif /* ALLOW_SST_CONTROL */
444 heimbach 1.6
445 heimbach 1.16 c----------------------------------------------------------------------
446 heimbach 1.6 c--
447 heimbach 1.20 #if (defined (ALLOW_SSS_CONTROL))
448 mlosch 1.36 call ctrl_init_rec (
449     I xx_sssstartdate1, xx_sssstartdate2, xx_sssperiod, 1,
450     O xx_sssstartdate, diffrec, startrec, endrec,
451     I mythid )
452     call ctrl_init_ctrlvar (
453     & xx_sss_file, 19, 119, diffrec, startrec, endrec,
454     & snx, sny, 1, 'c', 'xy', mythid )
455 heimbach 1.20
456     #elif (defined (ALLOW_SSS0_CONTROL))
457 mlosch 1.36 call ctrl_init_ctrlvar (
458     & xx_sss_file, 19, 119, 1, 1, 1,
459     & snx, sny, 1, 'c', 'xy', mythid )
460    
461 heimbach 1.6 #endif /* ALLOW_SSS0_CONTROL */
462    
463 heimbach 1.16 c----------------------------------------------------------------------
464 heimbach 1.6 c--
465 heimbach 1.23 #ifdef ALLOW_DEPTH_CONTROL
466 heimbach 1.11 call ctrl_init_ctrlvar (
467 heimbach 1.23 & xx_depth_file, 20, 120, 1, 1, 1,
468 heimbach 1.11 & snx, sny, 1, 'c', 'xy', mythid )
469 heimbach 1.23 #endif /* ALLOW_DEPTH_CONTROL */
470 heimbach 1.6
471 heimbach 1.16 c----------------------------------------------------------------------
472 heimbach 1.6 c--
473 heimbach 1.5 #ifdef ALLOW_EFLUXY0_CONTROL
474 heimbach 1.11 call ctrl_init_ctrlvar (
475     & xx_efluxy_file, 21, 121, 1, 1, 1,
476     & snx, sny, nr, 's', '3d', mythid )
477 heimbach 1.5 #endif /* ALLOW_EFLUXY0_CONTROL */
478    
479 heimbach 1.16 c----------------------------------------------------------------------
480 heimbach 1.6 c--
481 heimbach 1.5 #ifdef ALLOW_EFLUXP0_CONTROL
482 heimbach 1.11 call ctrl_init_ctrlvar (
483     & xx_efluxp_file, 22, 122, 1, 1, 1,
484     & snx, sny, nr, 'v', '3d', mythid )
485 heimbach 1.5 #endif /* ALLOW_EFLUXP0_CONTROL */
486 heimbach 1.6
487 heimbach 1.16 c----------------------------------------------------------------------
488 heimbach 1.6 c--
489     #ifdef ALLOW_BOTTOMDRAG_CONTROL
490 heimbach 1.11 call ctrl_init_ctrlvar (
491     & xx_bottomdrag_file, 23, 123, 1, 1, 1,
492     & snx, sny, 1, 'c', 'xy', mythid )
493 heimbach 1.6 #endif /* ALLOW_BOTTOMDRAG_CONTROL */
494    
495 heimbach 1.16 c----------------------------------------------------------------------
496 heimbach 1.15 c--
497 dfer 1.28 #ifdef ALLOW_HFLUXM_CONTROL
498     call ctrl_init_ctrlvar (
499     & xx_hfluxm_file, 24, 124, 1, 1, 1,
500     & snx, sny, 1, 'c', 'xy', mythid )
501     #endif /* ALLOW_HFLUXM_CONTROL */
502    
503     c----------------------------------------------------------------------
504     c--
505 gforget 1.30 #ifdef ALLOW_EDDYPSI_CONTROL
506 heimbach 1.15 call ctrl_init_ctrlvar (
507     & xx_edtaux_file, 25, 125, 1, 1, 1,
508     & snx, sny, nr, 'w', '3d', mythid )
509    
510     call ctrl_init_ctrlvar (
511     & xx_edtauy_file, 26, 126, 1, 1, 1,
512     & snx, sny, nr, 's', '3d', mythid )
513 gforget 1.30 #endif /* ALLOW_EDDYPSI_CONTROL */
514 heimbach 1.15
515 heimbach 1.16 c----------------------------------------------------------------------
516     c--
517     #ifdef ALLOW_UVEL0_CONTROL
518     call ctrl_init_ctrlvar (
519     & xx_uvel_file, 27, 127, 1, 1, 1,
520     & snx, sny, nr, 'w', '3d', mythid )
521     #endif /* ALLOW_UVEL0_CONTROL */
522    
523     c----------------------------------------------------------------------
524     c--
525     #ifdef ALLOW_VVEL0_CONTROL
526     call ctrl_init_ctrlvar (
527     & xx_vvel_file, 28, 128, 1, 1, 1,
528     & snx, sny, nr, 's', '3d', mythid )
529     #endif /* ALLOW_VVEL0_CONTROL */
530    
531     c----------------------------------------------------------------------
532     c--
533     #ifdef ALLOW_ETAN0_CONTROL
534     call ctrl_init_ctrlvar (
535     & xx_etan_file, 29, 129, 1, 1, 1,
536     & snx, sny, 1, 'c', 'xy', mythid )
537     #endif /* ALLOW_VVEL0_CONTROL */
538    
539     c----------------------------------------------------------------------
540     c--
541 heimbach 1.32 #ifdef ALLOW_GEN2D_CONTROL
542 heimbach 1.16 call ctrl_init_ctrlvar (
543 heimbach 1.32 & xx_gen2d_file, 30, 130, 1, 1, 1,
544 heimbach 1.16 & snx, sny, 1, 'c', 'xy', mythid )
545 heimbach 1.32 #endif /* ALLOW_GEN2D_CONTROL */
546 heimbach 1.16
547     c----------------------------------------------------------------------
548     c--
549 heimbach 1.32 #ifdef ALLOW_GEN3D_CONTROL
550 heimbach 1.16 call ctrl_init_ctrlvar (
551 heimbach 1.32 & xx_gen3d_file, 31, 131, 1, 1, 1,
552     & snx, sny, nr, 'c', '3d', mythid )
553     #endif /* ALLOW_GEN3D_CONTROL */
554 heimbach 1.16
555     c----------------------------------------------------------------------
556 heimbach 1.17 c--
557 heimbach 1.18 #ifdef ALLOW_PRECIP_CONTROL
558     c-- Atmos. precipitation
559 mlosch 1.36 call ctrl_init_rec (
560     I xx_precipstartdate1, xx_precipstartdate2, xx_precipperiod,1,
561     O xx_precipstartdate, diffrec, startrec, endrec,
562     I mythid )
563     call ctrl_init_ctrlvar (
564     & xx_precip_file, 32, 132, diffrec, startrec, endrec,
565     & snx, sny, 1, 'c', 'xy', mythid )
566 heimbach 1.18
567     #endif /* ALLOW_PRECIP_CONTROL */
568    
569     c----------------------------------------------------------------------
570     c--
571     #ifdef ALLOW_SWFLUX_CONTROL
572     c-- Atmos. swflux
573 mlosch 1.36 call ctrl_init_rec (
574     I xx_swfluxstartdate1, xx_swfluxstartdate2, xx_swfluxperiod, 1,
575     O xx_swfluxstartdate, diffrec, startrec, endrec,
576     I mythid )
577     call ctrl_init_ctrlvar (
578     & xx_swflux_file, 33, 133, diffrec, startrec, endrec,
579     & snx, sny, 1, 'c', 'xy', mythid )
580 heimbach 1.18
581     #endif /* ALLOW_SWFLUX_CONTROL */
582 heimbach 1.17
583     c----------------------------------------------------------------------
584 heimbach 1.19 c--
585     #ifdef ALLOW_SWDOWN_CONTROL
586     c-- Atmos. swdown
587 mlosch 1.36 call ctrl_init_rec (
588     I xx_swdownstartdate1, xx_swdownstartdate2, xx_swdownperiod, 1,
589     O xx_swdownstartdate, diffrec, startrec, endrec,
590     I mythid )
591     call ctrl_init_ctrlvar (
592     & xx_swdown_file, 34, 134, diffrec, startrec, endrec,
593     & snx, sny, 1, 'c', 'xy', mythid )
594 heimbach 1.19
595     #endif /* ALLOW_SWDOWN_CONTROL */
596    
597     c----------------------------------------------------------------------
598 heimbach 1.24 c--
599     #ifdef ALLOW_LWFLUX_CONTROL
600     c-- Atmos. lwflux
601 mlosch 1.36 call ctrl_init_rec (
602     I xx_lwfluxstartdate1, xx_lwfluxstartdate2, xx_lwfluxperiod, 1,
603     O xx_lwfluxstartdate, diffrec, startrec, endrec,
604     I mythid )
605     call ctrl_init_ctrlvar (
606     & xx_lwflux_file, 35, 135, diffrec, startrec, endrec,
607     & snx, sny, 1, 'c', 'xy', mythid )
608 heimbach 1.24
609     #endif /* ALLOW_LWFLUX_CONTROL */
610    
611     c----------------------------------------------------------------------
612     c--
613     #ifdef ALLOW_LWDOWN_CONTROL
614     c-- Atmos. lwdown
615 mlosch 1.36 call ctrl_init_rec (
616     I xx_lwdownstartdate1, xx_lwdownstartdate2, xx_lwdownperiod, 1,
617     O xx_lwdownstartdate, diffrec, startrec, endrec,
618     I mythid )
619     call ctrl_init_ctrlvar (
620     & xx_lwdown_file, 36, 136, diffrec, startrec, endrec,
621     & snx, sny, 1, 'c', 'xy', mythid )
622 heimbach 1.24
623     #endif /* ALLOW_LWDOWN_CONTROL */
624    
625     c----------------------------------------------------------------------
626     c--
627     #ifdef ALLOW_EVAP_CONTROL
628     c-- Atmos. evap
629 mlosch 1.36 call ctrl_init_rec (
630     I xx_evapstartdate1, xx_evapstartdate2, xx_evapperiod, 1,
631     O xx_evapstartdate, diffrec, startrec, endrec,
632     I mythid )
633     call ctrl_init_ctrlvar (
634     & xx_evap_file, 37, 137, diffrec, startrec, endrec,
635     & snx, sny, 1, 'c', 'xy', mythid )
636 heimbach 1.24
637     #endif /* ALLOW_EVAP_CONTROL */
638    
639     c----------------------------------------------------------------------
640     c--
641     #ifdef ALLOW_SNOWPRECIP_CONTROL
642     c-- Atmos. snowprecip
643 mlosch 1.36 call ctrl_init_rec (
644     I xx_snowprecipstartdate1, xx_snowprecipstartdate2,
645     I xx_snowprecipperiod, 1,
646     O xx_snowprecipstartdate, diffrec, startrec, endrec,
647     I mythid )
648     call ctrl_init_ctrlvar (
649     & xx_snowprecip_file, 38, 138, diffrec, startrec, endrec,
650     & snx, sny, 1, 'c', 'xy', mythid )
651 heimbach 1.24
652     #endif /* ALLOW_SNOWPRECIP_CONTROL */
653    
654     c----------------------------------------------------------------------
655     c--
656     #ifdef ALLOW_APRESSURE_CONTROL
657     c-- Atmos. apressure
658 mlosch 1.36 call ctrl_init_rec (
659     I xx_apressurestartdate1, xx_apressurestartdate2,
660     I xx_apressureperiod, 1,
661     O xx_apressurestartdate, diffrec, startrec, endrec,
662     I mythid )
663     call ctrl_init_ctrlvar (
664     & xx_apressure_file, 39, 139, diffrec, startrec, endrec,
665     & snx, sny, 1, 'c', 'xy', mythid )
666 heimbach 1.24
667     #endif /* ALLOW_APRESSURE_CONTROL */
668    
669     c----------------------------------------------------------------------
670     c--
671     #ifdef ALLOW_RUNOFF_CONTROL
672     c-- Atmos. runoff
673 mlosch 1.36 call ctrl_init_rec (
674     I xx_runoffstartdate1, xx_runoffstartdate2, xx_runoffperiod, 1,
675     O xx_runoffstartdate, diffrec, startrec, endrec,
676     I mythid )
677     call ctrl_init_ctrlvar (
678     & xx_runoff_file, 40, 140, diffrec, startrec, endrec,
679     & snx, sny, 1, 'c', 'xy', mythid )
680 heimbach 1.24 #endif /* ALLOW_RUNOFF_CONTROL */
681    
682     c----------------------------------------------------------------------
683 heimbach 1.26 c--
684     #ifdef ALLOW_SIAREA_CONTROL
685 mlosch 1.36 C-- so far there are no xx_siareastartdate1, etc., so we need to fudge it.
686     CML call ctrl_init_rec (
687     CML I xx_siareastartdate1, xx_siareastartdate2, xx_siareaperiod, 1,
688     CML O xx_siareastartdate, diffrec, startrec, endrec,
689     CML I mythid )
690     startrec = 1
691     endrec = 1
692     diffrec = endrec - startrec + 1
693     call ctrl_init_ctrlvar (
694     & xx_siarea_file, 41, 141, diffrec, startrec, endrec,
695     & snx, sny, 1, 'c', 'xy', mythid )
696 heimbach 1.26 #endif /* ALLOW_siarea_CONTROL */
697    
698     c----------------------------------------------------------------------
699     c--
700     #ifdef ALLOW_SIHEFF_CONTROL
701 mlosch 1.36 C-- so far there are no xx_siheffstartdate1, etc., so we need to fudge it.
702     CML call ctrl_init_rec (
703     CML I xx_siheffstartdate1, xx_siheffstartdate2, xx_siheffperiod, 1,
704     CML O xx_siheffstartdate, diffrec, startrec, endrec,
705     CML I mythid )
706     startrec = 1
707     endrec = 1
708     diffrec = endrec - startrec + 1
709     call ctrl_init_ctrlvar (
710     & xx_siheff_file, 42, 142, diffrec, startrec, endrec,
711     & snx, sny, 1, 'c', 'xy', mythid )
712 heimbach 1.26 #endif /* ALLOW_siheff_CONTROL */
713    
714     c----------------------------------------------------------------------
715     c--
716     #ifdef ALLOW_SIHSNOW_CONTROL
717 mlosch 1.36 C-- so far there are no xx_sihsnowstartdate1, etc., so we need to fudge it.
718     CML call ctrl_init_rec (
719     CML I xx_sihsnowstartdate1, xx_sihsnowstartdate2, xx_sihsnowperiod, 1,
720     CML O xx_sihsnowstartdate, diffrec, startrec, endrec,
721     CML I mythid )
722     startrec = 1
723     endrec = 1
724     diffrec = endrec - startrec + 1
725     call ctrl_init_ctrlvar (
726     & xx_sihsnow_file, 43, 143, diffrec, startrec, endrec,
727     & snx, sny, 1, 'c', 'xy', mythid )
728 heimbach 1.26 #endif /* ALLOW_sihsnow_CONTROL */
729    
730 gforget 1.29
731     c----------------------------------------------------------------------
732     c--
733     #ifdef ALLOW_KAPREDI_CONTROL
734 mlosch 1.36 call ctrl_init_ctrlvar (
735     & xx_kapredi_file, 44, 144, 1, 1, 1,
736     & snx, sny, nr, 'c', '3d', mythid )
737 gforget 1.29 #endif /* ALLOW_KAPREDI_CONTROL */
738    
739 heimbach 1.26 c----------------------------------------------------------------------
740 heimbach 1.16 c----------------------------------------------------------------------
741 heimbach 1.21
742 mlosch 1.39 #ifdef ALLOW_SHIFWFLX_CONTROL
743     c-- freshwater flux underneath ice-shelves
744     call ctrl_init_rec (
745     I xx_shifwflxstartdate1, xx_shifwflxstartdate2,
746     I xx_shifwflxperiod, 1,
747     O xx_shifwflxstartdate, diffrec, startrec, endrec,
748     I mythid )
749     call ctrl_init_ctrlvar (
750     & xx_shifwflx_file, 45, 145, diffrec, startrec, endrec,
751     & snx, sny, 1, 'i', 'xy', mythid )
752     #endif /* ALLOW_SHIFWFLX_CONTROL */
753    
754     c----------------------------------------------------------------------
755     c----------------------------------------------------------------------
756    
757 mlosch 1.36 call ctrl_init_wet( mythid )
758    
759 heimbach 1.21 c----------------------------------------------------------------------
760 heimbach 1.16 c----------------------------------------------------------------------
761 heimbach 1.1
762 heimbach 1.33 #ifdef ALLOW_DIC_CONTROL
763 mlosch 1.36 do i = 1, dic_n_control
764     xx_dic(i) = 0. _d 0
765     enddo
766 heimbach 1.33 #endif
767    
768     c----------------------------------------------------------------------
769     c----------------------------------------------------------------------
770    
771 heimbach 1.21 do bj = jtlo,jthi
772 mlosch 1.36 do bi = itlo,ithi
773     do j = jmin,jmax
774     do i = imin,imax
775     wareaunit (i,j,bi,bj) = 1.0
776 heimbach 1.21 #ifndef ALLOW_ECCO
777 mlosch 1.36 whflux (i,j,bi,bj) = maskC(i,j,1,bi,bj)
778     wsflux (i,j,bi,bj) = maskC(i,j,1,bi,bj)
779     wtauu (i,j,bi,bj) = maskW(i,j,1,bi,bj)
780     wtauv (i,j,bi,bj) = maskS(i,j,1,bi,bj)
781     watemp (i,j,bi,bj) = maskC(i,j,1,bi,bj)
782     waqh (i,j,bi,bj) = maskC(i,j,1,bi,bj)
783     wprecip (i,j,bi,bj) = maskC(i,j,1,bi,bj)
784     wswflux (i,j,bi,bj) = maskC(i,j,1,bi,bj)
785     wswdown (i,j,bi,bj) = maskC(i,j,1,bi,bj)
786     wuwind (i,j,bi,bj) = maskC(i,j,1,bi,bj)
787     wvwind (i,j,bi,bj) = maskC(i,j,1,bi,bj)
788     wlwflux (i,j,bi,bj) = maskC(i,j,1,bi,bj)
789     wlwdown (i,j,bi,bj) = maskC(i,j,1,bi,bj)
790     wevap (i,j,bi,bj) = maskC(i,j,1,bi,bj)
791     wsnowprecip(i,j,bi,bj) = maskC(i,j,1,bi,bj)
792     wapressure(i,j,bi,bj) = maskC(i,j,1,bi,bj)
793     wrunoff (i,j,bi,bj) = maskC(i,j,1,bi,bj)
794     wsst (i,j,bi,bj) = maskC(i,j,1,bi,bj)
795     wsss (i,j,bi,bj) = maskC(i,j,1,bi,bj)
796 heimbach 1.21 #endif
797 mlosch 1.36 enddo
798 heimbach 1.21 enddo
799 mlosch 1.36 enddo
800 heimbach 1.21 enddo
801    
802 heimbach 1.1 return
803     end
804    
805 mlosch 1.36 subroutine ctrl_init_rec(
806     I fldstartdate1, fldstartdate2, fldperiod, nfac,
807     O fldstartdate, diffrec, startrec, endrec,
808     I mythid )
809    
810     c ==================================================================
811     c SUBROUTINE ctrl_init_rec
812     c ==================================================================
813     c
814     c helper routine to compute the first and last record of a
815     c time dependent control variable
816     c
817     c Martin.Losch@awi.de, 2011-Mar-15
818     c
819     c ==================================================================
820     c SUBROUTINE ctrl_init_rec
821     c ==================================================================
822    
823     implicit none
824    
825     c == global variables ==
826     #include "SIZE.h"
827     #include "EEPARAMS.h"
828     #include "PARAMS.h"
829     #ifdef ALLOW_CAL
830     # include "cal.h"
831     #endif
832    
833     c == input variables ==
834     c fldstartdate1/2 : start time (date/time) of fld
835     c fldperod : sampling interval of fld
836     c nfac : factor for the case that fld is an obcs variable
837     c in this case nfac = 4, otherwise nfac = 1
838     c mythid : thread ID of this instance
839     integer fldstartdate1
840     integer fldstartdate2
841     _RL fldperiod
842     integer nfac
843     integer mythid
844    
845     c == output variables ==
846     c fldstartdate : full date from fldstartdate1 and 2
847     c startrec : first record of ctrl variable
848     c startrec : last record of ctrl variable
849     c diffrec : difference between first and last record of ctrl variable
850     integer fldstartdate(4)
851     integer startrec
852     integer endrec
853     integer diffrec
854    
855     c == local variables ==
856     integer i
857     #ifdef ALLOW_CAL
858     integer difftime(4)
859     _RL diffsecs
860     #endif /* ALLOW_CAL */
861    
862     c initialise some output
863     do i = 1,4
864     fldstartdate(i) = 0
865     end do
866     startrec = 0
867     endrec = 0
868     diffrec = 0
869     # ifdef ALLOW_CAL
870     call cal_FullDate( fldstartdate1, fldstartdate2,
871     & fldstartdate , mythid )
872     call cal_TimePassed( fldstartdate, modelstartdate,
873     & difftime, mythid )
874     call cal_ToSeconds ( difftime, diffsecs, mythid )
875     if ( fldperiod .EQ. -12. ) then
876     startrec = 1
877     endrec = 12*nfac
878     elseif ( fldperiod .EQ. 0. ) then
879     startrec = 1
880     endrec = 1*nfac
881     else
882     startrec = int((modelstart + startTime - diffsecs)/
883     & fldperiod) + 1
884     endrec = int((modelend + startTime - diffsecs + modelstep/2)/
885     & fldperiod) + 2
886     if ( nfac .ne. 1 ) then
887     c This is the case of obcs. I am not sure that this is correct, but
888     c it seems to work in most configurations.
889     endrec = (endrec - startrec + 1)*nfac
890     startrec = (startrec - 1)*nfac + 1
891     endif
892     endif
893     # else /* ndef ALLOW_CAL */
894     if ( fldperiod .EQ. 0. ) then
895     startrec = 1
896     endrec = 1*nfac
897     else
898     startrec = 1
899     endrec = (int((endTime - startTime)/fldperiod) + 1)*nfac
900     endif
901     #endif /* ALLOW_CAL */
902     diffrec = endrec - startrec + 1
903    
904     return
905     end

  ViewVC Help
Powered by ViewVC 1.1.22