/[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.34 - (hide annotations) (download)
Wed Aug 7 16:55:52 2002 UTC (21 years, 9 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint46g_pre, checkpoint46f_post, checkpoint46b_post, checkpoint46d_pre, checkpoint46e_pre, checkpoint46c_pre, checkpoint46h_pre, checkpoint46g_post, checkpoint46c_post, checkpoint46e_post, checkpoint46d_post
Changes since 1.33: +2 -1 lines
o Added new equation of state -> JMD95Z and JMD95P
  - EOS of Jackett and McDougall, 1995, JPO
  - moved all EOS parameters into EOS.h
  - new routines ini_eos.F, store_pressure.F
o Added UNESCO EOS, but not recommended because it requires
  in-situ temperature (see JMD95)
o Modified formatting for knudsen2.f in utils/knudsen2 and added
  unesco.f to be used with POLY3

1 mlosch 1.34 C $Header: /u/gcmpack/MITgcm/model/src/config_summary.F,v 1.33 2002/06/15 03:28:39 jmc 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 cnh 1.13 CALL WRITE_1D_R8( tRef, Nr, INDEX_K,'tRef =',
86 cnh 1.5 &' /* Reference temperature profile ( oC or oK ) */')
87 cnh 1.13 CALL WRITE_1D_R8( sRef, Nr, INDEX_K,'sRef =',
88 cnh 1.6 &' /* Reference salinity profile ( ppt ) */')
89 heimbach 1.22 CALL WRITE_0D_R8( viscAh, INDEX_NONE,'viscAh =',
90 cnh 1.5 &' /* Lateral eddy viscosity ( m^2/s ) */')
91 heimbach 1.22 CALL WRITE_0D_R8( viscA4, INDEX_NONE,'viscAh =',
92 cnh 1.14 &' /* Lateral biharmonic viscosity ( m^4/s ) */')
93 heimbach 1.22 CALL WRITE_0D_L( no_slip_sides, INDEX_NONE,
94 adcroft 1.20 & 'no_slip_sides =', ' /* Viscous BCs: No-slip sides */')
95 cnh 1.16 IF ( viscAz .NE. UNSET_RL ) THEN
96 heimbach 1.22 CALL WRITE_0D_R8( viscAz, INDEX_NONE,'viscAz =',
97 cnh 1.16 & ' /* Vertical eddy viscosity ( m^2/s ) */')
98     ENDIF
99     IF ( viscAp .NE. UNSET_RL ) THEN
100 heimbach 1.22 CALL WRITE_0D_R8( viscAp, INDEX_NONE,'viscAp =',
101 cnh 1.16 & ' /* Vertical eddy viscosity ( Pa^2/s ) */')
102     ENDIF
103 heimbach 1.22 CALL WRITE_0D_R8( viscAr, INDEX_NONE,'viscAr =',
104 cnh 1.16 &' /* Vertical eddy viscosity ( units of r^2/s ) */')
105 heimbach 1.22 CALL WRITE_0D_R8( diffKhT, INDEX_NONE,'diffKhT =',
106 cnh 1.5 &' /* Laplacian diffusion of heat laterally ( m^2/s ) */')
107 heimbach 1.22 CALL WRITE_0D_R8( diffK4T, INDEX_NONE,'diffK4T =',
108 adcroft 1.20 &' /* Bihaarmonic diffusion of heat laterally ( m^4/s ) */')
109 heimbach 1.22 CALL WRITE_0D_R8( diffKzT, INDEX_NONE,'diffKzT =',
110 cnh 1.5 &' /* Laplacian diffusion of heat vertically ( m^2/s ) */')
111 heimbach 1.22 CALL WRITE_0D_R8( diffKrT, INDEX_NONE,'diffKrT =',
112 adcroft 1.20 &' /* Laplacian diffusion of heat vertically ( m^2/s ) */')
113 heimbach 1.22 CALL WRITE_0D_R8( diffKhS, INDEX_NONE,'diffKhS =',
114 cnh 1.5 &' /* Laplacian diffusion of salt laterally ( m^2/s ) */')
115 heimbach 1.22 CALL WRITE_0D_R8( diffK4S, INDEX_NONE,'diffK4S =',
116 adcroft 1.20 &' /* Bihaarmonic diffusion of salt laterally ( m^4/s ) */')
117 heimbach 1.22 CALL WRITE_0D_R8( diffKzS, INDEX_NONE,'diffKzS =',
118 cnh 1.5 &' /* Laplacian diffusion of salt vertically ( m^2/s ) */')
119 heimbach 1.22 CALL WRITE_0D_R8( diffKrS, INDEX_NONE,'diffKrS =',
120 adcroft 1.20 &' /* Laplacian diffusion of salt vertically ( m^2/s ) */')
121 heimbach 1.22 CALL WRITE_0D_R8( tAlpha, INDEX_NONE,'tAlpha =',
122 cnh 1.6 &' /* Linear EOS thermal expansion coefficient ( 1/degree ) */')
123 heimbach 1.22 CALL WRITE_0D_R8( sBeta, INDEX_NONE,'sBeta =',
124 cnh 1.6 &' /* Linear EOS haline contraction coefficient ( 1/ppt ) */')
125 cnh 1.16 IF ( eosType .EQ. 'POLY3' ) THEN
126 cnh 1.17 WRITE(msgBuf,'(A)')
127     & '// Polynomial EQS parameters ( from POLY3.COEFFS ) '
128 cnh 1.16 DO K = 1, Nr
129     WRITE(msgBuf,'(I3,13F8.3)')
130     & K,eosRefT(K),eosRefS(K),eosSig0(K), (eosC(I,K),I=1,9)
131 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
132     & SQUEEZE_RIGHT , 1)
133 cnh 1.16 ENDDO
134     ENDIF
135 heimbach 1.22 CALL WRITE_0D_R8( rhonil, INDEX_NONE,'rhonil =',
136 cnh 1.6 &' /* Reference density ( kg/m^3 ) */')
137 heimbach 1.22 CALL WRITE_0D_R8( rhoConst, INDEX_NONE,'rhoConst =',
138 adcroft 1.20 &' /* Reference density ( kg/m^3 ) */')
139 heimbach 1.22 CALL WRITE_0D_R8( gravity, INDEX_NONE,'gravity =',
140 cnh 1.6 &' /* Gravitational acceleration ( m/s^2 ) */')
141 jmc 1.29 CALL WRITE_0D_R8( gBaro, INDEX_NONE,'gBaro =',
142     &' /* Barotropic gravity ( m/s^2 ) */')
143 heimbach 1.22 CALL WRITE_0D_R8( f0, INDEX_NONE,'f0 =',
144 cnh 1.6 &' /* Reference coriolis parameter ( 1/s ) */')
145 heimbach 1.22 CALL WRITE_0D_R8( beta, INDEX_NONE,'beta =',
146 cnh 1.6 &' /* Beta ( 1/(m.s) ) */')
147 jmc 1.31
148 heimbach 1.22 CALL WRITE_0D_R8( freeSurfFac, INDEX_NONE,'freeSurfFac =',
149 jmc 1.27 &' /* Implicit free surface factor */')
150 heimbach 1.22 CALL WRITE_0D_L( implicitFreeSurface, INDEX_NONE,
151 cnh 1.8 & 'implicitFreeSurface =',
152     &' /* Implicit free surface on/off flag */')
153 heimbach 1.22 CALL WRITE_0D_L( rigidLid, INDEX_NONE,
154 cnh 1.8 & 'rigidLid =',
155     &' /* Rigid lid on/off flag */')
156 jmc 1.27 CALL WRITE_0D_R8( implicSurfPress, INDEX_NONE,
157     &'implicSurfPress =',
158     &' /* Surface Pressure implicit factor (0-1)*/')
159     CALL WRITE_0D_R8( implicDiv2Dflow, INDEX_NONE,
160     &'implicDiv2Dflow =',
161     &' /* Barot. Flow Div. implicit factor (0-1)*/')
162 jmc 1.31 CALL WRITE_0D_L( exactConserv, INDEX_NONE,
163     &'exactConserv =',
164     &' /* Exact Volume Conservation on/off flag*/')
165     CALL WRITE_0D_L( uniformLin_PhiSurf, INDEX_NONE,
166     &'uniformLin_PhiSurf =',
167     &' /* use uniform Bo_surf on/off flag*/')
168     CALL WRITE_0D_I( nonlinFreeSurf, INDEX_NONE,
169     &'nonlinFreeSurf =',
170     &' /* Non-linear Free Surf. options (-1,0,1,2,3)*/')
171     WRITE(msgBuf,'(2A)') ' -1,0= Off ; 1,2,3= On,',
172     & ' 2=+rescale gU,gV, 3=+update cg2d solv.'
173     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
174     & SQUEEZE_RIGHT , 1)
175     CALL WRITE_0D_R8( hFacInf, INDEX_NONE,
176     &'hFacInf =',
177     &' /* lower threshold for hFac (nonlinFreeSurf only)*/')
178     CALL WRITE_0D_R8( hFacSup, INDEX_NONE,
179     &'hFacSup =',
180     &' /* upper threshold for hFac (nonlinFreeSurf only)*/')
181     CALL WRITE_0D_L( useRealFreshWaterFlux, INDEX_NONE,
182     &'useRealFreshWaterFlux =',
183     &' /* Real Fresh Water Flux on/off flag*/')
184     IF (useRealFreshWaterFlux .AND. nonlinFreeSurf.GT.0) THEN
185     CALL WRITE_0D_R8( temp_EvPrRn, INDEX_NONE,
186     &'temp_EvPrRn =',
187     &' /* Temp. of Evap/Prec/R (UNSET=use local T)(oC)*/')
188     CALL WRITE_0D_R8( salt_EvPrRn, INDEX_NONE,
189     &'salt_EvPrRn =',
190     &' /* Salin. of Evap/Prec/R (UNSET=use local S)(ppt)*/')
191     CALL WRITE_0D_R8( trac_EvPrRn, INDEX_NONE,
192     &'trac_EvPrRn =',
193     &' /* Tracer in Evap/Prec/R (UNSET=use local Tr)*/')
194     ELSE
195     CALL WRITE_0D_R8( convertFW2Salt, INDEX_NONE,
196     &'convertFW2Salt =',
197     &' /* convert F.W. Flux to Salt Flux (-1=use local S)(ppt)*/')
198     ENDIF
199    
200 jmc 1.33 CALL WRITE_0D_L( multiDimAdvection, INDEX_NONE,
201     & 'multiDimAdvection =',
202     &' /* enable/disable Multi-Dim Advection */')
203 jmc 1.27 CALL WRITE_0D_L( staggerTimeStep, INDEX_NONE,
204     & 'staggerTimeStep =',
205     &' /* Stagger time stepping on/off flag */')
206 heimbach 1.22 CALL WRITE_0D_L( momStepping, INDEX_NONE,
207 cnh 1.10 & 'momStepping =', ' /* Momentum equation on/off flag */')
208 heimbach 1.22 CALL WRITE_0D_L( momAdvection, INDEX_NONE,
209 cnh 1.10 & 'momAdvection =', ' /* Momentum advection on/off flag */')
210 heimbach 1.22 CALL WRITE_0D_L( momViscosity, INDEX_NONE,
211 cnh 1.9 & 'momViscosity =', ' /* Momentum viscosity on/off flag */')
212 heimbach 1.22 CALL WRITE_0D_L( useCoriolis, INDEX_NONE,
213 cnh 1.9 & 'useCoriolis =', ' /* Coriolis on/off flag */')
214 heimbach 1.22 CALL WRITE_0D_L( momForcing, INDEX_NONE,
215 cnh 1.9 & 'momForcing =', ' /* Momentum forcing on/off flag */')
216 heimbach 1.22 CALL WRITE_0D_L( momPressureForcing, INDEX_NONE,
217 cnh 1.17 & 'momPressureForcing =',
218     & ' /* Momentum pressure term on/off flag */')
219 heimbach 1.22 CALL WRITE_0D_L( tempStepping, INDEX_NONE,
220 cnh 1.10 & 'tempStepping =', ' /* Temperature equation on/off flag */')
221 jmc 1.33 CALL WRITE_0D_L( tempAdvection, INDEX_NONE,
222     & 'tempAdvection=', ' /* Temperature advection on/off flag */')
223     CALL WRITE_0D_L( tempForcing, INDEX_NONE,
224     & 'tempForcing =', ' /* Temperature forcing on/off flag */')
225     CALL WRITE_0D_L( saltStepping, INDEX_NONE,
226     & 'saltStepping =', ' /* Salinity equation on/off flag */')
227     CALL WRITE_0D_L( saltAdvection, INDEX_NONE,
228     & 'saltAdvection=', ' /* Salinity advection on/off flag */')
229     CALL WRITE_0D_L( saltForcing, INDEX_NONE,
230     & 'saltForcing =', ' /* Salinity forcing on/off flag */')
231 heimbach 1.22 CALL WRITE_0D_L( nonHydrostatic, INDEX_NONE,
232 adcroft 1.20 & 'nonHydrostatic =', ' /* Non-Hydrostatic on/off flag */')
233 cnh 1.6 WRITE(msgBuf,'(A)') '// '
234 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
235     & SQUEEZE_RIGHT , 1)
236 cnh 1.9
237 cnh 1.17 WRITE(msgBuf,'(A)')
238     & '// Elliptic solver(s) paramters ( PARM02 in namelist ) '
239     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
240     & SQUEEZE_RIGHT , 1)
241 cnh 1.6 WRITE(msgBuf,'(A)') '// '
242 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
243     & SQUEEZE_RIGHT , 1)
244 heimbach 1.22 CALL WRITE_0D_I( cg2dMaxIters, INDEX_NONE,'cg2dMaxIters =',
245 cnh 1.6 &' /* Upper limit on 2d con. grad iterations */')
246 heimbach 1.22 CALL WRITE_0D_I( cg2dChkResFreq, INDEX_NONE,'cg2dChkResFreq =',
247 cnh 1.6 &' /* 2d con. grad convergence test frequency */')
248 heimbach 1.22 CALL WRITE_0D_R8( cg2dTargetResidual, INDEX_NONE,
249 cnh 1.17 & 'cg2dTargetResidual =',
250 cnh 1.6 &' /* 2d con. grad target residual */')
251    
252     WRITE(msgBuf,'(A)') '// '
253 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
254     & SQUEEZE_RIGHT , 1)
255     WRITE(msgBuf,'(A)')
256     & '// Time stepping paramters ( PARM03 in namelist ) '
257     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
258     & SQUEEZE_RIGHT , 1)
259 cnh 1.6 WRITE(msgBuf,'(A)') '// '
260 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
261     & SQUEEZE_RIGHT , 1)
262 heimbach 1.22 CALL WRITE_0D_I( nIter0, INDEX_NONE,'nIter0 =',
263 cnh 1.6 &' /* Base timestep number */')
264 heimbach 1.22 CALL WRITE_0D_I( nTimeSteps, INDEX_NONE,'nTimeSteps =',
265 cnh 1.6 &' /* Number of timesteps */')
266 heimbach 1.22 CALL WRITE_0D_R8( deltaTmom, INDEX_NONE,'deltatTmom =',
267 cnh 1.6 &' /* Momentum equation timestep ( s ) */')
268 heimbach 1.22 CALL WRITE_0D_R8( deltaTtracer, INDEX_NONE,'deltatTtracer =',
269 cnh 1.6 &' /* Tracer equation timestep ( s ) */')
270 heimbach 1.22 CALL WRITE_0D_R8( deltaTClock, INDEX_NONE,'deltatTClock =',
271 cnh 1.12 &' /* Model clock timestep ( s ) */')
272 heimbach 1.22 CALL WRITE_0D_R8( cAdjFreq, INDEX_NONE,'cAdjFreq =',
273 cnh 1.9 &' /* Convective adjustment interval ( s ) */')
274 jmc 1.33 CALL WRITE_0D_L( forcing_In_AB,INDEX_NONE,'forcing_In_AB =',
275     &' /* put T,S Forcing in Adams-Bash. stepping */')
276 heimbach 1.22 CALL WRITE_0D_R8( abeps, INDEX_NONE,'abeps =',
277 cnh 1.6 &' /* Adams-Bashforth stabilizing weight */')
278 heimbach 1.22 CALL WRITE_0D_R8( tauCD, INDEX_NONE,'tauCD =',
279 cnh 1.6 &' /* CD coupling time-scale ( s ) */')
280 heimbach 1.22 CALL WRITE_0D_R8( rCD, INDEX_NONE,'rCD =',
281 cnh 1.6 &' /* Normalised CD coupling parameter */')
282 heimbach 1.22 CALL WRITE_0D_R8( startTime, INDEX_NONE,'startTime =',
283 cnh 1.6 &' /* Run start time ( s ). */')
284 heimbach 1.22 CALL WRITE_0D_R8( endTime, INDEX_NONE,'endTime =',
285 cnh 1.6 &' /* Integration ending time ( s ). */')
286 heimbach 1.22 CALL WRITE_0D_R8( pChkPtFreq, INDEX_NONE,'pChkPtFreq =',
287 cnh 1.7 &' /* Permanent restart/checkpoint file interval ( s ). */')
288 heimbach 1.22 CALL WRITE_0D_R8( chkPtFreq, INDEX_NONE,'chkPtFreq =',
289 cnh 1.7 &' /* Rolling restart/checkpoint file interval ( s ). */')
290 heimbach 1.22 CALL WRITE_0D_R8( dumpFreq, INDEX_NONE,'dumpFreq =',
291 cnh 1.6 &' /* Model state write out interval ( s ). */')
292    
293     WRITE(msgBuf,'(A)') '// '
294 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
295     & SQUEEZE_RIGHT , 1)
296     WRITE(msgBuf,'(A)')
297     & '// Gridding paramters ( PARM04 in namelist ) '
298     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
299     & SQUEEZE_RIGHT , 1)
300 cnh 1.6 WRITE(msgBuf,'(A)') '// '
301 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
302     & SQUEEZE_RIGHT , 1)
303 heimbach 1.22 CALL WRITE_0D_L( usingCartesianGrid, INDEX_NONE,
304 cnh 1.17 & 'usingCartesianGrid =',
305 cnh 1.6 &' /* Cartesian coordinates flag ( True / False ) */')
306 heimbach 1.22 CALL WRITE_0D_L( usingSphericalPolarGrid, INDEX_NONE,
307 cnh 1.17 & 'usingSphericalPolarGrid =',
308 cnh 1.6 &' /* Spherical coordinates flag ( True / False ) */')
309 adcroft 1.24 CALL WRITE_0D_L( groundAtK1, INDEX_NONE, 'groundAtK1 =',
310     &' /* Lower Boundary (ground) at the surface(k=1) ( T / F ) */')
311     CALL WRITE_1D_R8( Ro_SeaLevel,1, INDEX_NONE,'Ro_SeaLevel =',
312     &' /* r(1) ( units of r ) */')
313     CALL WRITE_1D_R8( rkFac,1, INDEX_NONE,'rkFac =',
314     &' /* minus Vertical index orientation */')
315     CALL WRITE_1D_R8( horiVertRatio,1, INDEX_NONE,'horiVertRatio =',
316     &' /* Ratio on units : Horiz - Vertical */')
317 jmc 1.32 c CALL WRITE_1D_R8( delZ,Nr, INDEX_K,'delZ = ',
318     c &' /* W spacing ( m ) */')
319     c CALL WRITE_1D_R8( delP,Nr, INDEX_K,'delP = ',
320     c &' /* W spacing ( Pa ) */')
321     c CALL WRITE_1D_R8( delR,Nr, INDEX_K,'delR = ',
322     c &' /* W spacing ( units of r ) */')
323     CALL WRITE_1D_R8( drC,Nr, INDEX_K,'drC = ',
324     &' /* C spacing ( units of r ) */')
325     CALL WRITE_1D_R8( drF,Nr, INDEX_K,'drF = ',
326 cnh 1.15 &' /* W spacing ( units of r ) */')
327 cnh 1.6 CALL WRITE_1D_R8( delX, Nx, INDEX_I,'delX = ',
328     &' /* U spacing ( m - cartesian, degrees - spherical ) */')
329     CALL WRITE_1D_R8( delY, Ny, INDEX_J,'delY = ',
330     &' /* V spacing ( m - cartesian, degrees - spherical ) */')
331 heimbach 1.22 CALL WRITE_0D_R8( phiMin, INDEX_NONE,'phiMin = ',
332 cnh 1.17 &' /* South edge (ignored - cartesian, degrees - spherical ) */')
333 heimbach 1.22 CALL WRITE_0D_R8( thetaMin, INDEX_NONE,'thetaMin = ',
334 cnh 1.17 &' /* West edge ( ignored - cartesian, degrees - spherical ) */')
335 heimbach 1.22 CALL WRITE_0D_R8( rSphere, INDEX_NONE,'rSphere = ',
336 cnh 1.6 &' /* Radius ( ignored - cartesian, m - spherical ) */')
337     DO bi=1,nSx
338     DO I=1,sNx
339 heimbach 1.22 xcoord((bi-1)*sNx+I) = xC(I,1,bi,1)
340 cnh 1.6 ENDDO
341     ENDDO
342 cnh 1.11 CALL WRITE_1D_R8( xcoord, sNx*nSx, INDEX_I,'xcoord = ',
343 cnh 1.17 &' /* P-point X coord ( m - cartesian, degrees - spherical ) */')
344 cnh 1.6 DO bj=1,nSy
345     DO J=1,sNy
346 heimbach 1.22 ycoord((bj-1)*sNy+J) = yC(1,J,1,bj)
347 cnh 1.6 ENDDO
348     ENDDO
349 cnh 1.11 CALL WRITE_1D_R8( ycoord, sNy*nSy, INDEX_J,'ycoord = ',
350 cnh 1.17 &' /* P-point Y coord ( m - cartesian, degrees - spherical ) */')
351 cnh 1.13 DO K=1,Nr
352 heimbach 1.22 rcoord(K) = rC(K)
353 cnh 1.6 ENDDO
354 cnh 1.13 CALL WRITE_1D_R8( rcoord, Nr, INDEX_K,'rcoord = ',
355     &' /* P-point R coordinate ( units of r ) */')
356 jmc 1.32 DO K=1,Nr+1
357     rcoord(K) = rF(K)
358     ENDDO
359     CALL WRITE_1D_R8( rcoord, Nr+1, INDEX_K,'rF = ',
360     &' /* W-Interf. R coordinate ( units of r ) */')
361 cnh 1.6
362 cnh 1.26 C Grid along selected grid lines
363     coordLine = 1
364     tileLine = 1
365     CALL WRITE_XY_XLINE_RS( dxF, coordLine, tileLine,
366     I 'dxF','( m - cartesian, degrees - spherical )')
367     CALL WRITE_XY_YLINE_RS( dxF, coordLine, tileLine,
368     I 'dxF','( m - cartesian, degrees - spherical )')
369     CALL WRITE_XY_XLINE_RS( dyF, coordLine, tileLine,
370     I 'dyF','( m - cartesian, degrees - spherical )')
371     CALL WRITE_XY_YLINE_RS( dyF, coordLine, tileLine,
372     I 'dyF','( m - cartesian, degrees - spherical )')
373     CALL WRITE_XY_XLINE_RS( dxG, coordLine, tileLine,
374     I 'dxG','( m - cartesian, degrees - spherical )')
375     CALL WRITE_XY_YLINE_RS( dxG, coordLine, tileLine,
376     I 'dxG','( m - cartesian, degrees - spherical )')
377     CALL WRITE_XY_XLINE_RS( dyG, coordLine, tileLine,
378     I 'dyG','( m - cartesian, degrees - spherical )')
379     CALL WRITE_XY_YLINE_RS( dyG, coordLine, tileLine,
380     I 'dyG','( m - cartesian, degrees - spherical )')
381     CALL WRITE_XY_XLINE_RS( dxC, coordLine, tileLine,
382     I 'dxC','( m - cartesian, degrees - spherical )')
383     CALL WRITE_XY_YLINE_RS( dxC, coordLine, tileLine,
384     I 'dxC','( m - cartesian, degrees - spherical )')
385     CALL WRITE_XY_XLINE_RS( dyC, coordLine, tileLine,
386     I 'dyC','( m - cartesian, degrees - spherical )')
387     CALL WRITE_XY_YLINE_RS( dyC, coordLine, tileLine,
388     I 'dyC','( m - cartesian, degrees - spherical )')
389     CALL WRITE_XY_XLINE_RS( dxV, coordLine, tileLine,
390     I 'dxV','( m - cartesian, degrees - spherical )')
391     CALL WRITE_XY_YLINE_RS( dxV, coordLine, tileLine,
392     I 'dxV','( m - cartesian, degrees - spherical )')
393     CALL WRITE_XY_XLINE_RS( dyU, coordLine, tileLine,
394     I 'dyU','( m - cartesian, degrees - spherical )')
395     CALL WRITE_XY_YLINE_RS( dyU, coordLine, tileLine,
396     I 'dyU','( m - cartesian, degrees - spherical )')
397     CALL WRITE_XY_XLINE_RS( rA, coordLine, tileLine,
398     I 'rA','( m - cartesian, degrees - spherical )')
399     CALL WRITE_XY_YLINE_RS( rA, coordLine, tileLine,
400     I 'rA','( m - cartesian, degrees - spherical )')
401     CALL WRITE_XY_XLINE_RS( rAw, coordLine, tileLine,
402     I 'rAw','( m - cartesian, degrees - spherical )')
403     CALL WRITE_XY_YLINE_RS( rAw, coordLine, tileLine,
404     I 'rAw','( m - cartesian, degrees - spherical )')
405     CALL WRITE_XY_XLINE_RS( rAs, coordLine, tileLine,
406     I 'rAs','( m - cartesian, degrees - spherical )')
407     CALL WRITE_XY_YLINE_RS( rAs, coordLine, tileLine,
408     I 'rAs','( m - cartesian, degrees - spherical )')
409 cnh 1.5
410 cnh 1.1 WRITE(msgBuf,'(A)') ' '
411     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
412     & SQUEEZE_RIGHT , 1)
413 cnh 1.5
414 cnh 1.1 _END_MASTER(myThid)
415     _BARRIER
416    
417    
418     RETURN
419     100 FORMAT(A,
420 cnh 1.4 &' '
421 cnh 1.1 &)
422     END
423    

  ViewVC Help
Powered by ViewVC 1.1.22