/[MITgcm]/MITgcm_contrib/ifenty/seaiceAdjointCode/seaice_readparms.F
ViewVC logotype

Annotation of /MITgcm_contrib/ifenty/seaiceAdjointCode/seaice_readparms.F

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


Revision 1.1 - (hide annotations) (download)
Fri Jun 29 18:54:03 2007 UTC (18 years ago) by gforget
Branch: MAIN
CVS Tags: HEAD
Ian Fenty sea-ice growth routines (adjointable, in developement)

1 gforget 1.1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_readparms.F,v 1.44 2007/04/22 19:56:22 mlosch Exp $
2     C $Name: $
3    
4     #include "SEAICE_OPTIONS.h"
5    
6     SUBROUTINE SEAICE_READPARMS( myThid )
7     C /==========================================================\
8     C | SUBROUTINE SEAICE_READPARMS |
9     C | o Routine to read in file data.seaice |
10     C \==========================================================/
11     IMPLICIT NONE
12    
13     C === Global variables ===
14     #include "SIZE.h"
15     #include "EEPARAMS.h"
16     #include "PARAMS.h"
17     #include "GRID.h"
18     #include "SEAICE_PARAMS.h"
19     #ifdef ALLOW_COST
20     # include "SEAICE_COST.h"
21     #endif
22     #ifdef ALLOW_MNC
23     # include "MNC_PARAMS.h"
24     #endif
25     #ifdef ALLOW_CAL
26     # include "cal.h"
27     #endif
28    
29     C === Routine arguments ===
30     C myThid - Number of this instance of SEAICE_READPARMS
31     INTEGER myThid
32    
33     C === Local variables ===
34     C msgBuf - Informational/error meesage buffer
35     C errIO - IO error flag
36     C iUnit - Work variable for IO unit number
37    
38     CHARACTER*(MAX_LEN_MBUF) msgBuf
39     INTEGER errIO, iUnit
40    
41     C-- SEAICE parameters
42     NAMELIST /SEAICE_PARM01/
43     & SEAICEwriteState, SEAICEuseDYNAMICS,
44     & SEAICEuseEVPpickup, SEAICEuseFluxForm,
45     & useHB87stressCoupling, SEAICEuseFlooding, SEAICEadvSnow,
46     & SEAICE_clipVelocities, SEAICE_maskRHS, SEAICE_no_slip,
47     & LAD, IMAX_TICE, SEAICEadvScheme, SEAICEadvSchArea,
48     & SEAICEadvSchHeff, SEAICEadvSchEnth, SEAICEadvSchSnow,
49     & SEAICE_deltaTtherm, SEAICE_deltaTdyn,
50     & SEAICE_deltaTevp, SEAICE_elasticParm,
51     & SEAICE_monFreq, SEAICE_dumpFreq, SEAICE_taveFreq,
52     & SEAICE_initialHEFF,
53     & SEAICE_rhoAir, SEAICE_rhoIce,
54     & SEAICE_drag, SEAICE_waterDrag, SEAICE_dryIceAlb,
55     & SEAICE_wetIceAlb, SEAICE_drySnowAlb, SEAICE_wetSnowAlb,
56     & SEAICE_waterAlbedo, SEAICE_strength, SEAICE_eccen,
57     & SEAICE_sensHeat, SEAICE_latentWater, SEAICE_latentIce,
58     & SEAICE_iceConduct, SEAICE_snowConduct, SEAICE_emissivity,
59     & SEAICE_snowThick, SEAICE_shortwave, SEAICE_freeze, OCEAN_drag,
60     & SEAICEstressFactor,
61     & uwindFile, vwindFile, atempFile, aqhFile, lwdownFile,
62     & swdownFile, precipFile, evapFile, runoffFile, HeffFile,
63     & LSR_ERROR, DIFF1, A22, HO,
64     & WindForcingStart, WindForcingEnd, WindForcingPeriod,
65     & FluxForcingStart, FluxForcingEnd, FluxForcingPeriod,
66     & SSTForcingStart, SSTForcingEnd, SSTForcingPeriod,
67     & SSSForcingStart, SSSForcingEnd, SSSForcingPeriod,
68     & StartingYear, EndingYear,
69     & SEAICE_airTurnAngle, SEAICE_waterTurnAngle,
70     & MAX_HEFF, MIN_ATEMP, MIN_LWDOWN, MAX_TICE, MIN_TICE,
71     & SEAICE_EPS, SEAICE_EPS_SQ,
72     & SEAICE_tave_mnc, SEAICE_dump_mnc, SEAICE_mon_mnc,
73     & SEAICE_gamma_t, SEAICE_debugPointX, SEAICE_debugPointY
74    
75     #ifdef ALLOW_COST
76     NAMELIST /SEAICE_PARM02/
77     & mult_ice, cost_ice_flag,
78     & costIceStart1, costIceStart2,
79     & costIceEnd1, costIceEnd2,
80     & cost_ice_flag,
81     & mult_smrarea, smrareadatfile, smrareabarfile,
82     & wsmrarea0, wmean_smrarea, smrarea_errfile,
83     & smrareastartdate1, smrareastartdate2, smrareaperiod
84     #endif
85    
86     _BEGIN_MASTER(myThid)
87    
88     WRITE(msgBuf,'(A)')
89     &' '
90     CALL PRINT_MESSAGE( msgBuf, standardmessageunit,
91     & SQUEEZE_RIGHT , myThid)
92     WRITE(msgBuf,'(A)') ' SEAICE_READPARMS: opening data.seaice'
93     CALL PRINT_MESSAGE( msgBuf, standardmessageunit,
94     & SQUEEZE_RIGHT , myThid)
95    
96     CALL OPEN_COPY_DATA_FILE(
97     I 'data.seaice', 'SEAICE_READPARMS',
98     O iUnit,
99     I myThid )
100    
101     C-- set default sea ice parameters
102     SEAICEwriteState = .FALSE.
103     #ifdef SEAICE_ALLOW_DYNAMICS
104     SEAICEuseDYNAMICS = .TRUE.
105     #else
106     SEAICEuseDYNAMICS = .FALSE.
107     #endif
108     SEAICEuseEVP = .FALSE.
109     SEAICEuseEVPpickup = .TRUE.
110     SEAICEuseFluxForm = .FALSE.
111     useHB87stressCoupling = .FALSE.
112     SEAICEadvSnow = .FALSE.
113     SEAICEuseFlooding = .FALSE.
114     SEAICE_no_slip = .FALSE.
115     SEAICE_clipVelocities = .TRUE.
116     SEAICE_maskRHS = .FALSE.
117     SEAICEadvScheme = 2
118     SEAICEadvSchArea = UNSET_I
119     SEAICEadvSchHeff = UNSET_I
120     SEAICEadvSchEnth = UNSET_I
121     SEAICEadvSchSnow = UNSET_I
122     SEAICE_deltaTtherm = dTtracerLev(1)
123     SEAICE_deltaTdyn = dTtracerLev(1)
124     SEAICE_deltaTevp = UNSET_RL
125     SEAICE_monFreq = monitorFreq
126     SEAICE_dumpFreq = dumpFreq
127     SEAICE_taveFreq = taveFreq
128     SEAICE_elasticParm = 0.33333333333333333333333333 _d 0
129     #ifdef ALLOW_MNC
130     SEAICE_tave_mnc = timeave_mnc
131     SEAICE_dump_mnc = snapshot_mnc
132     SEAICE_mon_mnc = monitor_mnc
133     #else
134     SEAICE_tave_mnc = .FALSE.
135     SEAICE_dump_mnc = .FALSE.
136     SEAICE_mon_mnc = .FALSE.
137     #endif
138     SEAICE_initialHEFF = ZERO
139     SEAICE_gamma_t = 3600.0*24.0*3.0
140     SEAICE_debugPointX = 1
141     SEAICE_debugPointY = 1
142     SEAICE_rhoAir = 1.3 _d 0
143     SEAICE_rhoIce = 0.91 _d +03
144     SEAICE_drag = 0.002 _d 0
145     OCEAN_drag = 0.001 _d 0
146     SEAICE_waterDrag = 5.5 _d 0
147     SEAICE_dryIceAlb = 0.75 _d 0
148     SEAICE_wetIceAlb = 0.66 _d 0
149     SEAICE_drySnowAlb = 0.84 _d 0
150     SEAICE_wetSnowAlb = 0.7 _d 0
151     SEAICE_waterAlbedo = 0.1 _d +00
152     SEAICE_strength = 2.75 _d +04
153     SEAICE_eccen = 2. _d 0
154     C SEAICE_sensHeat = 1.75 _d -03 * 1004 * 1.3
155     SEAICE_sensHeat = 2.284 _d +00
156     C SEAICE_latentWater = 1.75 _d -03 * 2.500 _d 06 * 1.3
157     SEAICE_latentWater = 5.6875 _d +03
158     C SEAICE_latentIce = 1.75 _d -03 * 2.834 _d 06 * 1.3
159     SEAICE_latentIce = 6.4474 _d +03
160     SEAICE_iceConduct = 2.1656 _d +00
161     SEAICE_snowConduct = 3.1 _d -01
162     SEAICE_emissivity = 5.5 _d -08
163     SEAICE_snowThick = 0.15 _d 0
164     SEAICE_shortwave = 0.30 _d 0
165     SEAICE_freeze = -1.96 _d 0
166     SEAICEstressFactor = 1. _d 0
167     uwindFile = ' '
168     vwindFile = ' '
169     atempFile = ' '
170     aqhFile = ' '
171     lwdownFile = ' '
172     swdownFile = ' '
173     precipFile = ' '
174     evapFile = ' '
175     runoffFile = ' '
176     HeffFile = ' '
177     LAD = 2
178     IMAX_TICE = 10
179     LSR_ERROR = 0.0001 _d 0
180     DIFF1 = .002 _d 0
181     DIFF1 = 2.0*DIFF1
182     A22 = 0.15 _d 0
183     HO = 0.5 _d 0
184     SEAICE_airTurnAngle = 0.0 _d 0
185     SEAICE_waterTurnAngle = 0.0 _d 0
186     WindForcingStart = -99999.
187     WindForcingEnd = -99999.
188     WindForcingPeriod = -99999.
189     FluxForcingStart = -99999.
190     FluxForcingEnd = -99999.
191     FluxForcingPeriod = -99999.
192     SSTForcingStart = -99999.
193     SSTForcingEnd = -99999.
194     SSTForcingPeriod = -99999.
195     SSSForcingStart = -99999.
196     SSSForcingEnd = -99999.
197     SSSForcingPeriod = -99999.
198     StartingYear = 1948.
199     EndingYear = 2000.
200     MAX_HEFF = 10. _d 0
201     MIN_ATEMP = -50. _d 0
202     MIN_LWDOWN = 60. _d 0
203     MAX_TICE = 30. _d 0
204     MIN_TICE = -50. _d 0
205     SEAICE_EPS = 1. _d -10
206     SEAICE_EPS_SQ = -99999.
207    
208     #ifdef ALLOW_COST
209     mult_ice = 0. _d 0
210     costIceStart1 = 0
211     costIceStart2 = 0
212     costIceEnd1 = 0
213     costIceEnd2 = 0
214     cost_ice_flag = 1
215     c
216     mult_smrarea = 0. _d 0
217     wsmrarea0 = 0.5 _d 0
218     wmean_smrarea = 0.5 _d 0
219     smrareabarfile = 'smrareabar'
220     smrareadatfile = ' '
221     smrarea_errfile = ' '
222     # ifdef ALLOW_CAL
223     smrareastartdate1 = startDate_1
224     smrareastartdate2 = startDate_2
225     # endif
226     #endif
227    
228     C-- Read settings from model parameter file "data.seaice".
229     READ(UNIT=iUnit,NML=SEAICE_PARM01,IOSTAT=errIO)
230     IF ( errIO .LT. 0 ) THEN
231     WRITE(msgBuf,'(A)')
232     & 'S/R SEAICE_READPARMS'
233     CALL PRINT_ERROR( msgBuf , myThid)
234     WRITE(msgBuf,'(A)')
235     & 'Error reading numerical model '
236     CALL PRINT_ERROR( msgBuf , myThid)
237     WRITE(msgBuf,'(A)')
238     & 'parameter file "data.seaice"'
239     CALL PRINT_ERROR( msgBuf , myThid)
240     WRITE(msgBuf,'(A)')
241     & 'Problem in namelist SEAICE_PARM01'
242     CALL PRINT_ERROR( msgBuf , myThid)
243     C CALL MODELDATA_EXAMPLE( myThid )
244     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
245     ENDIF
246    
247     #ifdef ALLOW_COST
248     READ(UNIT=iUnit,NML=SEAICE_PARM02,IOSTAT=errIO)
249     IF ( errIO .LT. 0 ) THEN
250     WRITE(msgBuf,'(A)')
251     & 'S/R SEAICE_READPARMS'
252     CALL PRINT_ERROR( msgBuf , myThid)
253     WRITE(msgBuf,'(A)')
254     & 'Error reading numerical model '
255     CALL PRINT_ERROR( msgBuf , myThid)
256     WRITE(msgBuf,'(A)')
257     & 'parameter file "data.seaice"'
258     CALL PRINT_ERROR( msgBuf , myThid)
259     WRITE(msgBuf,'(A)')
260     & 'Problem in namelist SEAICE_PARM02'
261     CALL PRINT_ERROR( msgBuf , myThid)
262     C CALL MODELDATA_EXAMPLE( myThid )
263     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
264     ENDIF
265     #endif
266    
267     CLOSE(iUnit)
268    
269     WRITE(msgBuf,'(A)')
270     & ' SEAICE_READPARMS: finished reading data.seaice'
271     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
272     & SQUEEZE_RIGHT , myThid)
273    
274     C Check that requested time step size is supported. The combination
275     C below is the only one that is supported at this time. Does not
276     C mean that something fancier will not work, just that it has not
277     C yet been tried nor thought through.
278     IF ( SEAICE_deltaTtherm .NE. dTtracerLev(1) .OR.
279     & SEAICE_deltaTdyn .LT. SEAICE_deltaTtherm .OR.
280     & (SEAICE_deltaTdyn/SEAICE_deltaTtherm) .NE.
281     & INT(SEAICE_deltaTdyn/SEAICE_deltaTtherm) ) THEN
282     WRITE(msgBuf,'(A)')
283     & 'Unsupported combination of SEAICE_deltaTtherm,'
284     CALL PRINT_ERROR( msgBuf , myThid)
285     WRITE(msgBuf,'(A)')
286     & ' SEAICE_deltaTdyn, and dTtracerLev(1)'
287     CALL PRINT_ERROR( msgBuf , myThid)
288     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
289     ENDIF
290     #ifdef SEAICE_ALLOW_EVP
291     SEAICEuseEVP = .FALSE.
292     IF ( SEAICE_deltaTevp .NE. UNSET_RL ) SEAICEuseEVP = .TRUE.
293     IF ( SEAICEuseEVP ) THEN
294     IF ( (SEAICE_deltaTdyn/SEAICE_deltaTevp) .NE.
295     & INT(SEAICE_deltaTdyn/SEAICE_deltaTevp) ) THEN
296     WRITE(msgBuf,'(A)')
297     & 'SEAICE_deltaTevp must be a factor of SEAICE_deltaTdyn.'
298     CALL PRINT_ERROR( msgBuf , myThid)
299     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
300     ENDIF
301     IF ( SEAICE_elasticParm .LE. 0. _d 0 .OR.
302     & SEAICE_elasticParm .GT. 1. _d 0 ) THEN
303     WRITE(msgBuf,'(A)')
304     & 'SEAICE_elasticParm must greater than 0 and less than 1.'
305     CALL PRINT_ERROR( msgBuf , myThid)
306     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
307     ENDIF
308     ENDIF
309     #endif /* SEAICE_ALLOW_EVP */
310    
311     C Set advection schemes to some sensible values if not done
312     C in data.seaice
313     IF ( SEAICEadvSchArea .EQ. UNSET_I )
314     & SEAICEadvSchArea = SEAICEadvScheme
315     IF ( SEAICEadvScheme .NE. SEAICEadvSchArea )
316     & SEAICEadvScheme = SEAICEadvSchArea
317     IF ( SEAICEadvSchHeff .EQ. UNSET_I )
318     & SEAICEadvSchHeff = SEAICEadvSchArea
319     IF ( SEAICEadvSchEnth .EQ. UNSET_I )
320     & SEAICEadvSchEnth = SEAICEadvSchArea
321     IF ( SEAICEadvSchSnow .EQ. UNSET_I )
322     & SEAICEadvSchSnow = SEAICEadvSchHeff
323    
324     #ifndef SEAICE_EXTERNAL_FORCING
325     IF ( FluxForcingStart .EQ. -99999. .OR.
326     & FluxForcingEnd .EQ. -99999. .OR.
327     & FluxForcingPeriod .EQ. -99999. ) THEN
328     WRITE(msgBuf,'(A)') 'Specify FluxForcing* in data.seaice'
329     CALL PRINT_ERROR( msgBuf , myThid)
330     STOP 'ABNORMAL END: S/R SEAICE_READPARMS'
331     ENDIF
332     IF ( WindForcingStart .EQ. -99999. )
333     & WindForcingStart = FluxForcingStart
334     IF ( WindForcingEnd .EQ. -99999. )
335     & WindForcingEnd = FluxForcingEnd
336     IF ( WindForcingPeriod .EQ. -99999. )
337     & WindForcingPeriod = FluxForcingPeriod
338     IF ( SSTForcingStart .EQ. -99999. )
339     & SSTForcingStart = FluxForcingStart
340     IF ( SSTForcingEnd .EQ. -99999. )
341     & SSTForcingEnd = FluxForcingEnd
342     IF ( SSTForcingPeriod .EQ. -99999. )
343     & SSTForcingPeriod = FluxForcingPeriod
344     IF ( SSSForcingStart .EQ. -99999. )
345     & SSSForcingStart = FluxForcingStart
346     IF ( SSSForcingEnd .EQ. -99999. )
347     & SSSForcingEnd = FluxForcingEnd
348     IF ( SSSForcingPeriod .EQ. -99999. )
349     & SSSForcingPeriod = FluxForcingPeriod
350     #endif /* SEAICE_EXTERNAL_FORCING */
351    
352     IF ( SEAICE_EPS_SQ .EQ. -99999. )
353     & SEAICE_EPS_SQ = SEAICE_EPS * SEAICE_EPS
354    
355     C- Set Output type flags :
356     SEAICE_tave_mdsio = .TRUE.
357     SEAICE_dump_mdsio = .TRUE.
358     SEAICE_mon_stdio = .TRUE.
359     #ifdef ALLOW_MNC
360     IF (useMNC) THEN
361     IF ( .NOT.outputTypesInclusive
362     & .AND. SEAICE_tave_mnc ) SEAICE_tave_mdsio = .FALSE.
363     IF ( .NOT.outputTypesInclusive
364     & .AND. SEAICE_dump_mnc ) SEAICE_dump_mdsio = .FALSE.
365     IF ( .NOT.outputTypesInclusive
366     & .AND. SEAICE_mon_mnc ) SEAICE_mon_stdio = .FALSE.
367     ENDIF
368     #endif
369    
370     _END_MASTER(myThid)
371    
372     C-- Everyone else must wait for the parameters to be loaded
373     _BARRIER
374    
375     C-- Summarise pkg/seaice cofiguration
376     CALL SEAICE_SUMMARY( myThid )
377    
378     C Initialize MNC variable information for SEAICE
379     IF ( useMNC .AND.
380     & (seaice_tave_mnc.OR.seaice_dump_mnc.OR.SEAICE_mon_mnc)
381     & ) THEN
382     CALL SEAICE_MNC_INIT( myThid )
383     ENDIF
384    
385     RETURN
386     END

  ViewVC Help
Powered by ViewVC 1.1.22