/[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.25 - (hide annotations) (download)
Sun Feb 4 14:38:46 2001 UTC (23 years, 4 months ago) by cnh
Branch: MAIN
Changes since 1.24: +2 -1 lines
Made sure each .F and .h file had
the CVS keywords Header and Name at its start.
Most had header but very few currently have Name, so
lots of changes!

1 cnh 1.25 C $Header: /u/gcmpack/models/MITgcmUV/model/src/config_summary.F,v 1.24 2001/02/02 21:04:47 adcroft 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.5
43 cnh 1.1
44     _BARRIER
45 cnh 1.5 _BEGIN_MASTER(myThid)
46 cnh 1.1
47     WRITE(msgBuf,'(A)')
48     &'// ======================================================='
49 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
50     & SQUEEZE_RIGHT , 1)
51 cnh 1.1 WRITE(msgBuf,'(A)') '// Model configuration'
52 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
53     & SQUEEZE_RIGHT , 1)
54 cnh 1.1 WRITE(msgBuf,'(A)')
55     &'// ======================================================='
56     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
57     & SQUEEZE_RIGHT , 1)
58 cnh 1.5
59 cnh 1.6 WRITE(msgBuf,'(A)') '// '
60 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
61     & SQUEEZE_RIGHT , 1)
62     WRITE(msgBuf,'(A)')
63     & '// "Physical" paramters ( PARM01 in namelist ) '
64     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
65     & SQUEEZE_RIGHT , 1)
66 cnh 1.6 WRITE(msgBuf,'(A)') '// '
67 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
68     & SQUEEZE_RIGHT , 1)
69 cnh 1.13 CALL WRITE_1D_R8( tRef, Nr, INDEX_K,'tRef =',
70 cnh 1.5 &' /* Reference temperature profile ( oC or oK ) */')
71 cnh 1.13 CALL WRITE_1D_R8( sRef, Nr, INDEX_K,'sRef =',
72 cnh 1.6 &' /* Reference salinity profile ( ppt ) */')
73 heimbach 1.22 CALL WRITE_0D_R8( viscAh, INDEX_NONE,'viscAh =',
74 cnh 1.5 &' /* Lateral eddy viscosity ( m^2/s ) */')
75 heimbach 1.22 CALL WRITE_0D_R8( viscA4, INDEX_NONE,'viscAh =',
76 cnh 1.14 &' /* Lateral biharmonic viscosity ( m^4/s ) */')
77 heimbach 1.22 CALL WRITE_0D_L( no_slip_sides, INDEX_NONE,
78 adcroft 1.20 & 'no_slip_sides =', ' /* Viscous BCs: No-slip sides */')
79 cnh 1.16 IF ( viscAz .NE. UNSET_RL ) THEN
80 heimbach 1.22 CALL WRITE_0D_R8( viscAz, INDEX_NONE,'viscAz =',
81 cnh 1.16 & ' /* Vertical eddy viscosity ( m^2/s ) */')
82     ENDIF
83     IF ( viscAp .NE. UNSET_RL ) THEN
84 heimbach 1.22 CALL WRITE_0D_R8( viscAp, INDEX_NONE,'viscAp =',
85 cnh 1.16 & ' /* Vertical eddy viscosity ( Pa^2/s ) */')
86     ENDIF
87 heimbach 1.22 CALL WRITE_0D_R8( viscAr, INDEX_NONE,'viscAr =',
88 cnh 1.16 &' /* Vertical eddy viscosity ( units of r^2/s ) */')
89 heimbach 1.22 CALL WRITE_0D_R8( diffKhT, INDEX_NONE,'diffKhT =',
90 cnh 1.5 &' /* Laplacian diffusion of heat laterally ( m^2/s ) */')
91 heimbach 1.22 CALL WRITE_0D_R8( diffK4T, INDEX_NONE,'diffK4T =',
92 adcroft 1.20 &' /* Bihaarmonic diffusion of heat laterally ( m^4/s ) */')
93 heimbach 1.22 CALL WRITE_0D_R8( diffKzT, INDEX_NONE,'diffKzT =',
94 cnh 1.5 &' /* Laplacian diffusion of heat vertically ( m^2/s ) */')
95 heimbach 1.22 CALL WRITE_0D_R8( diffKrT, INDEX_NONE,'diffKrT =',
96 adcroft 1.20 &' /* Laplacian diffusion of heat vertically ( m^2/s ) */')
97 heimbach 1.22 CALL WRITE_0D_R8( diffKhS, INDEX_NONE,'diffKhS =',
98 cnh 1.5 &' /* Laplacian diffusion of salt laterally ( m^2/s ) */')
99 heimbach 1.22 CALL WRITE_0D_R8( diffK4S, INDEX_NONE,'diffK4S =',
100 adcroft 1.20 &' /* Bihaarmonic diffusion of salt laterally ( m^4/s ) */')
101 heimbach 1.22 CALL WRITE_0D_R8( diffKzS, INDEX_NONE,'diffKzS =',
102 cnh 1.5 &' /* Laplacian diffusion of salt vertically ( m^2/s ) */')
103 heimbach 1.22 CALL WRITE_0D_R8( diffKrS, INDEX_NONE,'diffKrS =',
104 adcroft 1.20 &' /* Laplacian diffusion of salt vertically ( m^2/s ) */')
105 heimbach 1.22 CALL WRITE_0D_R8( tAlpha, INDEX_NONE,'tAlpha =',
106 cnh 1.6 &' /* Linear EOS thermal expansion coefficient ( 1/degree ) */')
107 heimbach 1.22 CALL WRITE_0D_R8( sBeta, INDEX_NONE,'sBeta =',
108 cnh 1.6 &' /* Linear EOS haline contraction coefficient ( 1/ppt ) */')
109 cnh 1.16 IF ( eosType .EQ. 'POLY3' ) THEN
110 cnh 1.17 WRITE(msgBuf,'(A)')
111     & '// Polynomial EQS parameters ( from POLY3.COEFFS ) '
112 cnh 1.16 DO K = 1, Nr
113     WRITE(msgBuf,'(I3,13F8.3)')
114     & K,eosRefT(K),eosRefS(K),eosSig0(K), (eosC(I,K),I=1,9)
115 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
116     & SQUEEZE_RIGHT , 1)
117 cnh 1.16 ENDDO
118     ENDIF
119 heimbach 1.22 CALL WRITE_0D_R8( rhonil, INDEX_NONE,'rhonil =',
120 cnh 1.6 &' /* Reference density ( kg/m^3 ) */')
121 heimbach 1.22 CALL WRITE_0D_R8( rhoConst, INDEX_NONE,'rhoConst =',
122 adcroft 1.20 &' /* Reference density ( kg/m^3 ) */')
123 heimbach 1.22 CALL WRITE_0D_R8( gravity, INDEX_NONE,'gravity =',
124 cnh 1.6 &' /* Gravitational acceleration ( m/s^2 ) */')
125 heimbach 1.22 CALL WRITE_0D_R8( gBaro, INDEX_NONE,'gBaro =',
126 cnh 1.8 &' /* Barotropic gravity ( m/s^2 ) */')
127 heimbach 1.22 CALL WRITE_0D_R8( f0, INDEX_NONE,'f0 =',
128 cnh 1.6 &' /* Reference coriolis parameter ( 1/s ) */')
129 heimbach 1.22 CALL WRITE_0D_R8( beta, INDEX_NONE,'beta =',
130 cnh 1.6 &' /* Beta ( 1/(m.s) ) */')
131 heimbach 1.22 CALL WRITE_0D_R8( freeSurfFac, INDEX_NONE,'freeSurfFac =',
132 cnh 1.8 &' /* Implcit free surface factor */')
133 heimbach 1.22 CALL WRITE_0D_L( implicitFreeSurface, INDEX_NONE,
134 cnh 1.8 & 'implicitFreeSurface =',
135     &' /* Implicit free surface on/off flag */')
136 heimbach 1.22 CALL WRITE_0D_L( rigidLid, INDEX_NONE,
137 cnh 1.8 & 'rigidLid =',
138     &' /* Rigid lid on/off flag */')
139 heimbach 1.22 CALL WRITE_0D_L( momStepping, INDEX_NONE,
140 cnh 1.10 & 'momStepping =', ' /* Momentum equation on/off flag */')
141 heimbach 1.22 CALL WRITE_0D_L( momAdvection, INDEX_NONE,
142 cnh 1.10 & 'momAdvection =', ' /* Momentum advection on/off flag */')
143 heimbach 1.22 CALL WRITE_0D_L( momViscosity, INDEX_NONE,
144 cnh 1.9 & 'momViscosity =', ' /* Momentum viscosity on/off flag */')
145 heimbach 1.22 CALL WRITE_0D_L( useCoriolis, INDEX_NONE,
146 cnh 1.9 & 'useCoriolis =', ' /* Coriolis on/off flag */')
147 heimbach 1.22 CALL WRITE_0D_L( momForcing, INDEX_NONE,
148 cnh 1.9 & 'momForcing =', ' /* Momentum forcing on/off flag */')
149 heimbach 1.22 CALL WRITE_0D_L( momPressureForcing, INDEX_NONE,
150 cnh 1.17 & 'momPressureForcing =',
151     & ' /* Momentum pressure term on/off flag */')
152 heimbach 1.22 CALL WRITE_0D_L( tempStepping, INDEX_NONE,
153 cnh 1.10 & 'tempStepping =', ' /* Temperature equation on/off flag */')
154 heimbach 1.22 CALL WRITE_0D_L( nonHydrostatic, INDEX_NONE,
155 adcroft 1.20 & 'nonHydrostatic =', ' /* Non-Hydrostatic on/off flag */')
156 cnh 1.6 WRITE(msgBuf,'(A)') '// '
157 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
158     & SQUEEZE_RIGHT , 1)
159 cnh 1.9
160 cnh 1.17 WRITE(msgBuf,'(A)')
161     & '// Elliptic solver(s) paramters ( PARM02 in namelist ) '
162     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
163     & SQUEEZE_RIGHT , 1)
164 cnh 1.6 WRITE(msgBuf,'(A)') '// '
165 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
166     & SQUEEZE_RIGHT , 1)
167 heimbach 1.22 CALL WRITE_0D_I( cg2dMaxIters, INDEX_NONE,'cg2dMaxIters =',
168 cnh 1.6 &' /* Upper limit on 2d con. grad iterations */')
169 heimbach 1.22 CALL WRITE_0D_I( cg2dChkResFreq, INDEX_NONE,'cg2dChkResFreq =',
170 cnh 1.6 &' /* 2d con. grad convergence test frequency */')
171 heimbach 1.22 CALL WRITE_0D_R8( cg2dTargetResidual, INDEX_NONE,
172 cnh 1.17 & 'cg2dTargetResidual =',
173 cnh 1.6 &' /* 2d con. grad target residual */')
174    
175     WRITE(msgBuf,'(A)') '// '
176 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
177     & SQUEEZE_RIGHT , 1)
178     WRITE(msgBuf,'(A)')
179     & '// Time stepping paramters ( PARM03 in namelist ) '
180     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
181     & SQUEEZE_RIGHT , 1)
182 cnh 1.6 WRITE(msgBuf,'(A)') '// '
183 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
184     & SQUEEZE_RIGHT , 1)
185 heimbach 1.22 CALL WRITE_0D_I( nIter0, INDEX_NONE,'nIter0 =',
186 cnh 1.6 &' /* Base timestep number */')
187 heimbach 1.22 CALL WRITE_0D_I( nTimeSteps, INDEX_NONE,'nTimeSteps =',
188 cnh 1.6 &' /* Number of timesteps */')
189 heimbach 1.22 CALL WRITE_0D_R8( deltaTmom, INDEX_NONE,'deltatTmom =',
190 cnh 1.6 &' /* Momentum equation timestep ( s ) */')
191 heimbach 1.22 CALL WRITE_0D_R8( deltaTtracer, INDEX_NONE,'deltatTtracer =',
192 cnh 1.6 &' /* Tracer equation timestep ( s ) */')
193 heimbach 1.22 CALL WRITE_0D_R8( deltaTClock, INDEX_NONE,'deltatTClock =',
194 cnh 1.12 &' /* Model clock timestep ( s ) */')
195 heimbach 1.22 CALL WRITE_0D_R8( cAdjFreq, INDEX_NONE,'cAdjFreq =',
196 cnh 1.9 &' /* Convective adjustment interval ( s ) */')
197 heimbach 1.22 CALL WRITE_0D_R8( abeps, INDEX_NONE,'abeps =',
198 cnh 1.6 &' /* Adams-Bashforth stabilizing weight */')
199 heimbach 1.22 CALL WRITE_0D_R8( tauCD, INDEX_NONE,'tauCD =',
200 cnh 1.6 &' /* CD coupling time-scale ( s ) */')
201 heimbach 1.22 CALL WRITE_0D_R8( rCD, INDEX_NONE,'rCD =',
202 cnh 1.6 &' /* Normalised CD coupling parameter */')
203 heimbach 1.22 CALL WRITE_0D_R8( startTime, INDEX_NONE,'startTime =',
204 cnh 1.6 &' /* Run start time ( s ). */')
205 heimbach 1.22 CALL WRITE_0D_R8( endTime, INDEX_NONE,'endTime =',
206 cnh 1.6 &' /* Integration ending time ( s ). */')
207 heimbach 1.22 CALL WRITE_0D_R8( pChkPtFreq, INDEX_NONE,'pChkPtFreq =',
208 cnh 1.7 &' /* Permanent restart/checkpoint file interval ( s ). */')
209 heimbach 1.22 CALL WRITE_0D_R8( chkPtFreq, INDEX_NONE,'chkPtFreq =',
210 cnh 1.7 &' /* Rolling restart/checkpoint file interval ( s ). */')
211 heimbach 1.22 CALL WRITE_0D_R8( dumpFreq, INDEX_NONE,'dumpFreq =',
212 cnh 1.6 &' /* Model state write out interval ( s ). */')
213    
214     WRITE(msgBuf,'(A)') '// '
215 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
216     & SQUEEZE_RIGHT , 1)
217     WRITE(msgBuf,'(A)')
218     & '// Gridding paramters ( PARM04 in namelist ) '
219     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
220     & SQUEEZE_RIGHT , 1)
221 cnh 1.6 WRITE(msgBuf,'(A)') '// '
222 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
223     & SQUEEZE_RIGHT , 1)
224 heimbach 1.22 CALL WRITE_0D_L( usingCartesianGrid, INDEX_NONE,
225 cnh 1.17 & 'usingCartesianGrid =',
226 cnh 1.6 &' /* Cartesian coordinates flag ( True / False ) */')
227 heimbach 1.22 CALL WRITE_0D_L( usingSphericalPolarGrid, INDEX_NONE,
228 cnh 1.17 & 'usingSphericalPolarGrid =',
229 cnh 1.6 &' /* Spherical coordinates flag ( True / False ) */')
230 adcroft 1.24 CALL WRITE_0D_L( groundAtK1, INDEX_NONE, 'groundAtK1 =',
231     &' /* Lower Boundary (ground) at the surface(k=1) ( T / F ) */')
232     CALL WRITE_1D_R8( Ro_SeaLevel,1, INDEX_NONE,'Ro_SeaLevel =',
233     &' /* r(1) ( units of r ) */')
234     CALL WRITE_1D_R8( rkFac,1, INDEX_NONE,'rkFac =',
235     &' /* minus Vertical index orientation */')
236     CALL WRITE_1D_R8( horiVertRatio,1, INDEX_NONE,'horiVertRatio =',
237     &' /* Ratio on units : Horiz - Vertical */')
238 cnh 1.13 CALL WRITE_1D_R8( delZ,Nr, INDEX_K,'delZ = ',
239 cnh 1.6 &' /* W spacing ( m ) */')
240 cnh 1.15 CALL WRITE_1D_R8( delP,Nr, INDEX_K,'delP = ',
241     &' /* W spacing ( Pa ) */')
242     CALL WRITE_1D_R8( delR,Nr, INDEX_K,'delR = ',
243     &' /* W spacing ( units of r ) */')
244 cnh 1.6 CALL WRITE_1D_R8( delX, Nx, INDEX_I,'delX = ',
245     &' /* U spacing ( m - cartesian, degrees - spherical ) */')
246     CALL WRITE_1D_R8( delY, Ny, INDEX_J,'delY = ',
247     &' /* V spacing ( m - cartesian, degrees - spherical ) */')
248 heimbach 1.22 CALL WRITE_0D_R8( phiMin, INDEX_NONE,'phiMin = ',
249 cnh 1.17 &' /* South edge (ignored - cartesian, degrees - spherical ) */')
250 heimbach 1.22 CALL WRITE_0D_R8( thetaMin, INDEX_NONE,'thetaMin = ',
251 cnh 1.17 &' /* West edge ( ignored - cartesian, degrees - spherical ) */')
252 heimbach 1.22 CALL WRITE_0D_R8( rSphere, INDEX_NONE,'rSphere = ',
253 cnh 1.6 &' /* Radius ( ignored - cartesian, m - spherical ) */')
254     DO bi=1,nSx
255     DO I=1,sNx
256 heimbach 1.22 xcoord((bi-1)*sNx+I) = xC(I,1,bi,1)
257 cnh 1.6 ENDDO
258     ENDDO
259 cnh 1.11 CALL WRITE_1D_R8( xcoord, sNx*nSx, INDEX_I,'xcoord = ',
260 cnh 1.17 &' /* P-point X coord ( m - cartesian, degrees - spherical ) */')
261 cnh 1.6 DO bj=1,nSy
262     DO J=1,sNy
263 heimbach 1.22 ycoord((bj-1)*sNy+J) = yC(1,J,1,bj)
264 cnh 1.6 ENDDO
265     ENDDO
266 cnh 1.11 CALL WRITE_1D_R8( ycoord, sNy*nSy, INDEX_J,'ycoord = ',
267 cnh 1.17 &' /* P-point Y coord ( m - cartesian, degrees - spherical ) */')
268 cnh 1.13 DO K=1,Nr
269 heimbach 1.22 rcoord(K) = rC(K)
270 cnh 1.6 ENDDO
271 cnh 1.13 CALL WRITE_1D_R8( rcoord, Nr, INDEX_K,'rcoord = ',
272     &' /* P-point R coordinate ( units of r ) */')
273 cnh 1.6
274 cnh 1.5
275    
276 cnh 1.1 WRITE(msgBuf,'(A)') ' '
277     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
278     & SQUEEZE_RIGHT , 1)
279 cnh 1.5
280 cnh 1.1 _END_MASTER(myThid)
281     _BARRIER
282    
283    
284     RETURN
285     100 FORMAT(A,
286 cnh 1.4 &' '
287 cnh 1.1 &)
288     END
289    

  ViewVC Help
Powered by ViewVC 1.1.22