/[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.7 - (hide annotations) (download)
Wed Mar 27 18:59:53 2013 UTC (12 years, 4 months ago) by torge
Branch: MAIN
Changes since 1.6: +77 -57 lines
updating my MITgcm_contrib directory to include latest changes on main branch;
settings are to run a 1D test szenario with ITD code and 7 categories

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

  ViewVC Help
Powered by ViewVC 1.1.22