/[MITgcm]/MITgcm/pkg/seaice/seaice_check.F
ViewVC logotype

Contents of /MITgcm/pkg/seaice/seaice_check.F

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


Revision 1.89 - (show annotations) (download)
Tue May 27 09:27:14 2014 UTC (9 years, 11 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65d, checkpoint65e, checkpoint65, checkpoint64y, checkpoint64z
Changes since 1.88: +26 -1 lines
remove code that resets useThSice in S/R seaice_readparms and add a
warning instead

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_check.F,v 1.88 2014/03/20 09:23:36 mlosch Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5 #ifdef ALLOW_EXF
6 # include "EXF_OPTIONS.h"
7 #endif
8
9 CBOP
10 C !ROUTINE: SEAICE_CHECK
11 C !INTERFACE:
12 SUBROUTINE SEAICE_CHECK( myThid )
13
14 C !DESCRIPTION: \bv
15 C *==========================================================*
16 C | S/R SEAICE_CHECK
17 C | o Validate basic package setup and inter-package
18 C | dependencies.
19 C *==========================================================*
20 C \ev
21
22 C !USES:
23 IMPLICIT NONE
24
25 C === Global variables ===
26 #include "SIZE.h"
27 #include "EEPARAMS.h"
28 #include "PARAMS.h"
29 #ifdef ALLOW_EXF
30 # include "EXF_PARAM.h"
31 #endif
32 #include "GRID.h"
33 #include "SEAICE_SIZE.h"
34 #include "SEAICE_PARAMS.h"
35 #include "SEAICE.h"
36 #include "SEAICE_TRACER.h"
37 #include "GAD.h"
38
39 C !INPUT/OUTPUT PARAMETERS:
40 C === Routine arguments ===
41 C myThid :: my Thread Id. number
42 INTEGER myThid
43 CEOP
44
45 C !LOCAL VARIABLES:
46 C === Local variables ===
47 C ioUnit :: temp for writing msg unit
48 C msgBuf :: Informational/error message buffer
49 INTEGER ioUnit
50 CHARACTER*(MAX_LEN_MBUF) msgBuf
51 LOGICAL checkAdvSchArea, checkAdvSchHeff, checkAdvSchSnow
52 LOGICAL checkAdvSchSalt
53 #ifdef ALLOW_SITRACER
54 INTEGER iTracer
55 #endif
56 _RL SEAICE_mcphee_max
57 INTEGER kSurface
58 INTEGER i
59 INTEGER ILNBLNK
60 EXTERNAL ILNBLNK
61 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
62
63 IF ( buoyancyRelation .EQ. 'OCEANICP' ) THEN
64 kSurface = Nr
65 ELSE
66 kSurface = 1
67 ENDIF
68 ioUnit = errorMessageUnit
69
70 _BEGIN_MASTER(myThid)
71
72 C-- ALLOW_SEAICE
73 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: #define ALLOW_SEAICE'
74 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
75 & SQUEEZE_RIGHT, myThid )
76
77 C-- SEAICE needs forcing_In_AB FALSE
78 IF (tracForcingOutAB.NE.1) THEN
79 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK:',
80 & ' Need T,S forcing out of AB (tracForcingOutAB=1)'
81 CALL PRINT_ERROR( msgBuf, myThid )
82 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
83 ENDIF
84
85 C-- check ice cover fraction formula
86 IF ((SEAICE_areaGainFormula.LT.1).OR.
87 & (SEAICE_areaGainFormula.GT.2)) THEN
88 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK:',
89 & ' SEAICE_areaGainFormula must be between 1 and 2'
90 CALL PRINT_ERROR( msgBuf, myThid )
91 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
92 ENDIF
93 IF ((SEAICE_areaLossFormula.LT.1).OR.
94 & (SEAICE_areaLossFormula.GT.3)) THEN
95 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK:',
96 & ' SEAICE_areaLossFormula must be between 1 and 2'
97 CALL PRINT_ERROR( msgBuf, myThid )
98 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
99 ENDIF
100
101 IF ( (.NOT.useThSIce).AND.(.NOT.SEAICE_doOpenWaterGrowth)
102 & .AND.( (SEAICE_areaGainFormula.NE.2).OR.
103 & (SEAICE_areaLossFormula.NE.3) ) ) THEN
104 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK: ',
105 & 'when SEAICE_doOpenWaterGrowth is false, you need to set'
106 CALL PRINT_ERROR( msgBuf, myThid )
107 WRITE(msgBuf,'(A)')
108 & 'SEAICE_areaGainFormula.EQ.2 and SEAICE_areaLossFormula.EQ.3'
109 CALL PRINT_ERROR( msgBuf, myThid )
110 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
111 ENDIF
112
113 C-- check concistency of turbulent flux term etc. specification
114
115 SEAICE_mcphee_max=drF(kSurface)/SEAICE_deltaTtherm
116 IF ( usePW79thermodynamics .AND.
117 & ( SEAICE_mcPheePiston .LT. 0. _d 0 .OR.
118 & SEAICE_mcPheePiston .GT. SEAICE_mcphee_max ) ) THEN
119 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK:',
120 & ' SEAICE_mcPheePiston is out of bounds.'
121 CALL PRINT_ERROR( msgBuf, myThid )
122 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK:',
123 & ' They must lie within 0. and drF(1)/SEAICE_deltaTtherm '
124 CALL PRINT_ERROR( msgBuf, myThid )
125 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
126 ENDIF
127
128 IF ( ( SEAICE_frazilFrac .LT. 0. _d 0 ) .OR.
129 & ( SEAICE_frazilFrac .GT. 1. _d 0 ) ) THEN
130 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK:',
131 & ' SEAICE_frazilFrac is out of bounds.'
132 CALL PRINT_ERROR( msgBuf, myThid )
133 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK:',
134 & ' They must lie within 0. and 1. '
135 CALL PRINT_ERROR( msgBuf, myThid )
136 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
137 ENDIF
138
139 IF ( ( SEAICE_mcPheeTaper .LT. 0. _d 0 ) .OR.
140 & ( SEAICE_mcPheeTaper .GT. 1. _d 0 ) ) THEN
141 WRITE(msgBuf,'(2A)')
142 & 'SEAICE_mcPheeTaper cannot be specified ',
143 & 'outside of the [0. 1.] range'
144 CALL PRINT_ERROR( msgBuf, myThid )
145 STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
146 ENDIF
147
148 IF ( (.NOT.useThSIce).AND.SEAICE_doOpenWaterMelt
149 & .AND.(.NOT.SEAICE_doOpenWaterGrowth) ) THEN
150 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK: ',
151 & 'to use SEAICE_doOpenWaterMelt, you need to '
152 CALL PRINT_ERROR( msgBuf, myThid )
153 WRITE(msgBuf,'(A)')
154 & 'also set SEAICE_doOpenWaterGrowth to .TRUE.'
155 CALL PRINT_ERROR( msgBuf, myThid )
156 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
157 ENDIF
158
159 C-- check specifications of new features for testing
160
161 #ifdef SEAICE_DISABLE_HEATCONSFIX
162 IF ( SEAICEheatConsFix ) THEN
163 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK: ',
164 & 'to use SEAICEheatConsFix, you need to '
165 CALL PRINT_ERROR( msgBuf, myThid )
166 WRITE(msgBuf,'(A)')
167 & 'undef SEAICE_DISABLE_HEATCONSFIX and recompile'
168 CALL PRINT_ERROR( msgBuf, myThid )
169 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
170 ENDIF
171 #endif
172
173 #ifndef ALLOW_SITRACER
174 IF ( SEAICE_salinityTracer ) THEN
175 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK: ',
176 & 'to use SEAICE_salinityTracer, you need to '
177 CALL PRINT_ERROR( msgBuf, myThid )
178 WRITE(msgBuf,'(A)')
179 & 'define ALLOW_SITRACER and recompile'
180 CALL PRINT_ERROR( msgBuf, myThid )
181 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
182 ENDIF
183
184 IF ( SEAICE_ageTracer ) THEN
185 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK: ',
186 & 'to use SEAICE_ageTracer, you need to '
187 CALL PRINT_ERROR( msgBuf, myThid )
188 WRITE(msgBuf,'(A)')
189 & 'define ALLOW_SITRACER and recompile'
190 CALL PRINT_ERROR( msgBuf, myThid )
191 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
192 ENDIF
193 #endif
194
195 C-- check SItracer specifications
196 #ifdef ALLOW_SITRACER
197
198 c to be added : if SEAICE_salinityTracer we need one tracer doing that
199 c to be added : if SEAICE_ageTracer we suggest that one tracer does that
200
201 DO iTracer = 1, SItrNumInUse
202
203 IF ( ( SItrFromOceanFrac(iTracer) .LT. 0. _d 0 ) .OR.
204 & ( SItrFromOceanFrac(iTracer) .GT. 1. _d 0 ) ) THEN
205 WRITE(msgBuf,'(2A)')
206 & 'SItrFromOceanFrac cannot be specified ',
207 & 'outside of the [0. 1.] range'
208 CALL PRINT_ERROR( msgBuf, myThid )
209 STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
210 ENDIF
211
212 IF ( ( SItrFromFloodFrac(iTracer) .LT. 0. _d 0 ) .OR.
213 & ( SItrFromFloodFrac(iTracer) .GT. 1. _d 0 ) ) THEN
214 WRITE(msgBuf,'(2A)')
215 & 'SItrFromFloodFrac cannot be specified ',
216 & 'outside of the [0. 1.] range'
217 CALL PRINT_ERROR( msgBuf, myThid )
218 STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
219 ENDIF
220
221 c IF ( (SItrName(iTracer).EQ.'salinity') .AND.
222 c & (SItrMate(iTracer).NE.'HEFF') ) THEN
223 c WRITE(msgBuf,'(2A)')
224 c & 'SItrName = "salinity" requires ',
225 c & 'SItrMate = "HEFF" '
226 c CALL PRINT_ERROR( msgBuf, myThid )
227 c STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
228 c ENDIF
229
230 IF ( (SItrName(iTracer).NE.'salinity').AND.
231 & ( (SItrFromOceanFrac(iTracer).NE.ZERO).OR.
232 & (SItrFromFloodFrac(iTracer).NE.ZERO) ) ) THEN
233 WRITE(msgBuf,'(2A)')
234 & 'SItrFromOceanFrac / SItrFromFloodFrac is only ',
235 & 'available for SItrName = "salinity" (for now)'
236 CALL PRINT_ERROR( msgBuf, myThid )
237 STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
238 ENDIF
239
240 ENDDO
241 #endif
242
243 C-- Check advection schemes
244 checkAdvSchArea = SEAICEadvArea .AND. (
245 & SEAICEadvSchArea.NE.ENUM_UPWIND_1RST .AND.
246 & SEAICEadvSchArea.NE.ENUM_CENTERED_2ND .AND.
247 & SEAICEadvSchArea.NE.ENUM_DST2 .AND.
248 & SEAICEadvSchArea.NE.ENUM_FLUX_LIMIT .AND.
249 & SEAICEadvSchArea.NE.ENUM_DST3 .AND.
250 & SEAICEadvSchArea.NE.ENUM_DST3_FLUX_LIMIT .AND.
251 & SEAICEadvSchArea.NE.ENUM_OS7MP )
252 checkAdvSchHEFF = SEAICEadvHeff .AND. (
253 & SEAICEadvSchHeff.NE.ENUM_UPWIND_1RST .AND.
254 & SEAICEadvSchHeff.NE.ENUM_CENTERED_2ND .AND.
255 & SEAICEadvSchHeff.NE.ENUM_DST2 .AND.
256 & SEAICEadvSchHeff.NE.ENUM_FLUX_LIMIT .AND.
257 & SEAICEadvSchHeff.NE.ENUM_DST3 .AND.
258 & SEAICEadvSchHeff.NE.ENUM_DST3_FLUX_LIMIT .AND.
259 & SEAICEadvSchHeff.NE.ENUM_OS7MP )
260 checkAdvSchSnow = SEAICEadvSnow .AND. (
261 & SEAICEadvSchSnow.NE.ENUM_UPWIND_1RST .AND.
262 & SEAICEadvSchSnow.NE.ENUM_CENTERED_2ND .AND.
263 & SEAICEadvSchSnow.NE.ENUM_DST2 .AND.
264 & SEAICEadvSchSnow.NE.ENUM_FLUX_LIMIT .AND.
265 & SEAICEadvSchSnow.NE.ENUM_DST3 .AND.
266 & SEAICEadvSchSnow.NE.ENUM_DST3_FLUX_LIMIT .AND.
267 & SEAICEadvSchSnow.NE.ENUM_OS7MP )
268 checkAdvSchSalt = SEAICEadvSalt .AND. (
269 & SEAICEadvSchSalt.NE.ENUM_UPWIND_1RST .AND.
270 & SEAICEadvSchSalt.NE.ENUM_CENTERED_2ND .AND.
271 & SEAICEadvSchSalt.NE.ENUM_DST2 .AND.
272 & SEAICEadvSchSalt.NE.ENUM_FLUX_LIMIT .AND.
273 & SEAICEadvSchSalt.NE.ENUM_DST3 .AND.
274 & SEAICEadvSchSalt.NE.ENUM_DST3_FLUX_LIMIT .AND.
275 & SEAICEadvSchSalt.NE.ENUM_OS7MP )
276 IF ( checkAdvSchArea .OR. checkAdvSchHeff .OR.
277 & checkAdvSchSnow .OR. checkAdvSchSalt ) THEN
278 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK: allowed advection schemes',
279 & ' for heff, area, snow, and salt are: '
280 CALL PRINT_ERROR( msgBuf, myThid )
281 WRITE(msgBuf,'(A,7I3)') 'SEAICE_CHECK:',
282 & ENUM_UPWIND_1RST, ENUM_CENTERED_2ND, ENUM_DST2,
283 & ENUM_FLUX_LIMIT, ENUM_DST3, ENUM_DST3_FLUX_LIMIT,
284 & ENUM_OS7MP
285 CALL PRINT_ERROR( msgBuf, myThid )
286 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK:',
287 & ' the following Adv.Scheme are not allowed:'
288 CALL PRINT_ERROR( msgBuf, myThid )
289 IF ( checkAdvSchArea ) THEN
290 WRITE(msgBuf,'(2A,I3)') 'SEAICE_CHECK:',
291 & ' SEAICEadvSchArea = ', SEAICEadvSchArea
292 CALL PRINT_ERROR( msgBuf, myThid )
293 ENDIF
294 IF ( checkAdvSchHeff ) THEN
295 WRITE(msgBuf,'(2A,I3)') 'SEAICE_CHECK:',
296 & ' SEAICEadvSchHeff = ', SEAICEadvSchHeff
297 CALL PRINT_ERROR( msgBuf, myThid )
298 ENDIF
299 IF ( checkAdvSchSnow ) THEN
300 WRITE(msgBuf,'(2A,I3)') 'SEAICE_CHECK:',
301 & ' SEAICEadvSchSnow = ', SEAICEadvSchSnow
302 CALL PRINT_ERROR( msgBuf, myThid )
303 ENDIF
304 IF ( checkAdvSchSalt ) THEN
305 WRITE(msgBuf,'(2A,I3)') 'SEAICE_CHECK:',
306 & ' SEAICEadvSchSalt = ', SEAICEadvSchSalt
307 CALL PRINT_ERROR( msgBuf, myThid )
308 ENDIF
309 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
310 ENDIF
311 IF ( SEAICEadvScheme.EQ.ENUM_CENTERED_2ND ) THEN
312 C-- for now, the code does not allow to use the default advection scheme
313 C (Centered 2nd order) for 1 ice-field and an other advection scheme
314 C for an other ice-field. In this case, stop here.
315 checkAdvSchArea = SEAICEadvArea .AND.
316 & SEAICEadvSchArea.NE.ENUM_CENTERED_2ND
317 checkAdvSchHEFF = SEAICEadvHeff .AND.
318 & SEAICEadvSchHeff.NE.ENUM_CENTERED_2ND
319 checkAdvSchSnow = SEAICEadvSnow .AND.
320 & SEAICEadvSchSnow.NE.ENUM_CENTERED_2ND
321 checkAdvSchSalt = SEAICEadvSalt .AND.
322 & SEAICEadvSchSalt.NE.ENUM_CENTERED_2ND
323 IF ( checkAdvSchArea .OR. checkAdvSchHeff .OR.
324 & checkAdvSchSnow .OR. checkAdvSchSalt ) THEN
325 WRITE(msgBuf,'(A,I3,A)') 'SEAICE_CHECK: SEAICEadvScheme=',
326 & SEAICEadvScheme, ' not compatible with those Adv.Scheme:'
327 CALL PRINT_ERROR( msgBuf, myThid )
328 IF ( checkAdvSchArea ) THEN
329 WRITE(msgBuf,'(2A,I3)') 'SEAICE_CHECK:',
330 & ' SEAICEadvSchArea = ', SEAICEadvSchArea
331 CALL PRINT_ERROR( msgBuf, myThid )
332 ENDIF
333 IF ( checkAdvSchHeff ) THEN
334 WRITE(msgBuf,'(2A,I3)') 'SEAICE_CHECK:',
335 & ' SEAICEadvSchHeff = ', SEAICEadvSchHeff
336 CALL PRINT_ERROR( msgBuf, myThid )
337 ENDIF
338 IF ( checkAdvSchSnow ) THEN
339 WRITE(msgBuf,'(2A,I3)') 'SEAICE_CHECK:',
340 & ' SEAICEadvSchSnow = ', SEAICEadvSchSnow
341 CALL PRINT_ERROR( msgBuf, myThid )
342 ENDIF
343 IF ( checkAdvSchSalt ) THEN
344 WRITE(msgBuf,'(2A,I3)') 'SEAICE_CHECK:',
345 & ' SEAICEadvSchSalt = ', SEAICEadvSchSalt
346 CALL PRINT_ERROR( msgBuf, myThid )
347 ENDIF
348 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
349 ENDIF
350 ELSEIF ( DIFF1 .NE. 0. _d 0 ) THEN
351 C-- for now, the code does not allow to use DIFF1 without the default
352 C advection scheme (Centered 2nd order). In this case, stop here.
353 WRITE(msgBuf,'(2A,1PE16.8)') 'SEAICE_CHECK: ',
354 & 'harmonic+biharmonic DIFF1=', DIFF1
355 CALL PRINT_ERROR( msgBuf, myThid )
356 WRITE(msgBuf,'(2A,I3)') 'SEAICE_CHECK: ',
357 & 'not available with SEAICEadvScheme=', SEAICEadvScheme
358 CALL PRINT_ERROR( msgBuf, myThid )
359 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
360 ENDIF
361
362 C Avoid using both type of diffusion scheme (DIFF1 & SEAICEdiffKh)
363 IF ( DIFF1 .NE. 0. _d 0 .AND. (
364 & ( SEAICEdiffKhHeff .NE. 0. _d 0 ) .OR.
365 & ( SEAICEdiffKhArea .NE. 0. _d 0 ) .OR.
366 & ( SEAICEdiffKhSnow .NE. 0. _d 0 ) .OR.
367 & ( SEAICEdiffKhSalt .NE. 0. _d 0 )
368 & ) ) THEN
369 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK:',
370 & ' DIFF1 > 0 and one of the SEAICEdiffKh[] > 0'
371 CALL PRINT_ERROR( msgBuf, myThid )
372 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK:',
373 & ' => Cannot use both type of diffusion'
374 CALL PRINT_ERROR( msgBuf, myThid )
375 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
376 ENDIF
377
378 IF ( postSolvTempIter.GT.2 .OR. postSolvTempIter .LT. 0 ) THEN
379 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK:',
380 & ' => allowed values for postSolveTempIter: 0, 1, 2'
381 CALL PRINT_ERROR( msgBuf, myThid )
382 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
383 ENDIF
384
385 IF ( SEAICEpresH0 .LE. 0. _d 0 .OR.
386 & SEAICEpresPow0 .LT. 0 .OR. SEAICEpresPow1 .LT. 0 ) THEN
387 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK: ',
388 & 'SEAICEpresH0 (real), SEAICEpresPow0 (integer)'
389 CALL PRINT_ERROR( msgBuf, myThid )
390 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK: OR SEAICEpresPow1 ',
391 & '(integer) has been specified as negative (data.seaice)'
392 CALL PRINT_ERROR( msgBuf, myThid )
393 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
394 ENDIF
395
396 C--
397 #ifdef ALLOW_AUTODIFF_TAMC
398 IF ( NPSEUDOTIMESTEPS .GT. MPSEUDOTIMESTEPS ) THEN
399 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK:',
400 & ' need to increase MPSEUDOTIMESTEPS in SEAICE_PARAMS.h'
401 CALL PRINT_ERROR( msgBuf, myThid )
402 WRITE(msgBuf,'(2A,2I4)') 'SEAICE_CHECK:',
403 & ' MPSEUDOTIMESTEPS, NPSEUDOTIMESTEPS = ',
404 & MPSEUDOTIMESTEPS, NPSEUDOTIMESTEPS
405 CALL PRINT_ERROR( msgBuf, myThid )
406 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
407 ENDIF
408 IF ( IMAX_TICE .GT. NMAX_TICE ) THEN
409 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK:',
410 & ' need to increase NMAX_TICE in SEAICE_PARAMS.h'
411 CALL PRINT_ERROR( msgBuf, myThid )
412 WRITE(msgBuf,'(2A,2I4)') 'SEAICE_CHECK:',
413 & ' NMAX_TICE, MAX_TICE = ', NMAX_TICE, IMAX_TICE
414 CALL PRINT_ERROR( msgBuf, myThid )
415 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
416 ENDIF
417 IF ( SEAICE_maskRHS ) THEN
418 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: SEAICE_maskRHS not allowed'
419 CALL PRINT_ERROR( msgBuf, myThid )
420 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
421 ENDIF
422 #endif
423
424 C-- SEAICE_ALLOW_DYNAMICS and SEAICEuseDYNAMICS
425 #ifndef SEAICE_ALLOW_DYNAMICS
426 IF (SEAICEuseDYNAMICS) THEN
427 WRITE(msgBuf,'(A)')
428 & 'SEAICE_ALLOW_DYNAMICS needed for SEAICEuseDYNAMICS'
429 CALL PRINT_ERROR( msgBuf, myThid )
430 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
431 ENDIF
432 #endif
433
434 C-- SEAICE_EXTERNAL_FORCING is obsolete: issue warning but continue.
435 #ifdef SEAICE_EXTERNAL_FORCING
436 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
437 & 'SEAICE_EXTERNAL_FORCING option is obsolete:'
438 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
439 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
440 & 'seaice now always uses exf to read input files.'
441 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
442 #endif
443
444 C-- SEAICE_GROWTH_LEGACY is obsolete: issue warning but continue.
445 #ifdef SEAICE_GROWTH_LEGACY
446 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
447 & 'CPP flag SEAICE_GROWTH_LEGACY has been retired.'
448 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
449 #endif /* SEAICE_GROWTH_LEGACY */
450
451 C-- SEAICE_CAP_HEFF is obsolete: issue warning but continue.
452 #ifdef SEAICE_CAP_HEFF
453 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
454 & 'CPP flag SEAICE_CAP_HEFF has been retired.'
455 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
456 #endif /* SEAICE_CAP_HEFF */
457
458 C-- SEAICE_MULTICATEGORY is obsolete: issue warning but continue.
459 #ifdef SEAICE_MULTICATEGORY
460 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
461 & 'CPP flag SEAICE_MULTICATEGORY has been retired.'
462 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
463 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
464 & 'Specify SEAICE_multDim=7 in data.seaice to recover'
465 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
466 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
467 & 'previous default SEAICE_MULTICATEGORY setting.'
468 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
469 #endif /* SEAICE_MULTICATEGORY */
470
471 C-- SEAICE_ALLOW_TD_IF is obsolete: issue warning and stop.
472 #ifdef SEAICE_ALLOW_TD_IF
473 WRITE(msgBuf,'(A)')
474 & 'SEAICE_ALLOW_TD_IF option is obsolete:'
475 CALL PRINT_ERROR( msgBuf, myThid )
476 WRITE(msgBuf,'(A)')
477 & 'the seaice*_IF codes are now merged into the main branch.'
478 CALL PRINT_ERROR( msgBuf, myThid )
479 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
480 #endif /* SEAICE_ALLOW_TD_IF */
481
482 IF ( usePW79thermodynamics ) THEN
483 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
484 & 'turbulent ice-ocn heat flux default changed.'
485 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
486 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
487 & ' To recover the old default : set '
488 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
489 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
490 & ' SEAICE_mcPheePiston to the first ocn level'
491 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
492 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
493 & ' thickness divided by SEAICE_deltaTtherm.'
494 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
495 ENDIF
496
497 C-- SEAICE_DO_OPEN_WATER_GROWTH is obsolete: issue warning and stop.
498 #if defined(SEAICE_DO_OPEN_WATER_GROWTH) || \
499 defined(SEAICE_DO_OPEN_WATER_MELT)
500 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK: ',
501 & 'SEAICE_DO_OPEN_WATER_GROWTH / MELT options are obsolete'
502 CALL PRINT_ERROR( msgBuf, myThid )
503 WRITE(msgBuf,'(2A)') 'they are replaced with run time',
504 & ' parameter SEAICE_doOpenWaterGrowth / Melt'
505 CALL PRINT_ERROR( msgBuf, myThid )
506 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
507 #endif /* SEAICE_DO_OPEN_WATER_GROWTH */
508
509 C-- SEAICE_OCN_MELT_ACT_ON_AREA is obsolete: issue warning and stop.
510 #ifdef SEAICE_OCN_MELT_ACT_ON_AREA
511 WRITE(msgBuf,'(A)')
512 & 'SEAICE_OCN_MELT_ACT_ON_AREA option is obsolete:'
513 CALL PRINT_ERROR( msgBuf, myThid )
514 WRITE(msgBuf,'(A)')
515 & 'it is now done with SEAICE_areaLossFormula.EQ.1 and 2'
516 CALL PRINT_ERROR( msgBuf, myThid )
517 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
518 #endif /* SEAICE_OCN_MELT_ACT_ON_AREA */
519
520 C-- FENTY_AREA_EXPANSION_CONTRACTION is obsolete: issue warning and stop.
521 #ifdef FENTY_AREA_EXPANSION_CONTRACTION
522 WRITE(msgBuf,'(A)')
523 & 'FENTY_AREA_EXPANSION_CONTRACTION option is obsolete:'
524 CALL PRINT_ERROR( msgBuf, myThid )
525 WRITE(msgBuf,'(A)')
526 & 'it is now done with SEAICE_areaLoss(Melt)Formula.EQ.1'
527 CALL PRINT_ERROR( msgBuf, myThid )
528 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
529 #endif /* SEAICE_DO_OPEN_WATER_MELT */
530
531 C-- SEAICE_AGE is obsolete: issue warning and stop.
532 #ifdef SEAICE_AGE
533 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK: ',
534 & 'SEAICE_AGE option is obsolete: '
535 CALL PRINT_ERROR( msgBuf, myThid )
536 WRITE(msgBuf,'(2A)') 'it now is done',
537 & ' with SEAICE_SITRACER and siTrName=age'
538 CALL PRINT_ERROR( msgBuf, myThid )
539 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
540 #endif /* SEAICE_AGE */
541
542 C-- SEAICE_SALINITY is obsolete: issue warning and stop.
543 #ifdef SEAICE_SALINITY
544 WRITE(msgBuf,'(A)')
545 & 'SEAICE_SALINITY option is obsolete'
546 CALL PRINT_ERROR( msgBuf, myThid )
547 WRITE(msgBuf,'(A)')
548 & 'use SEAICE_VARIABLE_SALINITY instead.'
549 CALL PRINT_ERROR( msgBuf, myThid )
550 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
551 #endif /* SEAICE_SALINITY */
552
553 C-- SEAICE_OLD_AND_BAD_DISCRETIZATION is obsolete: issue warning and stop.
554 #ifdef SEAICE_OLD_AND_BAD_DISCRETIZATION
555 WRITE(msgBuf,'(A)')
556 & 'SEAICE_OLD_AND_BAD_DISCRETIZATION option is obsolete'
557 CALL PRINT_ERROR( msgBuf, myThid )
558 WRITE(msgBuf,'(A)')
559 & 'and has no effect.'
560 CALL PRINT_ERROR( msgBuf, myThid )
561 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
562 #endif /* SEAICE_OLD_AND_BAD_DISCRETIZATION */
563
564 C-- pkg/seaice requires pkg/exf with following CPP options/
565 IF ( usePW79thermodynamics .OR. .NOT.useCheapAML ) THEN
566 #ifndef ALLOW_EXF
567 WRITE(msgBuf,'(A)')
568 & 'need to define ALLOW_EXF'
569 CALL PRINT_ERROR( msgBuf, myThid )
570 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
571 #else /* ALLOW_EXF */
572 IF ( .NOT.useEXF ) THEN
573 WRITE(msgBuf,'(A)')
574 & 'S/R SEAICE_CHECK: need to set useEXF in data.pkg'
575 CALL PRINT_ERROR( msgBuf, myThid )
576 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
577 ENDIF
578 #ifndef ALLOW_ATM_TEMP
579 WRITE(msgBuf,'(2A)') 'S/R SEAICE_CHECK: ',
580 & 'need to define pkg/exf ALLOW_ATM_TEMP'
581 CALL PRINT_ERROR( msgBuf, myThid )
582 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
583 #endif
584 #ifndef ALLOW_DOWNWARD_RADIATION
585 WRITE(msgBuf,'(2A)') 'S/R SEAICE_CHECK: ',
586 & 'need to define pkg/exf ALLOW_DOWNWARD_RADIATION'
587 CALL PRINT_ERROR( msgBuf, myThid )
588 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
589 #endif
590 #ifdef SEAICE_EXTERNAL_FLUXES
591 # if !defined(EXF_READ_EVAP) && !defined(ALLOW_BULKFORMULAE)
592 WRITE(msgBuf,'(2A)') 'S/R SEAICE_CHECK: ',
593 & 'need to set EXF_READ_EVAP or ALLOW_BULKFORMULAE in pkg/exf'
594 CALL PRINT_ERROR( msgBuf, myThid )
595 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
596 # endif /* !defined(EXF_READ_EVAP) && !defined(ALLOW_BULKFORMULAE) */
597 IF ( SEAICE_waterAlbedo .NE. UNSET_RL ) THEN
598 WRITE(msgBuf,'(A)')
599 & 'SEAICE_waterAlbedo is not used with SEAICE_EXTERNAL_FLUXES'
600 CALL PRINT_ERROR( msgBuf, myThid )
601 WRITE(msgBuf,'(A)')
602 & 'Set exf_albedo in data.exf EXF_NML_01 instead'
603 CALL PRINT_ERROR( msgBuf, myThid )
604 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
605 ENDIF
606 IF ( lwfluxfile .NE. ' ' .AND. lwdownfile .EQ. ' ' ) THEN
607 i = ILNBLNK(lwfluxfile)
608 WRITE(msgBuf,'(A,A)')
609 & 'lwFlux is read from lwfluxfile = ',lwfluxfile(1:i)
610 CALL PRINT_ERROR( msgBuf, myThid )
611 WRITE(msgBuf,'(A)')
612 & 'implying that lwdown = 0. For pkg/seaice to work '//
613 & 'properly lwdown should be read from lwdownfile!'
614 CALL PRINT_ERROR( msgBuf, myThid )
615 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
616 ENDIF
617 IF ( swfluxfile .NE. ' ' .AND. swdownfile .EQ. ' ' ) THEN
618 i = ILNBLNK(swfluxfile)
619 WRITE(msgBuf,'(A,A)')
620 & 'swFlux is read from swfluxfile = ',swfluxfile(1:i)
621 CALL PRINT_ERROR( msgBuf, myThid )
622 WRITE(msgBuf,'(A)')
623 & 'implying that swdown = 0. For pkg/seaice to work '//
624 & 'properly swdown should be read from swdownfile!'
625 CALL PRINT_ERROR( msgBuf, myThid )
626 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
627 ENDIF
628 #else /* if undef SEAICE_EXTERNAL_FLUXES */
629 WRITE(msgBuf,'(3A)') 'S/R SEAICE_CHECK: ',
630 & 'SEAICE_EXTERNAL_FLUXES is undefined, so we assume you ',
631 & 'know what you are doing.'
632 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
633 & SQUEEZE_RIGHT, myThid )
634 CALL PRINT_ERROR( msgBuf, myThid )
635 WRITE(msgBuf,'(2A)') 'S/R SEAICE_CHECK: ',
636 & 'Use S/R SEAICE_BUDGET_OCEAN to compute fluxes over ocean.'
637 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
638 & SQUEEZE_RIGHT, myThid )
639 CALL PRINT_ERROR( msgBuf, myThid )
640 #endif /* SEAICE_EXTERNAL_FLUXES */
641 #ifndef SEAICE_CGRID
642 IF ( .NOT.useAtmWind ) THEN
643 WRITE(msgBuf,'(2A)') 'S/R SEAICE_CHECK: ',
644 & 'needs pkg/exf useAtmWind to be true'
645 CALL PRINT_ERROR( msgBuf, myThid )
646 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
647 ENDIF
648 #endif
649 #ifndef EXF_SEAICE_FRACTION
650 IF ( SEAICE_tauAreaObsRelax.GT.zeroRL ) THEN
651 WRITE(msgBuf,'(2A)') 'S/R SEAICE_CHECK: ',
652 & 'ice-area relaxation needs #define EXF_SEAICE_FRACTION'
653 CALL PRINT_ERROR( msgBuf, myThid )
654 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
655 ENDIF
656 #endif
657 #endif /* ALLOW_EXF */
658 ENDIF
659
660 IF ( OLx.LT.3 .OR. OLy.LT.3 ) THEN
661 WRITE(msgBuf,'(A,A)')
662 & 'SEAICE_CHECK: cannot use EVP nor LSR solver with',
663 & ' overlap (OLx,OLy) smaller than 3'
664 CALL PRINT_ERROR( msgBuf, myThid )
665 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
666 ENDIF
667
668 #ifdef SEAICE_ALLOW_EVP
669 # ifdef ALLOW_AUTODIFF_TAMC
670 IF ( INT(SEAICE_deltaTdyn/SEAICE_deltaTevp).GT.nEVPstepMax ) THEN
671 WRITE(msgBuf,'(A)')
672 & 'SEAICE_ALLOW_EVP: need to set nEVPstepMax to >= nEVPstep'
673 CALL PRINT_ERROR( msgBuf, myThid )
674 WRITE(msgBuf,'(A,I4)')
675 & 'nEVPstep = INT(SEAICE_deltaTdyn/SEAICE_deltaTevp) = ',
676 & INT(SEAICE_deltaTdyn/SEAICE_deltaTevp)
677 CALL PRINT_ERROR( msgBuf, myThid )
678 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
679 ENDIF
680 IF ( SEAICEnEVPstarSteps.NE.UNSET_I .AND.
681 & SEAICEnEVPstarSteps.GT.nEVPstepMax ) THEN
682 WRITE(msgBuf,'(A)')
683 & 'SEAICE_CHECK: need to set nEVPstepMax to >= '//
684 & 'SEAICEnEVPstarSteps'
685 CALL PRINT_ERROR( msgBuf, myThid )
686 WRITE(msgBuf,'(A,I4)')
687 & 'SEAICE_CHECK: SEAICEnEVPstarSteps = ', SEAICEnEVPstarSteps
688 CALL PRINT_ERROR( msgBuf, myThid )
689 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
690 ENDIF
691 # endif
692 IF ( .NOT.SEAICEuseEVPstar
693 & .AND. SEAICEnEVPstarSteps.NE.UNSET_I ) THEN
694 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: SEAICEnEVPstarSteps is '//
695 & 'set, but SEAICEuseEVPstar = .FALSE.'
696 CALL PRINT_ERROR( msgBuf, myThid )
697 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
698 ENDIF
699 IF ( SEAICE_deltaTevp .EQ. UNSET_RL .AND.
700 & SEAICEnEVPstarSteps.NE.UNSET_I ) THEN
701 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: SEAICEnEVPstarSteps is '//
702 & 'set, but SEAICE_deltaTevp is unset (EVP is not turned on)'
703 CALL PRINT_ERROR( msgBuf, myThid )
704 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
705 ENDIF
706 #else
707 IF ( SEAICE_deltaTevp .NE. UNSET_RL ) THEN
708 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: SEAICE_deltaTevp is set'
709 CALL PRINT_ERROR( msgBuf, myThid )
710 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: but cpp-flag '//
711 & 'SEAICE_ALLOW_EVP is not defined in SEAICE_OPTIONS.h'
712 CALL PRINT_ERROR( msgBuf, myThid )
713 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
714 ENDIF
715 #endif
716
717 IF ( usePW79thermodynamics ) THEN
718 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
719 & 'variable freezing point is new default.'
720 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
721 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
722 & ' To recover old constant freezing : '
723 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
724 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
725 & ' set SEAICE_tempFrz0 = -1.96 and '
726 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
727 WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_CHECK: ',
728 & ' SEAICE_dTempFrz_dS = 0.'
729 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
730 ENDIF
731
732 #ifndef SEAICE_GLOBAL_3DIAG_SOLVER
733 IF ( SEAICEuseMultiTileSolver ) THEN
734 WRITE(msgBuf,'(A)')
735 & 'SEAICE_CHECK: SEAICEuseMultiTileSolver = .TRUE.'
736 CALL PRINT_ERROR( msgBuf, myThid )
737 WRITE(msgBuf,'(2A)') ' but CPP-flag ',
738 & 'SEAICE_GLOBAL_3DIAG_SOLVER is #undef in SEAICE_OPTIONS.h'
739 CALL PRINT_ERROR( msgBuf, myThid )
740 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
741 ENDIF
742 #endif /* SEAICE_GLOBAL_3DIAG_SOLVER */
743
744 #ifndef SEAICE_ALLOW_CLIPVELS
745 IF ( SEAICE_clipVelocities ) THEN
746 WRITE(msgBuf,'(A)')
747 & 'SEAICE_CHECK: SEAICE_clipVelocities = .TRUE.'
748 CALL PRINT_ERROR( msgBuf, myThid )
749 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: but cpp-flag '//
750 & 'SEAICE_ALLOW_CLIPVELS is not defined in SEAICE_OPTIONS.h'
751 CALL PRINT_ERROR( msgBuf, myThid )
752 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
753 ENDIF
754 #endif /* SEAICE_ALLOW_CLIPVELS */
755
756 #ifndef SEAICE_ALLOW_CLIPZETA
757 IF ( SEAICE_evpDampC .GT. 0. _d 0 .OR.
758 & SEAICE_zetaMin .GT. 0. _d 0 ) THEN
759 WRITE(msgBuf,'(A)')
760 & 'SEAICE_CHECK: SEAICE_evpDampC and/or SEAICE_zetaMin '//
761 & 'are set in data.seaice'
762 CALL PRINT_ERROR( msgBuf, myThid )
763 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: but cpp-flag '//
764 & 'SEAICE_ALLOW_CLIPZETA is not defined in SEAICE_OPTIONS.h'
765 CALL PRINT_ERROR( msgBuf, myThid )
766 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
767 ENDIF
768 #endif /* SEAICE_ALLOW_CLIPZETA */
769
770 #if !defined(SEAICE_ALLOW_TEM) || !defined(SEAICE_CGRID)
771 IF ( SEAICEuseTEM ) THEN
772 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: SEAICEuseTEM requires that'
773 CALL PRINT_ERROR( msgBuf, myThid )
774 WRITE(msgBuf,'(A)')
775 & 'SEAICE_CHECK: SEAICE_ALLOW_TEM and SEAICE_CGRID are defined'
776 CALL PRINT_ERROR( msgBuf, myThid )
777 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
778 ENDIF
779 #endif
780
781 #ifndef SEAICE_CGRID
782 #ifdef SEAICE_TEST_ICE_STRESS_1
783 WRITE(msgBuf,'(A)')
784 & 'SEAICE_CHECK: Only relevant for B-grid:'
785 CALL PRINT_ERROR( msgBuf, myThid )
786 WRITE(msgBuf,'(A)')
787 & 'SEAICE_CHECK: SEAICE_TEST_ICE_STRESS_1 is replaced by'
788 CALL PRINT_ERROR( msgBuf, myThid )
789 WRITE(msgBuf,'(A)')
790 & 'SEAICE_CHECK: SEAICE_BICE_STRESS (defined by default)'
791 CALL PRINT_ERROR( msgBuf, myThid )
792 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
793 #endif /* SEAICE_TEST_ICE_STRESS_1 */
794 IF ( SEAICEuseDYNAMICS.AND.useCubedSphereExchange ) THEN
795 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK: ',
796 & 'B-grid dynamics not working on Cubed-Sphere grid'
797 CALL PRINT_ERROR( msgBuf, myThid )
798 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
799 ENDIF
800 IF ( SEAICEuseDYNAMICS.AND.useOBCS ) THEN
801 WRITE(msgBuf,'(2A)') 'SEAICE_CHECK: ',
802 & 'Open-Boundaries not implemented in B-grid dynamics'
803 CALL PRINT_ERROR( msgBuf, myThid )
804 C STOP 'ABNORMAL END: S/R SEAICE_CHECK'
805 ENDIF
806 #endif /* ndef SEAICE_CGRID */
807
808 C-- SEAICE_ALLOW_FREEDRIFT and SEAICEuseFREEDRIFT
809 #ifndef SEAICE_ALLOW_FREEDRIFT
810 IF (SEAICEuseFREEDRIFT) THEN
811 WRITE(msgBuf,'(A)')
812 & 'need to #define SEAICE_ALLOW_FREEDRIFT for SEAICEuseFREEDRIFT'
813 CALL PRINT_ERROR( msgBuf, myThid )
814 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
815 ENDIF
816 IF ( LSR_mixIniGuess.GE.0 ) THEN
817 WRITE(msgBuf,'(A)')
818 & 'need to #define SEAICE_ALLOW_FREEDRIFT to use LSR_mixIniGuess'
819 CALL PRINT_ERROR( msgBuf, myThid )
820 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
821 ENDIF
822 #endif
823
824 #ifndef SEAICE_VARIABLE_SALINITY
825 IF ( SEAICEadvSalt ) THEN
826 WRITE(msgBuf,'(A)')
827 & 'SEAICE_CHECK: SEAICEadvSalt = .TRUE. but cpp-flag'
828 CALL PRINT_ERROR( msgBuf, myThid )
829 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: '//
830 & 'SEAICE_VARIABLE_SALINITY is undef in SEAICE_OPTIONS.h'
831 CALL PRINT_ERROR( msgBuf, myThid )
832 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
833 ENDIF
834 #endif /* SEAICE_VARIABLE_SALINITY */
835
836 #ifdef SEAICE_ALLOW_JFNK
837 IF ( SEAICEuseJFNK ) THEN
838 IF ( JFNKres_t.NE.UNSET_RL .AND. JFNKres_tFac.NE.UNSET_RL) THEN
839 WRITE(msgBuf,'(3A)') 'S/R SEAICE_CHECK: JFNKres_t and ',
840 & 'JFNKres_tFac are both set, so that JFNKres_t will be'
841 CALL PRINT_ERROR( msgBuf, myThid )
842 WRITE(msgBuf,'(3A)') 'S/R SEAICE_CHECK: ',
843 & 'overwritten by JFNKres_tFac*JFNKresidual ',
844 & 'in each initial Newton iteration.'
845 CALL PRINT_ERROR( msgBuf, myThid )
846 WRITE(msgBuf,'(2A)')
847 & 'S/R SEAICE_CHECK: For safety we stop here. ',
848 & 'Please unset one of the two parameters.'
849 CALL PRINT_ERROR( msgBuf, myThid )
850 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
851 ELSEIF (JFNKres_t.EQ.UNSET_RL.AND.JFNKres_tFac.EQ.UNSET_RL) THEN
852 WRITE(msgBuf,'(2A)') 'S/R SEAICE_CHECK: need to specify ',
853 & 'JFNKres_t or JFNKres_tFac for SEAICEuseJFNK=.TRUE.'
854 CALL PRINT_ERROR( msgBuf, myThid )
855 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
856 ENDIF
857 C
858 IF ( SEAICE_OLx .GT. OLx-2 .OR. SEAICE_OLy .GT. OLy-2 .OR.
859 & SEAICE_OLx .LT. 0 .OR. SEAICE_OLy .LT. 0 ) THEN
860 WRITE(msgBuf,'(A,I2,A,I2)') 'S/R SEAICE_CHECK: SEAICE_OLx/y = ',
861 & SEAICE_OLx, '/', SEAICE_OLy
862 CALL PRINT_ERROR( msgBuf, myThid )
863 WRITE(msgBuf,'(2A,I2,A,I2)')
864 & 'S/R SEAICE_CHECK: SEAICE_OLx/y cannot be smaller than 0 ',
865 & 'or larger than OLx/y-2 = ', OLx-2, '/', OLy-2
866 CALL PRINT_ERROR( msgBuf, myThid )
867 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
868 ENDIF
869 ENDIF
870 IF ( SEAICEuseJFNK .AND. SEAICEuseEVP ) THEN
871 WRITE(msgBuf,'(2A)')
872 & 'S/R SEAICE_CHECK: cannot have both SEAICEuseJFNK=.TRUE.',
873 & 'and SEAICEuseEVP=.TRUE. (i.e. SEAICE_deltaTevp > 0)'
874 CALL PRINT_ERROR( msgBuf, myThid )
875 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
876 ENDIF
877 #else
878 IF ( SEAICEuseJFNK ) THEN
879 WRITE(msgBuf,'(A)')
880 & 'SEAICE_CHECK: SEAICEuseJFNK = .TRUE. but cpp-flag'
881 CALL PRINT_ERROR( msgBuf, myThid )
882 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: '//
883 & 'SEAICE_ALLOW_JFNK is undef in SEAICE_OPTIONS.h'
884 CALL PRINT_ERROR( msgBuf, myThid )
885 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
886 ENDIF
887 #endif /* SEAICE_ALLOW_JFNK */
888
889 IF ( SEAICEuseDynamics .AND. .NOT.SEAICEuseJFNK ) THEN
890 IF ( SEAICEuseBDF2 ) THEN
891 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: SEAICEuseBDF2 = .TRUE. '//
892 & 'only allowed with SEAICEuseJFNK = .TRUE.'
893 CALL PRINT_ERROR( msgBuf, myThid )
894 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
895 ENDIF
896 IF ( SEAICEuseIMEX ) THEN
897 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: SEAICEuseIMEX = .TRUE. '//
898 & 'only allowed with SEAICEuseJFNK = .TRUE.'
899 CALL PRINT_ERROR( msgBuf, myThid )
900 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
901 ENDIF
902 ENDIF
903 IF ( SEAICEuseIMEX ) THEN
904 WRITE(msgBuf,'(A)') '** WARNING ** SEAICE_CHECK: '//
905 & 'SEAICEuseIMEX = .TRUE. '//
906 & 'currently has no effect, because the code is missing'
907 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
908 ENDIF
909
910 IF ( .NOT.(SEAICEetaZmethod.EQ.0.OR.SEAICEetaZmethod.EQ.3) ) THEN
911 WRITE(msgBuf,'(A,I2)')
912 & 'SEAICE_CHECK: SEAICEetaZmethod = ', SEAICEetaZmethod
913 CALL PRINT_ERROR( msgBuf, myThid )
914 WRITE(msgBuf,'(A)') 'SEAICE_CHECK: '//
915 & 'is no longer allowed; allowed values are 0 and 3'
916 CALL PRINT_ERROR( msgBuf, myThid )
917 STOP 'ABNORMAL END: S/R SEAICE_CHECK'
918 ENDIF
919
920 #ifdef SEAICE_ITD
921 C The ice thickness distribution (ITD) module can only be used with
922 C the zero-layer thermodynamics of S/R SEAICE_GROWTH and the
923 C advection in S/R SEAICE_ADVDIFF
924 C If useThSice=.TRUE., do not reset it here, but issue a warning
925 IF ( useThSice ) THEN
926 WRITE(msgBuf,'(A)') '** WARNING ** SEAICE_CHECK: '//
927 & 'SEAICE_ITD is defined, but useThSice = .TRUE.'
928 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
929 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
930 & SQUEEZE_RIGHT, myThid )
931 WRITE(msgBuf,'(A)') '** WARNING ** SEAICE_CHECK: '//
932 & 'avoids the ice thickness distribution code.'
933 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
934 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
935 & SQUEEZE_RIGHT, myThid )
936 WRITE(msgBuf,'(A)') '** WARNING ** SEAICE_CHECK: '//
937 & 'If you want the ITD code, set useThSice=.FALSE.'
938 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
939 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
940 & SQUEEZE_RIGHT, myThid )
941 ENDIF
942 C SEAICE_GROWTH, i.e. needs usePW79thermodynamics = .TRUE.
943 #endif
944
945 _END_MASTER(myThid)
946
947 RETURN
948 END

  ViewVC Help
Powered by ViewVC 1.1.22