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

Annotation of /MITgcm/model/src/config_check.F

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


Revision 1.8 - (hide annotations) (download)
Tue Feb 11 04:05:32 2003 UTC (21 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint48e_post, checkpoint48i_post, checkpoint50, checkpoint50b_pre, checkpoint48f_post, checkpoint48h_post, checkpoint50a_post, checkpoint49, checkpoint48g_post
Branch point for: ecco-branch
Changes since 1.7: +9 -1 lines
dynamics: change definition of computational domain & adapt mom_fluxform
 accordingly ; when viscA4=0, allows to run the dynamics with Olx=Oly=2.

1 jmc 1.8 C $Header: /u/gcmpack/MITgcm/model/src/config_check.F,v 1.7 2003/01/30 00:08:29 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "CPP_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: CONFIG_CHECK
8     C !INTERFACE:
9     SUBROUTINE CONFIG_CHECK( myThid )
10     C !DESCRIPTION: \bv
11     C *=========================================================*
12     C | SUBROUTINE CONFIG_CHECK
13     C | o Check model parameter settings.
14     C *=========================================================*
15     C | This routine help to prevent the use of parameters
16     C | that are not compatible with the model configuration.
17     C *=========================================================*
18     C \ev
19    
20     C !USES:
21     IMPLICIT NONE
22     C === Global variables ===
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "PARAMS.h"
26     c #include "GRID.h"
27    
28     C !INPUT/OUTPUT PARAMETERS:
29     C === Routine arguments ===
30     C myThid - Number of this instances of CONFIG_CHECK
31     INTEGER myThid
32     CEndOfInterface
33    
34     C !LOCAL VARIABLES:
35     C == Local variables ==
36     C msgBuf :: Informational/error meesage buffer
37     CHARACTER*(MAX_LEN_MBUF) msgBuf
38     CEOP
39    
40     C- check that CPP option is "defined" when running-flag parameter is on:
41    
42     #ifndef ALLOW_NONHYDROSTATIC
43     IF (nonHydrostatic) THEN
44     WRITE(msgBuf,'(A)')
45     & 'CONFIG_CHECK: #undef ALLOW_NONHYDROSTATIC and'
46 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
47 jmc 1.1 WRITE(msgBuf,'(A)')
48     & 'CONFIG_CHECK: nonHydrostatic is TRUE'
49 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
50 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
51     ENDIF
52     #endif
53    
54     #ifndef EXACT_CONSERV
55     IF (exactConserv) THEN
56     WRITE(msgBuf,'(A)')
57     & 'CONFIG_CHECK: #undef EXACT_CONSERV and'
58 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
59 jmc 1.1 WRITE(msgBuf,'(A)')
60     & 'CONFIG_CHECK: exactConserv is TRUE'
61 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
62 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
63     ENDIF
64     #endif
65    
66     #ifndef NONLIN_FRSURF
67     IF (nonlinFreeSurf.NE.0) THEN
68     WRITE(msgBuf,'(A)')
69     & 'CONFIG_CHECK: #undef NONLIN_FRSURF and'
70 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
71 jmc 1.1 WRITE(msgBuf,'(A)')
72     & 'CONFIG_CHECK: nonlinFreeSurf is non-zero'
73 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
74 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
75     ENDIF
76     #endif
77    
78     #ifdef USE_NATURAL_BCS
79     WRITE(msgBuf,'(A)')
80 jmc 1.3 & 'CONFIG_CHECK: USE_NATURAL_BCS option has been replaced'
81     CALL PRINT_ERROR( msgBuf , myThid)
82 jmc 1.1 WRITE(msgBuf,'(A)')
83 jmc 1.3 & 'CONFIG_CHECK: by useRealFreshWaterFlux=TRUE in data file'
84     CALL PRINT_ERROR( msgBuf , myThid)
85 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
86 jmc 1.3 #endif
87    
88 jmc 1.4 C o If pLoadFile is set, then we should make sure the corresponing
89     C code is being compiled
90     #ifndef ATMOSPHERIC_LOADING
91     IF (pLoadFile.NE.' ') THEN
92     WRITE(msgBuf,'(A)')
93     & 'CONFIG_CHECK: pLoadFile is set but you have not'
94     CALL PRINT_ERROR( msgBuf , myThid)
95     WRITE(msgBuf,'(A)')
96     & 'compiled the model with the pressure loading code.'
97     CALL PRINT_ERROR( msgBuf , myThid)
98     WRITE(msgBuf,'(A,A)')
99     & 'Re-compile with: #define ATMOSPHERIC_LOADING',
100     & ' or -DATMOSPHERIC_LOADING'
101     CALL PRINT_ERROR( msgBuf , myThid)
102     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
103     ENDIF
104     #endif
105    
106     C o If taveFreq is finite, then we must make sure the diagnostics
107     C code is being compiled
108     #ifndef ALLOW_TIMEAVE
109     IF (taveFreq.NE.0.) THEN
110     WRITE(msgBuf,'(A)')
111     & 'CONFIG_CHECK: taveFreq <> 0 but you have'
112     CALL PRINT_ERROR( msgBuf , 1)
113     WRITE(msgBuf,'(A)')
114     & 'not compiled the model with the diagnostics routines.'
115     CALL PRINT_ERROR( msgBuf , 1)
116     WRITE(msgBuf,'(A,A)')
117     & 'Re-compile with: #define ALLOW_TIMEAVE',
118     & ' or -DALLOW_TIMEAVE'
119     CALL PRINT_ERROR( msgBuf , 1)
120     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
121     ENDIF
122     #endif
123    
124 jmc 1.3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
125    
126     C- check parameter consistency :
127 jmc 1.8
128     IF ( viscA4.NE.0. .AND. (Olx.LT.3 .OR. Oly.LT.3)) THEN
129     WRITE(msgBuf,'(A,A)')
130     & 'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',
131     & ' overlap (Olx,Oly) smaller than 3'
132     CALL PRINT_ERROR( msgBuf , myThid)
133     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
134     ENDIF
135 jmc 1.3
136     IF ( rigidLid .AND. implicitFreeSurface ) THEN
137     WRITE(msgBuf,'(A,A)')
138     & 'CONFIG_CHECK: Cannot select both implicitFreeSurface',
139     & ' and rigidLid.'
140     CALL PRINT_ERROR( msgBuf , myThid)
141     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
142     ENDIF
143    
144     IF (rigidLid .AND. exactConserv) THEN
145 jmc 1.1 WRITE(msgBuf,'(A)')
146 jmc 1.3 & 'CONFIG_CHECK: exactConserv not compatible with'
147     CALL PRINT_ERROR( msgBuf , myThid)
148 jmc 1.1 WRITE(msgBuf,'(A)')
149 jmc 1.3 & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
150     CALL PRINT_ERROR( msgBuf , myThid)
151 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
152     ENDIF
153    
154 jmc 1.3 IF (rigidLid .AND. useRealFreshWaterFlux) THEN
155 jmc 1.1 WRITE(msgBuf,'(A)')
156 jmc 1.3 & 'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'
157     CALL PRINT_ERROR( msgBuf , myThid)
158 jmc 1.1 WRITE(msgBuf,'(A)')
159     & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
160 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
161     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
162     ENDIF
163    
164     IF ( (implicSurfPress.NE.1. .OR. implicDiv2DFlow.NE.1.)
165     & .AND. nonHydrostatic ) THEN
166     WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: nonHydrostatic',
167     & ' NOT SAFE with non-fully implicit Barotropic solver'
168     CALL PRINT_ERROR( msgBuf , myThid)
169     WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: To by-pass this',
170     & 'STOP, comment this test and re-compile config_check'
171     CALL PRINT_ERROR( msgBuf , myThid)
172 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
173     ENDIF
174    
175     IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN
176     WRITE(msgBuf,'(A)')
177     & 'CONFIG_CHECK: nonlinFreeSurf cannot be used'
178 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
179 jmc 1.1 WRITE(msgBuf,'(A)')
180     & 'CONFIG_CHECK: without exactConserv'
181 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
182 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
183     ENDIF
184    
185 jmc 1.6 IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN
186     WRITE(msgBuf,'(A)')
187     & 'CONFIG_CHECK: r* Coordinate cannot be used'
188     CALL PRINT_ERROR( msgBuf , myThid)
189     WRITE(msgBuf,'(A)')
190     & 'CONFIG_CHECK: without exactConserv'
191     CALL PRINT_ERROR( msgBuf , myThid)
192     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
193     ENDIF
194    
195 jmc 1.7 C- note : not implemented in checkpoint48b but it's done now (since 01-28-03)
196     c IF (select_rStar.GT.0 .AND. useOBCS ) THEN
197     c WRITE(msgBuf,'(A)')
198     c & 'CONFIG_CHECK: r* Coordinate not yet implemented'
199     c CALL PRINT_ERROR( msgBuf , 1)
200     c WRITE(msgBuf,'(A)')
201     c & 'CONFIG_CHECK: in OBC package'
202     c CALL PRINT_ERROR( msgBuf , 1)
203     c STOP 'ABNORMAL END: S/R CONFIG_CHECK'
204     c ENDIF
205 jmc 1.1
206     IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN
207     WRITE(msgBuf,'(A)')
208     & 'CONFIG_CHECK: nonlinFreeSurf not yet implemented'
209 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
210 jmc 1.1 WRITE(msgBuf,'(A)')
211     & 'CONFIG_CHECK: in nonHydrostatic code'
212 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
213 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
214     ENDIF
215 jmc 1.3
216 jmc 1.4 IF (nonlinFreeSurf.NE.0.AND.deltaTfreesurf.NE.deltaTtracer) THEN
217 jmc 1.3 WRITE(msgBuf,'(A)')
218 jmc 1.4 & 'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'
219     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
220     & SQUEEZE_RIGHT , myThid)
221     WRITE(msgBuf,'(A)')
222     & 'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'
223     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
224     & SQUEEZE_RIGHT , myThid)
225 jmc 1.3 ENDIF
226    
227     IF (useRealFreshWaterFlux .AND. exactConserv
228     & .AND.startTime.NE.0. .AND. implicSurfPress.EQ.0. _d 0) THEN
229     WRITE(msgBuf,'(A)')
230     & 'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'
231     CALL PRINT_ERROR( msgBuf , myThid)
232     WRITE(msgBuf,'(A)')
233     & 'CONFIG_CHECK: restart not implemented in this config'
234     CALL PRINT_ERROR( msgBuf , myThid)
235     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
236     ENDIF
237    
238 jmc 1.4 #ifdef NONLIN_FRSURF
239     IF (useRealFreshWaterFlux .AND. .NOT.exactConserv
240     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
241     WRITE(msgBuf,'(A)')
242     & 'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'
243     CALL PRINT_ERROR( msgBuf , myThid)
244     WRITE(msgBuf,'(A)')
245     & 'CONFIG_CHECK: requires exactConserv=T'
246     CALL PRINT_ERROR( msgBuf , myThid)
247     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
248     ENDIF
249     #else
250 jmc 1.3 IF (useRealFreshWaterFlux .AND. exactConserv
251     & .AND. implicSurfPress.NE.1. _d 0 ) THEN
252     WRITE(msgBuf,'(A)')
253     & 'CONFIG_CHECK: Pb with restart in this config'
254     CALL PRINT_ERROR( msgBuf , myThid)
255     WRITE(msgBuf,'(A)')
256     & 'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to fix it'
257     CALL PRINT_ERROR( msgBuf , myThid)
258     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
259     ENDIF
260 jmc 1.4
261     IF (useRealFreshWaterFlux
262     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
263     WRITE(msgBuf,'(A)')
264     & 'CONFIG_CHECK: E-P effects on wVel are not included'
265     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
266     & SQUEEZE_RIGHT , myThid)
267     WRITE(msgBuf,'(A)')
268     & 'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to fix it'
269 jmc 1.5 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
270     & SQUEEZE_RIGHT , myThid)
271     ENDIF
272    
273     IF (select_rStar .NE. 0) THEN
274     WRITE(msgBuf,'(A)')
275     & 'CONFIG_CHECK: rStar is part of NonLin-FS '
276     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
277     & SQUEEZE_RIGHT , myThid)
278     WRITE(msgBuf,'(A)')
279     & 'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to use it'
280 jmc 1.4 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
281     & SQUEEZE_RIGHT , myThid)
282     ENDIF
283     #endif /* NONLIN_FRSURF */
284 jmc 1.1
285     WRITE(msgBuf,'(A)') 'CONFIG_CHECK: OK'
286     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
287     & SQUEEZE_RIGHT,myThid)
288    
289     RETURN
290     END

  ViewVC Help
Powered by ViewVC 1.1.22