/[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.7 - (hide annotations) (download)
Fri Jun 24 04:36:54 2005 UTC (19 years ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint57y_post, checkpoint57y_pre, checkpoint57v_post, checkpoint57r_post, checkpoint58, checkpoint57x_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint57q_post, checkpoint57z_post, checkpoint57j_post, checkpoint58b_post, checkpoint57l_post
Changes since 1.6: +31 -27 lines
 o mnc-ify the thsice package as requested by Daniel Enderton
   - the monitor--MNC output needs work
   - many attributes need to be added (most are currently blank)
   - does not break testreport (at least on IA32)

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

  ViewVC Help
Powered by ViewVC 1.1.22