/[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.5 - (hide annotations) (download)
Fri Dec 17 04:29:07 2004 UTC (19 years, 5 months ago) by jmc
Branch: MAIN
Changes since 1.4: +48 -4 lines
allow to start from an initial state (6 input files)

1 jmc 1.5 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_readparms.F,v 1.4 2004/12/04 00:19:32 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     INTEGER myThid
36 jmc 1.3 CEOP
37 jmc 1.1
38     #ifdef ALLOW_THSICE
39    
40     C === Local variables ===
41 jmc 1.3 C msgBuf - Informational/error message buffer
42 jmc 1.1 C iUnit - Work variable for IO unit number
43     CHARACTER*(MAX_LEN_MBUF) msgBuf
44     INTEGER iUnit
45    
46     C-- Th-Sea-ICE parameter
47     NAMELIST /THSICE_CONST/
48     & rhos, rhoi, rhosw, rhofw,
49     & cpice, cpwater,
50     & kice, ksnow,
51     & transcoef, Lfresh, qsnow,
52 jmc 1.2 & albColdSnow, albWarmSnow, albOldSnow, hNewSnowAge,
53     & albIceMax, albIceMin, hAlbIce, hAlbSnow,
54 jmc 1.1 & i0, ksolar,
55     & saltice, S_winton, mu_Tf,
56     & Tf0kel,
57     & himin, Terrmax, nitMaxTsf, hiMax, hsMax,
58     & iceMaskmax, iceMaskmin, himin0,
59     & frac_energy, hihig
60    
61     NAMELIST /THSICE_PARM01/
62 jmc 1.3 & startIceModel, stepFwd_oceMxL,
63     & thSIce_deltaT, ocean_deltaT, tauRelax_MxL,
64     & hMxL_default, sMxL_default, vMxL_default,
65 jmc 1.1 & stressReduction,
66 jmc 1.5 & thSIce_taveFreq, thSIce_diagFreq, thSIce_monFreq,
67     c & thSIce_tave_mnc, thSIce_diag_mnc, thSIce_mon_mnc,
68     & thSIceFract_InitFile, thSIceThick_InitFile,
69     & thSIceSnowH_InitFile, thSIceSnowA_InitFile,
70     & thSIceEnthp_InitFile, thSIceTsurf_InitFile
71 jmc 1.1
72     _BEGIN_MASTER(myThid)
73    
74     WRITE(msgBuf,'(A)') ' THSICE_READPARMS: opening data.ice'
75     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
76     & SQUEEZE_RIGHT , 1)
77    
78     CALL OPEN_COPY_DATA_FILE(
79     I 'data.ice', 'THSICE_READPARMS',
80     O iUnit,
81     I myThid )
82    
83     C-- Default values (constants)
84     rhos = 330. _d 0
85     rhoi = 900. _d 0
86     rhosw = rhoConst
87     rhofw = rhoConstFresh
88     cpice = 2106. _d 0
89     cpwater = HeatCapacity_Cp
90     kice = 2.03 _d 0
91     ksnow = 0.30 _d 0
92     transcoef=0.006 _d 0
93     Lfresh = 3.34 _d 5
94     qsnow = Lfresh
95 jmc 1.2 albColdSnow= 0.85 _d 0
96     albWarmSnow= 0.70 _d 0
97     albOldSnow = 0.55 _d 0
98     albIceMax = 0.65 _d 0
99     albIceMin = 0.20 _d 0
100     hAlbIce = 0.50 _d 0
101     hAlbSnow = 0.30 _d 0
102     hNewSnowAge= 2. _d -3
103 jmc 1.1 i0 = 0.3 _d 0
104     ksolar = 1.5 _d 0
105     saltice = 4. _d 0
106     S_winton = 1. _d 0
107     mu_Tf = 0.054 _d 0
108     Tf0kel = celsius2K
109     himin = 0.01 _d 0
110     Terrmax = 5.0 _d -1
111     nitMaxTsf= 20
112     hiMax = 10. _d 0
113     hsMax = 10. _d 0
114     iceMaskmax = 1. _d 0
115     iceMaskmin = .1 _d 0
116     himin0 = 0.2 _d 0
117     frac_energy= .4 _d 0
118     hihig = 2.5 _d 0
119    
120     C-- Default values (parameters)
121 jmc 1.3 stepFwd_oceMxL = .FALSE.
122     startIceModel = 0
123 jmc 1.4 thSIce_deltaT = dTtracerLev(1)
124     ocean_deltaT = dTtracerLev(1)
125 jmc 1.3 tauRelax_MxL = 0. _d 0
126     hMxL_default = 50. _d 0
127     sMxL_default = 35. _d 0
128     vMxL_default = 5. _d -2
129 jmc 1.1 stressReduction = 1. _d 0
130     thSIce_taveFreq = taveFreq
131     thSIce_diagFreq = dumpFreq
132     thSIce_monFreq = monitorFreq
133 jmc 1.5 #ifdef ALLOW_MNC
134     thSIce_tave_mnc = timeave_mnc
135     thSIce_diag_mnc = snapshot_mnc
136     thSIce_mon_mnc = monitor_mnc
137     #else
138     thSIce_tave_mnc = .FALSE.
139     thSIce_diag_mnc = .FALSE.
140     thSIce_mon_mnc = .FALSE.
141     #endif
142     thSIceFract_InitFile = ' '
143     thSIceThick_InitFile = ' '
144     thSIceSnowH_InitFile = ' '
145     thSIceSnowA_InitFile = ' '
146     thSIceEnthp_InitFile = ' '
147     thSIceTsurf_InitFile = ' '
148    
149 jmc 1.1
150     C-- Read parameters from open data file
151     READ(UNIT=iUnit,NML=THSICE_CONST)
152     WRITE(msgBuf,'(A)') ' THSICE_READPARMS: read THSICE_CONST'
153     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
154     & SQUEEZE_RIGHT , 1)
155    
156     READ(UNIT=iUnit,NML=THSICE_PARM01)
157     WRITE(msgBuf,'(A)') ' THSICE_READPARMS: read THSICE_PARM01'
158     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
159     & SQUEEZE_RIGHT , 1)
160    
161     C-- Close the open data file
162     CLOSE(iUnit)
163    
164     C- Define other constants (from previous ones):
165     Tmlt1=-mu_Tf*S_winton
166     rhoiw = rhosw - rhoi
167    
168 jmc 1.5 C- Set other parameters (from previous ones):
169     thSIce_tave_mdsio = .TRUE.
170     thSIce_diag_mdsio = .TRUE.
171     thSIce_mon_stdio = .TRUE.
172     #ifdef ALLOW_MNC
173     IF (useMNC) THEN
174     C-------
175     C- MNC not yet available in this package => turn off MNC flags for now
176     thSIce_tave_mnc = .FALSE.
177     thSIce_diag_mnc = .FALSE.
178     thSIce_mon_mnc = .FALSE.
179     C-------
180     IF ( .NOT.outputTypesInclusive
181     & .AND. thSIce_tave_mnc ) thSIce_tave_mdsio = .FALSE.
182     IF ( .NOT.outputTypesInclusive)
183     & .AND. thSIce_diag_mnc ) thSIce_diag_mdsio = .FALSE.
184     IF ( .NOT.outputTypesInclusive
185     & .AND. thSIce_mon_mnc ) thSIce_mon_stdio = .FALSE.
186     ENDIF
187     #endif
188    
189 jmc 1.1 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
190     iUnit = standardMessageUnit
191 jmc 1.5 c CALL MDSFINDUNIT( iUnit, mythid )
192 jmc 1.1 c OPEN(iUnit,file='thsice_check_params',status='unknown')
193     WRITE(iUnit,*) 'ThSI: rhos =',rhos
194     WRITE(iUnit,*) 'ThSI: rhoi =',rhoi
195     WRITE(iUnit,*) 'ThSI: rhosw =',rhosw
196     WRITE(iUnit,*) 'ThSI: rhofw =',rhofw
197     WRITE(iUnit,*) 'ThSI: rhoiw =',rhoiw
198     WRITE(iUnit,*) 'ThSI: cpice =',cpice
199     WRITE(iUnit,*) 'ThSI: cpwater =',cpwater
200     WRITE(iUnit,*) 'ThSI: kice =',kice
201     WRITE(iUnit,*) 'ThSI: ksnow =',ksnow
202     WRITE(iUnit,*) 'ThSI: transcoef=',transcoef
203     WRITE(iUnit,*) 'ThSI: Lfresh =',Lfresh
204     WRITE(iUnit,*) 'ThSI: qsnow =',qsnow
205 jmc 1.2 WRITE(iUnit,*) 'ThSI: albColdSnow=',albColdSnow
206     WRITE(iUnit,*) 'ThSI: albWarmSnow=',albWarmSnow
207     WRITE(iUnit,*) 'ThSI: albOldSnow =',albOldSnow
208     WRITE(iUnit,*) 'ThSI: hNewSnowAge=',hNewSnowAge
209     WRITE(iUnit,*) 'ThSI: albIceMax =',albIceMax
210     WRITE(iUnit,*) 'ThSI: albIceMin =',albIceMin
211     WRITE(iUnit,*) 'ThSI: hAlbIce =',hAlbIce
212     WRITE(iUnit,*) 'ThSI: hAlbSnow =',hAlbSnow
213 jmc 1.1 WRITE(iUnit,*) 'ThSI: i0 =',i0
214     WRITE(iUnit,*) 'ThSI: ksolar =',ksolar
215     WRITE(iUnit,*) 'ThSI: saltice =',saltice
216     WRITE(iUnit,*) 'ThSI: S_winton=',S_winton
217     WRITE(iUnit,*) 'ThSI: mu_Tf =',mu_Tf
218     WRITE(iUnit,*) 'ThSI: Tf0kel =',Tf0kel
219     WRITE(iUnit,*) 'ThSI: Tmlt1 =',Tmlt1
220     WRITE(iUnit,*) 'ThSI: himin =',himin
221     WRITE(iUnit,*) 'ThSI: Terrmax =',Terrmax
222     WRITE(iUnit,*) 'ThSI: nitMaxTsf=',nitMaxTsf
223     WRITE(iUnit,*) 'ThSI: hiMax =',hiMax
224     WRITE(iUnit,*) 'ThSI: hsMax =',hsMax
225     WRITE(iUnit,*) 'ThSI: iceMaskmax=',iceMaskmax
226     WRITE(iUnit,*) 'ThSI: iceMaskmin=',iceMaskmin
227     WRITE(iUnit,*) 'ThSI: himin0 =',himin0
228     WRITE(iUnit,*) 'ThSI: frac_energy',frac_energy
229     WRITE(iUnit,*) 'ThSI: hihig =',hihig
230     WRITE(iUnit,*) 'ThSI: stressReduction =',stressReduction
231 jmc 1.3 WRITE(iUnit,*) 'ThSI: thSIce_deltaT =',thSIce_deltaT
232     WRITE(iUnit,*) 'ThSI: ocean_deltaT =',ocean_deltaT
233     WRITE(iUnit,*) 'ThSI: stepFwd_oceMxL=',stepFwd_oceMxL
234     WRITE(iUnit,*) 'ThSI: tauRelax_MxL =',tauRelax_MxL
235     WRITE(iUnit,*) 'ThSI: hMxL_default =',hMxL_default
236     WRITE(iUnit,*) 'ThSI: sMxL_default =',sMxL_default
237     WRITE(iUnit,*) 'ThSI: vMxL_default =',vMxL_default
238 jmc 1.1 WRITE(iUnit,*) 'ThSI: thSIce_taveFreq=',thSIce_taveFreq
239     WRITE(iUnit,*) 'ThSI: thSIce_diagFreq=',thSIce_diagFreq
240     WRITE(iUnit,*) 'ThSI: thSIce_monFreq =',thSIce_monFreq
241     WRITE(iUnit,*) 'ThSI: startIceModel =',startIceModel
242 jmc 1.5 IF (iUnit.NE.standardMessageUnit) CLOSE(iUnit)
243 jmc 1.1 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
244    
245     _END_MASTER(myThid)
246    
247     C-- Everyone else must wait for the parameters to be loaded
248     _BARRIER
249    
250     #endif /* ALLOW_THSICE */
251    
252     RETURN
253     END

  ViewVC Help
Powered by ViewVC 1.1.22