/[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.8 - (hide annotations) (download)
Wed Mar 27 19:13:51 2013 UTC (12 years, 4 months ago) by torge
Branch: MAIN
CVS Tags: HEAD
Changes since 1.7: +15 -7 lines
fixing 2 bugs when running with ITD enabled
1) adding "," after Hlimit_c3 in namelist PARM01 definition
2) SEAICE_multDim needs to equal nITD when running ITD code
   because there's some shared multicategory code. But this
   default was overwritten when SEAICE_multDim is  given
   in data.seaice because the namelist is read after
   defaults have been set.
   (actually nITD should be replaced by SEAICE_multDim in
   the near future)

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

  ViewVC Help
Powered by ViewVC 1.1.22