/[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.9 - (hide annotations) (download)
Mon May 25 20:05:55 1998 UTC (25 years, 11 months ago) by cnh
Branch: MAIN
Changes since 1.8: +15 -1 lines
Added extra IO features
 - runtime on/off flags
 - more reporting of configuration

1 cnh 1.9 C $Header: /u/gcmpack/models/MITgcmUV/model/src/config_summary.F,v 1.8 1998/05/25 16:17:36 cnh Exp $
2 cnh 1.1
3     #include "CPP_EEOPTIONS.h"
4    
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    
21     C === Global variables ===
22     #include "SIZE.h"
23     #include "EEPARAMS.h"
24     #include "PARAMS.h"
25     #include "GRID.h"
26     #include "DYNVARS.h"
27    
28     C == Routine arguments ==
29     C myThid - Number of this instance of CONFIG_SUMMARY
30     INTEGER myThid
31     CEndOfInterface
32    
33     C == Local variables ==
34     CHARACTER*(MAX_LEN_MBUF) msgBuf
35 cnh 1.5 INTEGER I,J,K
36 cnh 1.6 INTEGER bi, bj
37     REAL xcoord(Nx)
38     REAL ycoord(Ny)
39     REAL zcoord(Nz)
40 cnh 1.5
41 cnh 1.1
42     _BARRIER
43 cnh 1.5 _BEGIN_MASTER(myThid)
44 cnh 1.1
45     WRITE(msgBuf,'(A)')
46     &'// ======================================================='
47     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
48     WRITE(msgBuf,'(A)') '// Model configuration'
49     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
50     WRITE(msgBuf,'(A)')
51     &'// ======================================================='
52     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
53     & SQUEEZE_RIGHT , 1)
54 cnh 1.5
55 cnh 1.6 WRITE(msgBuf,'(A)') '// '
56     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
57     WRITE(msgBuf,'(A)') '// "Physical" paramters ( PARM01 in namelist ) '
58     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
59     WRITE(msgBuf,'(A)') '// '
60     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
61 cnh 1.5 CALL WRITE_1D_R8( tRef, Nz, INDEX_K,'tRef =',
62     &' /* Reference temperature profile ( oC or oK ) */')
63 cnh 1.6 CALL WRITE_1D_R8( sRef, Nz, INDEX_K,'sRef =',
64     &' /* Reference salinity profile ( ppt ) */')
65 cnh 1.5 CALL WRITE_1D_R8( viscAh, 1, INDEX_NONE,'viscAh =',
66     &' /* Lateral eddy viscosity ( m^2/s ) */')
67     CALL WRITE_1D_R8( viscAz, 1, INDEX_NONE,'viscAz =',
68     &' /* Vertical eddy viscosity ( m^2/s ) */')
69     CALL WRITE_1D_R8( diffKhT, 1, INDEX_NONE,'diffKhT =',
70     &' /* Laplacian diffusion of heat laterally ( m^2/s ) */')
71     CALL WRITE_1D_R8( diffKzT, 1, INDEX_NONE,'diffKzT =',
72     &' /* Laplacian diffusion of heat vertically ( m^2/s ) */')
73     CALL WRITE_1D_R8( diffK4T, 1, INDEX_NONE,'diffK4T =',
74     &' /* Bihaarmonic diffusion of heat laterally ( m^4/s ) */')
75     CALL WRITE_1D_R8( diffKhS, 1, INDEX_NONE,'diffKhS =',
76     &' /* Laplacian diffusion of salt laterally ( m^2/s ) */')
77     CALL WRITE_1D_R8( diffKzS, 1, INDEX_NONE,'diffKzS =',
78     &' /* Laplacian diffusion of salt vertically ( m^2/s ) */')
79     CALL WRITE_1D_R8( diffK4S, 1, INDEX_NONE,'diffK4S =',
80     &' /* Bihaarmonic diffusion of salt laterally ( m^4/s ) */')
81 cnh 1.6 CALL WRITE_1D_R8( tAlpha,1, INDEX_NONE,'tAlpha =',
82     &' /* Linear EOS thermal expansion coefficient ( 1/degree ) */')
83     CALL WRITE_1D_R8( sBeta, 1, INDEX_NONE,'sBeta =',
84     &' /* Linear EOS haline contraction coefficient ( 1/ppt ) */')
85     CALL WRITE_1D_R8( rhonil,1, INDEX_NONE,'rhonil =',
86     &' /* Reference density ( kg/m^3 ) */')
87     CALL WRITE_1D_R8( gravity,1, INDEX_NONE,'gravity =',
88     &' /* Gravitational acceleration ( m/s^2 ) */')
89 cnh 1.8 CALL WRITE_1D_R8( gBaro,1, INDEX_NONE,'gBaro =',
90     &' /* Barotropic gravity ( m/s^2 ) */')
91 cnh 1.6 CALL WRITE_1D_R8( f0,1, INDEX_NONE,'f0 =',
92     &' /* Reference coriolis parameter ( 1/s ) */')
93     CALL WRITE_1D_R8( beta,1, INDEX_NONE,'beta =',
94     &' /* Beta ( 1/(m.s) ) */')
95 cnh 1.8 CALL WRITE_1D_R8( freeSurfFac,1, INDEX_NONE,'freeSurfFac =',
96     &' /* Implcit free surface factor */')
97     CALL WRITE_1D_L( implicitFreeSurface,1, INDEX_NONE,
98     & 'implicitFreeSurface =',
99     &' /* Implicit free surface on/off flag */')
100     CALL WRITE_1D_L( rigidLid,1, INDEX_NONE,
101     & 'rigidLid =',
102     &' /* Rigid lid on/off flag */')
103 cnh 1.9 CALL WRITE_1D_L( momAdvection,1, INDEX_NONE,
104     & 'momAdvection =',
105     & ' /* Momentum advection on/off flag */')
106     CALL WRITE_1D_L( momViscosity,1, INDEX_NONE,
107     & 'momViscosity =', ' /* Momentum viscosity on/off flag */')
108     CALL WRITE_1D_L( useCoriolis,1, INDEX_NONE,
109     & 'useCoriolis =', ' /* Coriolis on/off flag */')
110     CALL WRITE_1D_L( momForcing,1, INDEX_NONE,
111     & 'momForcing =', ' /* Momentum forcing on/off flag */')
112     CALL WRITE_1D_L( momPressureForcing,1, INDEX_NONE,
113     & 'momPressureForcing =', ' /* Momentum pressure term on/off flag */')
114 cnh 1.8 CALL WRITE_1D_R8( GMMaxSlope,1, INDEX_NONE,'GMMaxSlope =',
115     &' /* Max. slope allowed in GM/Redi tensor */')
116     CALL WRITE_1D_R8( GMLength,1, INDEX_NONE,'GMLength =',
117     &' /* Length to use in Visbeck et al. formula for K (m) */')
118     CALL WRITE_1D_R8( GMAlpha,1, INDEX_NONE,'GMAlpha =',
119     &' /* alpha to use in Visbeck et al. formula for K */')
120     CALL WRITE_1D_R8( GMdepth,1, INDEX_NONE,'GMdepth =',
121     &' /* Depth to integrate for Visbeck et. al Richardson # (m) */')
122     CALL WRITE_1D_R8( GMkbackground,1, INDEX_NONE,'GMkbackground =',
123     &' /* background value of GM/Redi coefficient m^2/s */')
124 cnh 1.6 WRITE(msgBuf,'(A)') '// '
125     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
126 cnh 1.9
127 cnh 1.6 WRITE(msgBuf,'(A)') '// Elliptic solver(s) paramters ( PARM02 in namelist ) '
128     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
129     WRITE(msgBuf,'(A)') '// '
130     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
131     CALL WRITE_1D_I( cg2dMaxIters,1, INDEX_NONE,'cg2dMaxIters =',
132     &' /* Upper limit on 2d con. grad iterations */')
133     CALL WRITE_1D_I( cg2dChkResFreq,1, INDEX_NONE,'cg2dChkResFreq =',
134     &' /* 2d con. grad convergence test frequency */')
135     CALL WRITE_1D_R8( cg2dTargetResidual,1, INDEX_NONE,'cg2dTargetResidual =',
136     &' /* 2d con. grad target residual */')
137    
138     WRITE(msgBuf,'(A)') '// '
139     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
140     WRITE(msgBuf,'(A)') '// Time stepping paramters ( PARM03 in namelist ) '
141     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
142     WRITE(msgBuf,'(A)') '// '
143     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
144     CALL WRITE_1D_I( nIter0,1, INDEX_NONE,'nIter0 =',
145     &' /* Base timestep number */')
146     CALL WRITE_1D_I( nTimeSteps,1, INDEX_NONE,'nTimeSteps =',
147     &' /* Number of timesteps */')
148     CALL WRITE_1D_R8( deltaTmom,1, INDEX_NONE,'deltatTmom =',
149     &' /* Momentum equation timestep ( s ) */')
150     CALL WRITE_1D_R8( deltaTtracer,1, INDEX_NONE,'deltatTtracer =',
151     &' /* Tracer equation timestep ( s ) */')
152 cnh 1.9 CALL WRITE_1D_R8( cAdjFreq,1, INDEX_NONE,'cAdjFreq =',
153     &' /* Convective adjustment interval ( s ) */')
154 cnh 1.6 CALL WRITE_1D_R8( abEps,1, INDEX_NONE,'abEps =',
155     &' /* Adams-Bashforth stabilizing weight */')
156     CALL WRITE_1D_R8( tauCD,1, INDEX_NONE,'tauCD =',
157     &' /* CD coupling time-scale ( s ) */')
158     CALL WRITE_1D_R8( rCD,1, INDEX_NONE,'rCD =',
159     &' /* Normalised CD coupling parameter */')
160     CALL WRITE_1D_R8( startTime,1, INDEX_NONE,'startTime =',
161     &' /* Run start time ( s ). */')
162     CALL WRITE_1D_R8( endTime,1, INDEX_NONE,'endTime =',
163     &' /* Integration ending time ( s ). */')
164 cnh 1.7 CALL WRITE_1D_R8( pChkPtFreq,1, INDEX_NONE,'pChkPtFreq =',
165     &' /* Permanent restart/checkpoint file interval ( s ). */')
166 cnh 1.6 CALL WRITE_1D_R8( chkPtFreq,1, INDEX_NONE,'chkPtFreq =',
167 cnh 1.7 &' /* Rolling restart/checkpoint file interval ( s ). */')
168 cnh 1.6 CALL WRITE_1D_R8( dumpFreq,1, INDEX_NONE,'dumpFreq =',
169     &' /* Model state write out interval ( s ). */')
170    
171     WRITE(msgBuf,'(A)') '// '
172     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
173     WRITE(msgBuf,'(A)') '// Gridding paramters ( PARM04 in namelist ) '
174     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
175     WRITE(msgBuf,'(A)') '// '
176     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
177     CALL WRITE_1D_L( usingCartesianGrid,1, INDEX_NONE,'usingCartesianGrid =',
178     &' /* Cartesian coordinates flag ( True / False ) */')
179     CALL WRITE_1D_L( usingSphericalPolarGrid,1, INDEX_NONE,'usingSphericalPolarGrid =',
180     &' /* Spherical coordinates flag ( True / False ) */')
181     CALL WRITE_1D_R8( delZ,Nz, INDEX_K,'delZ = ',
182     &' /* W spacing ( m ) */')
183     CALL WRITE_1D_R8( delX, Nx, INDEX_I,'delX = ',
184     &' /* U spacing ( m - cartesian, degrees - spherical ) */')
185     CALL WRITE_1D_R8( delY, Ny, INDEX_J,'delY = ',
186     &' /* V spacing ( m - cartesian, degrees - spherical ) */')
187     CALL WRITE_1D_R8( phiMin, 1, INDEX_NONE,'phiMin = ',
188     &' /* Southern boundary ( ignored - cartesian, degrees - spherical ) */')
189     CALL WRITE_1D_R8( thetaMin, 1, INDEX_NONE,'thetaMin = ',
190     &' /* Western boundary ( ignored - cartesian, degrees - spherical ) */')
191     CALL WRITE_1D_R8( rSphere, 1, INDEX_NONE,'rSphere = ',
192     &' /* Radius ( ignored - cartesian, m - spherical ) */')
193     DO bi=1,nSx
194     DO I=1,sNx
195     xcoord((bi-1)*sNx+I) = xc(I,1,bi,1)
196     ENDDO
197     ENDDO
198     CALL WRITE_1D_R8( xcoord, Nx, INDEX_I,'xcoord = ',
199     &' /* P-point X coordinate ( m - cartesian, degrees - spherical ) */')
200     DO bj=1,nSy
201     DO J=1,sNy
202     ycoord((bj-1)*sNy+J) = yc(1,J,1,bj)
203     ENDDO
204     ENDDO
205     CALL WRITE_1D_R8( ycoord, Ny, INDEX_J,'ycoord = ',
206     &' /* P-point Y coordinate ( m - cartesian, degrees - spherical ) */')
207     DO K=1,Nz
208     zcoord(K) = zc(K)
209     ENDDO
210     CALL WRITE_1D_R8( zcoord, Nz, INDEX_K,'zcoord = ',
211     &' /* P-point Z coordinate ( m ) */')
212    
213 cnh 1.5
214    
215 cnh 1.1 WRITE(msgBuf,'(A)') ' '
216     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
217     & SQUEEZE_RIGHT , 1)
218 cnh 1.5
219 cnh 1.1 _END_MASTER(myThid)
220     _BARRIER
221    
222    
223     RETURN
224     100 FORMAT(A,
225 cnh 1.4 &' '
226 cnh 1.1 &)
227     END
228    

  ViewVC Help
Powered by ViewVC 1.1.22