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

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

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


Revision 1.53 - (hide annotations) (download)
Wed Jul 7 22:23:12 2004 UTC (19 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint54b_post
Changes since 1.52: +4 -1 lines
needs valid U,V in halo region for multi-Dim-Advec; do Exch(U,V) if staggerTimeStep

1 jmc 1.53 C $Header: /u/gcmpack/MITgcm/model/src/config_summary.F,v 1.52 2004/06/24 20:25:44 afe Exp $
2 cnh 1.26 C $Name: $
3 cnh 1.1
4 cnh 1.18 #include "CPP_OPTIONS.h"
5 cnh 1.1
6 cnh 1.30 CBOP
7     C !ROUTINE: CONFIG_SUMMARY
8     C !INTERFACE:
9 cnh 1.1 SUBROUTINE CONFIG_SUMMARY( myThid )
10 cnh 1.30 C !DESCRIPTION: \bv
11     C *=========================================================*
12     C | SUBROUTINE CONFIG_SUMMARY
13     C | o Summarize model parameter settings.
14     C *=========================================================*
15     C | This routine writes a tabulated summary of the kernel
16     C | model configuration. Information describes all the
17     C | parameter setting in force and the meaning and units of
18     C | those parameters. Individal packages report a similar
19     C | table for each package using the same format as employed
20     C | here. If parameters are missing or incorrectly described
21     C | or dimensioned please contact support@mitgcm.org
22     C *=========================================================*
23     C \ev
24    
25     C !USES:
26 adcroft 1.19 IMPLICIT NONE
27 cnh 1.1 C === Global variables ===
28     #include "SIZE.h"
29     #include "EEPARAMS.h"
30     #include "PARAMS.h"
31 mlosch 1.34 #include "EOS.h"
32 cnh 1.1 #include "GRID.h"
33     #include "DYNVARS.h"
34    
35 cnh 1.30 C !INPUT/OUTPUT PARAMETERS:
36 cnh 1.1 C == Routine arguments ==
37     C myThid - Number of this instance of CONFIG_SUMMARY
38     INTEGER myThid
39     CEndOfInterface
40    
41 cnh 1.30 C !LOCAL VARIABLES:
42 cnh 1.1 C == Local variables ==
43 cnh 1.30 C msgBuf :: Temp. for building output string.
44     C I,J,K :: Loop counters.
45     C bi,bj :: Tile loop counters.
46     C xcoord :: Temps. for building lists of values for uni-dimensionally
47     C ycoord :: varying parameters.
48     C zcoord ::
49 cnh 1.1 CHARACTER*(MAX_LEN_MBUF) msgBuf
50 cnh 1.5 INTEGER I,J,K
51 cnh 1.6 INTEGER bi, bj
52 heimbach 1.22 _RL xcoord(Nx)
53     _RL ycoord(Ny)
54 jmc 1.32 _RL rcoord(Nr+1)
55 cnh 1.26 INTEGER coordLine
56     INTEGER tileLine
57 cnh 1.30 CEOP
58 cnh 1.5
59 cnh 1.1
60     _BARRIER
61 cnh 1.5 _BEGIN_MASTER(myThid)
62 cnh 1.1
63     WRITE(msgBuf,'(A)')
64     &'// ======================================================='
65 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
66     & SQUEEZE_RIGHT , 1)
67 cnh 1.1 WRITE(msgBuf,'(A)') '// Model configuration'
68 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
69     & SQUEEZE_RIGHT , 1)
70 cnh 1.1 WRITE(msgBuf,'(A)')
71     &'// ======================================================='
72     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
73     & SQUEEZE_RIGHT , 1)
74 cnh 1.5
75 cnh 1.6 WRITE(msgBuf,'(A)') '// '
76 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
77     & SQUEEZE_RIGHT , 1)
78     WRITE(msgBuf,'(A)')
79     & '// "Physical" paramters ( PARM01 in namelist ) '
80     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
81     & SQUEEZE_RIGHT , 1)
82 cnh 1.6 WRITE(msgBuf,'(A)') '// '
83 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
84     & SQUEEZE_RIGHT , 1)
85 jmc 1.37 WRITE(msgBuf,'(A,A40)') 'buoyancyRelation = ', buoyancyRelation
86     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
87     & SQUEEZE_RIGHT , 1)
88 cnh 1.13 CALL WRITE_1D_R8( tRef, Nr, INDEX_K,'tRef =',
89 cnh 1.5 &' /* Reference temperature profile ( oC or oK ) */')
90 cnh 1.13 CALL WRITE_1D_R8( sRef, Nr, INDEX_K,'sRef =',
91 cnh 1.6 &' /* Reference salinity profile ( ppt ) */')
92 heimbach 1.22 CALL WRITE_0D_R8( viscAh, INDEX_NONE,'viscAh =',
93 cnh 1.5 &' /* Lateral eddy viscosity ( m^2/s ) */')
94 adcroft 1.47 CALL WRITE_0D_R8( viscAhMax, INDEX_NONE,'viscAhMax =',
95     &' /* Maximum lateral eddy viscosity ( m^2/s ) */')
96     CALL WRITE_0D_R8( viscAhGrid, INDEX_NONE,'viscAhGrid =',
97     &' /* Grid dependent lateral eddy viscosity ( non-dim. ) */')
98 adcroft 1.48 CALL WRITE_0D_R8( viscC2leith, INDEX_NONE,'viscC2leith =',
99     &' /* Leith harmonic viscosity factor ( non-dom. ) */')
100 jmc 1.45 CALL WRITE_0D_R8( viscA4, INDEX_NONE,'viscA4 =',
101 cnh 1.14 &' /* Lateral biharmonic viscosity ( m^4/s ) */')
102 adcroft 1.47 CALL WRITE_0D_R8( viscA4Max, INDEX_NONE,'viscA4Max =',
103     &' /* Maximum biharmonic viscosity ( m^2/s ) */')
104     CALL WRITE_0D_R8( viscA4Grid, INDEX_NONE,'viscA4Grid =',
105     &' /* Grid dependent biharmonic viscosity ( non-dim. ) */')
106 adcroft 1.48 CALL WRITE_0D_R8( viscC4leith, INDEX_NONE,'viscC4leith =',
107     &' /* Leith biharmonic viscosity factor ( non-dom. ) */')
108 heimbach 1.22 CALL WRITE_0D_L( no_slip_sides, INDEX_NONE,
109 adcroft 1.20 & 'no_slip_sides =', ' /* Viscous BCs: No-slip sides */')
110 jmc 1.44 c IF ( viscAz .NE. UNSET_RL ) THEN
111     c CALL WRITE_0D_R8( viscAz, INDEX_NONE,'viscAz =',
112     c & ' /* Vertical eddy viscosity ( m^2/s ) */')
113     c ENDIF
114     c IF ( viscAp .NE. UNSET_RL ) THEN
115     c CALL WRITE_0D_R8( viscAp, INDEX_NONE,'viscAp =',
116     c & ' /* Vertical eddy viscosity ( Pa^2/s ) */')
117     c ENDIF
118 heimbach 1.22 CALL WRITE_0D_R8( viscAr, INDEX_NONE,'viscAr =',
119 cnh 1.16 &' /* Vertical eddy viscosity ( units of r^2/s ) */')
120 heimbach 1.22 CALL WRITE_0D_R8( diffKhT, INDEX_NONE,'diffKhT =',
121 cnh 1.5 &' /* Laplacian diffusion of heat laterally ( m^2/s ) */')
122 heimbach 1.22 CALL WRITE_0D_R8( diffK4T, INDEX_NONE,'diffK4T =',
123 adcroft 1.20 &' /* Bihaarmonic diffusion of heat laterally ( m^4/s ) */')
124 jmc 1.44 c CALL WRITE_0D_R8( diffKzT, INDEX_NONE,'diffKzT =',
125     c &' /* Laplacian diffusion of heat vertically ( m^2/s ) */')
126 heimbach 1.22 CALL WRITE_0D_R8( diffKrT, INDEX_NONE,'diffKrT =',
127 adcroft 1.20 &' /* Laplacian diffusion of heat vertically ( m^2/s ) */')
128 heimbach 1.22 CALL WRITE_0D_R8( diffKhS, INDEX_NONE,'diffKhS =',
129 cnh 1.5 &' /* Laplacian diffusion of salt laterally ( m^2/s ) */')
130 heimbach 1.22 CALL WRITE_0D_R8( diffK4S, INDEX_NONE,'diffK4S =',
131 adcroft 1.20 &' /* Bihaarmonic diffusion of salt laterally ( m^4/s ) */')
132 jmc 1.44 c CALL WRITE_0D_R8( diffKzS, INDEX_NONE,'diffKzS =',
133     c &' /* Laplacian diffusion of salt vertically ( m^2/s ) */')
134 heimbach 1.22 CALL WRITE_0D_R8( diffKrS, INDEX_NONE,'diffKrS =',
135 adcroft 1.20 &' /* Laplacian diffusion of salt vertically ( m^2/s ) */')
136 adcroft 1.50 CALL WRITE_0D_R8( diffKrBL79surf, INDEX_NONE,'diffKrBL79surf =',
137     &' /* Surface diffusion for Bryan and Lewis 1979 ( m^2/s ) */')
138     CALL WRITE_0D_R8( diffKrBL79deep, INDEX_NONE,'diffKrBL79deep =',
139     &' /* Deep diffusion for Bryan and Lewis 1979 ( m^2/s ) */')
140     CALL WRITE_0D_R8( diffKrBL79scl, INDEX_NONE,'diffKrBL79scl =',
141     &' /* Depth scale for Bryan and Lewis 1979 ( m ) */')
142     CALL WRITE_0D_R8( diffKrBL79Ho, INDEX_NONE,'diffKrBL79Ho =',
143     &' /* Turning depth for Bryan and Lewis 1979 ( m ) */')
144 jmc 1.37 WRITE(msgBuf,'(2A)') ' Equation of State : eosType = ', eosType
145     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
146     & SQUEEZE_RIGHT , 1)
147 heimbach 1.22 CALL WRITE_0D_R8( tAlpha, INDEX_NONE,'tAlpha =',
148 cnh 1.6 &' /* Linear EOS thermal expansion coefficient ( 1/degree ) */')
149 heimbach 1.22 CALL WRITE_0D_R8( sBeta, INDEX_NONE,'sBeta =',
150 cnh 1.6 &' /* Linear EOS haline contraction coefficient ( 1/ppt ) */')
151 cnh 1.16 IF ( eosType .EQ. 'POLY3' ) THEN
152 cnh 1.17 WRITE(msgBuf,'(A)')
153     & '// Polynomial EQS parameters ( from POLY3.COEFFS ) '
154 cnh 1.16 DO K = 1, Nr
155     WRITE(msgBuf,'(I3,13F8.3)')
156     & K,eosRefT(K),eosRefS(K),eosSig0(K), (eosC(I,K),I=1,9)
157 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
158     & SQUEEZE_RIGHT , 1)
159 cnh 1.16 ENDDO
160     ENDIF
161 jmc 1.37 IF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
162     CALL WRITE_0D_R8( atm_Rd, INDEX_NONE, 'atm_Rd =',
163     & ' /* gas constant for dry air ( J/kg/K ) */')
164     CALL WRITE_0D_R8( atm_Cp, INDEX_NONE, 'atm_Cp =',
165     & ' /* specific heat (Cp) of dry air ( J/kg/K ) */')
166     CALL WRITE_0D_R8( atm_kappa, INDEX_NONE, 'atm_kappa =',
167     & ' /* kappa (=Rd/Cp ) of dry air */')
168 jmc 1.42 CALL WRITE_0D_R8( atm_Rq, INDEX_NONE, 'atm_Rq =',
169     & ' /* water vap. specific vol. anomaly relative to dry air */')
170 jmc 1.37 CALL WRITE_0D_R8( atm_Po, INDEX_NONE, 'atm_Po =',
171     & ' /* standard reference pressure ( Pa ) */')
172     CALL WRITE_0D_I( integr_GeoPot, INDEX_NONE, 'integr_GeoPot =',
173     & ' /* select how the geopotential is integrated */')
174     CALL WRITE_0D_I( selectFindRoSurf, INDEX_NONE,
175     & 'selectFindRoSurf=',
176     & ' /* select how Surf.Ref. pressure is defined */')
177     ENDIF
178 heimbach 1.22 CALL WRITE_0D_R8( rhonil, INDEX_NONE,'rhonil =',
179 cnh 1.6 &' /* Reference density ( kg/m^3 ) */')
180 heimbach 1.22 CALL WRITE_0D_R8( rhoConst, INDEX_NONE,'rhoConst =',
181 mlosch 1.35 &' /* Reference density ( kg/m^3 ) */')
182     CALL WRITE_0D_R8( rhoConstFresh, INDEX_NONE,'rhoConstFresh =',
183 adcroft 1.20 &' /* Reference density ( kg/m^3 ) */')
184 heimbach 1.22 CALL WRITE_0D_R8( gravity, INDEX_NONE,'gravity =',
185 cnh 1.6 &' /* Gravitational acceleration ( m/s^2 ) */')
186 jmc 1.29 CALL WRITE_0D_R8( gBaro, INDEX_NONE,'gBaro =',
187     &' /* Barotropic gravity ( m/s^2 ) */')
188 jmc 1.40 CALL WRITE_0D_R8(rotationPeriod,INDEX_NONE,'rotationPeriod =',
189     &' /* Rotation Period ( s ) */')
190     CALL WRITE_0D_R8( omega, INDEX_NONE,'omega =',
191     &' /* Angular velocity ( rad/s ) */')
192 heimbach 1.22 CALL WRITE_0D_R8( f0, INDEX_NONE,'f0 =',
193 cnh 1.6 &' /* Reference coriolis parameter ( 1/s ) */')
194 heimbach 1.22 CALL WRITE_0D_R8( beta, INDEX_NONE,'beta =',
195 cnh 1.6 &' /* Beta ( 1/(m.s) ) */')
196 jmc 1.31
197 heimbach 1.22 CALL WRITE_0D_R8( freeSurfFac, INDEX_NONE,'freeSurfFac =',
198 jmc 1.27 &' /* Implicit free surface factor */')
199 heimbach 1.22 CALL WRITE_0D_L( implicitFreeSurface, INDEX_NONE,
200 cnh 1.8 & 'implicitFreeSurface =',
201     &' /* Implicit free surface on/off flag */')
202 heimbach 1.22 CALL WRITE_0D_L( rigidLid, INDEX_NONE,
203 cnh 1.8 & 'rigidLid =',
204     &' /* Rigid lid on/off flag */')
205 jmc 1.27 CALL WRITE_0D_R8( implicSurfPress, INDEX_NONE,
206     &'implicSurfPress =',
207     &' /* Surface Pressure implicit factor (0-1)*/')
208     CALL WRITE_0D_R8( implicDiv2Dflow, INDEX_NONE,
209     &'implicDiv2Dflow =',
210     &' /* Barot. Flow Div. implicit factor (0-1)*/')
211 jmc 1.31 CALL WRITE_0D_L( exactConserv, INDEX_NONE,
212     &'exactConserv =',
213     &' /* Exact Volume Conservation on/off flag*/')
214     CALL WRITE_0D_L( uniformLin_PhiSurf, INDEX_NONE,
215     &'uniformLin_PhiSurf =',
216     &' /* use uniform Bo_surf on/off flag*/')
217     CALL WRITE_0D_I( nonlinFreeSurf, INDEX_NONE,
218     &'nonlinFreeSurf =',
219     &' /* Non-linear Free Surf. options (-1,0,1,2,3)*/')
220     WRITE(msgBuf,'(2A)') ' -1,0= Off ; 1,2,3= On,',
221     & ' 2=+rescale gU,gV, 3=+update cg2d solv.'
222     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
223     & SQUEEZE_RIGHT , 1)
224     CALL WRITE_0D_R8( hFacInf, INDEX_NONE,
225     &'hFacInf =',
226     &' /* lower threshold for hFac (nonlinFreeSurf only)*/')
227     CALL WRITE_0D_R8( hFacSup, INDEX_NONE,
228     &'hFacSup =',
229     &' /* upper threshold for hFac (nonlinFreeSurf only)*/')
230 jmc 1.38 CALL WRITE_0D_I( select_rStar, INDEX_NONE,
231     &'select_rStar =',
232     &' /* r* Coordinate options (not yet implemented)*/')
233 jmc 1.31 CALL WRITE_0D_L( useRealFreshWaterFlux, INDEX_NONE,
234     &'useRealFreshWaterFlux =',
235     &' /* Real Fresh Water Flux on/off flag*/')
236     IF (useRealFreshWaterFlux .AND. nonlinFreeSurf.GT.0) THEN
237     CALL WRITE_0D_R8( temp_EvPrRn, INDEX_NONE,
238     &'temp_EvPrRn =',
239     &' /* Temp. of Evap/Prec/R (UNSET=use local T)(oC)*/')
240     CALL WRITE_0D_R8( salt_EvPrRn, INDEX_NONE,
241     &'salt_EvPrRn =',
242     &' /* Salin. of Evap/Prec/R (UNSET=use local S)(ppt)*/')
243     CALL WRITE_0D_R8( trac_EvPrRn, INDEX_NONE,
244     &'trac_EvPrRn =',
245     &' /* Tracer in Evap/Prec/R (UNSET=use local Tr)*/')
246     ELSE
247     CALL WRITE_0D_R8( convertFW2Salt, INDEX_NONE,
248     &'convertFW2Salt =',
249     &' /* convert F.W. Flux to Salt Flux (-1=use local S)(ppt)*/')
250     ENDIF
251    
252 jmc 1.46 CALL WRITE_0D_L( nonHydrostatic, INDEX_NONE,
253     & 'nonHydrostatic =', ' /* Non-Hydrostatic on/off flag */')
254 heimbach 1.22 CALL WRITE_0D_L( momStepping, INDEX_NONE,
255 cnh 1.10 & 'momStepping =', ' /* Momentum equation on/off flag */')
256 heimbach 1.22 CALL WRITE_0D_L( momAdvection, INDEX_NONE,
257 cnh 1.10 & 'momAdvection =', ' /* Momentum advection on/off flag */')
258 heimbach 1.22 CALL WRITE_0D_L( momViscosity, INDEX_NONE,
259 cnh 1.9 & 'momViscosity =', ' /* Momentum viscosity on/off flag */')
260 jmc 1.46 CALL WRITE_0D_L( momImplVertAdv, INDEX_NONE, 'momImplVertAdv =',
261     & '/* Momentum implicit vert. advection on/off*/')
262     CALL WRITE_0D_L( implicitViscosity, INDEX_NONE,
263     & 'implicitViscosity =', ' /* Implicit viscosity on/off flag */')
264 heimbach 1.22 CALL WRITE_0D_L( useCoriolis, INDEX_NONE,
265 cnh 1.9 & 'useCoriolis =', ' /* Coriolis on/off flag */')
266 jmc 1.46 CALL WRITE_0D_L( useCDscheme, INDEX_NONE,
267     & 'useCDscheme =', ' /* CD scheme on/off flag */')
268     CALL WRITE_0D_L( useJamartWetPoints, INDEX_NONE,
269     & 'useJamartWetPoints=',' /* Coriolis WetPoints method flag */')
270 adcroft 1.51 CALL WRITE_0D_L( useJamartMomAdv, INDEX_NONE,
271     & 'useJamartMomAdv=',' /* V.I. Non-linear terms Jamart flag */')
272 adcroft 1.49 CALL WRITE_0D_L( SadournyCoriolis, INDEX_NONE,
273     & 'SadournyCoriolis=',' /* Sadourny Coriolis discr. flag */')
274     CALL WRITE_0D_L( upwindVorticity, INDEX_NONE,
275     & 'upwindVorticity=',' /* Upwind bias vorticity flag */')
276     CALL WRITE_0D_L( useAbsVorticity, INDEX_NONE,
277     & 'useAbsVorticity=',' /* Work with f+zeta in Coriolis */')
278     CALL WRITE_0D_L( highOrderVorticity, INDEX_NONE,
279     & 'highOrderVorticity=',' /* High order interp. of vort. flag */')
280 heimbach 1.22 CALL WRITE_0D_L( momForcing, INDEX_NONE,
281 cnh 1.9 & 'momForcing =', ' /* Momentum forcing on/off flag */')
282 heimbach 1.22 CALL WRITE_0D_L( momPressureForcing, INDEX_NONE,
283 cnh 1.17 & 'momPressureForcing =',
284     & ' /* Momentum pressure term on/off flag */')
285 jmc 1.46 CALL WRITE_0D_L( staggerTimeStep, INDEX_NONE,
286     & 'staggerTimeStep =',
287     &' /* Stagger time stepping on/off flag */')
288     CALL WRITE_0D_L( multiDimAdvection, INDEX_NONE,
289     & 'multiDimAdvection =',
290     &' /* enable/disable Multi-Dim Advection */')
291 jmc 1.53 CALL WRITE_0D_L( useMultiDimAdvec, INDEX_NONE,
292     & 'useMultiDimAdvec =',
293     &' /* Multi-Dim Advection is/is-not used */')
294 jmc 1.46 CALL WRITE_0D_L( implicitDiffusion, INDEX_NONE,
295     & 'implicitDiffusion =','/* Implicit Diffusion on/off flag */')
296 heimbach 1.22 CALL WRITE_0D_L( tempStepping, INDEX_NONE,
297 cnh 1.10 & 'tempStepping =', ' /* Temperature equation on/off flag */')
298 jmc 1.33 CALL WRITE_0D_L( tempAdvection, INDEX_NONE,
299     & 'tempAdvection=', ' /* Temperature advection on/off flag */')
300 jmc 1.46 CALL WRITE_0D_L( tempImplVertAdv,INDEX_NONE,'tempImplVertAdv =',
301     & '/* Temp. implicit vert. advection on/off */')
302 jmc 1.33 CALL WRITE_0D_L( tempForcing, INDEX_NONE,
303     & 'tempForcing =', ' /* Temperature forcing on/off flag */')
304     CALL WRITE_0D_L( saltStepping, INDEX_NONE,
305     & 'saltStepping =', ' /* Salinity equation on/off flag */')
306     CALL WRITE_0D_L( saltAdvection, INDEX_NONE,
307     & 'saltAdvection=', ' /* Salinity advection on/off flag */')
308 jmc 1.46 CALL WRITE_0D_L( saltImplVertAdv,INDEX_NONE,'saltImplVertAdv =',
309     & '/* Sali. implicit vert. advection on/off */')
310 jmc 1.33 CALL WRITE_0D_L( saltForcing, INDEX_NONE,
311     & 'saltForcing =', ' /* Salinity forcing on/off flag */')
312 cnh 1.6 WRITE(msgBuf,'(A)') '// '
313 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
314     & SQUEEZE_RIGHT , 1)
315 cnh 1.9
316 cnh 1.17 WRITE(msgBuf,'(A)')
317     & '// Elliptic solver(s) paramters ( PARM02 in namelist ) '
318     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
319     & SQUEEZE_RIGHT , 1)
320 cnh 1.6 WRITE(msgBuf,'(A)') '// '
321 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
322     & SQUEEZE_RIGHT , 1)
323 heimbach 1.22 CALL WRITE_0D_I( cg2dMaxIters, INDEX_NONE,'cg2dMaxIters =',
324 cnh 1.6 &' /* Upper limit on 2d con. grad iterations */')
325 heimbach 1.22 CALL WRITE_0D_I( cg2dChkResFreq, INDEX_NONE,'cg2dChkResFreq =',
326 cnh 1.6 &' /* 2d con. grad convergence test frequency */')
327 heimbach 1.22 CALL WRITE_0D_R8( cg2dTargetResidual, INDEX_NONE,
328 cnh 1.17 & 'cg2dTargetResidual =',
329 cnh 1.6 &' /* 2d con. grad target residual */')
330    
331     WRITE(msgBuf,'(A)') '// '
332 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
333     & SQUEEZE_RIGHT , 1)
334     WRITE(msgBuf,'(A)')
335     & '// Time stepping paramters ( PARM03 in namelist ) '
336     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
337     & SQUEEZE_RIGHT , 1)
338 cnh 1.6 WRITE(msgBuf,'(A)') '// '
339 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
340     & SQUEEZE_RIGHT , 1)
341 heimbach 1.22 CALL WRITE_0D_I( nIter0, INDEX_NONE,'nIter0 =',
342 cnh 1.6 &' /* Base timestep number */')
343 heimbach 1.22 CALL WRITE_0D_I( nTimeSteps, INDEX_NONE,'nTimeSteps =',
344 cnh 1.6 &' /* Number of timesteps */')
345 heimbach 1.22 CALL WRITE_0D_R8( deltaTmom, INDEX_NONE,'deltatTmom =',
346 cnh 1.6 &' /* Momentum equation timestep ( s ) */')
347 jmc 1.37 CALL WRITE_0D_R8( deltaTfreesurf,INDEX_NONE,'deltaTfreesurf =',
348     &' /* FreeSurface equation timestep ( s ) */')
349 heimbach 1.22 CALL WRITE_0D_R8( deltaTtracer, INDEX_NONE,'deltatTtracer =',
350 cnh 1.6 &' /* Tracer equation timestep ( s ) */')
351 heimbach 1.22 CALL WRITE_0D_R8( deltaTClock, INDEX_NONE,'deltatTClock =',
352 cnh 1.12 &' /* Model clock timestep ( s ) */')
353 heimbach 1.22 CALL WRITE_0D_R8( cAdjFreq, INDEX_NONE,'cAdjFreq =',
354 cnh 1.9 &' /* Convective adjustment interval ( s ) */')
355 jmc 1.33 CALL WRITE_0D_L( forcing_In_AB,INDEX_NONE,'forcing_In_AB =',
356     &' /* put T,S Forcing in Adams-Bash. stepping */')
357 heimbach 1.22 CALL WRITE_0D_R8( abeps, INDEX_NONE,'abeps =',
358 cnh 1.6 &' /* Adams-Bashforth stabilizing weight */')
359 jmc 1.41 IF (useCDscheme) THEN
360 heimbach 1.22 CALL WRITE_0D_R8( tauCD, INDEX_NONE,'tauCD =',
361 cnh 1.6 &' /* CD coupling time-scale ( s ) */')
362 heimbach 1.22 CALL WRITE_0D_R8( rCD, INDEX_NONE,'rCD =',
363 cnh 1.6 &' /* Normalised CD coupling parameter */')
364 jmc 1.41 ENDIF
365 heimbach 1.22 CALL WRITE_0D_R8( startTime, INDEX_NONE,'startTime =',
366 cnh 1.6 &' /* Run start time ( s ). */')
367 heimbach 1.22 CALL WRITE_0D_R8( endTime, INDEX_NONE,'endTime =',
368 cnh 1.6 &' /* Integration ending time ( s ). */')
369 heimbach 1.22 CALL WRITE_0D_R8( pChkPtFreq, INDEX_NONE,'pChkPtFreq =',
370 cnh 1.7 &' /* Permanent restart/checkpoint file interval ( s ). */')
371 heimbach 1.22 CALL WRITE_0D_R8( chkPtFreq, INDEX_NONE,'chkPtFreq =',
372 cnh 1.7 &' /* Rolling restart/checkpoint file interval ( s ). */')
373 heimbach 1.22 CALL WRITE_0D_R8( dumpFreq, INDEX_NONE,'dumpFreq =',
374 cnh 1.6 &' /* Model state write out interval ( s ). */')
375 jmc 1.43 CALL WRITE_0D_R8( externForcingPeriod, INDEX_NONE,
376     & 'externForcingPeriod =', ' /* forcing period (s) */')
377     CALL WRITE_0D_R8( externForcingCycle, INDEX_NONE,
378     & 'externForcingCycle =', ' /* period of the cyle (s). */')
379     CALL WRITE_0D_R8( tauThetaClimRelax, INDEX_NONE,
380     & 'tauThetaClimRelax =', ' /* relaxation time scale (s) */')
381     CALL WRITE_0D_R8( tauSaltClimRelax, INDEX_NONE,
382     & 'tauSaltClimRelax =', ' /* relaxation time scale (s) */')
383     CALL WRITE_0D_R8( latBandClimRelax, INDEX_NONE,
384     & 'latBandClimRelax =', ' /* max. Lat. where relaxation */')
385 cnh 1.6 WRITE(msgBuf,'(A)') '// '
386 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
387     & SQUEEZE_RIGHT , 1)
388     WRITE(msgBuf,'(A)')
389     & '// Gridding paramters ( PARM04 in namelist ) '
390     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
391     & SQUEEZE_RIGHT , 1)
392 cnh 1.6 WRITE(msgBuf,'(A)') '// '
393 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
394     & SQUEEZE_RIGHT , 1)
395 heimbach 1.22 CALL WRITE_0D_L( usingCartesianGrid, INDEX_NONE,
396 cnh 1.17 & 'usingCartesianGrid =',
397 cnh 1.6 &' /* Cartesian coordinates flag ( True / False ) */')
398 heimbach 1.22 CALL WRITE_0D_L( usingSphericalPolarGrid, INDEX_NONE,
399 cnh 1.17 & 'usingSphericalPolarGrid =',
400 cnh 1.6 &' /* Spherical coordinates flag ( True / False ) */')
401 afe 1.52 CALL WRITE_0D_L( usingCylindricalGrid, INDEX_NONE,
402     & 'usingCylindricalGrid =',
403     &' /* Spherical coordinates flag ( True / False ) */')
404 adcroft 1.24 CALL WRITE_0D_L( groundAtK1, INDEX_NONE, 'groundAtK1 =',
405     &' /* Lower Boundary (ground) at the surface(k=1) ( T / F ) */')
406 adcroft 1.36 CALL WRITE_0D_R8( Ro_SeaLevel, INDEX_NONE,'Ro_SeaLevel =',
407 adcroft 1.24 &' /* r(1) ( units of r ) */')
408 adcroft 1.36 CALL WRITE_0D_R8( rkFac, INDEX_NONE,'rkFac =',
409 adcroft 1.24 &' /* minus Vertical index orientation */')
410 adcroft 1.36 CALL WRITE_0D_R8( horiVertRatio, INDEX_NONE,'horiVertRatio =',
411 adcroft 1.24 &' /* Ratio on units : Horiz - Vertical */')
412 jmc 1.32 c CALL WRITE_1D_R8( delZ,Nr, INDEX_K,'delZ = ',
413     c &' /* W spacing ( m ) */')
414     c CALL WRITE_1D_R8( delP,Nr, INDEX_K,'delP = ',
415     c &' /* W spacing ( Pa ) */')
416     c CALL WRITE_1D_R8( delR,Nr, INDEX_K,'delR = ',
417     c &' /* W spacing ( units of r ) */')
418     CALL WRITE_1D_R8( drC,Nr, INDEX_K,'drC = ',
419     &' /* C spacing ( units of r ) */')
420     CALL WRITE_1D_R8( drF,Nr, INDEX_K,'drF = ',
421 cnh 1.15 &' /* W spacing ( units of r ) */')
422 cnh 1.6 CALL WRITE_1D_R8( delX, Nx, INDEX_I,'delX = ',
423     &' /* U spacing ( m - cartesian, degrees - spherical ) */')
424     CALL WRITE_1D_R8( delY, Ny, INDEX_J,'delY = ',
425     &' /* V spacing ( m - cartesian, degrees - spherical ) */')
426 heimbach 1.22 CALL WRITE_0D_R8( phiMin, INDEX_NONE,'phiMin = ',
427 cnh 1.17 &' /* South edge (ignored - cartesian, degrees - spherical ) */')
428 heimbach 1.22 CALL WRITE_0D_R8( thetaMin, INDEX_NONE,'thetaMin = ',
429 cnh 1.17 &' /* West edge ( ignored - cartesian, degrees - spherical ) */')
430 heimbach 1.22 CALL WRITE_0D_R8( rSphere, INDEX_NONE,'rSphere = ',
431 cnh 1.6 &' /* Radius ( ignored - cartesian, m - spherical ) */')
432     DO bi=1,nSx
433     DO I=1,sNx
434 heimbach 1.22 xcoord((bi-1)*sNx+I) = xC(I,1,bi,1)
435 cnh 1.6 ENDDO
436     ENDDO
437 cnh 1.11 CALL WRITE_1D_R8( xcoord, sNx*nSx, INDEX_I,'xcoord = ',
438 cnh 1.17 &' /* P-point X coord ( m - cartesian, degrees - spherical ) */')
439 cnh 1.6 DO bj=1,nSy
440     DO J=1,sNy
441 heimbach 1.22 ycoord((bj-1)*sNy+J) = yC(1,J,1,bj)
442 cnh 1.6 ENDDO
443     ENDDO
444 cnh 1.11 CALL WRITE_1D_R8( ycoord, sNy*nSy, INDEX_J,'ycoord = ',
445 cnh 1.17 &' /* P-point Y coord ( m - cartesian, degrees - spherical ) */')
446 cnh 1.13 DO K=1,Nr
447 heimbach 1.22 rcoord(K) = rC(K)
448 cnh 1.6 ENDDO
449 cnh 1.13 CALL WRITE_1D_R8( rcoord, Nr, INDEX_K,'rcoord = ',
450     &' /* P-point R coordinate ( units of r ) */')
451 jmc 1.32 DO K=1,Nr+1
452     rcoord(K) = rF(K)
453     ENDDO
454     CALL WRITE_1D_R8( rcoord, Nr+1, INDEX_K,'rF = ',
455     &' /* W-Interf. R coordinate ( units of r ) */')
456 cnh 1.6
457 cnh 1.26 C Grid along selected grid lines
458     coordLine = 1
459     tileLine = 1
460     CALL WRITE_XY_XLINE_RS( dxF, coordLine, tileLine,
461     I 'dxF','( m - cartesian, degrees - spherical )')
462     CALL WRITE_XY_YLINE_RS( dxF, coordLine, tileLine,
463     I 'dxF','( m - cartesian, degrees - spherical )')
464     CALL WRITE_XY_XLINE_RS( dyF, coordLine, tileLine,
465     I 'dyF','( m - cartesian, degrees - spherical )')
466     CALL WRITE_XY_YLINE_RS( dyF, coordLine, tileLine,
467     I 'dyF','( m - cartesian, degrees - spherical )')
468     CALL WRITE_XY_XLINE_RS( dxG, coordLine, tileLine,
469     I 'dxG','( m - cartesian, degrees - spherical )')
470     CALL WRITE_XY_YLINE_RS( dxG, coordLine, tileLine,
471     I 'dxG','( m - cartesian, degrees - spherical )')
472     CALL WRITE_XY_XLINE_RS( dyG, coordLine, tileLine,
473     I 'dyG','( m - cartesian, degrees - spherical )')
474     CALL WRITE_XY_YLINE_RS( dyG, coordLine, tileLine,
475     I 'dyG','( m - cartesian, degrees - spherical )')
476     CALL WRITE_XY_XLINE_RS( dxC, coordLine, tileLine,
477     I 'dxC','( m - cartesian, degrees - spherical )')
478     CALL WRITE_XY_YLINE_RS( dxC, coordLine, tileLine,
479     I 'dxC','( m - cartesian, degrees - spherical )')
480     CALL WRITE_XY_XLINE_RS( dyC, coordLine, tileLine,
481     I 'dyC','( m - cartesian, degrees - spherical )')
482     CALL WRITE_XY_YLINE_RS( dyC, coordLine, tileLine,
483     I 'dyC','( m - cartesian, degrees - spherical )')
484     CALL WRITE_XY_XLINE_RS( dxV, coordLine, tileLine,
485     I 'dxV','( m - cartesian, degrees - spherical )')
486     CALL WRITE_XY_YLINE_RS( dxV, coordLine, tileLine,
487     I 'dxV','( m - cartesian, degrees - spherical )')
488     CALL WRITE_XY_XLINE_RS( dyU, coordLine, tileLine,
489     I 'dyU','( m - cartesian, degrees - spherical )')
490     CALL WRITE_XY_YLINE_RS( dyU, coordLine, tileLine,
491     I 'dyU','( m - cartesian, degrees - spherical )')
492     CALL WRITE_XY_XLINE_RS( rA, coordLine, tileLine,
493     I 'rA','( m - cartesian, degrees - spherical )')
494     CALL WRITE_XY_YLINE_RS( rA, coordLine, tileLine,
495     I 'rA','( m - cartesian, degrees - spherical )')
496     CALL WRITE_XY_XLINE_RS( rAw, coordLine, tileLine,
497     I 'rAw','( m - cartesian, degrees - spherical )')
498     CALL WRITE_XY_YLINE_RS( rAw, coordLine, tileLine,
499     I 'rAw','( m - cartesian, degrees - spherical )')
500     CALL WRITE_XY_XLINE_RS( rAs, coordLine, tileLine,
501     I 'rAs','( m - cartesian, degrees - spherical )')
502     CALL WRITE_XY_YLINE_RS( rAs, coordLine, tileLine,
503     I 'rAs','( m - cartesian, degrees - spherical )')
504 cnh 1.5
505 cnh 1.1 WRITE(msgBuf,'(A)') ' '
506     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
507     & SQUEEZE_RIGHT , 1)
508 cnh 1.5
509 cnh 1.1 _END_MASTER(myThid)
510     _BARRIER
511    
512    
513     RETURN
514     100 FORMAT(A,
515 cnh 1.4 &' '
516 cnh 1.1 &)
517     END
518    

  ViewVC Help
Powered by ViewVC 1.1.22