/[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.23 - (hide annotations) (download)
Wed Jun 21 19:14:10 2000 UTC (23 years, 11 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint29, branch-atmos-merge-start, checkpoint33, checkpoint32, checkpoint31, checkpoint30, checkpoint34, branch-atmos-merge-phase5, branch-atmos-merge-phase4, branch-atmos-merge-phase6, branch-atmos-merge-phase1, branch-atmos-merge-phase3, branch-atmos-merge-phase2
Branch point for: branch-atmos-merge
Changes since 1.22: +1 -11 lines
Removed GM/Redi parameters as part of packaging process.

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

  ViewVC Help
Powered by ViewVC 1.1.22