/[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.1 - (hide annotations) (download)
Fri Apr 27 22:22:17 2012 UTC (13 years, 3 months ago) by dimitri
Branch: MAIN
check-in original code, before itd modifications
seaice_advdiff.F,v 1.60 2012/02/16 01:22:02
seaice_check_pickup.F,v 1.7 2012/03/05 15:21:44
seaice_diagnostics_init.F,v 1.33 2012/02/16 01:22:02
seaice_growth.F,v 1.162 2012/03/15 03:07:31
seaice_init_fixed.F,v 1.19 2012/03/11 13:41:38
seaice_init_varia.F,v 1.72 2012/03/14 22:55:53
seaice_readparms.F,v 1.120 2012/03/14 22:55:53
seaice_write_pickup.F,v 1.14 2012/03/05 15:21:45
seaice_read_pickup.F,v 1.16 2012/03/05 15:21:44
seaice_model.F,v 1.100 2012/03/02 18:56:06
SEAICE.h,v 1.62 2012/03/06 16:51:21
SEAICE_OPTIONS.h,v 1.63 2012/03/08 01:15:02
SEAICE_PARAMS.h,v 1.91 2012/03/11 13:41:38
SEAICE_SIZE.h,v 1.5 2012/03/06 16:51:21
SIZE.h,v 1.28 2009/05/17 21:15:07

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

  ViewVC Help
Powered by ViewVC 1.1.22