/[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.57 - (hide annotations) (download)
Fri Sep 10 12:19:29 2004 UTC (20 years ago) by edhill
Branch: MAIN
Changes since 1.56: +41 -23 lines
 o overhaul of IO so that we now have flags for MDSIO and/or MNC
   - all verification tests compile and run with linux_ia32_g77
   - defaults are compatible with current input files--nothing
     should change if you were not previously using MNC
   - MNC output has been added in numerous places (eg. timeave)
     but there are still a few writes not yet do-able with MNC
     (this is in progress)
   - flags now allow for either/or/both use of MDSIO and MNC and
     documentation will soon follow
   - numerous small formatting cleanups for ProTeX

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

  ViewVC Help
Powered by ViewVC 1.1.22