/[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.26 - (hide annotations) (download)
Sun Feb 4 16:46:44 2001 UTC (23 years, 3 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint35
Changes since 1.25: +51 -3 lines
o Added printing of key grid variables in config_summary.F
  and removed write(0,*) output of these variables in ini_spherical_polar_grid.F
o Added two new routines to do consistently formatted output of
  lines of constant X or Y for an XY variable. New routines are in
  read_write.F

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

  ViewVC Help
Powered by ViewVC 1.1.22