/[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.19 - (hide annotations) (download)
Wed Dec 9 16:11:51 1998 UTC (25 years, 5 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint19
Changes since 1.18: +2 -1 lines
Added IMPLICIT NONE in a lot of subroutines.
Also corrected the recip_Rhonil bug: we didn't set it in ini_parms.F

1 adcroft 1.19 C $Header: /u/gcmpack/models/MITgcmUV/model/src/config_summary.F,v 1.18 1998/11/06 22:44:45 cnh 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     C /==========================================================\
8     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     REAL xcoord(Nx)
39     REAL ycoord(Ny)
40 cnh 1.13 REAL 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 cnh 1.5 CALL WRITE_1D_R8( viscAh, 1, INDEX_NONE,'viscAh =',
73     &' /* Lateral eddy viscosity ( m^2/s ) */')
74 cnh 1.14 CALL WRITE_1D_R8( viscA4, 1, INDEX_NONE,'viscAh =',
75     &' /* Lateral biharmonic viscosity ( m^4/s ) */')
76 cnh 1.16 IF ( viscAz .NE. UNSET_RL ) THEN
77     CALL WRITE_1D_R8( viscAz, 1, INDEX_NONE,'viscAz =',
78     & ' /* Vertical eddy viscosity ( m^2/s ) */')
79     ENDIF
80     IF ( viscAp .NE. UNSET_RL ) THEN
81     CALL WRITE_1D_R8( viscAp, 1, INDEX_NONE,'viscAp =',
82     & ' /* Vertical eddy viscosity ( Pa^2/s ) */')
83     ENDIF
84     CALL WRITE_1D_R8( viscAr, 1, INDEX_NONE,'viscAr =',
85     &' /* Vertical eddy viscosity ( units of r^2/s ) */')
86 cnh 1.5 CALL WRITE_1D_R8( diffKhT, 1, INDEX_NONE,'diffKhT =',
87     &' /* Laplacian diffusion of heat laterally ( m^2/s ) */')
88     CALL WRITE_1D_R8( diffKzT, 1, INDEX_NONE,'diffKzT =',
89     &' /* Laplacian diffusion of heat vertically ( m^2/s ) */')
90     CALL WRITE_1D_R8( diffK4T, 1, INDEX_NONE,'diffK4T =',
91     &' /* Bihaarmonic diffusion of heat laterally ( m^4/s ) */')
92     CALL WRITE_1D_R8( diffKhS, 1, INDEX_NONE,'diffKhS =',
93     &' /* Laplacian diffusion of salt laterally ( m^2/s ) */')
94     CALL WRITE_1D_R8( diffKzS, 1, INDEX_NONE,'diffKzS =',
95     &' /* Laplacian diffusion of salt vertically ( m^2/s ) */')
96     CALL WRITE_1D_R8( diffK4S, 1, INDEX_NONE,'diffK4S =',
97     &' /* Bihaarmonic diffusion of salt laterally ( m^4/s ) */')
98 cnh 1.6 CALL WRITE_1D_R8( tAlpha,1, INDEX_NONE,'tAlpha =',
99     &' /* Linear EOS thermal expansion coefficient ( 1/degree ) */')
100     CALL WRITE_1D_R8( sBeta, 1, INDEX_NONE,'sBeta =',
101     &' /* Linear EOS haline contraction coefficient ( 1/ppt ) */')
102 cnh 1.16 IF ( eosType .EQ. 'POLY3' ) THEN
103 cnh 1.17 WRITE(msgBuf,'(A)')
104     & '// Polynomial EQS parameters ( from POLY3.COEFFS ) '
105 cnh 1.16 DO K = 1, Nr
106     WRITE(msgBuf,'(I3,13F8.3)')
107     & K,eosRefT(K),eosRefS(K),eosSig0(K), (eosC(I,K),I=1,9)
108 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
109     & SQUEEZE_RIGHT , 1)
110 cnh 1.16 ENDDO
111     ENDIF
112 cnh 1.6 CALL WRITE_1D_R8( rhonil,1, INDEX_NONE,'rhonil =',
113     &' /* Reference density ( kg/m^3 ) */')
114     CALL WRITE_1D_R8( gravity,1, INDEX_NONE,'gravity =',
115     &' /* Gravitational acceleration ( m/s^2 ) */')
116 cnh 1.8 CALL WRITE_1D_R8( gBaro,1, INDEX_NONE,'gBaro =',
117     &' /* Barotropic gravity ( m/s^2 ) */')
118 cnh 1.6 CALL WRITE_1D_R8( f0,1, INDEX_NONE,'f0 =',
119     &' /* Reference coriolis parameter ( 1/s ) */')
120     CALL WRITE_1D_R8( beta,1, INDEX_NONE,'beta =',
121     &' /* Beta ( 1/(m.s) ) */')
122 cnh 1.8 CALL WRITE_1D_R8( freeSurfFac,1, INDEX_NONE,'freeSurfFac =',
123     &' /* Implcit free surface factor */')
124     CALL WRITE_1D_L( implicitFreeSurface,1, INDEX_NONE,
125     & 'implicitFreeSurface =',
126     &' /* Implicit free surface on/off flag */')
127     CALL WRITE_1D_L( rigidLid,1, INDEX_NONE,
128     & 'rigidLid =',
129     &' /* Rigid lid on/off flag */')
130 cnh 1.10 CALL WRITE_1D_L( momStepping,1, INDEX_NONE,
131     & 'momStepping =', ' /* Momentum equation on/off flag */')
132 cnh 1.9 CALL WRITE_1D_L( momAdvection,1, INDEX_NONE,
133 cnh 1.10 & 'momAdvection =', ' /* Momentum advection on/off flag */')
134 cnh 1.9 CALL WRITE_1D_L( momViscosity,1, INDEX_NONE,
135     & 'momViscosity =', ' /* Momentum viscosity on/off flag */')
136     CALL WRITE_1D_L( useCoriolis,1, INDEX_NONE,
137     & 'useCoriolis =', ' /* Coriolis on/off flag */')
138     CALL WRITE_1D_L( momForcing,1, INDEX_NONE,
139     & 'momForcing =', ' /* Momentum forcing on/off flag */')
140     CALL WRITE_1D_L( momPressureForcing,1, INDEX_NONE,
141 cnh 1.17 & 'momPressureForcing =',
142     & ' /* Momentum pressure term on/off flag */')
143 cnh 1.10 CALL WRITE_1D_L( tempStepping,1, INDEX_NONE,
144     & 'tempStepping =', ' /* Temperature equation on/off flag */')
145 cnh 1.8 CALL WRITE_1D_R8( GMMaxSlope,1, INDEX_NONE,'GMMaxSlope =',
146     &' /* Max. slope allowed in GM/Redi tensor */')
147     CALL WRITE_1D_R8( GMLength,1, INDEX_NONE,'GMLength =',
148     &' /* Length to use in Visbeck et al. formula for K (m) */')
149     CALL WRITE_1D_R8( GMAlpha,1, INDEX_NONE,'GMAlpha =',
150     &' /* alpha to use in Visbeck et al. formula for K */')
151     CALL WRITE_1D_R8( GMdepth,1, INDEX_NONE,'GMdepth =',
152     &' /* Depth to integrate for Visbeck et. al Richardson # (m) */')
153     CALL WRITE_1D_R8( GMkbackground,1, INDEX_NONE,'GMkbackground =',
154     &' /* background value of GM/Redi coefficient m^2/s */')
155 cnh 1.6 WRITE(msgBuf,'(A)') '// '
156 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
157     & SQUEEZE_RIGHT , 1)
158 cnh 1.9
159 cnh 1.17 WRITE(msgBuf,'(A)')
160     & '// Elliptic solver(s) paramters ( PARM02 in namelist ) '
161     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
162     & SQUEEZE_RIGHT , 1)
163 cnh 1.6 WRITE(msgBuf,'(A)') '// '
164 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
165     & SQUEEZE_RIGHT , 1)
166 cnh 1.6 CALL WRITE_1D_I( cg2dMaxIters,1, INDEX_NONE,'cg2dMaxIters =',
167     &' /* Upper limit on 2d con. grad iterations */')
168     CALL WRITE_1D_I( cg2dChkResFreq,1, INDEX_NONE,'cg2dChkResFreq =',
169     &' /* 2d con. grad convergence test frequency */')
170 cnh 1.17 CALL WRITE_1D_R8( cg2dTargetResidual,1, INDEX_NONE,
171     & 'cg2dTargetResidual =',
172 cnh 1.6 &' /* 2d con. grad target residual */')
173    
174     WRITE(msgBuf,'(A)') '// '
175 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
176     & SQUEEZE_RIGHT , 1)
177     WRITE(msgBuf,'(A)')
178     & '// Time stepping paramters ( PARM03 in namelist ) '
179     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
180     & SQUEEZE_RIGHT , 1)
181 cnh 1.6 WRITE(msgBuf,'(A)') '// '
182 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
183     & SQUEEZE_RIGHT , 1)
184 cnh 1.6 CALL WRITE_1D_I( nIter0,1, INDEX_NONE,'nIter0 =',
185     &' /* Base timestep number */')
186     CALL WRITE_1D_I( nTimeSteps,1, INDEX_NONE,'nTimeSteps =',
187     &' /* Number of timesteps */')
188     CALL WRITE_1D_R8( deltaTmom,1, INDEX_NONE,'deltatTmom =',
189     &' /* Momentum equation timestep ( s ) */')
190     CALL WRITE_1D_R8( deltaTtracer,1, INDEX_NONE,'deltatTtracer =',
191     &' /* Tracer equation timestep ( s ) */')
192 cnh 1.12 CALL WRITE_1D_R8( deltaTClock ,1, INDEX_NONE,'deltatTClock =',
193     &' /* Model clock timestep ( s ) */')
194 cnh 1.9 CALL WRITE_1D_R8( cAdjFreq,1, INDEX_NONE,'cAdjFreq =',
195     &' /* Convective adjustment interval ( s ) */')
196 cnh 1.6 CALL WRITE_1D_R8( abEps,1, INDEX_NONE,'abEps =',
197     &' /* Adams-Bashforth stabilizing weight */')
198     CALL WRITE_1D_R8( tauCD,1, INDEX_NONE,'tauCD =',
199     &' /* CD coupling time-scale ( s ) */')
200     CALL WRITE_1D_R8( rCD,1, INDEX_NONE,'rCD =',
201     &' /* Normalised CD coupling parameter */')
202     CALL WRITE_1D_R8( startTime,1, INDEX_NONE,'startTime =',
203     &' /* Run start time ( s ). */')
204     CALL WRITE_1D_R8( endTime,1, INDEX_NONE,'endTime =',
205     &' /* Integration ending time ( s ). */')
206 cnh 1.7 CALL WRITE_1D_R8( pChkPtFreq,1, INDEX_NONE,'pChkPtFreq =',
207     &' /* Permanent restart/checkpoint file interval ( s ). */')
208 cnh 1.6 CALL WRITE_1D_R8( chkPtFreq,1, INDEX_NONE,'chkPtFreq =',
209 cnh 1.7 &' /* Rolling restart/checkpoint file interval ( s ). */')
210 cnh 1.6 CALL WRITE_1D_R8( dumpFreq,1, INDEX_NONE,'dumpFreq =',
211     &' /* Model state write out interval ( s ). */')
212    
213     WRITE(msgBuf,'(A)') '// '
214 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
215     & SQUEEZE_RIGHT , 1)
216     WRITE(msgBuf,'(A)')
217     & '// Gridding paramters ( PARM04 in namelist ) '
218     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
219     & SQUEEZE_RIGHT , 1)
220 cnh 1.6 WRITE(msgBuf,'(A)') '// '
221 cnh 1.17 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
222     & SQUEEZE_RIGHT , 1)
223     CALL WRITE_1D_L( usingCartesianGrid,1, INDEX_NONE,
224     & 'usingCartesianGrid =',
225 cnh 1.6 &' /* Cartesian coordinates flag ( True / False ) */')
226 cnh 1.17 CALL WRITE_1D_L( usingSphericalPolarGrid,1, INDEX_NONE,
227     & 'usingSphericalPolarGrid =',
228 cnh 1.6 &' /* Spherical coordinates flag ( True / False ) */')
229 cnh 1.13 CALL WRITE_1D_R8( delZ,Nr, INDEX_K,'delZ = ',
230 cnh 1.6 &' /* W spacing ( m ) */')
231 cnh 1.15 CALL WRITE_1D_R8( delP,Nr, INDEX_K,'delP = ',
232     &' /* W spacing ( Pa ) */')
233     CALL WRITE_1D_R8( delR,Nr, INDEX_K,'delR = ',
234     &' /* W spacing ( units of r ) */')
235 cnh 1.6 CALL WRITE_1D_R8( delX, Nx, INDEX_I,'delX = ',
236     &' /* U spacing ( m - cartesian, degrees - spherical ) */')
237     CALL WRITE_1D_R8( delY, Ny, INDEX_J,'delY = ',
238     &' /* V spacing ( m - cartesian, degrees - spherical ) */')
239     CALL WRITE_1D_R8( phiMin, 1, INDEX_NONE,'phiMin = ',
240 cnh 1.17 &' /* South edge (ignored - cartesian, degrees - spherical ) */')
241 cnh 1.6 CALL WRITE_1D_R8( thetaMin, 1, INDEX_NONE,'thetaMin = ',
242 cnh 1.17 &' /* West edge ( ignored - cartesian, degrees - spherical ) */')
243 cnh 1.6 CALL WRITE_1D_R8( rSphere, 1, INDEX_NONE,'rSphere = ',
244     &' /* Radius ( ignored - cartesian, m - spherical ) */')
245     DO bi=1,nSx
246     DO I=1,sNx
247     xcoord((bi-1)*sNx+I) = xc(I,1,bi,1)
248     ENDDO
249     ENDDO
250 cnh 1.11 CALL WRITE_1D_R8( xcoord, sNx*nSx, INDEX_I,'xcoord = ',
251 cnh 1.17 &' /* P-point X coord ( m - cartesian, degrees - spherical ) */')
252 cnh 1.6 DO bj=1,nSy
253     DO J=1,sNy
254     ycoord((bj-1)*sNy+J) = yc(1,J,1,bj)
255     ENDDO
256     ENDDO
257 cnh 1.11 CALL WRITE_1D_R8( ycoord, sNy*nSy, INDEX_J,'ycoord = ',
258 cnh 1.17 &' /* P-point Y coord ( m - cartesian, degrees - spherical ) */')
259 cnh 1.13 DO K=1,Nr
260     rcoord(K) = rc(K)
261 cnh 1.6 ENDDO
262 cnh 1.13 CALL WRITE_1D_R8( rcoord, Nr, INDEX_K,'rcoord = ',
263     &' /* P-point R coordinate ( units of r ) */')
264 cnh 1.6
265 cnh 1.5
266    
267 cnh 1.1 WRITE(msgBuf,'(A)') ' '
268     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
269     & SQUEEZE_RIGHT , 1)
270 cnh 1.5
271 cnh 1.1 _END_MASTER(myThid)
272     _BARRIER
273    
274    
275     RETURN
276     100 FORMAT(A,
277 cnh 1.4 &' '
278 cnh 1.1 &)
279     END
280    

  ViewVC Help
Powered by ViewVC 1.1.22