/[MITgcm]/MITgcm/pkg/ecco/ecco_check_exp.F
ViewVC logotype

Annotation of /MITgcm/pkg/ecco/ecco_check_exp.F

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


Revision 1.5 - (hide annotations) (download)
Fri Sep 17 23:02:01 2004 UTC (19 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: HEAD
Changes since 1.4: +0 -0 lines
FILE REMOVED
o bringing adjoint up to date for sheduled c55

1 heimbach 1.1 #include "CPP_OPTIONS.h"
2    
3     subroutine ecco_check_exp(
4     & mythid, mycurrentiter, mycurrenttime, yprefix )
5    
6     c =================================================================
7     c SUBROUTINE ecco_check_exp
8     c =================================================================
9     c
10     c o Check details of the model run
11     c
12     c This routine dumps a collection of model fields for diagnostic
13     c or testimg purposes, respectively.
14     c
15     c Variables for experiment 06:
16     c
17     c Dynamical core:
18     c Potential temperature theta [C]
19     c Salinity salt [psu]
20     c Zonal velocity uvel [m/s]
21     c Meridional velocity vvel [m/s]
22     c Vertical velocity ( --> check_fld) rvel [m/s]
23     c Surface pressure cg2d_x [m]
24     c Surface heat flux qnet [K/s]
25     c Qnet contrib. from external forcing tflux [K/s]
26     c Qnet contrib. from relaxation to Levitus qlev [K/s]
27     c Qnet contrib. from relaxation to Reynolds qrey [K/s]
28     c Surface virtual salt flux empmr [psu/s]
29     c Surface zonal wind stress fu [m/s^2]
30     c Surface meridional wind stress fv [m/s^2]
31     c
32     c Control vector contributions:
33     c Heat flux correction xx_hflux [W/m^2]
34     c Virtual salt flux correction xx_sflux [psu/s/m^2]
35     c Zonal wind stress correction xx_tauu [N/m^2]
36     c Meridional wind stress correction xx_tauv [N/m^2]
37     c
38     c Bulk formulae:
39     c Atmospheric zonal wind uwind [m/s]
40     c Atmospheric meridional wind vwind [m/s]
41     c Air temperature atemp [K]
42     c Specific humidity aqh [kg/kg]
43     c Precipitation precip [kg/s/m^2]
44     c Short wave radiative flux swflux/qsw [W/m^2]
45     c Long wave radiative flux lwflux/qlw [W/m^2]
46     c
47     c Non-local K-Profile Parameterization (KPP):
48     c Short wave radiative flux swflux/qsw [W/m^2]
49     c Boundary layer depth kpphbl [m]
50     c
51     c
52     c Beta Version: Christian Eckert (MIT) 15-Nov-1999
53     c
54     c =================================================================
55     c SUBROUTINE check_exp
56     c =================================================================
57    
58     implicit none
59    
60     c-- == global variables ==
61    
62     cph#ifdef ALLOW_SNAPSHOTS
63    
64     #include "EEPARAMS.h"
65     #include "SIZE.h"
66     #include "PARAMS.h"
67     cph#include "CG2D_EXTERNAL.h"
68     #include "DYNVARS.h"
69     #include "FFIELDS.h"
70     #include "GRID.h"
71     cph#include "cal.h"
72     cph#include "exf_clim_param.h"
73 heimbach 1.4 #ifdef ALLOW_BULKFORMULAE
74     #include "exf_fields.h"
75     #endif
76 heimbach 1.1
77     #ifdef ALLOW_KPP
78     # include "KPP_OPTIONS.h"
79     # include "KPP_PARAMS.h"
80     # include "KPP.h"
81     #endif
82    
83     cph#endif
84    
85     c == routine arguments ==
86     c mythid - thread number for this instance of the routine.
87    
88     integer mythid
89     integer mycurrentiter
90     _RL mycurrenttime
91     character yprefix*3
92    
93     cph#ifdef ALLOW_SNAPSHOTS
94    
95     c-- == local variables ==
96    
97     INTEGER bi,bj,i,j
98     integer irec
99     integer mydate(4)
100     character yfname*128
101    
102     _RS tmpflux (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
103    
104     c == end of interface ==
105    
106     irec = 0
107    
108 heimbach 1.4 if ( mod((mycurrentiter),240) .eq. 0 ) then
109     irec = (mycurrentiter)/240 + 1
110 heimbach 1.1
111     cph(
112     cph call cal_GetDate(
113     cph I mycurrentiter,
114     cph I mycurrenttime,
115     cph O mydate,
116     cph I mythid
117     cph & )
118    
119     print *, 'pathei: in check_exp: iter/time/rec/yprefix ',
120     & mycurrentiter, mycurrenttime, irec, ' ', yprefix
121     print *, 'pathei: in check_exp: date ', mycurrentiter
122     print *, 'pathei: in check_exp: theta ', theta(10,10,1,1,1)
123     print *, 'pathei: in check_exp: salt ', salt(10,10,1,1,1)
124     print *, 'pathei: in check_exp: uvel ', uvel(10,10,1,1,1)
125     print *, 'pathei: in check_exp: vvel ', vvel(10,10,1,1,1)
126     print *, 'pathei: in check_exp: qnet ', qnet(10,10,1,1)
127     print *, 'pathei: in check_exp: empmr ', empmr(10,10,1,1)
128     print *, 'pathei: in check_exp: fu ', fu(10,10,1,1)
129     print *, 'pathei: in check_exp: fv ', fv(10,10,1,1)
130     cph)
131    
132     c-- Potential temperature:
133     write(yfname,'(128a)') ' '
134     write(yfname,'(2a)') yprefix, 'snapshot_theta'
135     call mdswritefield( yfname, 32, .false.,
136     & 'RL', nr, theta, irec,
137     & mycurrentiter, mythid )
138    
139     c-- Salinity:
140     write(yfname,'(128a)') ' '
141     write(yfname,'(2a)') yprefix, 'snapshot_salt'
142     call mdswritefield( yfname, 32, .false.,
143     & 'RL', nr, salt, irec,
144     & mycurrentiter, mythid )
145    
146     c-- Zonal velocity:
147     write(yfname,'(128a)') ' '
148     write(yfname,'(2a)') yprefix, 'snapshot_uvel'
149     call mdswritefield( yfname, 32, .false.,
150     & 'RL', nr, uvel, irec,
151     & mycurrentiter, mythid )
152    
153     c-- Meridional velocity:
154     write(yfname,'(128a)') ' '
155     write(yfname,'(2a)') yprefix, 'snapshot_vvel'
156     call mdswritefield( yfname, 32, .false.,
157     & 'RL', nr, vvel, irec,
158     & mycurrentiter, mythid )
159    
160     c-- Surface pressure:
161     cph write(yfname,'(128a)') ' '
162     cph write(yfname,'(2a)') yprefix, 'snapshot_cg2d_x'
163     cph call mdswritefield( yfname, 32, .false.,
164     cph & 'RL', 1, cg2d_x, irec,
165     cph & mycurrentiter, mythid )
166    
167     c-- Surface heat flux:
168     DO bj = myByLo(myThid), myByHi(myThid)
169     DO bi = myBxLo(myThid), myBxHi(myThid)
170     DO j=1-oLy,sNy+oLy
171     DO i=1-oLx,sNx+oLx
172     tmpflux(i,j,bi,bj) =
173 heimbach 1.4 & - Qnet(i,j,bi,bj)*HeatCapacity_Cp*rhoNil*dRf(1)
174 heimbach 1.1 ENDDO
175     ENDDO
176     ENDDO
177     ENDDO
178     write(yfname,'(128a)') ' '
179     write(yfname,'(2a)') yprefix, 'snapshot_qnet'
180     call mdswritefield( yfname, 32, .false.,
181     & 'RS', 1, tmpflux, irec,
182     & mycurrentiter, mythid )
183    
184     c-- Surface virtual salt flux:
185     DO bj = myByLo(myThid), myByHi(myThid)
186     DO bi = myBxLo(myThid), myBxHi(myThid)
187     DO j=1-oLy,sNy+oLy
188     DO i=1-oLx,sNx+oLx
189     tmpflux(i,j,bi,bj) =
190     & EmPmR(i,j,bi,bj)*dRf(1)/35.
191     ENDDO
192     ENDDO
193     ENDDO
194     ENDDO
195     write(yfname,'(128a)') ' '
196     write(yfname,'(2a)') yprefix, 'snapshot_empmr'
197     call mdswritefield( yfname, 32, .false.,
198     & 'RS', 1, tmpflux, irec,
199     & mycurrentiter, mythid )
200    
201     c-- Surface zonal wind stress:
202     DO bj = myByLo(myThid), myByHi(myThid)
203     DO bi = myBxLo(myThid), myBxHi(myThid)
204     DO j=1-oLy,sNy+oLy
205     DO i=1-oLx,sNx+oLx
206     tmpflux(i,j,bi,bj) =
207 heimbach 1.4 & -fu(i,j,bi,bj)*rhoNil*dRf(1)/horiVertRatio
208 heimbach 1.1 ENDDO
209     ENDDO
210     ENDDO
211     ENDDO
212     write(yfname,'(128a)') ' '
213     write(yfname,'(2a)') yprefix, 'snapshot_fu'
214     call mdswritefield( yfname, 32, .false.,
215     & 'RS', 1, tmpflux, irec,
216     & mycurrentiter, mythid )
217    
218     c-- Surface meridional wind stress:
219     DO bj = myByLo(myThid), myByHi(myThid)
220     DO bi = myBxLo(myThid), myBxHi(myThid)
221     DO j=1-oLy,sNy+oLy
222     DO i=1-oLx,sNx+oLx
223     tmpflux(i,j,bi,bj) =
224 heimbach 1.4 & -fv(i,j,bi,bj)*rhoNil*dRf(1)/horiVertRatio
225 heimbach 1.1 ENDDO
226     ENDDO
227     ENDDO
228     ENDDO
229     write(yfname,'(128a)') ' '
230     write(yfname,'(2a)') yprefix, 'snapshot_fv'
231     call mdswritefield( yfname, 32, .false.,
232     & 'RS', 1, tmpflux, irec,
233     & mycurrentiter, mythid )
234    
235     c-- Control vector contributions:
236    
237     c-- Heat flux (control):
238     cph call mdswritefield( yprefix//'snapshot_xx_hfl', 32, .false.,
239     cph & 'RS', 1, xx_hfl, irec,
240     cph & mycurrentiter, mythid )
241    
242     c-- Virtual salt flux (control):
243     cph call mdswritefield( yprefix//'snapshot_xx_sfl', 32, .false.,
244     cph & 'RS', 1, xx_sfl, irec,
245     cph & mycurrentiter, mythid )
246    
247     c-- Zonal wind stress (control):
248     cph call mdswritefield( yprefix//'snapshot_xx_tauu', 32, .false.,
249     cph & 'RS', 1, xx_tauu, irec,
250     cph & mycurrentiter, mythid )
251    
252     c-- Meridional wind stress (control):
253     cph call mdswritefield( yprefix//'snapshot_xx_tauv', 32, .false.,
254     cph & 'RS', 1, xx_tauv, irec,
255     cph & mycurrentiter, mythid )
256    
257 heimbach 1.4 #if (defined (ALLOW_BULKFORMULAE) && defined (ALLOW_ATM_WIND))
258 heimbach 1.1 c-- Atmospheric zonal wind:
259     write(yfname,'(128a)') ' '
260     write(yfname,'(2a)') yprefix, 'snapshot_uwind'
261     call mdswritefield( yfname, 32, .false.,
262     & 'RS', 1, uwind, irec,
263     & mycurrentiter, mythid )
264 heimbach 1.4 #endif
265 heimbach 1.1
266 heimbach 1.4 #if (defined (ALLOW_BULKFORMULAE) && defined (ALLOW_ATM_WIND))
267 heimbach 1.1 c-- Atmospheric meridional wind:
268     write(yfname,'(128a)') ' '
269     write(yfname,'(2a)') yprefix, 'snapshot_vwind'
270     call mdswritefield( yfname, 32, .false.,
271     & 'RS', 1,vwind, irec,
272     & mycurrentiter, mythid )
273 heimbach 1.4 #endif
274 heimbach 1.1
275 heimbach 1.4 #if (defined (ALLOW_BULKFORMULAE) && defined (ALLOW_ATM_TEMP))
276 heimbach 1.1 c-- Air temperature:
277     write(yfname,'(128a)') ' '
278     write(yfname,'(2a)') yprefix, 'snapshot_atemp'
279     call mdswritefield( yfname, 32, .false.,
280     & 'RS', 1, atemp, irec,
281     & mycurrentiter, mythid )
282 heimbach 1.4 #endif
283 heimbach 1.1
284 heimbach 1.4 #if (defined (ALLOW_BULKFORMULAE) && defined (ALLOW_ATM_TEMP))
285 heimbach 1.1 c-- Relative humidity:
286     write(yfname,'(128a)') ' '
287     write(yfname,'(2a)') yprefix, 'snapshot_aqh'
288     call mdswritefield( yfname, 32, .false.,
289     & 'RS', 1, aqh, irec,
290     & mycurrentiter, mythid )
291 heimbach 1.4 #endif
292 heimbach 1.1
293 heimbach 1.4 #if (defined (ALLOW_BULKFORMULAE) && defined (ALLOW_ATM_TEMP))
294 heimbach 1.1 c-- Precipitation:
295     write(yfname,'(128a)') ' '
296     write(yfname,'(2a)') yprefix, 'snapshot_precip'
297     call mdswritefield( yfname, 32, .false.,
298     & 'RS', 1, precip, irec,
299     & mycurrentiter, mythid )
300     #endif
301    
302 heimbach 1.4 #ifdef ALLOW_BULKFORMULAE
303 heimbach 1.1 c-- Long wave radiative flux:
304 heimbach 1.4 cph write(yfname,'(128a)') ' '
305     cph write(yfname,'(2a)') yprefix, 'snapshot_lwflux'
306     cph call mdswritefield( yfname, 32, .false.,
307     cph & 'RS', 1, lwflux, irec,
308     cph & mycurrentiter, mythid )
309     #endif
310 heimbach 1.1
311     #ifdef ALLOW_KPP
312     c-- Short wave radiative flux:
313     DO bj = myByLo(myThid), myByHi(myThid)
314     DO bi = myBxLo(myThid), myBxHi(myThid)
315     DO j=1-oLy,sNy+oLy
316     DO i=1-oLx,sNx+oLx
317     tmpflux(i,j,bi,bj) =
318 heimbach 1.4 & -Qsw(i,j,bi,bj)*HeatCapacity_Cp*rhoNil*dRf(1)
319 heimbach 1.1 ENDDO
320     ENDDO
321     ENDDO
322     ENDDO
323     write(yfname,'(128a)') ' '
324     write(yfname,'(2a)') yprefix, 'snapshot_swflux'
325     call mdswritefield( yfname, 32, .false.,
326     & 'RS', 1, tmpflux, irec,
327     & mycurrentiter, mythid )
328    
329     c-- Boundary layer depth:
330     write(yfname,'(128a)') ' '
331     write(yfname,'(2a)') yprefix, 'snapshot_kpphbl'
332     call mdswritefield( yfname, 32, .false.,
333     & 'RL', 1, kpphbl, irec,
334     & mycurrentiter, mythid )
335     #endif / * ALLOW_KPP * /
336    
337     #ifdef ALLOW_CLIMSST_RELAXATION
338     c-- SST climatology:
339     write(yfname,'(128a)') ' '
340     write(yfname,'(2a)') yprefix, 'snapshot_sst'
341     call mdswritefield( yfname, 32, .false.,
342     & 'RS', 1, sst, irec,
343     & mycurrentiter, mythid )
344     #endif / * ALLOW_CLIMSST_RELAXATION * /
345    
346     #ifdef ALLOW_CLIMSSS_RELAXATION
347     c-- SSS climatology:
348     write(yfname,'(128a)') ' '
349     write(yfname,'(2a)') yprefix, 'snapshot_sss'
350     call mdswritefield( yfname, 32, .false.,
351     & 'RS', 1, sss, irec,
352     & mycurrentiter, mythid )
353     #endif / * ALLOW_CLIMSSS_RELAXATION * /
354    
355     endif
356    
357     cph#endif / * ALLOW_SNAPSHOTS * /
358    
359     return
360     end
361    
362    

  ViewVC Help
Powered by ViewVC 1.1.22