/[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.4 - (hide annotations) (download)
Mon Oct 22 19:34:55 2012 UTC (12 years, 9 months ago) by torge
Branch: MAIN
Changes since 1.3: +51 -19 lines
incorporate updates of main branch

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

  ViewVC Help
Powered by ViewVC 1.1.22