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

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

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


Revision 1.13 - (hide annotations) (download)
Mon Apr 9 17:44:13 2007 UTC (17 years, 1 month ago) by jscott
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58y_post
Changes since 1.12: +8 -3 lines
allow for different timesteps for ice-atm and ice-ocean interactions

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

  ViewVC Help
Powered by ViewVC 1.1.22