/[MITgcm]/MITgcm_contrib/torge/itd/code/seaice_readparms.F
ViewVC logotype

Annotation of /MITgcm_contrib/torge/itd/code/seaice_readparms.F

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


Revision 1.6 - (hide annotations) (download)
Mon Dec 10 22:19:50 2012 UTC (12 years, 7 months ago) by torge
Branch: MAIN
Changes since 1.5: +21 -11 lines
include updates from main branch

1 torge 1.6 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_readparms.F,v 1.132 2012/11/15 18:13:07 jmc Exp $
2 dimitri 1.1 C $Name: $
3    
4     #include "SEAICE_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: SEAICE_READPARMS
8     C !INTERFACE:
9     SUBROUTINE SEAICE_READPARMS( myThid )
10    
11     C !DESCRIPTION: \bv
12     C *==========================================================*
13     C | S/R SEAICE_READPARMS
14     C | o Routine to read in file data.seaice
15     C *==========================================================*
16     C \ev
17    
18     C !USES:
19     IMPLICIT NONE
20    
21     C === Global variables ===
22     #include "SIZE.h"
23     #include "EEPARAMS.h"
24     #include "PARAMS.h"
25     #include "GRID.h"
26     #include "SEAICE_SIZE.h"
27     #include "SEAICE_PARAMS.h"
28     #include "SEAICE_TRACER.h"
29     #ifdef ALLOW_COST
30     # include "SEAICE_COST.h"
31     #endif
32     #ifdef ALLOW_MNC
33     # include "MNC_PARAMS.h"
34     #endif
35     #ifdef ALLOW_EXF
36     # include "EXF_CONSTANTS.h"
37     #endif /* ALLOW_EXF */
38 torge 1.6 #ifdef ALLOW_AUTODIFF
39     # include "AUTODIFF_PARAMS.h"
40     #endif
41 dimitri 1.1
42     C !INPUT/OUTPUT PARAMETERS:
43     C === Routine arguments ===
44     C myThid :: my Thread Id. number
45     INTEGER myThid
46     CEOP
47    
48     C !LOCAL VARIABLES:
49     C === Local variables ===
50     C msgBuf :: Informational/error message buffer
51     C iUnit :: Work variable for IO unit number
52     CHARACTER*(MAX_LEN_MBUF) msgBuf
53     LOGICAL chkFlag
54     INTEGER iUnit
55     #ifdef ALLOW_SITRACER
56     INTEGER iTracer
57     #endif
58 torge 1.4 #ifdef ALLOW_COST
59     INTEGER locDate(4)
60     #endif /* ALLOW_COST */
61 dimitri 1.1 INTEGER nRetired
62    
63     C- Old parameters (to be retired one day):
64     _RL SEAICE_availHeatTaper
65     _RL SEAICE_gamma_t, SEAICE_gamma_t_frz, SEAICE_availHeatFracFrz
66    
67     C- Retired parameters:
68     C MAX_TICE :: maximum ice temperature (deg C)
69     C LAD :: time stepping used for sea-ice advection:
70     C 1 = LEAPFROG, 2 = BACKWARD EULER.
71     C SEAICE_freeze :: FREEZING TEMP. OF SEA WATER
72     _RL SEAICE_sensHeat, SEAICE_latentWater, SEAICE_latentIce
73     _RL SEAICE_salinity, SIsalFRAC, SIsal0
74     _RL SEAICE_lhSublim, SEAICE_freeze
75     _RL areaMin, areaMax, A22, hiceMin, MAX_TICE
76     LOGICAL SEAICEadvAge
77     INTEGER SEAICEadvSchAge, LAD, SEAICEturbFluxFormula
78     _RL SEAICEdiffKhAge
79     CHARACTER*(MAX_LEN_MBUF) IceAgeFile, IceAgeTrFile(4)
80    
81     C-- SEAICE parameters
82     NAMELIST /SEAICE_PARM01/
83     & SEAICEwriteState, SEAICEuseDYNAMICS, SEAICEuseTEM,
84     & SEAICEuseEVPpickup, SEAICEuseFluxForm,
85     & SEAICEuseMetricTerms,
86     & useHB87stressCoupling, SEAICEuseFlooding,
87     & usePW79thermodynamics, useMaykutSatVapPoly,
88     & SEAICErestoreUnderIce,
89     & SEAICE_salinityTracer, SEAICE_ageTracer,
90     & SEAICEadvHeff, SEAICEadvArea, SEAICEadvSnow,
91     & SEAICEadvSalt, SEAICEadvAge,
92     & SEAICE_clipVelocities, SEAICE_maskRHS, SEAICE_no_slip,
93 torge 1.6 & SEAICEetaZmethod, LAD, IMAX_TICE, postSolvTempIter,
94 dimitri 1.1 & SEAICEadvScheme, SEAICEadvSchArea,
95     & SEAICEadvSchHeff, SEAICEadvSchSnow,
96     & SEAICEadvSchSalt, SEAICEadvSchAge,
97     & SEAICEdiffKhHeff, SEAICEdiffKhSnow, SEAICEdiffKhArea,
98     & SEAICEdiffKhSalt, SEAICEdiffKhAge,
99     & SEAICE_deltaTtherm, SEAICE_deltaTdyn,
100 torge 1.6 & SEAICE_LSRrelaxU, SEAICE_LSRrelaxV,
101 dimitri 1.1 & SEAICE_deltaTevp, SEAICE_elasticParm, SEAICE_evpTauRelax,
102     & SEAICE_evpDampC, SEAICE_zetaMin, SEAICE_zetaMaxFac,
103 torge 1.4 & SEAICEuseJFNK, SEAICEnewtonIterMax, SEAICEkrylovIterMax,
104     & JFNKgamma_nonlin,JFNKres_t,JFNKgamma_lin_min,JFNKgamma_lin_max,
105     & SEAICEpresH0, SEAICEpresPow0, SEAICEpresPow1,
106 dimitri 1.1 & SEAICE_monFreq, SEAICE_dumpFreq, SEAICE_taveFreq,
107     & SEAICE_initialHEFF, SEAICEturbFluxFormula,
108     & SEAICE_areaGainFormula, SEAICE_areaLossFormula,
109     & SEAICE_doOpenWaterGrowth, SEAICE_doOpenWaterMelt,
110     & SEAICE_rhoAir, SEAICE_rhoIce, SEAICE_rhoSnow, ICE2WATR,
111     & SEAICE_cpAir,
112     & SEAICE_drag, SEAICE_waterDrag, SEAICE_dryIceAlb,
113     & SEAICE_wetIceAlb, SEAICE_drySnowAlb, SEAICE_wetSnowAlb, HO,
114     & SEAICE_drag_south, SEAICE_waterDrag_south,
115     & SEAICE_dryIceAlb_south, SEAICE_wetIceAlb_south,
116     & SEAICE_drySnowAlb_south, SEAICE_wetSnowAlb_south, HO_south,
117     & SEAICE_wetAlbTemp, SEAICE_waterAlbedo,
118     & SEAICE_strength, SEAICE_eccen,
119     & SEAICE_lhFusion, SEAICE_lhEvap, SEAICE_dalton,
120     & SEAICE_sensHeat, SEAICE_latentWater, SEAICE_latentIce,
121     & SEAICE_salinity, SIsalFRAC, SIsal0,
122     & areaMin, areaMax, A22, hiceMin,
123     & SEAICE_iceConduct, SEAICE_snowConduct,
124     & SEAICE_emissivity, SEAICE_ice_emiss, SEAICE_snow_emiss,
125     & SEAICE_snowThick, SEAICE_shortwave, SEAICE_freeze, OCEAN_drag,
126     & SEAICE_tempFrz0, SEAICE_dTempFrz_dS, SEAICE_salt0,
127     & SEAICE_saltFrac, SEAICEstressFactor, SEAICE_availHeatTaper,
128     & SEAICE_mcPheePiston, SEAICE_frazilFrac, SEAICE_mcPheeTaper,
129     & SEAICE_mcPheeStepFunc, SEAICE_gamma_t, SEAICE_gamma_t_frz,
130     & SEAICE_availHeatFrac, SEAICE_availHeatFracFrz,
131     & AreaFile, HeffFile, uIceFile, vIceFile, HsnowFile, HsaltFile,
132     & SOLV_MAX_ITERS, SOLV_NCHECK, NPSEUDOTIMESTEPS, LSR_mixIniGuess,
133 torge 1.4 & LSR_ERROR, DIFF1, SEAICEuseFREEDRIFT, SEAICEuseTILT,
134     & SEAICEheatConsFix, SEAICE_multDim, SEAICE_useMultDimSnow,
135 dimitri 1.1 & SEAICE_area_reg, SEAICE_hice_reg,
136     & SEAICE_area_floor, SEAICE_area_max, SEAICE_tauAreaObsRelax,
137     & SEAICE_airTurnAngle, SEAICE_waterTurnAngle,
138     & MAX_HEFF, MIN_ATEMP, MIN_LWDOWN, MAX_TICE, MIN_TICE,
139     & SEAICE_EPS, SEAICE_EPS_SQ,
140     & SEAICE_tave_mnc, SEAICE_dump_mnc, SEAICE_mon_mnc,
141 torge 1.4 #ifdef SEAICE_ITD
142 dimitri 1.2 & SEAICE_debugPointI, SEAICE_debugPointJ,
143     & Hlimit_c1, Hlimit_c2, Hlimit_c3
144 torge 1.5 #else
145     & SEAICE_debugPointI, SEAICE_debugPointJ
146 torge 1.4 #endif
147 dimitri 1.1
148     #ifdef ALLOW_COST
149     NAMELIST /SEAICE_PARM02/
150     & mult_ice_export, mult_ice, cost_ice_flag,
151     & costIceStart1, costIceStart2,
152     & costIceEnd1, costIceEnd2,
153     & cost_ice_flag,
154     & SEAICE_clamp_salt, SEAICE_clamp_theta,
155     & mult_smrsst, smrsstbarfile,
156     & mult_smrsss, smrsssbarfile,
157     & mult_smrarea, smrareabarfile, smrareadatfile,
158     & wsmrarea0, wmean_smrarea, smrarea_errfile,
159     & smrareastartdate1, smrareastartdate2, smrareaperiod
160     #endif
161    
162     #ifdef ALLOW_SITRACER
163     NAMELIST /SEAICE_PARM03/
164     & SItrFile, SItrName, SItrNameLong, SItrUnit, SItrMate,
165     & SItrFromOcean0, SItrFromOceanFrac, SItrFromFlood0,
166     & SItrFromFloodFrac, SItrExpand0,
167     & IceAgeTrFile, SItrNumInUse
168     #endif
169    
170     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
171    
172     _BEGIN_MASTER(myThid)
173    
174     C-- set default sea ice parameters
175     SEAICEwriteState = .FALSE.
176     #ifdef SEAICE_ALLOW_DYNAMICS
177     SEAICEuseDYNAMICS = .TRUE.
178     #else
179     SEAICEuseDYNAMICS = .FALSE.
180     #endif
181     SEAICEadjMODE = 0
182     SEAICEuseFREEDRIFT = .FALSE.
183 torge 1.4 SEAICEuseTILT = .TRUE.
184 dimitri 1.1 SEAICEheatConsFix = .FALSE.
185     SEAICEuseTEM = .FALSE.
186     SEAICEuseMetricTerms = .TRUE.
187     SEAICEuseEVPpickup = .TRUE.
188     SEAICEuseFluxForm = .TRUE.
189     C-- old default:
190     c SEAICEuseFluxForm = .FALSE.
191     SEAICErestoreUnderIce = .FALSE.
192     SEAICE_salinityTracer = .FALSE.
193     SEAICE_ageTracer = .FALSE.
194     useHB87stressCoupling = .FALSE.
195     usePW79thermodynamics = .TRUE.
196     useMaykutSatVapPoly = .FALSE.
197     SEAICEadvHeff = .TRUE.
198     SEAICEadvArea = .TRUE.
199     SEAICEadvSnow = .TRUE.
200     #ifdef SEAICE_VARIABLE_SALINITY
201     SEAICEadvSalt = .TRUE.
202     #else
203     SEAICEadvSalt = .FALSE.
204     #endif
205     SEAICEuseFlooding = .TRUE.
206     SEAICE_no_slip = .FALSE.
207     SEAICE_clipVelocities = .FALSE.
208     SEAICE_maskRHS = .FALSE.
209 torge 1.6 SEAICEetaZmethod = 0
210 dimitri 1.1 SEAICEadvScheme = 2
211     SEAICEadvSchArea = UNSET_I
212     SEAICEadvSchHeff = UNSET_I
213     SEAICEadvSchSnow = UNSET_I
214     SEAICEadvSchSalt = UNSET_I
215     SEAICEdiffKhArea = UNSET_RL
216     SEAICEdiffKhHeff = UNSET_RL
217     SEAICEdiffKhSnow = UNSET_RL
218     SEAICEdiffKhSalt = UNSET_RL
219     SEAICE_deltaTtherm = dTtracerLev(1)
220     SEAICE_deltaTdyn = dTtracerLev(1)
221     SEAICE_deltaTevp = UNSET_RL
222 torge 1.4 C JFNK stuff
223     SEAICEuseJFNK = .FALSE.
224     SEAICEnewtonIterMax = 10
225     SEAICEkrylovIterMax = 10
226     JFNKgamma_nonlin = 1. _d -05
227     JFNKgamma_lin_min = 0.10 _d 0
228     JFNKgamma_lin_max = 0.99 _d 0
229     JFNKres_t = UNSET_RL
230 dimitri 1.1 C Hunke, JCP, 2001 use 615 kg/m^2 for this, but does not recommend using it
231     SEAICE_evpDampC = -1. _d 0
232     SEAICE_zetaMin = 0. _d 0
233     SEAICE_zetaMaxFac = 2.5 _d 8
234 torge 1.4 SEAICEpresH0 = 1. _d 0
235     SEAICEpresPow0 = 1
236     SEAICEpresPow1 = 1
237 dimitri 1.1 SEAICE_monFreq = monitorFreq
238     SEAICE_dumpFreq = dumpFreq
239     SEAICE_taveFreq = taveFreq
240     SEAICE_elasticParm = 0.33333333333333333333333333 _d 0
241     SEAICE_evpTauRelax = -1. _d 0
242     #ifdef ALLOW_MNC
243     SEAICE_tave_mnc = timeave_mnc
244     SEAICE_dump_mnc = snapshot_mnc
245     SEAICE_mon_mnc = monitor_mnc
246     #else
247     SEAICE_tave_mnc = .FALSE.
248     SEAICE_dump_mnc = .FALSE.
249     SEAICE_mon_mnc = .FALSE.
250     #endif
251     SEAICE_initialHEFF = ZERO
252 torge 1.4 #ifdef SEAICE_ITD
253 dimitri 1.2 CToM<<<
254     C Coefficients used to calculate sea ice thickness category limits
255     C after Lipscomb et al. (2001, JGR), Equ. 22
256 torge 1.6 C choose between
257 torge 1.3 C - original parameters of Lipscomb et al. (2001):
258     C c1=3.0/N, c2=15*c1, c3=3.0
259     C - and a higher resolution of thin end of ITD:
260     C c1=1.5/N, c2=42*c1, c3=3.3
261 torge 1.6 Hlimit_c1 = 3.0
262 dimitri 1.2 Hlimit_c2 = 15.
263 torge 1.6 Hlimit_c3 = 3.0
264 dimitri 1.2 C>>>ToM
265 torge 1.4 #endif
266 dimitri 1.1 SEAICE_rhoIce = 0.91 _d +03
267     SEAICE_rhoSnow = 330. _d 0
268     ICE2WATR = UNSET_RL
269     SEAICE_drag = 0.002 _d 0
270     OCEAN_drag = 0.001 _d 0
271     SEAICE_waterDrag = 5.5 _d 0
272     SEAICE_dryIceAlb = 0.75 _d 0
273     SEAICE_wetIceAlb = 0.66 _d 0
274     SEAICE_drySnowAlb = 0.84 _d 0
275     SEAICE_wetSnowAlb = 0.7 _d 0
276     HO = 0.5 _d 0
277     SEAICE_drag_south = UNSET_RL
278     SEAICE_waterDrag_south = UNSET_RL
279     SEAICE_dryIceAlb_south = UNSET_RL
280     SEAICE_wetIceAlb_south = UNSET_RL
281     SEAICE_drySnowAlb_south = UNSET_RL
282     SEAICE_wetSnowAlb_south = UNSET_RL
283     HO_south = UNSET_RL
284     SEAICE_wetAlbTemp = -1. _d -3
285     #ifdef SEAICE_EXTERNAL_FLUXES
286     SEAICE_waterAlbedo = UNSET_RL
287     #else /* if undef SEAICE_EXTERNAL_FLUXES */
288     SEAICE_waterAlbedo = 0.1 _d +00
289     #endif /* SEAICE_EXTERNAL_FLUXES */
290     SEAICE_strength = 2.75 _d +04
291     SEAICE_eccen = 2. _d 0
292     C coefficients for flux computations/bulk formulae
293     SEAICE_dalton = 1.75 _d -03
294     #ifdef ALLOW_EXF
295     IF ( useEXF ) THEN
296     C Use parameters that have already been set in data.exf
297     C to be consistent
298     SEAICE_rhoAir = atmrho
299     SEAICE_cpAir = atmcp
300     SEAICE_lhEvap = flamb
301     SEAICE_lhFusion = flami
302     SEAICE_boltzmann = stefanBoltzmann
303     SEAICE_emissivity = ocean_emissivity
304     SEAICE_ice_emiss = ice_emissivity
305     SEAICE_snow_emiss = snow_emissivity
306     ELSE
307     #else
308     IF ( .TRUE. ) THEN
309     #endif /* ALLOW_EXF */
310     SEAICE_rhoAir = 1.3 _d 0
311     SEAICE_cpAir = 1004. _d 0
312     SEAICE_lhEvap = 2.50 _d 6
313     SEAICE_lhFusion = 3.34 _d 5
314     SEAICE_boltzmann = 5.670 _d -08
315     C old default value of 0.97001763668430343479
316     SEAICE_emissivity = 5.5 _d -08/5.670 _d -08
317     SEAICE_ice_emiss = SEAICE_emissivity
318     SEAICE_snow_emiss = SEAICE_emissivity
319     ENDIF
320     SEAICE_iceConduct = 2.1656 _d +00
321     SEAICE_snowConduct = 3.1 _d -01
322     SEAICE_snowThick = 0.15 _d 0
323     SEAICE_shortwave = 0.30 _d 0
324     SEAICE_salt0 = 0.0 _d 0
325     SEAICE_saltFrac = 0.0 _d 0
326 dimitri 1.2 CToM<<<
327     C#ifdef SEAICE_MULTICATEGORY
328     #if defined(SEAICE_MULTICATEGORY) || defined(SEAICE_ITD)
329     C in case defined(SEAICE_ITD) MULTDIM = nITD (see SEAICE_SIZE.h)
330 torge 1.3 C because SEAICE_ITD uses code related to SEAICE_MULTICATEGORY
331 dimitri 1.2 C>>>ToM
332 dimitri 1.1 SEAICE_multDim = MULTDIM
333     #else
334     SEAICE_multDim = 1
335     #endif
336 torge 1.4 SEAICE_useMultDimSnow = .FALSE.
337 dimitri 1.1 C default to be set later (ocean-seaice turbulent flux coeff):
338     SEAICE_mcPheeStepFunc = .FALSE.
339     SEAICE_mcPheeTaper = UNSET_RL
340     SEAICE_availHeatTaper = UNSET_RL
341     SEAICE_mcPheePiston = UNSET_RL
342     SEAICE_frazilFrac = UNSET_RL
343     SEAICE_gamma_t = UNSET_RL
344     SEAICE_gamma_t_frz = UNSET_RL
345     SEAICE_availHeatFrac = UNSET_RL
346     SEAICE_availHeatFracFrz = UNSET_RL
347     #ifndef SEAICE_GROWTH_LEGACY
348     SEAICE_doOpenWaterGrowth=.TRUE.
349     SEAICE_doOpenWaterMelt=.FALSE.
350     SEAICE_areaLossFormula=1
351     SEAICE_areaGainFormula=1
352     #else
353     SEAICE_doOpenWaterGrowth=.FALSE.
354     SEAICE_doOpenWaterMelt=.FALSE.
355     SEAICE_areaGainFormula=2
356     SEAICE_areaLossFormula=3
357     #endif
358     SEAICE_tempFrz0 = 0.0901 _d 0
359     SEAICE_dTempFrz_dS = -0.0575 _d 0
360     C old default for constant freezing point
361     c SEAICE_tempFrz0 = -1.96 _d 0
362     c SEAICE_dTempFrz_dS = 0. _d 0
363     SEAICEstressFactor = 1. _d 0
364     SEAICE_tauAreaObsRelax = -999. _d 0
365     AreaFile = ' '
366     HsnowFile = ' '
367     HsaltFile = ' '
368     HeffFile = ' '
369     uIceFile = ' '
370     vIceFile = ' '
371     IMAX_TICE = 10
372     postSolvTempIter = 2
373 torge 1.6 C LSR parameters
374     SEAICE_LSRrelaxU = 0.95 _d 0
375     SEAICE_LSRrelaxV = 0.95 _d 0
376 torge 1.4 SOLV_MAX_ITERS = UNSET_I
377 dimitri 1.1 SOLV_NCHECK= 2
378     C two pseudo time steps correspond to the original modified
379     C Euler time stepping scheme of Zhang+Hibler (1997)
380     NPSEUDOTIMESTEPS = 2
381     #ifdef SEAICE_ALLOW_FREEDRIFT
382     LSR_mixIniGuess = 0
383     #else
384     LSR_mixIniGuess = -1
385     #endif
386     LSR_ERROR = 0.0001 _d 0
387     DIFF1 = UNSET_RL
388     C-- old DIFF1 default:
389     c DIFF1 = .004 _d 0
390    
391     #ifdef SEAICE_GROWTH_LEGACY
392     SEAICE_area_reg = 0.15 _d 0
393     SEAICE_area_floor = 0.15 _d 0
394     #else
395     SEAICE_area_floor = siEPS
396     SEAICE_area_reg = siEPS
397     #endif
398     SEAICE_hice_reg = 0.05 _d 0
399 torge 1.4 SEAICE_area_max = 1.00 _d 0
400 dimitri 1.1
401     SEAICE_airTurnAngle = 0.0 _d 0
402     SEAICE_waterTurnAngle = 0.0 _d 0
403     MAX_HEFF = 10. _d 0
404     MIN_ATEMP = -50. _d 0
405     MIN_LWDOWN = 60. _d 0
406     MIN_TICE = -50. _d 0
407     SEAICE_EPS = 1. _d -10
408     SEAICE_EPS_SQ = -99999.
409     C- Retired parameters:
410     c LAD = 2
411     LAD = UNSET_I
412     c SEAICE_sensHeat = 1.75 _d -03 * 1004 * 1.3
413     c SEAICE_sensHeat = 2.284 _d +00
414     SEAICE_sensHeat = UNSET_RL
415     c SEAICE_latentWater = 1.75 _d -03 * 2.500 _d 06 * 1.3
416     c SEAICE_latentWater = 5.6875 _d +03
417     SEAICE_latentWater = UNSET_RL
418     c SEAICE_latentIce = 1.75 _d -03 * 2.834 _d 06 * 1.3
419     c SEAICE_latentIce = 6.4474 _d +03
420     SEAICE_latentIce = UNSET_RL
421     SEAICE_salinity = UNSET_RL
422     SIsalFRAC = UNSET_RL
423     SIsal0 = UNSET_RL
424     IceAgeFile = ' '
425     c MAX_TICE = 30. _d 0
426     MAX_TICE = UNSET_RL
427     areaMin = UNSET_RL
428     hiceMin = UNSET_RL
429     A22 = UNSET_RL
430     areaMax = UNSET_RL
431     SEAICE_lhSublim = UNSET_RL
432     SEAICEadvAge = .TRUE.
433     SEAICEadvSchAge = UNSET_I
434     SEAICEdiffKhAge = UNSET_RL
435     IceAgeTrFile(1) = ' '
436     IceAgeTrFile(2) = ' '
437     IceAgeTrFile(3) = ' '
438     IceAgeTrFile(4) = ' '
439     SEAICEturbFluxFormula =UNSET_I
440     SEAICE_freeze = UNSET_RL
441     C- end retired parameters
442     SEAICE_debugPointI = UNSET_I
443     SEAICE_debugPointJ = UNSET_I
444    
445     #ifdef ALLOW_COST
446 torge 1.4 locDate(1) = 0
447     locDate(2) = 0
448     # ifdef ALLOW_CAL
449     CALL CAL_GETDATE( -1, startTime, locDate, myThid )
450     # endif /* ALLOW_CAL */
451 dimitri 1.1 mult_ice_export = 0. _d 0
452     mult_ice = 0. _d 0
453 torge 1.4 costIceStart1 = locDate(1)
454     costIceStart2 = locDate(2)
455 dimitri 1.1 costIceEnd1 = 0
456     costIceEnd2 = 0
457     cost_ice_flag = 1
458     SEAICE_clamp_salt = 27.5 _d 0
459     SEAICE_clamp_theta = 0.0001 _d 0
460     c
461     mult_smrsst = 0. _d 0
462     mult_smrsss = 0. _d 0
463     mult_smrarea = 0. _d 0
464     wsmrarea0 = 0.5 _d 0
465     wmean_smrarea = 0.5 _d 0
466     smrsstbarfile = 'smrsstbar'
467     smrsssbarfile = 'smrsssbar'
468     smrareabarfile = 'smrareabar'
469     smrareadatfile = ' '
470     smrarea_errfile = ' '
471 torge 1.4 smrareastartdate1 = locDate(1)
472     smrareastartdate2 = locDate(2)
473 dimitri 1.1 #endif /* ALLOW_COST */
474    
475     #ifdef ALLOW_SITRACER
476     SItrNumInUse=SItrMaxNum
477     DO iTracer = 1, SItrMaxNum
478     SItrFile(iTracer) = ' '
479     SItrName(iTracer) = ' '
480     SItrNameLong(iTracer) = ' '
481     SItrUnit(iTracer) = ' '
482     SItrMate(iTracer) = 'HEFF'
483     SItrFromOcean0(iTracer) = ZERO
484     SItrFromOceanFrac(iTracer) = ZERO
485     SItrFromFlood0(iTracer) = ZERO
486     SItrFromFloodFrac(iTracer) = ZERO
487     SItrExpand0(iTracer) = ZERO
488     ENDDO
489     #endif /* ALLOW_SITRACER */
490     nRetired = 0
491    
492     C Open and read the data.seaice file
493     WRITE(msgBuf,'(A)')
494     &' '
495 torge 1.4 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
496 dimitri 1.1 & SQUEEZE_RIGHT , myThid)
497     WRITE(msgBuf,'(A)') ' SEAICE_READPARMS: opening data.seaice'
498 torge 1.4 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
499 dimitri 1.1 & SQUEEZE_RIGHT , myThid)
500    
501     CALL OPEN_COPY_DATA_FILE(
502     I 'data.seaice', 'SEAICE_READPARMS',
503     O iUnit,
504     I myThid )
505    
506     C-- Read settings from model parameter file "data.seaice".
507     READ(UNIT=iUnit,NML=SEAICE_PARM01)
508    
509     #ifdef ALLOW_COST
510     READ(UNIT=iUnit,NML=SEAICE_PARM02)
511     #endif /* ALLOW_COST */
512    
513     #ifdef ALLOW_SITRACER
514     READ(UNIT=iUnit,NML=SEAICE_PARM03)
515     #endif /* ALLOW_SITRACER */
516    
517     CLOSE(iUnit)
518    
519     WRITE(msgBuf,'(A)')
520     & ' SEAICE_READPARMS: finished reading data.seaice'
521     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
522     & SQUEEZE_RIGHT , myThid)
523    
524     C-- Set default values (if not specified in data.seaice namelist)
525     IF (ICE2WATR.EQ.UNSET_RL) ICE2WATR = SEAICE_rhoIce*recip_rhoConst
526     IF (SEAICE_drag_south .EQ. UNSET_RL)
527     & SEAICE_drag_south = SEAICE_drag
528     IF (SEAICE_waterDrag_south .EQ. UNSET_RL)
529     & SEAICE_waterDrag_south = SEAICE_waterDrag
530     IF (SEAICE_dryIceAlb_south .EQ. UNSET_RL)
531     & SEAICE_dryIceAlb_south = SEAICE_dryIceAlb
532     IF (SEAICE_wetIceAlb_south .EQ. UNSET_RL)
533     & SEAICE_wetIceAlb_south = SEAICE_wetIceAlb
534     IF (SEAICE_drySnowAlb_south .EQ. UNSET_RL)
535     & SEAICE_drySnowAlb_south = SEAICE_drySnowAlb
536     IF (SEAICE_wetSnowAlb_south .EQ. UNSET_RL)
537     & SEAICE_wetSnowAlb_south = SEAICE_wetSnowAlb
538     IF (HO_south .EQ. UNSET_RL)
539     & HO_south = HO
540    
541     C Check that requested time step size is supported. The combination
542     C below is the only one that is supported at this time. Does not
543     C mean that something fancier will not work, just that it has not
544     C yet been tried nor thought through.
545     IF ( SEAICE_deltaTtherm .NE. dTtracerLev(1) .OR.
546     & SEAICE_deltaTdyn .LT. SEAICE_deltaTtherm .OR.
547     & (SEAICE_deltaTdyn/SEAICE_deltaTtherm) .NE.
548     & INT(SEAICE_deltaTdyn/SEAICE_deltaTtherm) ) THEN
549     WRITE(msgBuf,'(A)')
550     & 'Unsupported combination of SEAICE_deltaTtherm,'
551     CALL PRINT_ERROR( msgBuf , myThid)
552     WRITE(msgBuf,'(A)')
553     & ' SEAICE_deltaTdyn, and dTtracerLev(1)'
554     CALL PRINT_ERROR( msgBuf , myThid)
555     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
556     ENDIF
557     SEAICEuseEVP = .FALSE.
558     #ifdef SEAICE_ALLOW_EVP
559     IF ( SEAICE_deltaTevp .NE. UNSET_RL ) SEAICEuseEVP = .TRUE.
560     IF ( SEAICEuseEVP ) THEN
561     IF ( (SEAICE_deltaTdyn/SEAICE_deltaTevp) .NE.
562     & INT(SEAICE_deltaTdyn/SEAICE_deltaTevp) ) THEN
563     WRITE(msgBuf,'(A)')
564     & 'SEAICE_deltaTevp must be a factor of SEAICE_deltaTdyn.'
565     CALL PRINT_ERROR( msgBuf , myThid)
566     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
567     ENDIF
568     IF ( SEAICE_elasticParm .LE. 0. _d 0 ) THEN
569     WRITE(msgBuf,'(A)')
570     & 'SEAICE_elasticParm must greater than 0.'
571     CALL PRINT_ERROR( msgBuf , myThid)
572     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
573     ENDIF
574     IF ( SEAICE_evpTauRelax .LE. 0. _d 0 )
575     & SEAICE_evpTauRelax = SEAICE_deltaTdyn*SEAICE_elasticParm
576     ENDIF
577     #endif /* SEAICE_ALLOW_EVP */
578 torge 1.4
579 dimitri 1.1 #ifdef SEAICE_ALLOW_FREEDRIFT
580     IF ( SEAICEuseFREEDRIFT ) SEAICEuseEVP = .FALSE.
581     IF ( SEAICEuseFREEDRIFT ) THEN
582     WRITE(msgBuf,'(A,A)')
583     & 'WARNING FROM S/R SEAICE_READPARMS:',
584     & ' switch seaice from LSR or EVP to "free drift"'
585     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
586     & SQUEEZE_RIGHT , myThid)
587     ENDIF
588     #endif /* SEAICE_ALLOW_FREEDRIFT */
589    
590     C Make sure that we have least two pseudo time steps
591     NPSEUDOTIMESTEPS = MAX(NPSEUDOTIMESTEPS,2)
592    
593 torge 1.4 C- limit preconditioner steps
594     IF ( SOLV_MAX_ITERS .EQ. UNSET_I ) THEN
595     C maximum number of LSOR steps in default Picard solver
596     SOLV_MAX_ITERS = 1500
597     C maximum number of LSOR steps as preconditioner in JFNK solver
598     IF ( SEAICEuseJFNK ) SOLV_MAX_ITERS = 10
599     ENDIF
600    
601 dimitri 1.1 C- The old ways of specifying mcPheeTaper, mcPheePiston & frazilFrac:
602     C a) prevent multiple specification of the same coeff;
603     C b) if specified, then try to recover old way of setting & default.
604     IF ( SEAICE_mcPheeTaper .EQ. UNSET_RL ) THEN
605     IF ( SEAICE_availHeatTaper.EQ.UNSET_RL ) THEN
606     SEAICE_mcPheeTaper = 0.0 _d 0
607     ELSE
608     SEAICE_mcPheeTaper = SEAICE_availHeatTaper
609     ENDIF
610     ELSEIF ( SEAICE_availHeatTaper.NE.UNSET_RL ) THEN
611     WRITE(msgBuf,'(2A)') 'S/R SEAICE_READPARMS: Cannot specify ',
612     & 'both SEAICE_mcPheeTaper & SEAICE_availHeatTaper'
613     CALL PRINT_ERROR( msgBuf , myThid)
614     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
615     ENDIF
616    
617     C- set SEAICE_frazilFrac if not yet done
618     IF ( SEAICE_gamma_t_frz .NE. UNSET_RL ) THEN
619     IF ( SEAICE_frazilFrac .EQ. UNSET_RL ) THEN
620     SEAICE_frazilFrac = SEAICE_deltaTtherm/SEAICE_gamma_t_frz
621     ELSE
622     WRITE(msgBuf,'(2A)') 'S/R SEAICE_READPARMS: Cannot specify ',
623     & 'both SEAICE_frazilFrac & SEAICE_gamma_t_frz'
624     CALL PRINT_ERROR( msgBuf , myThid)
625     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
626     ENDIF
627     ENDIF
628     IF ( SEAICE_availHeatFracFrz.NE.UNSET_RL ) THEN
629     IF ( SEAICE_frazilFrac .EQ. UNSET_RL ) THEN
630     SEAICE_frazilFrac = SEAICE_availHeatFracFrz
631     ELSE
632     IF ( SEAICE_gamma_t_frz .EQ. UNSET_RL ) THEN
633     WRITE(msgBuf,'(2A)') 'S/R SEAICE_READPARMS: Cannot specify ',
634     & 'both SEAICE_frazilFrac & SEAICE_availHeatFracFrz'
635     ELSE
636     WRITE(msgBuf,'(2A)') 'S/R SEAICE_READPARMS: Cannot specify ',
637     & 'both SEAICE_gamma_t_frz & SEAICE_availHeatFracFrz'
638     ENDIF
639     CALL PRINT_ERROR( msgBuf , myThid)
640     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
641     ENDIF
642     ENDIF
643     C the default for SEAICE_gamma_t_frz use to be SEAICE_gamma_t:
644     IF ( SEAICE_gamma_t .NE. UNSET_RL .AND.
645     & SEAICE_frazilFrac .EQ. UNSET_RL ) THEN
646     SEAICE_frazilFrac = SEAICE_deltaTtherm/SEAICE_gamma_t
647     ENDIF
648     C the default for SEAICE_availHeatFracFrz use to be SEAICE_availHeatFrac:
649     IF ( SEAICE_availHeatFrac.NE.UNSET_RL .AND.
650     & SEAICE_frazilFrac .EQ. UNSET_RL ) THEN
651     SEAICE_frazilFrac = SEAICE_availHeatFrac
652     ENDIF
653     IF ( SEAICE_frazilFrac .EQ. UNSET_RL ) THEN
654     SEAICE_frazilFrac = 1. _d 0
655     ENDIF
656    
657     C- start by setting SEAICE_availHeatFrac (used in seaice_init_fixed.F
658     C to set SEAICE_mcPheePiston once drF is known)
659     IF ( SEAICE_gamma_t .NE. UNSET_RL ) THEN
660     IF ( SEAICE_availHeatFrac.EQ.UNSET_RL ) THEN
661     SEAICE_availHeatFrac = SEAICE_deltaTtherm/SEAICE_gamma_t
662     ELSE
663     WRITE(msgBuf,'(2A)') 'S/R SEAICE_READPARMS: Cannot specify ',
664     & 'both SEAICE_gamma_t & SEAICE_availHeatFrac'
665     CALL PRINT_ERROR( msgBuf , myThid)
666     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
667     ENDIF
668     ENDIF
669     IF ( SEAICE_mcPheePiston .NE. UNSET_RL .AND.
670     & SEAICE_availHeatFrac.NE. UNSET_RL ) THEN
671     IF ( SEAICE_gamma_t .EQ. UNSET_RL ) THEN
672     WRITE(msgBuf,'(2A)') 'S/R SEAICE_READPARMS: Cannot specify ',
673     & 'both SEAICE_mcPheePiston & SEAICE_availHeatFrac'
674     ELSE
675     WRITE(msgBuf,'(2A)') 'S/R SEAICE_READPARMS: Cannot specify ',
676     & 'both SEAICE_mcPheePiston & SEAICE_gamma_t'
677     ENDIF
678     CALL PRINT_ERROR( msgBuf , myThid)
679     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
680     ENDIF
681    
682 torge 1.4 #ifdef SEAICE_ITD
683 torge 1.6 C The ice thickness distribution (ITD) module can only be used with
684     C package seaice thermodynamics (seaice_growth)
685 dimitri 1.2 C SEAICE_ADVDIFF and
686     C SEAICE_GROWTH, i.e. needs usePW79thermodynamics = .TRUE.
687     useTHSice = .FALSE.
688     #endif
689 dimitri 1.1 IF ( useThSice ) THEN
690     C If the thsice package with the Winton thermodynamics is used
691     C is does not make sense to have the following parameters defined,
692     C so we reset them here
693     usePW79thermodynamics = .FALSE.
694     SEAICEadvHeff = .FALSE.
695     SEAICEadvArea = .FALSE.
696     SEAICEadvSnow = .FALSE.
697     SEAICEadvSalt = .FALSE.
698     ENDIF
699     C Set advection schemes to some sensible values if not done in data.seaice
700     IF ( SEAICEadvSchArea .EQ. UNSET_I )
701     & SEAICEadvSchArea = SEAICEadvSchHeff
702     IF ( SEAICEadvSchArea .EQ. UNSET_I )
703     & SEAICEadvSchArea = SEAICEadvScheme
704     IF ( SEAICEadvScheme .NE. SEAICEadvSchArea )
705     & SEAICEadvScheme = SEAICEadvSchArea
706     IF ( SEAICEadvSchHeff .EQ. UNSET_I )
707     & SEAICEadvSchHeff = SEAICEadvSchArea
708     IF ( SEAICEadvSchSnow .EQ. UNSET_I )
709     & SEAICEadvSchSnow = SEAICEadvSchHeff
710     IF ( SEAICEadvSchSalt .EQ. UNSET_I )
711     & SEAICEadvSchSalt = SEAICEadvSchHeff
712     C Set diffusivity to some sensible values if not done in data.seaice
713     IF ( SEAICEdiffKhArea .EQ. UNSET_RL )
714     & SEAICEdiffKhArea = SEAICEdiffKhHeff
715     IF ( SEAICEdiffKhArea .EQ. UNSET_RL )
716     & SEAICEdiffKhArea = 0. _d 0
717     IF ( SEAICEdiffKhHeff .EQ. UNSET_RL )
718     & SEAICEdiffKhHeff = SEAICEdiffKhArea
719     IF ( SEAICEdiffKhSnow .EQ. UNSET_RL )
720     & SEAICEdiffKhSnow = SEAICEdiffKhHeff
721     IF ( SEAICEdiffKhSalt .EQ. UNSET_RL )
722     & SEAICEdiffKhSalt = SEAICEdiffKhHeff
723     IF ( SEAICE_EPS_SQ .EQ. -99999. )
724     & SEAICE_EPS_SQ = SEAICE_EPS * SEAICE_EPS
725    
726     C- Retired parameters
727     IF ( SEAICE_sensHeat .NE. UNSET_RL ) THEN
728     nRetired = nRetired + 1
729     WRITE(msgBuf,'(A,A)')
730     & 'S/R SEAICE_READPARMS: "SEAICE_sensHeat" ',
731     & 'is no longer allowed in file "data.seaice"'
732     CALL PRINT_ERROR( msgBuf, myThid )
733     WRITE(msgBuf,'(A,A)')
734     & 'S/R SEAICE_READPARMS: set "SEAICE_cpAir", ',
735     & '"SEAICE_dalton", and "SEAICE_rhoAir" instead'
736     CALL PRINT_ERROR( msgBuf, myThid )
737     ENDIF
738     IF ( SEAICE_latentWater .NE. UNSET_RL ) THEN
739     nRetired = nRetired + 1
740     WRITE(msgBuf,'(A,A)')
741     & 'S/R SEAICE_READPARMS: "SEAICE_latentWater" ',
742     & 'is no longer allowed in file "data.seaice"'
743     CALL PRINT_ERROR( msgBuf, myThid )
744     WRITE(msgBuf,'(A,A)')
745     & 'S/R SEAICE_READPARMS: set "SEAICE_lhEvap", ',
746     & '"SEAICE_dalton", and "SEAICE_rhoAir" instead'
747     CALL PRINT_ERROR( msgBuf, myThid )
748     ENDIF
749     IF ( SEAICE_latentIce .NE. UNSET_RL ) THEN
750     nRetired = nRetired + 1
751     WRITE(msgBuf,'(A,A)')
752     & 'S/R SEAICE_READPARMS: "SEAICE_latentIce" ',
753     & 'is no longer allowed in file "data.seaice"'
754     CALL PRINT_ERROR( msgBuf, myThid )
755     WRITE(msgBuf,'(A,A)')
756     & 'S/R SEAICE_READPARMS: set "SEAICE_lhFusion", ',
757     & '"SEAICE_dalton", and "SEAICE_rhoAir" instead'
758     CALL PRINT_ERROR( msgBuf, myThid )
759     ENDIF
760     IF ( SEAICE_freeze .NE. UNSET_RL ) THEN
761     WRITE(msgBuf,'(A,A)')'S/R SEAICE_READPARMS: ',
762     & '"SEAICE_freeze" no longer allowed in file "data.seaice"'
763     CALL PRINT_ERROR( msgBuf, myThid )
764     WRITE(msgBuf,'(A,A)')'S/R SEAICE_READPARMS: ',
765     & 'set instead "SEAICE_tempFrz0" and "SEAICE_dTempFrz_dS"'
766     CALL PRINT_ERROR( msgBuf, myThid )
767     ENDIF
768     IF ( SEAICE_salinity .NE. UNSET_RL ) THEN
769     nRetired = nRetired + 1
770     WRITE(msgBuf,'(A,A)') 'S/R SEAICE_READPARMS: ',
771     & '"SEAICE_salinity" is no longer allowed in file "data.seaice"'
772     CALL PRINT_ERROR( msgBuf, myThid )
773     WRITE(msgBuf,'(A,A)') 'S/R SEAICE_READPARMS: ',
774     & 'set "SEAICE_saltFrac" instead'
775     CALL PRINT_ERROR( msgBuf, myThid )
776     ENDIF
777     IF ( SIsalFrac .NE. UNSET_RL ) THEN
778     nRetired = nRetired + 1
779     WRITE(msgBuf,'(A,A)') 'S/R SEAICE_READPARMS: ',
780     & '"SIsalFrac" is no longer allowed in file "data.seaice"'
781     CALL PRINT_ERROR( msgBuf, myThid )
782     WRITE(msgBuf,'(A,A)') 'S/R SEAICE_READPARMS: ',
783     & 'set "SEAICE_saltFrac" instead'
784     CALL PRINT_ERROR( msgBuf, myThid )
785     ENDIF
786     IF ( SIsal0 .NE. UNSET_RL ) THEN
787     nRetired = nRetired + 1
788     WRITE(msgBuf,'(A,A)') 'S/R SEAICE_READPARMS: ',
789     & '"SIsal0" is no longer allowed in file "data.seaice"'
790     CALL PRINT_ERROR( msgBuf, myThid )
791     WRITE(msgBuf,'(A,A)') 'S/R SEAICE_READPARMS: ',
792     & 'set "SEAICE_salt0" instead'
793     CALL PRINT_ERROR( msgBuf, myThid )
794     ENDIF
795     IF ( IceAgeFile .NE. ' ' ) THEN
796     nRetired = nRetired + 1
797     WRITE(msgBuf,'(A,A)')
798     & 'S/R SEAICE_READPARMS: "IceAgeFile" ',
799     & 'is no longer allowed in file "data.seaice"'
800     CALL PRINT_ERROR( msgBuf, myThid )
801     WRITE(msgBuf,'(A,A)')
802     & 'S/R SEAICE_READPARMS: replaced by ',
803     & '"IceAgeTrFile(SEAICE_num)" array '
804     CALL PRINT_ERROR( msgBuf, myThid )
805     ENDIF
806     IF ( areaMax .NE. UNSET_RL ) THEN
807     nRetired = nRetired + 1
808     WRITE(msgBuf,'(A,A)')
809     & 'S/R SEAICE_READPARMS: "areaMax" ',
810     & 'is no longer allowed in file "data.seaice"'
811     CALL PRINT_ERROR( msgBuf, myThid )
812     WRITE(msgBuf,'(A,A)')
813     & 'S/R SEAICE_READPARMS: replaced by ',
814     & '"SEAICE_area_max"'
815     CALL PRINT_ERROR( msgBuf, myThid )
816     ENDIF
817     IF ( areaMin .NE. UNSET_RL ) THEN
818     nRetired = nRetired + 1
819     WRITE(msgBuf,'(A,A)')
820     & 'S/R SEAICE_READPARMS: "areaMin" ',
821     & 'is no longer allowed in file "data.seaice"'
822     CALL PRINT_ERROR( msgBuf, myThid )
823     WRITE(msgBuf,'(A,A)')
824     & 'S/R SEAICE_READPARMS: replaced by ',
825     & '"SEAICE_area_reg" for regularization and ',
826     & '"SEAICE_area_floor" setting a lower bound'
827     CALL PRINT_ERROR( msgBuf, myThid )
828     ENDIF
829     IF (SEAICE_lhSublim .NE. UNSET_RL ) THEN
830     nRetired = nRetired + 1
831     WRITE(msgBuf,'(A,A)')
832     & 'S/R SEAICE_READPARMS: "SEAICE_lhSublim" ',
833     & 'is no longer allowed in file "data.seaice"'
834     CALL PRINT_ERROR( msgBuf, myThid )
835     WRITE(msgBuf,'(A,A)')
836     & 'S/R SEAICE_READPARMS: specify ',
837     & '"SEAICE_lhFusion" and "SEAICE_lhEvap" instead'
838     CALL PRINT_ERROR( msgBuf, myThid )
839     ENDIF
840     IF ( A22 .NE. UNSET_RL ) THEN
841     nRetired = nRetired + 1
842     WRITE(msgBuf,'(A,A)')
843     & 'S/R SEAICE_READPARMS: "A22" ',
844     & 'is no longer allowed in file "data.seaice"'
845     CALL PRINT_ERROR( msgBuf, myThid )
846     WRITE(msgBuf,'(A,A)')
847     & 'S/R SEAICE_READPARMS: replaced by ',
848     & '"SEAICE_area_reg" for regularization'
849     CALL PRINT_ERROR( msgBuf, myThid )
850     ENDIF
851     IF ( LAD .NE. UNSET_I ) THEN
852     nRetired = nRetired + 1
853     WRITE(msgBuf,'(A,A)') 'S/R SEAICE_READPARMS: "LAD" ',
854     & 'is no longer allowed in file "data.seaice"'
855     CALL PRINT_ERROR( msgBuf, myThid )
856     WRITE(msgBuf,'(A,A)') 'always use modified Euler step ',
857     & '(LAD==2) since Leap frog code (LAD==1) is gone.'
858     CALL PRINT_ERROR( msgBuf, myThid )
859     ENDIF
860     IF ( MAX_TICE .NE. UNSET_RL ) THEN
861     nRetired = nRetired + 1
862     WRITE(msgBuf,'(A,A)')
863     & 'S/R SEAICE_READPARMS: "MAX_TICE" ',
864     & 'is no longer allowed in file "data.seaice"'
865     CALL PRINT_ERROR( msgBuf, myThid )
866     ENDIF
867     IF ( hiceMin .NE. UNSET_RL ) THEN
868     nRetired = nRetired + 1
869     WRITE(msgBuf,'(A,A)')
870     & 'S/R SEAICE_READPARMS: "hiceMin" ',
871     & 'is no longer allowed in file "data.seaice"'
872     CALL PRINT_ERROR( msgBuf, myThid )
873     WRITE(msgBuf,'(A,A)')
874     & 'S/R SEAICE_READPARMS: replaced by ',
875     & '"SEAICE_hice_reg" for regularization'
876     CALL PRINT_ERROR( msgBuf, myThid )
877     ENDIF
878     IF ( .NOT. SEAICEadvAge ) THEN
879     nRetired = nRetired + 1
880     WRITE(msgBuf,'(A,A)')
881     & 'S/R SEAICE_READPARMS: "SEAICEadvAge" ',
882     & 'is no longer allowed in file "data.seaice"'
883     CALL PRINT_ERROR( msgBuf, myThid )
884     WRITE(msgBuf,'(A,A)')
885     & 'S/R SEAICE_READPARMS: since ALLOW_SITRACER ',
886     & 'replaced and extended SEAICE_AGE'
887     CALL PRINT_ERROR( msgBuf, myThid )
888     ENDIF
889     IF ( SEAICEadvSchAge .NE. UNSET_I ) THEN
890     nRetired = nRetired + 1
891     WRITE(msgBuf,'(A,A)')
892     & 'S/R SEAICE_READPARMS: "SEAICEadvSchAge" ',
893     & 'is no longer allowed in file "data.seaice"'
894     CALL PRINT_ERROR( msgBuf, myThid )
895     WRITE(msgBuf,'(A,A)')
896     & 'S/R SEAICE_READPARMS: since ALLOW_SITRACER ',
897     & 'replaced and extended SEAICE_AGE'
898     CALL PRINT_ERROR( msgBuf, myThid )
899     ENDIF
900     IF ( SEAICEdiffKhAge .NE. UNSET_RL ) THEN
901     nRetired = nRetired + 1
902     WRITE(msgBuf,'(A,A)')
903     & 'S/R SEAICE_READPARMS: "SEAICEdiffKhAge" ',
904     & 'is no longer allowed in file "data.seaice"'
905     CALL PRINT_ERROR( msgBuf, myThid )
906     WRITE(msgBuf,'(A,A)')
907     & 'S/R SEAICE_READPARMS: since ALLOW_SITRACER ',
908     & 'replaced and extended SEAICE_AGE'
909     CALL PRINT_ERROR( msgBuf, myThid )
910     ENDIF
911     IF ( ( IceAgeTrFile(1) .NE. ' ' ).OR.
912     & ( IceAgeTrFile(2) .NE. ' ' ).OR.
913     & ( IceAgeTrFile(3) .NE. ' ' ).OR.
914     & ( IceAgeTrFile(4) .NE. ' ' ) ) THEN
915     nRetired = nRetired + 1
916     WRITE(msgBuf,'(A,A)')
917     & 'S/R SEAICE_READPARMS: "IceAgeTrFile" ',
918     & 'is no longer allowed in file "data.seaice"'
919     CALL PRINT_ERROR( msgBuf, myThid )
920     WRITE(msgBuf,'(A,A)')
921     & 'S/R SEAICE_READPARMS: since ALLOW_SITRACER ',
922     & 'replaced and extended SEAICE_AGE'
923     CALL PRINT_ERROR( msgBuf, myThid )
924     ENDIF
925     IF ( SEAICEturbFluxFormula .NE. UNSET_I ) THEN
926     WRITE(msgBuf,'(A,A)')'S/R SEAICE_READPARMS: ',
927     & '"SEAICEturbFluxFormula" no longer allowed in "data.seaice"'
928     CALL PRINT_ERROR( msgBuf, myThid )
929     WRITE(msgBuf,'(A,A)')'S/R SEAICE_READPARMS: ',
930     & ' Set instead "SEAICE_mcPheePiston" and "SEAICE_frazilFrac"'
931     CALL PRINT_ERROR( msgBuf, myThid )
932     ENDIF
933    
934     IF ( nRetired .GT. 0 ) THEN
935     WRITE(msgBuf,'(2A)') 'S/R SEAICE_READPARMS: ',
936     & 'Error reading parameter file "data.seaice"'
937     CALL PRINT_ERROR( msgBuf, myThid )
938     WRITE(msgBuf,'(A)')
939     & 'some out of date parameters were found in the namelist'
940     CALL PRINT_ERROR( msgBuf, myThid )
941     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
942     ENDIF
943    
944     C-- Now set-up any remaining parameters that result from other params
945    
946     C- convert SEAICE_doOpenWaterGrowth/Melt logical switch to numerical
947     C facOpenGrow/facOpenMelt
948     facOpenGrow = 0. _d 0
949     facOpenMelt = 0. _d 0
950     IF (SEAICE_doOpenWaterGrowth) facOpenGrow = 1. _d 0
951     IF (SEAICE_doOpenWaterMelt) facOpenMelt = 1. _d 0
952    
953     C- Set Output type flags :
954     SEAICE_tave_mdsio = .TRUE.
955     SEAICE_dump_mdsio = .TRUE.
956     SEAICE_mon_stdio = .TRUE.
957     #ifdef ALLOW_MNC
958     IF (useMNC) THEN
959     IF ( .NOT.outputTypesInclusive
960     & .AND. SEAICE_tave_mnc ) SEAICE_tave_mdsio = .FALSE.
961     IF ( .NOT.outputTypesInclusive
962     & .AND. SEAICE_dump_mnc ) SEAICE_dump_mdsio = .FALSE.
963     IF ( .NOT.outputTypesInclusive
964     & .AND. SEAICE_mon_mnc ) SEAICE_mon_stdio = .FALSE.
965     ENDIF
966     #endif
967    
968 torge 1.6 C- store value of logical flag which might be changed in AD mode
969     #ifdef ALLOW_AUTODIFF
970     SEAICEuseFREEDRIFTinFwdMode = SEAICEuseFREEDRIFT
971     SEAICEuseDYNAMICSinFwdMode = SEAICEuseDYNAMICS
972     #endif /* ALLOW_AUTODIFF */
973    
974 dimitri 1.1 C Check the consitency of a few parameters
975     IF ( SEAICE_emissivity .LT. 1. _d -04 ) THEN
976     WRITE(msgBuf,'(2A)')
977     & 'SEAICE_emissivity is no longer emissivity*(boltzmann ',
978     & 'constant) but really an emissivity.'
979     CALL PRINT_ERROR( msgBuf , myThid)
980     WRITE(msgBuf,'(2A)')
981     & 'Typical values are near 1 ',
982     & '(default is 5.5/5.67=0.9700176...).'
983     CALL PRINT_ERROR( msgBuf , myThid)
984     WRITE(msgBuf,'(A,E13.6,A)')
985     & 'Please change SEAICE_emissivity in data.seaice to ',
986     & SEAICE_emissivity, '/5.67e-8.'
987     CALL PRINT_ERROR( msgBuf , myThid)
988     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
989     ENDIF
990    
991     IF ( DIFF1 .EQ. UNSET_RL ) THEN
992     DIFF1 = 0. _d 0
993     chkFlag = .FALSE.
994     IF ( SEAICEadvScheme.EQ.2 ) THEN
995     C-- Since DIFF1 default value has been changed (2011/05/29), issue a warning
996     C in case using centered avection scheme without any diffusion:
997     IF ( SEAICEadvHeff .AND. SEAICEdiffKhHeff .EQ. 0. _d 0 ) THEN
998     WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_READPARMS: ',
999     & 'will use AdvScheme = 2 for HEFF without any diffusion'
1000     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
1001     & SQUEEZE_RIGHT, myThid )
1002     chkFlag = .TRUE.
1003     ENDIF
1004     IF ( SEAICEadvArea .AND. SEAICEdiffKhArea .EQ. 0. _d 0 ) THEN
1005     WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_READPARMS: ',
1006     & 'will use AdvScheme = 2 for AREA without any diffusion'
1007     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
1008     & SQUEEZE_RIGHT, myThid )
1009     chkFlag = .TRUE.
1010     ENDIF
1011     IF ( SEAICEadvSnow .AND. SEAICEdiffKhSnow .EQ. 0. _d 0 ) THEN
1012     WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_READPARMS: ',
1013     & 'will use AdvScheme = 2 for HSNOW without any diffusion'
1014     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
1015     & SQUEEZE_RIGHT, myThid )
1016     chkFlag = .TRUE.
1017     ENDIF
1018     IF ( SEAICEadvSalt .AND. SEAICEdiffKhSalt .EQ. 0. _d 0 ) THEN
1019     WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_READPARMS: ',
1020     & 'will use AdvScheme = 2 for HSALT without any diffusion'
1021     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
1022     & SQUEEZE_RIGHT, myThid )
1023     chkFlag = .TRUE.
1024     ENDIF
1025     IF ( chkFlag ) THEN
1026     WRITE(msgBuf,'(2A)') '** WARNING ** SEAICE_READPARMS: ',
1027     & 'since DIFF1 is set to 0 (= new DIFF1 default value)'
1028     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
1029     & SQUEEZE_RIGHT, myThid )
1030     ENDIF
1031     ENDIF
1032     ENDIF
1033    
1034     _END_MASTER(myThid)
1035    
1036     C-- Everyone else must wait for the parameters to be loaded
1037     _BARRIER
1038    
1039     RETURN
1040     END

  ViewVC Help
Powered by ViewVC 1.1.22