/[MITgcm]/MITgcm/model/src/config_summary.F
ViewVC logotype

Diff of /MITgcm/model/src/config_summary.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.5 by cnh, Sun Apr 26 23:41:54 1998 UTC revision 1.31 by jmc, Sun Feb 10 00:35:30 2002 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4  #include "CPP_EEOPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6  CStartOfInterface  CBOP
7    C     !ROUTINE: CONFIG_SUMMARY
8    C     !INTERFACE:
9        SUBROUTINE CONFIG_SUMMARY( myThid )        SUBROUTINE CONFIG_SUMMARY( myThid )
10  C     /==========================================================\  C     !DESCRIPTION: \bv
11  C     | SUBROUTINE CONFIG_SUMMARY                                |  C     *=========================================================*
12  C     | o Summarize model prognostic variables.                  |  C     | SUBROUTINE CONFIG_SUMMARY                                
13  C     |==========================================================|  C     | o Summarize model parameter settings.                    
14  C     | This routine writes a tabulated summary of the model     |  C     *=========================================================*
15  C     | configuration.                                           |  C     | This routine writes a tabulated summary of the kernel    
16  C     | Note                                                     |  C     | model configuration. Information describes all the
17  C     |  1. Under multi-process parallelism the summary          |  C     | parameter setting in force and the meaning and units of
18  C     |     is only given for the per-process data.              |  C     | those parameters. Individal packages report a similar
19  C     |  2. Under multi-threading the summary is produced by     |  C     | table for each package using the same format as employed
20  C     |     the master thread. This threads reads data managed by|  C     | here. If parameters are missing or incorrectly described
21  C     |     other threads.                                       |  C     | or dimensioned please contact support@mitgcm.org
22  C     \==========================================================/  C     *=========================================================*
23    C     \ev
24    
25    C     !USES:
26          IMPLICIT NONE
27  C     === Global variables ===  C     === Global variables ===
28  #include "SIZE.h"  #include "SIZE.h"
29  #include "EEPARAMS.h"  #include "EEPARAMS.h"
# Line 25  C     === Global variables === Line 31  C     === Global variables ===
31  #include "GRID.h"  #include "GRID.h"
32  #include "DYNVARS.h"  #include "DYNVARS.h"
33    
34    C     !INPUT/OUTPUT PARAMETERS:
35  C     == Routine arguments ==  C     == Routine arguments ==
36  C     myThid -  Number of this instance of CONFIG_SUMMARY  C     myThid -  Number of this instance of CONFIG_SUMMARY
37        INTEGER myThid        INTEGER myThid
38  CEndOfInterface  CEndOfInterface
39    
40    C     !LOCAL VARIABLES:
41  C     == Local variables ==  C     == Local variables ==
42    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        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
49        INTEGER                  I,J,K        INTEGER                  I,J,K
50          INTEGER                  bi, bj
51          _RL                     xcoord(Nx)
52          _RL                     ycoord(Ny)
53          _RL                     rcoord(Nr)
54          INTEGER coordLine
55          INTEGER tileLine
56    CEOP
57    
58    
59        _BARRIER        _BARRIER
# Line 40  C     == Local variables == Line 61  C     == Local variables ==
61    
62        WRITE(msgBuf,'(A)')        WRITE(msgBuf,'(A)')
63       &'// ======================================================='       &'// ======================================================='
64        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
65         &                    SQUEEZE_RIGHT , 1)
66        WRITE(msgBuf,'(A)') '// Model configuration'        WRITE(msgBuf,'(A)') '// Model configuration'
67        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
68         &                    SQUEEZE_RIGHT , 1)
69        WRITE(msgBuf,'(A)')        WRITE(msgBuf,'(A)')
70       &'// ======================================================='       &'// ======================================================='
71        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
72       &  SQUEEZE_RIGHT , 1)       &  SQUEEZE_RIGHT , 1)
73    
74        CALL WRITE_1D_R8( tRef, Nz, INDEX_K,'tRef =',        WRITE(msgBuf,'(A)') '//  '
75          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          WRITE(msgBuf,'(A)') '//  '
82          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
83         &                    SQUEEZE_RIGHT , 1)
84          CALL WRITE_1D_R8( tRef, Nr, INDEX_K,'tRef =',
85       &'   /* Reference temperature profile ( oC or oK ) */')       &'   /* Reference temperature profile ( oC or oK ) */')
86        CALL WRITE_1D_R8( viscAh, 1, INDEX_NONE,'viscAh =',        CALL WRITE_1D_R8( sRef, Nr, INDEX_K,'sRef =',
87         &'   /* Reference salinity profile ( ppt ) */')
88          CALL WRITE_0D_R8( viscAh, INDEX_NONE,'viscAh =',
89       &'   /* Lateral eddy viscosity ( m^2/s ) */')       &'   /* Lateral eddy viscosity ( m^2/s ) */')
90        CALL WRITE_1D_R8( viscAz, 1, INDEX_NONE,'viscAz =',        CALL WRITE_0D_R8( viscA4, INDEX_NONE,'viscAh =',
91       &'   /* Vertical eddy viscosity ( m^2/s ) */')       &'   /* Lateral biharmonic viscosity ( m^4/s ) */')
92        CALL WRITE_1D_R8( diffKhT, 1, INDEX_NONE,'diffKhT =',        CALL WRITE_0D_L( no_slip_sides, INDEX_NONE,
93         & 'no_slip_sides =', '  /* Viscous BCs: No-slip sides */')
94          IF ( viscAz .NE. UNSET_RL ) THEN
95           CALL WRITE_0D_R8( viscAz, INDEX_NONE,'viscAz =',
96         & '   /* Vertical eddy viscosity ( m^2/s ) */')
97          ENDIF
98          IF ( viscAp .NE. UNSET_RL ) THEN
99           CALL WRITE_0D_R8( viscAp, INDEX_NONE,'viscAp =',
100         & '   /* Vertical eddy viscosity ( Pa^2/s ) */')
101          ENDIF
102          CALL WRITE_0D_R8( viscAr,  INDEX_NONE,'viscAr =',
103         &'   /* Vertical eddy viscosity ( units of r^2/s ) */')
104          CALL WRITE_0D_R8( diffKhT, INDEX_NONE,'diffKhT =',
105       &'   /* Laplacian diffusion of heat laterally ( m^2/s ) */')       &'   /* Laplacian diffusion of heat laterally ( m^2/s ) */')
106        CALL WRITE_1D_R8( diffKzT, 1, INDEX_NONE,'diffKzT =',        CALL WRITE_0D_R8( diffK4T, INDEX_NONE,'diffK4T =',
      &'   /* Laplacian diffusion of heat vertically ( m^2/s ) */')  
       CALL WRITE_1D_R8( diffK4T, 1, INDEX_NONE,'diffK4T =',  
107       &'   /* Bihaarmonic diffusion of heat laterally ( m^4/s ) */')       &'   /* Bihaarmonic diffusion of heat laterally ( m^4/s ) */')
108        CALL WRITE_1D_R8( diffKhS, 1, INDEX_NONE,'diffKhS =',        CALL WRITE_0D_R8( diffKzT, INDEX_NONE,'diffKzT =',
109         &'   /* Laplacian diffusion of heat vertically ( m^2/s ) */')
110          CALL WRITE_0D_R8( diffKrT, INDEX_NONE,'diffKrT =',
111         &'   /* Laplacian diffusion of heat vertically ( m^2/s ) */')
112          CALL WRITE_0D_R8( diffKhS, INDEX_NONE,'diffKhS =',
113       &'   /* Laplacian diffusion of salt laterally ( m^2/s ) */')       &'   /* Laplacian diffusion of salt laterally ( m^2/s ) */')
114        CALL WRITE_1D_R8( diffKzS, 1, INDEX_NONE,'diffKzS =',        CALL WRITE_0D_R8( diffK4S, INDEX_NONE,'diffK4S =',
      &'   /* Laplacian diffusion of salt vertically ( m^2/s ) */')  
       CALL WRITE_1D_R8( diffK4S, 1, INDEX_NONE,'diffK4S =',  
115       &'   /* Bihaarmonic diffusion of salt laterally ( m^4/s ) */')       &'   /* Bihaarmonic diffusion of salt laterally ( m^4/s ) */')
116          CALL WRITE_0D_R8( diffKzS, INDEX_NONE,'diffKzS =',
117         &'   /* Laplacian diffusion of salt vertically ( m^2/s ) */')
118          CALL WRITE_0D_R8( diffKrS, INDEX_NONE,'diffKrS =',
119         &'   /* Laplacian diffusion of salt vertically ( m^2/s ) */')
120          CALL WRITE_0D_R8( tAlpha,  INDEX_NONE,'tAlpha =',
121         &'   /* Linear EOS thermal expansion coefficient ( 1/degree ) */')
122          CALL WRITE_0D_R8( sBeta,   INDEX_NONE,'sBeta =',
123         &'   /* Linear EOS haline contraction coefficient ( 1/ppt ) */')
124          IF ( eosType .EQ. 'POLY3' ) THEN
125            WRITE(msgBuf,'(A)')
126         &   '// Polynomial EQS parameters ( from POLY3.COEFFS ) '
127            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             CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
131         &                    SQUEEZE_RIGHT , 1)
132            ENDDO
133          ENDIF
134          CALL WRITE_0D_R8( rhonil,  INDEX_NONE,'rhonil =',
135         &'   /* Reference density ( kg/m^3 ) */')
136          CALL WRITE_0D_R8( rhoConst, INDEX_NONE,'rhoConst =',
137         &'   /* Reference density ( kg/m^3 ) */')
138          CALL WRITE_0D_R8( gravity, INDEX_NONE,'gravity =',
139         &'   /* Gravitational acceleration ( m/s^2 ) */')
140          CALL WRITE_0D_R8( gBaro,   INDEX_NONE,'gBaro =',
141         &'   /* Barotropic gravity ( m/s^2 ) */')
142          CALL WRITE_0D_R8( f0,      INDEX_NONE,'f0 =',
143         &'   /* Reference coriolis parameter ( 1/s ) */')
144          CALL WRITE_0D_R8( beta,    INDEX_NONE,'beta =',
145         &'   /* Beta ( 1/(m.s) ) */')
146    
147          CALL WRITE_0D_R8( freeSurfFac, INDEX_NONE,'freeSurfFac =',
148         &'   /* Implicit free surface factor */')
149          CALL WRITE_0D_L( implicitFreeSurface, INDEX_NONE,
150         &                 'implicitFreeSurface =',
151         &'   /* Implicit free surface on/off flag */')
152          CALL WRITE_0D_L( rigidLid, INDEX_NONE,
153         &                 'rigidLid =',
154         &'   /* Rigid lid on/off flag */')
155          CALL WRITE_0D_R8( implicSurfPress, INDEX_NONE,
156         &'implicSurfPress =',
157         &'   /* Surface Pressure implicit factor (0-1)*/')
158          CALL WRITE_0D_R8( implicDiv2Dflow, INDEX_NONE,
159         &'implicDiv2Dflow =',
160         &'   /* Barot. Flow Div. implicit factor (0-1)*/')
161          CALL WRITE_0D_L( exactConserv, INDEX_NONE,
162         &'exactConserv =',
163         &'   /* Exact Volume Conservation on/off flag*/')
164          CALL WRITE_0D_L( uniformLin_PhiSurf, INDEX_NONE,
165         &'uniformLin_PhiSurf =',
166         &'   /* use uniform Bo_surf on/off flag*/')
167          CALL WRITE_0D_I( nonlinFreeSurf, INDEX_NONE,
168         &'nonlinFreeSurf =',
169         &'   /* Non-linear Free Surf. options (-1,0,1,2,3)*/')
170          WRITE(msgBuf,'(2A)') '     -1,0= Off ; 1,2,3= On,',
171         &  ' 2=+rescale gU,gV, 3=+update cg2d solv.'
172          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
173         &                    SQUEEZE_RIGHT , 1)
174          CALL WRITE_0D_R8( hFacInf, INDEX_NONE,
175         &'hFacInf =',
176         &'   /* lower threshold for hFac (nonlinFreeSurf only)*/')
177          CALL WRITE_0D_R8( hFacSup, INDEX_NONE,
178         &'hFacSup =',
179         &'   /* upper threshold for hFac (nonlinFreeSurf only)*/')
180          CALL WRITE_0D_L( useRealFreshWaterFlux, INDEX_NONE,
181         &'useRealFreshWaterFlux =',
182         &'   /* Real Fresh Water Flux on/off flag*/')
183          IF (useRealFreshWaterFlux .AND. nonlinFreeSurf.GT.0) THEN
184          CALL WRITE_0D_R8( temp_EvPrRn, INDEX_NONE,
185         &'temp_EvPrRn =',
186         &' /* Temp. of Evap/Prec/R (UNSET=use local T)(oC)*/')
187          CALL WRITE_0D_R8( salt_EvPrRn, INDEX_NONE,
188         &'salt_EvPrRn =',
189         &' /* Salin. of Evap/Prec/R (UNSET=use local S)(ppt)*/')
190          CALL WRITE_0D_R8( trac_EvPrRn, INDEX_NONE,
191         &'trac_EvPrRn =',
192         &' /* Tracer in Evap/Prec/R (UNSET=use local Tr)*/')
193          ELSE
194          CALL WRITE_0D_R8( convertFW2Salt, INDEX_NONE,
195         &'convertFW2Salt =',
196         &' /* convert F.W. Flux to Salt Flux (-1=use local S)(ppt)*/')
197          ENDIF
198    
199          CALL WRITE_0D_L( staggerTimeStep, INDEX_NONE,
200         &                 'staggerTimeStep =',
201         &'   /* Stagger time stepping on/off flag */')
202          CALL WRITE_0D_L( momStepping,  INDEX_NONE,
203         & 'momStepping =', '  /* Momentum equation on/off flag */')
204          CALL WRITE_0D_L( momAdvection, INDEX_NONE,
205         & 'momAdvection =', '  /* Momentum advection on/off flag */')
206          CALL WRITE_0D_L( momViscosity, INDEX_NONE,
207         & 'momViscosity =', '  /* Momentum viscosity on/off flag */')
208          CALL WRITE_0D_L( useCoriolis,  INDEX_NONE,
209         & 'useCoriolis =', '  /* Coriolis on/off flag */')
210          CALL WRITE_0D_L( momForcing,   INDEX_NONE,
211         & 'momForcing =', '  /* Momentum forcing on/off flag */')
212          CALL WRITE_0D_L( momPressureForcing, INDEX_NONE,
213         & 'momPressureForcing =',  
214         & '  /* Momentum pressure term on/off flag */')
215          CALL WRITE_0D_L( tempStepping,  INDEX_NONE,
216         & 'tempStepping =', '  /* Temperature equation on/off flag */')
217          CALL WRITE_0D_L( nonHydrostatic, INDEX_NONE,
218         & 'nonHydrostatic =', '  /* Non-Hydrostatic on/off flag */')
219          WRITE(msgBuf,'(A)') '//  '
220          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
221         &                    SQUEEZE_RIGHT , 1)
222    
223          WRITE(msgBuf,'(A)')
224         & '// Elliptic solver(s) paramters ( PARM02 in namelist ) '
225          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
226         &                    SQUEEZE_RIGHT , 1)
227          WRITE(msgBuf,'(A)') '//  '
228          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
229         &                    SQUEEZE_RIGHT , 1)
230          CALL WRITE_0D_I( cg2dMaxIters,   INDEX_NONE,'cg2dMaxIters =',
231         &'   /* Upper limit on 2d con. grad iterations  */')
232          CALL WRITE_0D_I( cg2dChkResFreq, INDEX_NONE,'cg2dChkResFreq =',
233         &'   /* 2d con. grad convergence test frequency */')
234          CALL WRITE_0D_R8( cg2dTargetResidual, INDEX_NONE,
235         & 'cg2dTargetResidual =',
236         &'   /* 2d con. grad target residual  */')
237    
238          WRITE(msgBuf,'(A)') '//  '
239          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
240         &                    SQUEEZE_RIGHT , 1)
241          WRITE(msgBuf,'(A)')
242         & '// Time stepping paramters ( PARM03 in namelist ) '
243          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
244         &                    SQUEEZE_RIGHT , 1)
245          WRITE(msgBuf,'(A)') '//  '
246          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
247         &                    SQUEEZE_RIGHT , 1)
248          CALL WRITE_0D_I( nIter0, INDEX_NONE,'nIter0 =',
249         &'   /* Base timestep number  */')
250          CALL WRITE_0D_I( nTimeSteps, INDEX_NONE,'nTimeSteps =',
251         &'   /* Number of timesteps */')
252          CALL WRITE_0D_R8( deltaTmom, INDEX_NONE,'deltatTmom =',
253         &'   /* Momentum equation timestep ( s ) */')
254          CALL WRITE_0D_R8( deltaTtracer, INDEX_NONE,'deltatTtracer =',
255         &'   /* Tracer equation timestep ( s ) */')
256          CALL WRITE_0D_R8( deltaTClock, INDEX_NONE,'deltatTClock  =',
257         &'   /* Model clock timestep ( s ) */')
258          CALL WRITE_0D_R8( cAdjFreq, INDEX_NONE,'cAdjFreq =',
259         &'   /* Convective adjustment interval ( s ) */')
260          CALL WRITE_0D_R8( abeps, INDEX_NONE,'abeps =',
261         &'   /* Adams-Bashforth stabilizing weight */')
262          CALL WRITE_0D_R8( tauCD, INDEX_NONE,'tauCD =',
263         &'   /* CD coupling time-scale ( s ) */')
264          CALL WRITE_0D_R8( rCD, INDEX_NONE,'rCD =',
265         &'   /* Normalised CD coupling parameter */')
266          CALL WRITE_0D_R8( startTime, INDEX_NONE,'startTime =',
267         &'   /* Run start time ( s ). */')
268          CALL WRITE_0D_R8( endTime, INDEX_NONE,'endTime =',
269         &'   /* Integration ending time ( s ). */')
270          CALL WRITE_0D_R8( pChkPtFreq, INDEX_NONE,'pChkPtFreq =',
271         &'   /* Permanent restart/checkpoint file interval ( s ). */')
272          CALL WRITE_0D_R8( chkPtFreq, INDEX_NONE,'chkPtFreq =',
273         &'   /* Rolling restart/checkpoint file interval ( s ). */')
274          CALL WRITE_0D_R8( dumpFreq, INDEX_NONE,'dumpFreq =',
275         &'   /* Model state write out interval ( s ). */')
276    
277          WRITE(msgBuf,'(A)') '//  '
278          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
279         &                    SQUEEZE_RIGHT , 1)
280          WRITE(msgBuf,'(A)')
281         & '// Gridding paramters ( PARM04 in namelist ) '
282          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
283         &                    SQUEEZE_RIGHT , 1)
284          WRITE(msgBuf,'(A)') '//  '
285          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
286         &                    SQUEEZE_RIGHT , 1)
287          CALL WRITE_0D_L( usingCartesianGrid, INDEX_NONE,
288         & 'usingCartesianGrid =',
289         &'   /* Cartesian coordinates flag ( True / False ) */')
290          CALL WRITE_0D_L( usingSphericalPolarGrid, INDEX_NONE,
291         & 'usingSphericalPolarGrid =',
292         &'   /* Spherical coordinates flag ( True / False ) */')
293          CALL WRITE_0D_L( groundAtK1, INDEX_NONE, 'groundAtK1 =',
294         &'   /* Lower Boundary (ground) at the surface(k=1) ( T / F ) */')
295          CALL WRITE_1D_R8( Ro_SeaLevel,1, INDEX_NONE,'Ro_SeaLevel =',
296         &'   /* r(1) ( units of r ) */')
297          CALL WRITE_1D_R8( rkFac,1, INDEX_NONE,'rkFac =',
298         &'   /* minus Vertical index orientation  */')
299          CALL WRITE_1D_R8( horiVertRatio,1, INDEX_NONE,'horiVertRatio =',
300         &'   /* Ratio on units : Horiz - Vertical */')
301          CALL WRITE_1D_R8( delZ,Nr, INDEX_K,'delZ = ',
302         &'   /* W spacing ( m ) */')
303          CALL WRITE_1D_R8( delP,Nr, INDEX_K,'delP = ',
304         &'   /* W spacing ( Pa ) */')
305          CALL WRITE_1D_R8( delR,Nr, INDEX_K,'delR = ',
306         &'   /* W spacing ( units of r ) */')
307          CALL WRITE_1D_R8( delX, Nx, INDEX_I,'delX = ',
308         &'   /* U spacing ( m - cartesian, degrees - spherical ) */')
309          CALL WRITE_1D_R8( delY, Ny, INDEX_J,'delY = ',
310         &'   /* V spacing ( m - cartesian, degrees - spherical ) */')
311          CALL WRITE_0D_R8( phiMin, INDEX_NONE,'phiMin = ',
312         &'   /* South edge (ignored - cartesian, degrees - spherical ) */')
313          CALL WRITE_0D_R8( thetaMin, INDEX_NONE,'thetaMin = ',
314         &'   /* West edge ( ignored - cartesian, degrees - spherical ) */')
315          CALL WRITE_0D_R8( rSphere, INDEX_NONE,'rSphere = ',
316         &'   /* Radius ( ignored - cartesian, m - spherical ) */')
317          DO bi=1,nSx
318           DO I=1,sNx
319            xcoord((bi-1)*sNx+I) = xC(I,1,bi,1)
320           ENDDO
321          ENDDO
322          CALL WRITE_1D_R8( xcoord, sNx*nSx, INDEX_I,'xcoord = ',
323         &'   /* P-point X coord ( m - cartesian, degrees - spherical ) */')
324          DO bj=1,nSy
325           DO J=1,sNy
326            ycoord((bj-1)*sNy+J) = yC(1,J,1,bj)
327           ENDDO
328          ENDDO
329          CALL WRITE_1D_R8( ycoord, sNy*nSy, INDEX_J,'ycoord = ',
330         &'   /* P-point Y coord ( m - cartesian, degrees - spherical ) */')
331          DO K=1,Nr
332           rcoord(K) = rC(K)
333          ENDDO
334          CALL WRITE_1D_R8( rcoord, Nr, INDEX_K,'rcoord = ',
335         &'   /* P-point R coordinate (  units of r ) */')
336    
337    C     Grid along selected grid lines
338          coordLine = 1
339          tileLine  = 1
340          CALL WRITE_XY_XLINE_RS( dxF, coordLine, tileLine,
341         I 'dxF','( m - cartesian, degrees - spherical )')
342          CALL WRITE_XY_YLINE_RS( dxF, coordLine, tileLine,
343         I 'dxF','( m - cartesian, degrees - spherical )')
344          CALL WRITE_XY_XLINE_RS( dyF, coordLine, tileLine,
345         I 'dyF','( m - cartesian, degrees - spherical )')
346          CALL WRITE_XY_YLINE_RS( dyF, coordLine, tileLine,
347         I 'dyF','( m - cartesian, degrees - spherical )')
348          CALL WRITE_XY_XLINE_RS( dxG, coordLine, tileLine,
349         I 'dxG','( m - cartesian, degrees - spherical )')
350          CALL WRITE_XY_YLINE_RS( dxG, coordLine, tileLine,
351         I 'dxG','( m - cartesian, degrees - spherical )')
352          CALL WRITE_XY_XLINE_RS( dyG, coordLine, tileLine,
353         I 'dyG','( m - cartesian, degrees - spherical )')
354          CALL WRITE_XY_YLINE_RS( dyG, coordLine, tileLine,
355         I 'dyG','( m - cartesian, degrees - spherical )')
356          CALL WRITE_XY_XLINE_RS( dxC, coordLine, tileLine,
357         I 'dxC','( m - cartesian, degrees - spherical )')
358          CALL WRITE_XY_YLINE_RS( dxC, coordLine, tileLine,
359         I 'dxC','( m - cartesian, degrees - spherical )')
360          CALL WRITE_XY_XLINE_RS( dyC, coordLine, tileLine,
361         I 'dyC','( m - cartesian, degrees - spherical )')
362          CALL WRITE_XY_YLINE_RS( dyC, coordLine, tileLine,
363         I 'dyC','( m - cartesian, degrees - spherical )')
364          CALL WRITE_XY_XLINE_RS( dxV, coordLine, tileLine,
365         I 'dxV','( m - cartesian, degrees - spherical )')
366          CALL WRITE_XY_YLINE_RS( dxV, coordLine, tileLine,
367         I 'dxV','( m - cartesian, degrees - spherical )')
368          CALL WRITE_XY_XLINE_RS( dyU, coordLine, tileLine,
369         I 'dyU','( m - cartesian, degrees - spherical )')
370          CALL WRITE_XY_YLINE_RS( dyU, coordLine, tileLine,
371         I 'dyU','( m - cartesian, degrees - spherical )')
372          CALL WRITE_XY_XLINE_RS( rA, coordLine, tileLine,
373         I 'rA','( m - cartesian, degrees - spherical )')
374          CALL WRITE_XY_YLINE_RS( rA, coordLine, tileLine,
375         I 'rA','( m - cartesian, degrees - spherical )')
376          CALL WRITE_XY_XLINE_RS( rAw, coordLine, tileLine,
377         I 'rAw','( m - cartesian, degrees - spherical )')
378          CALL WRITE_XY_YLINE_RS( rAw, coordLine, tileLine,
379         I 'rAw','( m - cartesian, degrees - spherical )')
380          CALL WRITE_XY_XLINE_RS( rAs, coordLine, tileLine,
381         I 'rAs','( m - cartesian, degrees - spherical )')
382          CALL WRITE_XY_YLINE_RS( rAs, coordLine, tileLine,
383         I 'rAs','( m - cartesian, degrees - spherical )')
384    
385        WRITE(msgBuf,'(A)') ' '        WRITE(msgBuf,'(A)') ' '
386        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,

Legend:
Removed from v.1.5  
changed lines
  Added in v.1.31

  ViewVC Help
Powered by ViewVC 1.1.22