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

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

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


Revision 1.100 - (hide annotations) (download)
Fri Jun 9 13:18:16 2017 UTC (6 years, 11 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, HEAD
Changes since 1.99: +50 -19 lines
refine checking OLx/OLy and SEAICE_OLx/y, especially in the case of
SEAICE_2ndOrderBC=.True.

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

  ViewVC Help
Powered by ViewVC 1.1.22