/[MITgcm]/MITgcm/pkg/thsice/thsice_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/thsice/thsice_readparms.F

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


Revision 1.14 - (show annotations) (download)
Sun Apr 29 23:48:44 2007 UTC (17 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59p, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j
Changes since 1.13: +60 -52 lines
rename few parameters:
 himin  -> hIceMin
 himin0 -> hThinIce
 hihig  -> hThickIce
 i0     -> i0swFrac
 transCoef -> bMeltCoef
 frac_energy -> fracMelting
and add:
 hNewIceMax, fracFreezing, dhSnowLin

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_readparms.F,v 1.13 2007/04/09 17:44:13 jscott Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: THSICE_READPARMS
8 C !INTERFACE:
9 SUBROUTINE THSICE_READPARMS( myThid )
10
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | S/R THSICE_READPARMS
14 C | o Routine to initialize THSICE parameters and constants
15 C *==========================================================*
16 C | Initialize Th-Sea-ICE parameters, read in data.ice
17 C *==========================================================*
18 C \ev
19
20 C !USES:
21 IMPLICIT NONE
22
23 C === Global variables ===
24 #include "SIZE.h"
25 #include "EEPARAMS.h"
26 #include "PARAMS.h"
27 #include "GRID.h"
28 #include "THSICE_PARAMS.h"
29 #ifdef ALLOW_MNC
30 #include "MNC_PARAMS.h"
31 #endif
32
33 C !INPUT/OUTPUT PARAMETERS:
34 C === Routine arguments ===
35 C myThid :: My Thread Id. number
36 INTEGER myThid
37 CEOP
38
39 #ifdef ALLOW_THSICE
40
41 C === Local variables ===
42 C msgBuf :: Informational/error message buffer
43 C iUnit :: Work variable for IO unit number
44 CHARACTER*(MAX_LEN_MBUF) msgBuf
45 INTEGER iUnit
46
47 C-- Th-Sea-ICE parameter
48 NAMELIST /THSICE_CONST/
49 & rhos, rhoi, rhosw, rhofw,
50 & cpIce, cpWater,
51 & kIce, kSnow,
52 & bMeltCoef, Lfresh, qsnow,
53 & albColdSnow, albWarmSnow, tempSnowAlb,
54 & albOldSnow, hNewSnowAge, snowAgTime,
55 & albIceMax, albIceMin, hAlbIce, hAlbSnow,
56 & i0swFrac, ksolar, dhSnowLin,
57 & saltIce, S_winton, mu_Tf,
58 & Tf0kel, Terrmax, nitMaxTsf,
59 & hIceMin, hiMax, hsMax, iceMaskMax, iceMaskMin,
60 & fracEnMelt, fracEnFreez, hThinIce, hThickIce, hNewIceMax
61
62 NAMELIST /THSICE_PARM01/
63 & startIceModel, stepFwd_oceMxL,
64 & thSIce_deltaT, thSIce_dtTemp,
65 & ocean_deltaT, tauRelax_MxL,
66 & hMxL_default, sMxL_default, vMxL_default,
67 & thSIce_diffK, thSIceAdvScheme, stressReduction,
68 & thSIce_taveFreq, thSIce_diagFreq, thSIce_monFreq,
69 & thSIce_tave_mnc, thSIce_snapshot_mnc, thSIce_mon_mnc,
70 & thSIce_pickup_read_mnc, thSIce_pickup_write_mnc,
71 & thSIceFract_InitFile, thSIceThick_InitFile,
72 & thSIceSnowH_InitFile, thSIceSnowA_InitFile,
73 & thSIceEnthp_InitFile, thSIceTsurf_InitFile
74
75 _BEGIN_MASTER(myThid)
76
77 WRITE(msgBuf,'(A)') ' THSICE_READPARMS: opening data.ice'
78 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
79 & SQUEEZE_RIGHT , 1)
80
81 CALL OPEN_COPY_DATA_FILE(
82 I 'data.ice', 'THSICE_READPARMS',
83 O iUnit,
84 I myThid )
85
86 C-- Default values (constants)
87 rhos = 330. _d 0
88 rhoi = 900. _d 0
89 rhosw = rhoConst
90 rhofw = rhoConstFresh
91 cpIce = 2106. _d 0
92 cpWater = HeatCapacity_Cp
93 kIce = 2.03 _d 0
94 kSnow = 0.30 _d 0
95 bMeltCoef=0.006 _d 0
96 Lfresh = 3.34 _d 5
97 qsnow = Lfresh
98 albColdSnow= 0.85 _d 0
99 albWarmSnow= 0.70 _d 0
100 tempSnowAlb= -10. _d 0
101 albOldSnow = 0.55 _d 0
102 albIceMax = 0.65 _d 0
103 albIceMin = 0.20 _d 0
104 hAlbIce = 0.50 _d 0
105 hAlbSnow = 0.30 _d 0
106 hNewSnowAge= 2. _d -3
107 snowAgTime = 50. _d 0 * 86400. _d 0
108 i0swFrac = 0.3 _d 0
109 ksolar = 1.5 _d 0
110 dhSnowLin= 0. _d 0
111 saltIce = 4. _d 0
112 S_winton = 1. _d 0
113 mu_Tf = 0.054 _d 0
114 Tf0kel = celsius2K
115 Terrmax = 5.0 _d -1
116 nitMaxTsf= 20
117 hIceMin = 1. _d -2
118 hiMax = 10. _d 0
119 hsMax = 10. _d 0
120 iceMaskMax = 1. _d 0
121 iceMaskMin = 0.1 _d 0
122 fracEnMelt = 0.4 _d 0
123 fracEnFreez= 0. _d 0
124 hThinIce = 0.2 _d 0
125 hThickIce = 2.5 _d 0
126 hNewIceMax = UNSET_RL
127
128 C-- Default values (parameters)
129 stepFwd_oceMxL = .FALSE.
130 startIceModel = 0
131 thSIce_deltaT = dTtracerLev(1)
132 thSIce_dtTemp = UNSET_RL
133 ocean_deltaT = dTtracerLev(1)
134 tauRelax_MxL = 0. _d 0
135 hMxL_default = 50. _d 0
136 sMxL_default = 35. _d 0
137 vMxL_default = 5. _d -2
138 thSIce_diffK = 0. _d 0
139 thSIceAdvScheme = 0
140 stressReduction = 1. _d 0
141 IF ( useSEAICE ) stressReduction = 0. _d 0
142 thSIce_taveFreq = taveFreq
143 thSIce_diagFreq = dumpFreq
144 thSIce_monFreq = monitorFreq
145 #ifdef ALLOW_MNC
146 thSIce_tave_mnc = timeave_mnc
147 thSIce_snapshot_mnc = snapshot_mnc
148 thSIce_mon_mnc = monitor_mnc
149 thSIce_pickup_read_mnc = pickup_read_mnc
150 thSIce_pickup_write_mnc = pickup_write_mnc
151 #else
152 thSIce_tave_mnc = .FALSE.
153 thSIce_snapshot_mnc = .FALSE.
154 thSIce_mon_mnc = .FALSE.
155 thSIce_pickup_read_mnc = .FALSE.
156 thSIce_pickup_write_mnc = .FALSE.
157 #endif
158 thSIceFract_InitFile = ' '
159 thSIceThick_InitFile = ' '
160 thSIceSnowH_InitFile = ' '
161 thSIceSnowA_InitFile = ' '
162 thSIceEnthp_InitFile = ' '
163 thSIceTsurf_InitFile = ' '
164
165
166 C-- Read parameters from open data file
167 READ(UNIT=iUnit,NML=THSICE_CONST)
168 WRITE(msgBuf,'(A)') ' THSICE_READPARMS: read THSICE_CONST'
169 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
170 & SQUEEZE_RIGHT , 1)
171
172 READ(UNIT=iUnit,NML=THSICE_PARM01)
173 WRITE(msgBuf,'(A)') ' THSICE_READPARMS: read THSICE_PARM01'
174 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
175 & SQUEEZE_RIGHT , 1)
176
177 C-- Close the open data file
178 CLOSE(iUnit)
179
180 C- neutral default:
181 IF ( hNewIceMax .EQ. UNSET_RL ) hNewIceMax = hiMax
182
183 C If using the same time step for both icetop temp solver
184 C and ice thickness/growth, use thSIce_deltaT value
185 IF ( thSIce_dtTemp .EQ. UNSET_RL ) thSIce_dtTemp=thSIce_deltaT
186
187 C- Define other constants (from previous ones):
188 Tmlt1=-mu_Tf*S_winton
189 rhoiw = rhosw - rhoi
190
191 C Set I/O parameters
192 thSIce_tave_mdsio = .TRUE.
193 thSIce_snapshot_mdsio = .TRUE.
194 thSIce_mon_stdio = .TRUE.
195 thSIce_pickup_write_mdsio = .TRUE.
196 #ifdef ALLOW_MNC
197 IF (useMNC) THEN
198 IF ( .NOT.outputTypesInclusive
199 & .AND. thSIce_tave_mnc ) thSIce_tave_mdsio = .FALSE.
200 IF ( .NOT.outputTypesInclusive
201 & .AND. thSIce_snapshot_mnc )
202 & thSIce_snapshot_mdsio = .FALSE.
203 IF ( .NOT.outputTypesInclusive
204 & .AND. thSIce_mon_mnc ) thSIce_mon_stdio = .FALSE.
205 IF ( .NOT.outputTypesInclusive
206 & .AND. thSIce_pickup_write_mnc )
207 & thSIce_pickup_write_mdsio = .FALSE.
208 ENDIF
209 #endif
210
211 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
212 C-- Check parameter consistency:
213 IF ( thSIceAdvScheme.EQ.0 .AND. thSIce_diffK.NE.0. ) THEN
214 WRITE(msgBuf,'(2A)')
215 & 'THSICE_READPARMS: to use thSIce_diffK, needs to select',
216 & ' one advection scheme (thSIceAdvScheme<>0)'
217 CALL PRINT_ERROR( msgBuf , myThid )
218 STOP 'ABNORMAL END: THSICE_READPARMS'
219 ENDIF
220 #ifndef ALLOW_GENERIC_ADVDIFF
221 IF ( thSIceAdvScheme.NE.0 ) THEN
222 WRITE(msgBuf,'(2A)')
223 & 'THSICE_READPARMS: Need to compile "generic_advdiff" pkg',
224 & ' in order to use thSIceAdvScheme'
225 CALL PRINT_ERROR( msgBuf , myThid )
226 STOP 'ABNORMAL END: THSICE_READPARMS'
227 ENDIF
228 #endif /* ndef ALLOW_GENERIC_ADVDIFF */
229
230 IF ( useSEAICE .AND. stressReduction.NE.0. _d 0 ) THEN
231 C-- If useSEAICE=.true., the stress is computed in seaice_model,
232 C-- so that it does not need any further reduction
233 WRITE(msgBuf,'(2A)')
234 & 'THSICE_READPARMS: if useSEAICE, stress will be computed',
235 & ' by SEAICE pkg => no reduction'
236 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
237 & SQUEEZE_RIGHT , myThid)
238 WRITE(msgBuf,'(A)')
239 & 'THSICE_READPARMS: WARNING: reset stressReduction to zero'
240 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
241 & SQUEEZE_RIGHT , myThid)
242 stressReduction = 0. _d 0
243 ENDIF
244
245 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
246 iUnit = standardMessageUnit
247 c CALL MDSFINDUNIT( iUnit, mythid )
248 c OPEN(iUnit,file='thsice_check_params',status='unknown')
249 WRITE(iUnit,*) 'ThSI: rhos =',rhos
250 WRITE(iUnit,*) 'ThSI: rhoi =',rhoi
251 WRITE(iUnit,*) 'ThSI: rhosw =',rhosw
252 WRITE(iUnit,*) 'ThSI: rhofw =',rhofw
253 WRITE(iUnit,*) 'ThSI: rhoiw =',rhoiw
254 WRITE(iUnit,*) 'ThSI: cpIce =',cpIce
255 WRITE(iUnit,*) 'ThSI: cpWater =',cpWater
256 WRITE(iUnit,*) 'ThSI: kIce =',kIce
257 WRITE(iUnit,*) 'ThSI: kSnow =',kSnow
258 WRITE(iUnit,*) 'ThSI: bMeltCoef =',bMeltCoef
259 WRITE(iUnit,*) 'ThSI: Lfresh =',Lfresh
260 WRITE(iUnit,*) 'ThSI: qsnow =',qsnow
261 WRITE(iUnit,*) 'ThSI: albColdSnow=',albColdSnow
262 WRITE(iUnit,*) 'ThSI: albWarmSnow=',albWarmSnow
263 WRITE(iUnit,*) 'ThSI: tempSnowAlb=',tempSnowAlb
264 WRITE(iUnit,*) 'ThSI: albOldSnow =',albOldSnow
265 WRITE(iUnit,*) 'ThSI: hNewSnowAge=',hNewSnowAge
266 WRITE(iUnit,*) 'ThSI: snowAgTime =',snowAgTime
267 WRITE(iUnit,*) 'ThSI: albIceMax =',albIceMax
268 WRITE(iUnit,*) 'ThSI: albIceMin =',albIceMin
269 WRITE(iUnit,*) 'ThSI: hAlbIce =',hAlbIce
270 WRITE(iUnit,*) 'ThSI: hAlbSnow =',hAlbSnow
271 WRITE(iUnit,*) 'ThSI: i0swFrac =',i0swFrac
272 WRITE(iUnit,*) 'ThSI: ksolar =',ksolar
273 WRITE(iUnit,*) 'ThSI: dhSnowLin =',dhSnowLin
274 WRITE(iUnit,*) 'ThSI: saltIce =',saltIce
275 WRITE(iUnit,*) 'ThSI: S_winton =',S_winton
276 WRITE(iUnit,*) 'ThSI: mu_Tf =',mu_Tf
277 WRITE(iUnit,*) 'ThSI: Tf0kel =',Tf0kel
278 WRITE(iUnit,*) 'ThSI: Tmlt1 =',Tmlt1
279 WRITE(iUnit,*) 'ThSI: Terrmax =',Terrmax
280 WRITE(iUnit,*) 'ThSI: nitMaxTsf =',nitMaxTsf
281 WRITE(iUnit,*) 'ThSI: hIceMin =',hIceMin
282 WRITE(iUnit,*) 'ThSI: hiMax =',hiMax
283 WRITE(iUnit,*) 'ThSI: hsMax =',hsMax
284 WRITE(iUnit,*) 'ThSI: iceMaskMax =',iceMaskMax
285 WRITE(iUnit,*) 'ThSI: iceMaskMin =',iceMaskMin
286 WRITE(iUnit,*) 'ThSI: fracEnMelt =',fracEnMelt
287 WRITE(iUnit,*) 'ThSI: fracEnFreez=',fracEnFreez
288 WRITE(iUnit,*) 'ThSI: hThinIce =',hThinIce
289 WRITE(iUnit,*) 'ThSI: hThickIce =',hThickIce
290 WRITE(iUnit,*) 'ThSI: hNewIceMax =',hNewIceMax
291 WRITE(iUnit,*) 'ThSI: stressReduction =',stressReduction
292 WRITE(iUnit,*) 'ThSI: thSIceAdvScheme =',thSIceAdvScheme
293 WRITE(iUnit,*) 'ThSI: thSIce_diffK =',thSIce_diffK
294 WRITE(iUnit,*) 'ThSI: thSIce_deltaT =',thSIce_deltaT
295 WRITE(iUnit,*) 'ThSI: ocean_deltaT =',ocean_deltaT
296 WRITE(iUnit,*) 'ThSI: stepFwd_oceMxL=',stepFwd_oceMxL
297 WRITE(iUnit,*) 'ThSI: tauRelax_MxL =',tauRelax_MxL
298 WRITE(iUnit,*) 'ThSI: hMxL_default =',hMxL_default
299 WRITE(iUnit,*) 'ThSI: sMxL_default =',sMxL_default
300 WRITE(iUnit,*) 'ThSI: vMxL_default =',vMxL_default
301 WRITE(iUnit,*) 'ThSI: thSIce_taveFreq=',thSIce_taveFreq
302 WRITE(iUnit,*) 'ThSI: thSIce_diagFreq=',thSIce_diagFreq
303 WRITE(iUnit,*) 'ThSI: thSIce_monFreq =',thSIce_monFreq
304 WRITE(iUnit,*) 'ThSI: startIceModel =',startIceModel
305 IF (iUnit.NE.standardMessageUnit) CLOSE(iUnit)
306 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
307
308 _END_MASTER(myThid)
309
310 C-- Everyone else must wait for the parameters to be loaded
311 _BARRIER
312
313 #endif /* ALLOW_THSICE */
314
315 RETURN
316 END

  ViewVC Help
Powered by ViewVC 1.1.22