/[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.11 - (hide annotations) (download)
Wed Apr 4 02:11:35 2007 UTC (17 years, 1 month ago) by jmc
Branch: MAIN
Changes since 1.10: +10 -4 lines
add ice-thickness diffusivity & Advection scheme selector.

1 jmc 1.11 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_readparms.F,v 1.10 2006/07/24 20:30:54 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     & thSIce_deltaT, ocean_deltaT, tauRelax_MxL,
66     & hMxL_default, sMxL_default, vMxL_default,
67 jmc 1.11 & thSIce_diffK, thSIceAdvScheme, stressReduction,
68 edhill 1.7 & 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 jmc 1.1
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 jmc 1.8
81 jmc 1.1 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     transcoef=0.006 _d 0
96     Lfresh = 3.34 _d 5
97     qsnow = Lfresh
98 jmc 1.2 albColdSnow= 0.85 _d 0
99     albWarmSnow= 0.70 _d 0
100 jmc 1.10 tempSnowAlb= -10. _d 0
101 jmc 1.2 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 jmc 1.8 snowAgTime = 50. _d 0 * 86400. _d 0
108 jmc 1.1 i0 = 0.3 _d 0
109     ksolar = 1.5 _d 0
110     saltice = 4. _d 0
111     S_winton = 1. _d 0
112     mu_Tf = 0.054 _d 0
113     Tf0kel = celsius2K
114     himin = 0.01 _d 0
115     Terrmax = 5.0 _d -1
116     nitMaxTsf= 20
117     hiMax = 10. _d 0
118     hsMax = 10. _d 0
119     iceMaskmax = 1. _d 0
120     iceMaskmin = .1 _d 0
121     himin0 = 0.2 _d 0
122     frac_energy= .4 _d 0
123     hihig = 2.5 _d 0
124    
125     C-- Default values (parameters)
126 jmc 1.3 stepFwd_oceMxL = .FALSE.
127     startIceModel = 0
128 jmc 1.4 thSIce_deltaT = dTtracerLev(1)
129     ocean_deltaT = dTtracerLev(1)
130 jmc 1.3 tauRelax_MxL = 0. _d 0
131     hMxL_default = 50. _d 0
132     sMxL_default = 35. _d 0
133     vMxL_default = 5. _d -2
134 jmc 1.11 thSIce_diffK = 0. _d 0
135     thSIceAdvScheme = 0
136 jmc 1.1 stressReduction = 1. _d 0
137 jmc 1.9 IF ( useSEAICE ) stressReduction = 0. _d 0
138 jmc 1.8 thSIce_taveFreq = taveFreq
139 jmc 1.1 thSIce_diagFreq = dumpFreq
140     thSIce_monFreq = monitorFreq
141 jmc 1.5 #ifdef ALLOW_MNC
142 edhill 1.7 thSIce_tave_mnc = timeave_mnc
143     thSIce_snapshot_mnc = snapshot_mnc
144     thSIce_mon_mnc = monitor_mnc
145     thSIce_pickup_read_mnc = pickup_read_mnc
146     thSIce_pickup_write_mnc = pickup_write_mnc
147 jmc 1.5 #else
148 edhill 1.7 thSIce_tave_mnc = .FALSE.
149     thSIce_snapshot_mnc = .FALSE.
150     thSIce_mon_mnc = .FALSE.
151     thSIce_pickup_read_mnc = .FALSE.
152     thSIce_pickup_write_mnc = .FALSE.
153 jmc 1.5 #endif
154     thSIceFract_InitFile = ' '
155     thSIceThick_InitFile = ' '
156     thSIceSnowH_InitFile = ' '
157     thSIceSnowA_InitFile = ' '
158     thSIceEnthp_InitFile = ' '
159     thSIceTsurf_InitFile = ' '
160    
161 jmc 1.1
162     C-- Read parameters from open data file
163     READ(UNIT=iUnit,NML=THSICE_CONST)
164     WRITE(msgBuf,'(A)') ' THSICE_READPARMS: read THSICE_CONST'
165     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
166     & SQUEEZE_RIGHT , 1)
167    
168     READ(UNIT=iUnit,NML=THSICE_PARM01)
169     WRITE(msgBuf,'(A)') ' THSICE_READPARMS: read THSICE_PARM01'
170     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
171     & SQUEEZE_RIGHT , 1)
172    
173     C-- Close the open data file
174     CLOSE(iUnit)
175    
176     C- Define other constants (from previous ones):
177     Tmlt1=-mu_Tf*S_winton
178     rhoiw = rhosw - rhoi
179    
180 edhill 1.7 C Set I/O parameters
181     thSIce_tave_mdsio = .TRUE.
182     thSIce_snapshot_mdsio = .TRUE.
183     thSIce_mon_stdio = .TRUE.
184     thSIce_pickup_write_mdsio = .TRUE.
185 jmc 1.5 #ifdef ALLOW_MNC
186     IF (useMNC) THEN
187     IF ( .NOT.outputTypesInclusive
188     & .AND. thSIce_tave_mnc ) thSIce_tave_mdsio = .FALSE.
189 jmc 1.8 IF ( .NOT.outputTypesInclusive
190     & .AND. thSIce_snapshot_mnc )
191 edhill 1.7 & thSIce_snapshot_mdsio = .FALSE.
192 jmc 1.5 IF ( .NOT.outputTypesInclusive
193     & .AND. thSIce_mon_mnc ) thSIce_mon_stdio = .FALSE.
194 edhill 1.7 IF ( .NOT.outputTypesInclusive
195 jmc 1.8 & .AND. thSIce_pickup_write_mnc )
196 edhill 1.7 & thSIce_pickup_write_mdsio = .FALSE.
197 jmc 1.5 ENDIF
198     #endif
199    
200 jmc 1.9 C-- Check parameter consistency:
201     IF ( useSEAICE .AND. stressReduction.NE.0. _d 0 ) THEN
202     C-- If useSEAICE=.true., the stress is computed in seaice_model,
203     C-- so that it does not need any further reduction
204     WRITE(msgBuf,'(2A)')
205     & 'THSICE_READPARMS: if useSEAICE, stress will be computed',
206     & ' by SEAICE pkg => no reduction'
207     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
208     & SQUEEZE_RIGHT , myThid)
209     WRITE(msgBuf,'(A)')
210     & 'THSICE_READPARMS: WARNING: reset stressReduction to zero'
211     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
212     & SQUEEZE_RIGHT , myThid)
213     stressReduction = 0. _d 0
214     ENDIF
215    
216 jmc 1.1 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
217     iUnit = standardMessageUnit
218 jmc 1.5 c CALL MDSFINDUNIT( iUnit, mythid )
219 jmc 1.1 c OPEN(iUnit,file='thsice_check_params',status='unknown')
220     WRITE(iUnit,*) 'ThSI: rhos =',rhos
221     WRITE(iUnit,*) 'ThSI: rhoi =',rhoi
222     WRITE(iUnit,*) 'ThSI: rhosw =',rhosw
223     WRITE(iUnit,*) 'ThSI: rhofw =',rhofw
224     WRITE(iUnit,*) 'ThSI: rhoiw =',rhoiw
225     WRITE(iUnit,*) 'ThSI: cpice =',cpice
226     WRITE(iUnit,*) 'ThSI: cpwater =',cpwater
227     WRITE(iUnit,*) 'ThSI: kice =',kice
228     WRITE(iUnit,*) 'ThSI: ksnow =',ksnow
229     WRITE(iUnit,*) 'ThSI: transcoef=',transcoef
230     WRITE(iUnit,*) 'ThSI: Lfresh =',Lfresh
231     WRITE(iUnit,*) 'ThSI: qsnow =',qsnow
232 jmc 1.2 WRITE(iUnit,*) 'ThSI: albColdSnow=',albColdSnow
233     WRITE(iUnit,*) 'ThSI: albWarmSnow=',albWarmSnow
234 jmc 1.10 WRITE(iUnit,*) 'ThSI: tempSnowAlb=',tempSnowAlb
235 jmc 1.2 WRITE(iUnit,*) 'ThSI: albOldSnow =',albOldSnow
236 jmc 1.10 WRITE(iUnit,*) 'ThSI: hNewSnowAge=',hNewSnowAge
237     WRITE(iUnit,*) 'ThSI: snowAgTime =',snowAgTime
238 jmc 1.2 WRITE(iUnit,*) 'ThSI: albIceMax =',albIceMax
239     WRITE(iUnit,*) 'ThSI: albIceMin =',albIceMin
240     WRITE(iUnit,*) 'ThSI: hAlbIce =',hAlbIce
241     WRITE(iUnit,*) 'ThSI: hAlbSnow =',hAlbSnow
242 jmc 1.1 WRITE(iUnit,*) 'ThSI: i0 =',i0
243     WRITE(iUnit,*) 'ThSI: ksolar =',ksolar
244     WRITE(iUnit,*) 'ThSI: saltice =',saltice
245     WRITE(iUnit,*) 'ThSI: S_winton=',S_winton
246     WRITE(iUnit,*) 'ThSI: mu_Tf =',mu_Tf
247     WRITE(iUnit,*) 'ThSI: Tf0kel =',Tf0kel
248     WRITE(iUnit,*) 'ThSI: Tmlt1 =',Tmlt1
249     WRITE(iUnit,*) 'ThSI: himin =',himin
250     WRITE(iUnit,*) 'ThSI: Terrmax =',Terrmax
251     WRITE(iUnit,*) 'ThSI: nitMaxTsf=',nitMaxTsf
252     WRITE(iUnit,*) 'ThSI: hiMax =',hiMax
253     WRITE(iUnit,*) 'ThSI: hsMax =',hsMax
254     WRITE(iUnit,*) 'ThSI: iceMaskmax=',iceMaskmax
255     WRITE(iUnit,*) 'ThSI: iceMaskmin=',iceMaskmin
256     WRITE(iUnit,*) 'ThSI: himin0 =',himin0
257     WRITE(iUnit,*) 'ThSI: frac_energy',frac_energy
258     WRITE(iUnit,*) 'ThSI: hihig =',hihig
259     WRITE(iUnit,*) 'ThSI: stressReduction =',stressReduction
260 jmc 1.11 WRITE(iUnit,*) 'ThSI: thSIceAdvScheme =',thSIceAdvScheme
261     WRITE(iUnit,*) 'ThSI: thSIce_diffK =',thSIce_diffK
262 jmc 1.3 WRITE(iUnit,*) 'ThSI: thSIce_deltaT =',thSIce_deltaT
263     WRITE(iUnit,*) 'ThSI: ocean_deltaT =',ocean_deltaT
264     WRITE(iUnit,*) 'ThSI: stepFwd_oceMxL=',stepFwd_oceMxL
265     WRITE(iUnit,*) 'ThSI: tauRelax_MxL =',tauRelax_MxL
266     WRITE(iUnit,*) 'ThSI: hMxL_default =',hMxL_default
267     WRITE(iUnit,*) 'ThSI: sMxL_default =',sMxL_default
268     WRITE(iUnit,*) 'ThSI: vMxL_default =',vMxL_default
269 jmc 1.1 WRITE(iUnit,*) 'ThSI: thSIce_taveFreq=',thSIce_taveFreq
270     WRITE(iUnit,*) 'ThSI: thSIce_diagFreq=',thSIce_diagFreq
271     WRITE(iUnit,*) 'ThSI: thSIce_monFreq =',thSIce_monFreq
272     WRITE(iUnit,*) 'ThSI: startIceModel =',startIceModel
273 jmc 1.5 IF (iUnit.NE.standardMessageUnit) CLOSE(iUnit)
274 jmc 1.1 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
275    
276     _END_MASTER(myThid)
277    
278     C-- Everyone else must wait for the parameters to be loaded
279     _BARRIER
280    
281     #endif /* ALLOW_THSICE */
282    
283     RETURN
284     END
285 jmc 1.11

  ViewVC Help
Powered by ViewVC 1.1.22