/[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.71 - (hide annotations) (download)
Thu Mar 10 17:41:37 2005 UTC (19 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57f_pre
Changes since 1.70: +5 -9 lines
make the comments shorter.

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

  ViewVC Help
Powered by ViewVC 1.1.22