/[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.30 - (hide annotations) (download)
Wed Sep 26 18:09:14 2001 UTC (22 years, 9 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint43a-release1mods, release1_b1, checkpoint43, icebear5, icebear4, icebear3, icebear2, release1-branch_tutorials, chkpt44a_post, chkpt44c_pre, ecco_c44_e19, ecco_c44_e18, ecco_c44_e17, ecco_c44_e16, release1-branch-end, checkpoint44b_post, ecco_ice2, ecco_ice1, ecco_c44_e22, ecco_c44_e25, chkpt44a_pre, ecco_c44_e23, ecco_c44_e20, ecco_c44_e21, ecco_c44_e26, ecco_c44_e27, ecco_c44_e24, ecco-branch-mod1, ecco-branch-mod2, ecco-branch-mod3, ecco-branch-mod4, ecco-branch-mod5, release1_beta1, checkpoint44b_pre, checkpoint42, checkpoint41, checkpoint44, chkpt44c_post, release1-branch_branchpoint
Branch point for: c24_e25_ice, release1-branch, release1, ecco-branch, icebear, release1_coupled
Changes since 1.29: +29 -16 lines
Bringing comments up to data and formatting for document extraction.

1 cnh 1.30 C $Header: /u/gcmpack/models/MITgcmUV/model/src/config_summary.F,v 1.29 2001/03/09 20:42:56 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     #include "GRID.h"
32     #include "DYNVARS.h"
33    
34 cnh 1.30 C !INPUT/OUTPUT PARAMETERS:
35 cnh 1.1 C == Routine arguments ==
36     C myThid - Number of this instance of CONFIG_SUMMARY
37     INTEGER myThid
38     CEndOfInterface
39    
40 cnh 1.30 C !LOCAL VARIABLES:
41 cnh 1.1 C == Local variables ==
42 cnh 1.30 C msgBuf :: Temp. for building output string.
43     C I,J,K :: Loop counters.
44     C bi,bj :: Tile loop counters.
45     C xcoord :: Temps. for building lists of values for uni-dimensionally
46     C ycoord :: varying parameters.
47     C zcoord ::
48 cnh 1.1 CHARACTER*(MAX_LEN_MBUF) msgBuf
49 cnh 1.5 INTEGER I,J,K
50 cnh 1.6 INTEGER bi, bj
51 heimbach 1.22 _RL xcoord(Nx)
52     _RL ycoord(Ny)
53     _RL rcoord(Nr)
54 cnh 1.26 INTEGER coordLine
55     INTEGER tileLine
56 cnh 1.30 CEOP
57 cnh 1.5
58 cnh 1.1
59     _BARRIER
60 cnh 1.5 _BEGIN_MASTER(myThid)
61 cnh 1.1
62     WRITE(msgBuf,'(A)')
63     &'// ======================================================='
64 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
65     & SQUEEZE_RIGHT , 1)
66 cnh 1.1 WRITE(msgBuf,'(A)') '// Model configuration'
67 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
68     & SQUEEZE_RIGHT , 1)
69 cnh 1.1 WRITE(msgBuf,'(A)')
70     &'// ======================================================='
71     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
72     & SQUEEZE_RIGHT , 1)
73 cnh 1.5
74 cnh 1.6 WRITE(msgBuf,'(A)') '// '
75 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
76     & SQUEEZE_RIGHT , 1)
77     WRITE(msgBuf,'(A)')
78     & '// "Physical" paramters ( PARM01 in namelist ) '
79     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
80     & SQUEEZE_RIGHT , 1)
81 cnh 1.6 WRITE(msgBuf,'(A)') '// '
82 cnh 1.17 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 heimbach 1.22 CALL WRITE_0D_R8( viscA4, INDEX_NONE,'viscAh =',
91 cnh 1.14 &' /* Lateral biharmonic viscosity ( m^4/s ) */')
92 heimbach 1.22 CALL WRITE_0D_L( no_slip_sides, INDEX_NONE,
93 adcroft 1.20 & 'no_slip_sides =', ' /* Viscous BCs: No-slip sides */')
94 cnh 1.16 IF ( viscAz .NE. UNSET_RL ) THEN
95 heimbach 1.22 CALL WRITE_0D_R8( viscAz, INDEX_NONE,'viscAz =',
96 cnh 1.16 & ' /* Vertical eddy viscosity ( m^2/s ) */')
97     ENDIF
98     IF ( viscAp .NE. UNSET_RL ) THEN
99 heimbach 1.22 CALL WRITE_0D_R8( viscAp, INDEX_NONE,'viscAp =',
100 cnh 1.16 & ' /* Vertical eddy viscosity ( Pa^2/s ) */')
101     ENDIF
102 heimbach 1.22 CALL WRITE_0D_R8( viscAr, INDEX_NONE,'viscAr =',
103 cnh 1.16 &' /* Vertical eddy viscosity ( units of r^2/s ) */')
104 heimbach 1.22 CALL WRITE_0D_R8( diffKhT, INDEX_NONE,'diffKhT =',
105 cnh 1.5 &' /* Laplacian diffusion of heat laterally ( m^2/s ) */')
106 heimbach 1.22 CALL WRITE_0D_R8( diffK4T, INDEX_NONE,'diffK4T =',
107 adcroft 1.20 &' /* Bihaarmonic diffusion of heat laterally ( m^4/s ) */')
108 heimbach 1.22 CALL WRITE_0D_R8( diffKzT, INDEX_NONE,'diffKzT =',
109 cnh 1.5 &' /* Laplacian diffusion of heat vertically ( m^2/s ) */')
110 heimbach 1.22 CALL WRITE_0D_R8( diffKrT, INDEX_NONE,'diffKrT =',
111 adcroft 1.20 &' /* Laplacian diffusion of heat vertically ( m^2/s ) */')
112 heimbach 1.22 CALL WRITE_0D_R8( diffKhS, INDEX_NONE,'diffKhS =',
113 cnh 1.5 &' /* Laplacian diffusion of salt laterally ( m^2/s ) */')
114 heimbach 1.22 CALL WRITE_0D_R8( diffK4S, INDEX_NONE,'diffK4S =',
115 adcroft 1.20 &' /* Bihaarmonic diffusion of salt laterally ( m^4/s ) */')
116 heimbach 1.22 CALL WRITE_0D_R8( diffKzS, INDEX_NONE,'diffKzS =',
117 cnh 1.5 &' /* Laplacian diffusion of salt vertically ( m^2/s ) */')
118 heimbach 1.22 CALL WRITE_0D_R8( diffKrS, INDEX_NONE,'diffKrS =',
119 adcroft 1.20 &' /* Laplacian diffusion of salt vertically ( m^2/s ) */')
120 heimbach 1.22 CALL WRITE_0D_R8( tAlpha, INDEX_NONE,'tAlpha =',
121 cnh 1.6 &' /* Linear EOS thermal expansion coefficient ( 1/degree ) */')
122 heimbach 1.22 CALL WRITE_0D_R8( sBeta, INDEX_NONE,'sBeta =',
123 cnh 1.6 &' /* Linear EOS haline contraction coefficient ( 1/ppt ) */')
124 cnh 1.16 IF ( eosType .EQ. 'POLY3' ) THEN
125 cnh 1.17 WRITE(msgBuf,'(A)')
126     & '// Polynomial EQS parameters ( from POLY3.COEFFS ) '
127 cnh 1.16 DO K = 1, Nr
128     WRITE(msgBuf,'(I3,13F8.3)')
129     & K,eosRefT(K),eosRefS(K),eosSig0(K), (eosC(I,K),I=1,9)
130 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
131     & SQUEEZE_RIGHT , 1)
132 cnh 1.16 ENDDO
133     ENDIF
134 heimbach 1.22 CALL WRITE_0D_R8( rhonil, INDEX_NONE,'rhonil =',
135 cnh 1.6 &' /* Reference density ( kg/m^3 ) */')
136 heimbach 1.22 CALL WRITE_0D_R8( rhoConst, INDEX_NONE,'rhoConst =',
137 adcroft 1.20 &' /* Reference density ( kg/m^3 ) */')
138 heimbach 1.22 CALL WRITE_0D_R8( gravity, INDEX_NONE,'gravity =',
139 cnh 1.6 &' /* Gravitational acceleration ( m/s^2 ) */')
140 jmc 1.29 CALL WRITE_0D_R8( gBaro, INDEX_NONE,'gBaro =',
141     &' /* Barotropic gravity ( m/s^2 ) */')
142 heimbach 1.22 CALL WRITE_0D_R8( f0, INDEX_NONE,'f0 =',
143 cnh 1.6 &' /* Reference coriolis parameter ( 1/s ) */')
144 heimbach 1.22 CALL WRITE_0D_R8( beta, INDEX_NONE,'beta =',
145 cnh 1.6 &' /* Beta ( 1/(m.s) ) */')
146 heimbach 1.22 CALL WRITE_0D_R8( freeSurfFac, INDEX_NONE,'freeSurfFac =',
147 jmc 1.27 &' /* Implicit free surface factor */')
148 heimbach 1.22 CALL WRITE_0D_L( implicitFreeSurface, INDEX_NONE,
149 cnh 1.8 & 'implicitFreeSurface =',
150     &' /* Implicit free surface on/off flag */')
151 heimbach 1.22 CALL WRITE_0D_L( rigidLid, INDEX_NONE,
152 cnh 1.8 & 'rigidLid =',
153     &' /* Rigid lid on/off flag */')
154 jmc 1.27 CALL WRITE_0D_R8( implicSurfPress, INDEX_NONE,
155     &'implicSurfPress =',
156     &' /* Surface Pressure implicit factor (0-1)*/')
157     CALL WRITE_0D_R8( implicDiv2Dflow, INDEX_NONE,
158     &'implicDiv2Dflow =',
159     &' /* Barot. Flow Div. implicit factor (0-1)*/')
160     CALL WRITE_0D_L( staggerTimeStep, INDEX_NONE,
161     & 'staggerTimeStep =',
162     &' /* Stagger time stepping on/off flag */')
163 heimbach 1.22 CALL WRITE_0D_L( momStepping, INDEX_NONE,
164 cnh 1.10 & 'momStepping =', ' /* Momentum equation on/off flag */')
165 heimbach 1.22 CALL WRITE_0D_L( momAdvection, INDEX_NONE,
166 cnh 1.10 & 'momAdvection =', ' /* Momentum advection on/off flag */')
167 heimbach 1.22 CALL WRITE_0D_L( momViscosity, INDEX_NONE,
168 cnh 1.9 & 'momViscosity =', ' /* Momentum viscosity on/off flag */')
169 heimbach 1.22 CALL WRITE_0D_L( useCoriolis, INDEX_NONE,
170 cnh 1.9 & 'useCoriolis =', ' /* Coriolis on/off flag */')
171 heimbach 1.22 CALL WRITE_0D_L( momForcing, INDEX_NONE,
172 cnh 1.9 & 'momForcing =', ' /* Momentum forcing on/off flag */')
173 heimbach 1.22 CALL WRITE_0D_L( momPressureForcing, INDEX_NONE,
174 cnh 1.17 & 'momPressureForcing =',
175     & ' /* Momentum pressure term on/off flag */')
176 heimbach 1.22 CALL WRITE_0D_L( tempStepping, INDEX_NONE,
177 cnh 1.10 & 'tempStepping =', ' /* Temperature equation on/off flag */')
178 heimbach 1.22 CALL WRITE_0D_L( nonHydrostatic, INDEX_NONE,
179 adcroft 1.20 & 'nonHydrostatic =', ' /* Non-Hydrostatic on/off flag */')
180 cnh 1.6 WRITE(msgBuf,'(A)') '// '
181 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
182     & SQUEEZE_RIGHT , 1)
183 cnh 1.9
184 cnh 1.17 WRITE(msgBuf,'(A)')
185     & '// Elliptic solver(s) paramters ( PARM02 in namelist ) '
186     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
187     & SQUEEZE_RIGHT , 1)
188 cnh 1.6 WRITE(msgBuf,'(A)') '// '
189 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
190     & SQUEEZE_RIGHT , 1)
191 heimbach 1.22 CALL WRITE_0D_I( cg2dMaxIters, INDEX_NONE,'cg2dMaxIters =',
192 cnh 1.6 &' /* Upper limit on 2d con. grad iterations */')
193 heimbach 1.22 CALL WRITE_0D_I( cg2dChkResFreq, INDEX_NONE,'cg2dChkResFreq =',
194 cnh 1.6 &' /* 2d con. grad convergence test frequency */')
195 heimbach 1.22 CALL WRITE_0D_R8( cg2dTargetResidual, INDEX_NONE,
196 cnh 1.17 & 'cg2dTargetResidual =',
197 cnh 1.6 &' /* 2d con. grad target residual */')
198    
199     WRITE(msgBuf,'(A)') '// '
200 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
201     & SQUEEZE_RIGHT , 1)
202     WRITE(msgBuf,'(A)')
203     & '// Time stepping paramters ( PARM03 in namelist ) '
204     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
205     & SQUEEZE_RIGHT , 1)
206 cnh 1.6 WRITE(msgBuf,'(A)') '// '
207 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
208     & SQUEEZE_RIGHT , 1)
209 heimbach 1.22 CALL WRITE_0D_I( nIter0, INDEX_NONE,'nIter0 =',
210 cnh 1.6 &' /* Base timestep number */')
211 heimbach 1.22 CALL WRITE_0D_I( nTimeSteps, INDEX_NONE,'nTimeSteps =',
212 cnh 1.6 &' /* Number of timesteps */')
213 heimbach 1.22 CALL WRITE_0D_R8( deltaTmom, INDEX_NONE,'deltatTmom =',
214 cnh 1.6 &' /* Momentum equation timestep ( s ) */')
215 heimbach 1.22 CALL WRITE_0D_R8( deltaTtracer, INDEX_NONE,'deltatTtracer =',
216 cnh 1.6 &' /* Tracer equation timestep ( s ) */')
217 heimbach 1.22 CALL WRITE_0D_R8( deltaTClock, INDEX_NONE,'deltatTClock =',
218 cnh 1.12 &' /* Model clock timestep ( s ) */')
219 heimbach 1.22 CALL WRITE_0D_R8( cAdjFreq, INDEX_NONE,'cAdjFreq =',
220 cnh 1.9 &' /* Convective adjustment interval ( s ) */')
221 heimbach 1.22 CALL WRITE_0D_R8( abeps, INDEX_NONE,'abeps =',
222 cnh 1.6 &' /* Adams-Bashforth stabilizing weight */')
223 heimbach 1.22 CALL WRITE_0D_R8( tauCD, INDEX_NONE,'tauCD =',
224 cnh 1.6 &' /* CD coupling time-scale ( s ) */')
225 heimbach 1.22 CALL WRITE_0D_R8( rCD, INDEX_NONE,'rCD =',
226 cnh 1.6 &' /* Normalised CD coupling parameter */')
227 heimbach 1.22 CALL WRITE_0D_R8( startTime, INDEX_NONE,'startTime =',
228 cnh 1.6 &' /* Run start time ( s ). */')
229 heimbach 1.22 CALL WRITE_0D_R8( endTime, INDEX_NONE,'endTime =',
230 cnh 1.6 &' /* Integration ending time ( s ). */')
231 heimbach 1.22 CALL WRITE_0D_R8( pChkPtFreq, INDEX_NONE,'pChkPtFreq =',
232 cnh 1.7 &' /* Permanent restart/checkpoint file interval ( s ). */')
233 heimbach 1.22 CALL WRITE_0D_R8( chkPtFreq, INDEX_NONE,'chkPtFreq =',
234 cnh 1.7 &' /* Rolling restart/checkpoint file interval ( s ). */')
235 heimbach 1.22 CALL WRITE_0D_R8( dumpFreq, INDEX_NONE,'dumpFreq =',
236 cnh 1.6 &' /* Model state write out interval ( s ). */')
237    
238     WRITE(msgBuf,'(A)') '// '
239 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
240     & SQUEEZE_RIGHT , 1)
241     WRITE(msgBuf,'(A)')
242     & '// Gridding paramters ( PARM04 in namelist ) '
243     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
244     & SQUEEZE_RIGHT , 1)
245 cnh 1.6 WRITE(msgBuf,'(A)') '// '
246 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
247     & SQUEEZE_RIGHT , 1)
248 heimbach 1.22 CALL WRITE_0D_L( usingCartesianGrid, INDEX_NONE,
249 cnh 1.17 & 'usingCartesianGrid =',
250 cnh 1.6 &' /* Cartesian coordinates flag ( True / False ) */')
251 heimbach 1.22 CALL WRITE_0D_L( usingSphericalPolarGrid, INDEX_NONE,
252 cnh 1.17 & 'usingSphericalPolarGrid =',
253 cnh 1.6 &' /* Spherical coordinates flag ( True / False ) */')
254 adcroft 1.24 CALL WRITE_0D_L( groundAtK1, INDEX_NONE, 'groundAtK1 =',
255     &' /* Lower Boundary (ground) at the surface(k=1) ( T / F ) */')
256     CALL WRITE_1D_R8( Ro_SeaLevel,1, INDEX_NONE,'Ro_SeaLevel =',
257     &' /* r(1) ( units of r ) */')
258     CALL WRITE_1D_R8( rkFac,1, INDEX_NONE,'rkFac =',
259     &' /* minus Vertical index orientation */')
260     CALL WRITE_1D_R8( horiVertRatio,1, INDEX_NONE,'horiVertRatio =',
261     &' /* Ratio on units : Horiz - Vertical */')
262 cnh 1.13 CALL WRITE_1D_R8( delZ,Nr, INDEX_K,'delZ = ',
263 cnh 1.6 &' /* W spacing ( m ) */')
264 cnh 1.15 CALL WRITE_1D_R8( delP,Nr, INDEX_K,'delP = ',
265     &' /* W spacing ( Pa ) */')
266     CALL WRITE_1D_R8( delR,Nr, INDEX_K,'delR = ',
267     &' /* W spacing ( units of r ) */')
268 cnh 1.6 CALL WRITE_1D_R8( delX, Nx, INDEX_I,'delX = ',
269     &' /* U spacing ( m - cartesian, degrees - spherical ) */')
270     CALL WRITE_1D_R8( delY, Ny, INDEX_J,'delY = ',
271     &' /* V spacing ( m - cartesian, degrees - spherical ) */')
272 heimbach 1.22 CALL WRITE_0D_R8( phiMin, INDEX_NONE,'phiMin = ',
273 cnh 1.17 &' /* South edge (ignored - cartesian, degrees - spherical ) */')
274 heimbach 1.22 CALL WRITE_0D_R8( thetaMin, INDEX_NONE,'thetaMin = ',
275 cnh 1.17 &' /* West edge ( ignored - cartesian, degrees - spherical ) */')
276 heimbach 1.22 CALL WRITE_0D_R8( rSphere, INDEX_NONE,'rSphere = ',
277 cnh 1.6 &' /* Radius ( ignored - cartesian, m - spherical ) */')
278     DO bi=1,nSx
279     DO I=1,sNx
280 heimbach 1.22 xcoord((bi-1)*sNx+I) = xC(I,1,bi,1)
281 cnh 1.6 ENDDO
282     ENDDO
283 cnh 1.11 CALL WRITE_1D_R8( xcoord, sNx*nSx, INDEX_I,'xcoord = ',
284 cnh 1.17 &' /* P-point X coord ( m - cartesian, degrees - spherical ) */')
285 cnh 1.6 DO bj=1,nSy
286     DO J=1,sNy
287 heimbach 1.22 ycoord((bj-1)*sNy+J) = yC(1,J,1,bj)
288 cnh 1.6 ENDDO
289     ENDDO
290 cnh 1.11 CALL WRITE_1D_R8( ycoord, sNy*nSy, INDEX_J,'ycoord = ',
291 cnh 1.17 &' /* P-point Y coord ( m - cartesian, degrees - spherical ) */')
292 cnh 1.13 DO K=1,Nr
293 heimbach 1.22 rcoord(K) = rC(K)
294 cnh 1.6 ENDDO
295 cnh 1.13 CALL WRITE_1D_R8( rcoord, Nr, INDEX_K,'rcoord = ',
296     &' /* P-point R coordinate ( units of r ) */')
297 cnh 1.6
298 cnh 1.26 C Grid along selected grid lines
299     coordLine = 1
300     tileLine = 1
301     CALL WRITE_XY_XLINE_RS( dxF, coordLine, tileLine,
302     I 'dxF','( m - cartesian, degrees - spherical )')
303     CALL WRITE_XY_YLINE_RS( dxF, coordLine, tileLine,
304     I 'dxF','( m - cartesian, degrees - spherical )')
305     CALL WRITE_XY_XLINE_RS( dyF, coordLine, tileLine,
306     I 'dyF','( m - cartesian, degrees - spherical )')
307     CALL WRITE_XY_YLINE_RS( dyF, coordLine, tileLine,
308     I 'dyF','( m - cartesian, degrees - spherical )')
309     CALL WRITE_XY_XLINE_RS( dxG, coordLine, tileLine,
310     I 'dxG','( m - cartesian, degrees - spherical )')
311     CALL WRITE_XY_YLINE_RS( dxG, coordLine, tileLine,
312     I 'dxG','( m - cartesian, degrees - spherical )')
313     CALL WRITE_XY_XLINE_RS( dyG, coordLine, tileLine,
314     I 'dyG','( m - cartesian, degrees - spherical )')
315     CALL WRITE_XY_YLINE_RS( dyG, coordLine, tileLine,
316     I 'dyG','( m - cartesian, degrees - spherical )')
317     CALL WRITE_XY_XLINE_RS( dxC, coordLine, tileLine,
318     I 'dxC','( m - cartesian, degrees - spherical )')
319     CALL WRITE_XY_YLINE_RS( dxC, coordLine, tileLine,
320     I 'dxC','( m - cartesian, degrees - spherical )')
321     CALL WRITE_XY_XLINE_RS( dyC, coordLine, tileLine,
322     I 'dyC','( m - cartesian, degrees - spherical )')
323     CALL WRITE_XY_YLINE_RS( dyC, coordLine, tileLine,
324     I 'dyC','( m - cartesian, degrees - spherical )')
325     CALL WRITE_XY_XLINE_RS( dxV, coordLine, tileLine,
326     I 'dxV','( m - cartesian, degrees - spherical )')
327     CALL WRITE_XY_YLINE_RS( dxV, coordLine, tileLine,
328     I 'dxV','( m - cartesian, degrees - spherical )')
329     CALL WRITE_XY_XLINE_RS( dyU, coordLine, tileLine,
330     I 'dyU','( m - cartesian, degrees - spherical )')
331     CALL WRITE_XY_YLINE_RS( dyU, coordLine, tileLine,
332     I 'dyU','( m - cartesian, degrees - spherical )')
333     CALL WRITE_XY_XLINE_RS( rA, coordLine, tileLine,
334     I 'rA','( m - cartesian, degrees - spherical )')
335     CALL WRITE_XY_YLINE_RS( rA, coordLine, tileLine,
336     I 'rA','( m - cartesian, degrees - spherical )')
337     CALL WRITE_XY_XLINE_RS( rAw, coordLine, tileLine,
338     I 'rAw','( m - cartesian, degrees - spherical )')
339     CALL WRITE_XY_YLINE_RS( rAw, coordLine, tileLine,
340     I 'rAw','( m - cartesian, degrees - spherical )')
341     CALL WRITE_XY_XLINE_RS( rAs, coordLine, tileLine,
342     I 'rAs','( m - cartesian, degrees - spherical )')
343     CALL WRITE_XY_YLINE_RS( rAs, coordLine, tileLine,
344     I 'rAs','( m - cartesian, degrees - spherical )')
345 cnh 1.5
346 cnh 1.1 WRITE(msgBuf,'(A)') ' '
347     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
348     & SQUEEZE_RIGHT , 1)
349 cnh 1.5
350 cnh 1.1 _END_MASTER(myThid)
351     _BARRIER
352    
353    
354     RETURN
355     100 FORMAT(A,
356 cnh 1.4 &' '
357 cnh 1.1 &)
358     END
359    

  ViewVC Help
Powered by ViewVC 1.1.22