/[MITgcm]/MITgcm/pkg/streamice/streamice_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/streamice/streamice_readparms.F

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


Revision 1.6 - (show annotations) (download)
Thu Jul 10 15:09:40 2014 UTC (9 years, 10 months ago) by dgoldberg
Branch: MAIN
CVS Tags: checkpoint64z, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65
Changes since 1.5: +4 -5 lines
remove unused parameters

1 C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_readparms.F,v 1.5 2014/06/04 13:08:52 dgoldberg Exp $
2 C $Name: $
3
4
5 C this needs changes
6
7 #include "STREAMICE_OPTIONS.h"
8
9 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
10 CBOP 0
11 SUBROUTINE STREAMICE_READPARMS( myThid )
12
13 C !DESCRIPTION:
14 C Initialize STREAMICE variables and constants.
15
16 C !USES:
17 IMPLICIT NONE
18 #include "SIZE.h"
19 #include "EEPARAMS.h"
20 #include "PARAMS.h"
21 #include "STREAMICE.h"
22 #include "STREAMICE_BDRY.h"
23 #ifdef ALLOW_STREAMICE_FLUX_CONTROL
24 #include "STREAMICE_CTRL_FLUX.h"
25 #endif
26
27 C !INPUT PARAMETERS:
28 INTEGER myThid
29 CEOP
30
31 #ifdef ALLOW_STREAMICE
32
33 C !LOCAL VARIABLES:
34 C msgBuf :: Informational/error message buffer
35 C iUnit :: Work variable for IO unit number
36 CHARACTER*(MAX_LEN_MBUF) msgBuf
37 INTEGER iUnit, iarr, tarr
38
39 NAMELIST /STREAMICE_PARM01/
40 & streamice_density, streamice_density_ocean_avg,
41 & B_glen_isothermal, n_glen, eps_glen_min, eps_u_min,
42 & C_basal_fric_const, n_basal_friction,
43 & streamice_vel_update,streamice_cg_tol,streamice_nonlin_tol,
44 & streamice_nonlin_tol_fp,
45 & streamice_max_cg_iter, streamice_max_nl_iter,
46 & STREAMICEthickInit,
47 & STREAMICEsigcoordInit,
48 & STREAMICEsigcoordFile,
49 & STREAMICEthickFile,
50 & STREAMICEcalveMaskFile,
51 & STREAMICEcostMaskFile,
52 & STREAMICEison,
53 & STREAMICE_dump_mdsio, STREAMICE_tave_mdsio,
54 & STREAMICE_dump_mnc, STREAMICE_tave_mnc,
55 & STREAMICE_move_front,
56 & STREAMICE_calve_to_mask,
57 & STREAMICE_diagnostic_only,
58 & STREAMICE_lower_cg_tol,
59 & streamice_CFL_factor,
60 & streamice_adjDump,
61 & streamice_bg_surf_slope_x, streamice_bg_surf_slope_y,
62 & streamice_kx_b_init, streamice_ky_b_init,
63 & STREAMICEbasalTracConfig,
64 & STREAMICEBdotConfig,
65 & STREAMICEbasalTracFile,
66 & STREAMICEBdotFile,
67 & STREAMICEBdotTimeDepFile,
68 & STREAMICEvelOptimFile,
69 & STREAMICEtopogFile,
70 & STREAMICEhmaskFile,
71 & STREAMICEHBCyFile,
72 & STREAMICEHBCxFile,
73 & STREAMICEuFaceBdryFile,
74 & STREAMICEvFaceBdryFile,
75 & STREAMICEuDirichValsFile,
76 & STREAMICEvDirichValsFile,
77 & STREAMICEuMassFluxFile,
78 & STREAMICEvMassFluxFile,
79 & STREAMICEuNormalStressFile,
80 & STREAMICEvNormalStressFile,
81 & STREAMICEuShearStressFile,
82 & STREAMICEvShearStressFile,
83 & STREAMICEuNormalTimeDepFile,
84 & STREAMICEvNormalTimeDepFile,
85 & STREAMICEuShearTimeDepFile,
86 & STREAMICEvShearTimeDepFile,
87 & STREAMICEGlenConstFile, STREAMICEGlenConstConfig,
88 & STREAMICE_ppm_driving_stress,
89 & STREAMICE_h_ctrl_const_surf,
90 & streamice_wgt_drift,streamice_wgt_surf,streamice_wgt_vel,
91 & streamice_wgt_avthick, streamice_wgt_tikh,
92 & streamice_addl_backstress,
93 & streamice_smooth_gl_width,
94 & streamice_adot_uniform,
95 & STREAMICE_ADV_SCHEME, streamice_forcing_period
96
97 #ifdef ALLOW_STREAMICE_2DTRACER
98 NAMELIST /STREAMICE_PARMTRACER/
99 & STREAMICETrac2DBCxFile,
100 & STREAMICETrac2DBCyFile,
101 & STREAMICETrac2DINITFile
102 #endif
103
104 #ifdef ALLOW_PETSC
105 NAMELIST /STREAMICE_PARMPETSC/
106 & PETSC_PRECOND_TYPE, PETSC_SOLVER_TYPE
107 #endif
108
109 #ifdef ALLOW_STREAMICE_FLUX_CONTROL
110 NAMELIST /STREAMICE_PARMFLUXCTRL/
111 & n_fluxes, n_epochs,
112 & streamice_ctrl_flux_id,
113 & streamice_ctrl_flux_scaleVel
114 #endif
115
116
117 NAMELIST /STREAMICE_PARM02/
118 & shelf_max_draft,
119 & shelf_min_draft,
120 & shelf_edge_pos,
121 & shelf_slope_scale,
122 & shelf_flat_width,
123 & flow_dir
124
125 NAMELIST /STREAMICE_PARM03/
126 & min_x_noflow_NORTH, max_x_noflow_NORTH,
127 & min_x_noflow_SOUTH, max_x_noflow_SOUTH,
128 & min_y_noflow_WEST, max_y_noflow_WEST,
129 & min_y_noflow_EAST, max_y_noflow_EAST,
130 & min_x_noStress_NORTH, max_x_noStress_NORTH,
131 & min_x_noStress_SOUTH, max_x_noStress_SOUTH,
132 & min_y_noStress_WEST, max_y_noStress_WEST,
133 & min_y_noStress_EAST, max_y_noStress_EAST,
134 & min_x_FluxBdry_NORTH, max_x_FluxBdry_NORTH,
135 & min_x_FluxBdry_SOUTH, max_x_FluxBdry_SOUTH,
136 & min_y_FluxBdry_WEST, max_y_FluxBdry_WEST,
137 & min_y_FluxBdry_EAST, max_y_FluxBdry_EAST,
138 & min_x_Dirich_NORTH, max_x_Dirich_NORTH,
139 & min_x_Dirich_SOUTH, max_x_Dirich_SOUTH,
140 & min_y_Dirich_WEST, max_y_Dirich_WEST,
141 & min_y_Dirich_EAST, max_y_Dirich_EAST,
142 & min_x_CFBC_NORTH, max_x_CFBC_NORTH,
143 & min_x_CFBC_SOUTH, max_x_CFBC_SOUTH,
144 & min_y_CFBC_WEST, max_y_CFBC_WEST,
145 & min_y_CFBC_EAST, max_y_CFBC_EAST,
146 & flux_bdry_val_SOUTH, flux_bdry_val_NORTH,
147 & flux_bdry_val_WEST, flux_bdry_val_EAST,
148 & STREAMICE_NS_periodic, STREAMICE_EW_periodic
149
150 _BEGIN_MASTER(myThid)
151
152 C-- Default values for STREAMICE
153
154 streamice_density = 917.
155 streamice_density_ocean_avg = 1024.
156 B_glen_isothermal = 9.461e-18 ! Pa (-1/3) a
157 n_glen = 3.
158 eps_glen_min = 1.0e-12
159 eps_u_min = 1.0e-6
160 C_basal_fric_const = 31.71 ! Pa (m/a)-1n
161 n_basal_friction = 1.
162 streamice_vel_update = 169200. ! seconds
163 streamice_cg_tol = 1e-6
164 streamice_nonlin_tol = 1e-6
165 streamice_nonlin_tol_fp = 1.e-14
166 streamice_max_cg_iter = 2000
167 streamice_max_nl_iter = 100
168 ! streamice_n_sub_regularize = 4
169 streamice_CFL_factor = .5
170 streamice_adjDump = 0.
171 streamice_bg_surf_slope_x = .0
172 streamice_bg_surf_slope_y = 0.
173 streamice_kx_b_init = 1.
174 streamice_ky_b_init = 1.
175 streamice_wgt_drift = 0.
176 streamice_wgt_tikh = 0.
177 streamice_wgt_surf = 0.
178 streamice_wgt_vel = 0.
179 streamice_wgt_avthick = 0.
180 streamice_addl_backstress = 0.0
181 streamice_smooth_gl_width = 0.0
182 streamice_adot_uniform = 0.0
183 streamice_forcing_period = 0
184
185 STREAMICEthickInit = 'FILE'
186 STREAMICEthickFile = ' '
187 STREAMICEcalveMaskFile = ' '
188 STREAMICEsigcoordInit = 'UNIFORM'
189 STREAMICEsigcoordFile = ' '
190 STREAMICEbasalTracConfig = 'UNIFORM'
191 STREAMICEBdotConfig = ''
192 STREAMICEBdotFile = ''
193 STREAMICEBdotTimeDepFile = ' '
194 STREAMICEbasalTracFile = ' '
195 STREAMICEvelOptimFile = ''
196 STREAMICEtopogFile = ''
197 STREAMICEhmaskFile = ''
198 STREAMICEHBCyFile = ''
199 STREAMICEHBCxFile = ''
200 STREAMICEuNormalStressFile = ''
201 STREAMICEvNormalStressFile = ''
202 STREAMICEuShearStressFile = ''
203 STREAMICEvShearStressFile = ''
204 STREAMICEuNormalTimeDepFile = ' '
205 STREAMICEvNormalTimeDepFile = ' '
206 STREAMICEuShearTimeDepFile = ' '
207 STREAMICEvShearTimeDepFile = ' '
208
209 #ifdef ALLOW_STREAMICE_2DTRACER
210 STREAMICETrac2DBCxFile = ''
211 STREAMICETrac2DBCyFile = ''
212 STREAMICETrac2DInitFile = ''
213 #endif
214 STREAMICEuFaceBdryFile = ''
215 STREAMICEvFaceBdryFile = ''
216 STREAMICEuDirichValsFile = ''
217 STREAMICEvDirichValsFile = ''
218 STREAMICEuMassFluxFile = ''
219 STREAMICEvMassFluxFile = ''
220 STREAMICEGlenConstFile = ''
221 STREAMICEcostMaskFile = ''
222 STREAMICEGlenConstConfig = 'UNIFORM'
223 #ifdef ALLOW_PETSC
224 PETSC_PRECOND_TYPE = 'PCBJACOBI'
225 PETSC_SOLVER_TYPE = 'KSPCG'
226 #endif
227 STREAMICE_ADV_SCHEME = ''
228
229 #ifdef ALLOW_STREAMICE_FLUX_CONTROL
230 n_fluxes = 0
231 n_epochs = 0
232 DO iarr=1,n_fluxes_max
233 streamice_ctrl_flux_id(iarr) = 0
234 DO tarr=1,n_epochs_max
235 streamice_ctrl_flux_scaleVel(iarr,tarr) = 0. _d 0
236 ENDDO
237 ENDDO
238 #endif
239
240 STREAMICEison = .TRUE.
241 STREAMICE_tave_mdsio = .TRUE.
242 STREAMICE_dump_mdsio = .TRUE.
243 STREAMICE_dump_mnc = .FALSE.
244 STREAMICE_tave_mnc = .FALSE.
245 ! STREAMICE_GL_regularize = .FALSE.
246 STREAMICE_move_front = .FALSE.
247 STREAMICE_calve_to_mask = .FALSE.
248 ! STREAMICE_geom_file_setup = .FALSE.
249 ! STREAMICE_construct_matrix = .TRUE.
250 STREAMICE_lower_cg_tol = .FALSE.
251 STREAMICE_diagnostic_only = .FALSE.
252 STREAMICE_ppm_driving_stress = .FALSE.
253 STREAMICE_h_ctrl_const_surf = .FALSE.
254 ! STREAMICE_hybrid_stress= .FALSE.
255
256 min_x_noflow_NORTH = 0.
257 max_x_noflow_NORTH = 0.
258 min_x_noflow_SOUTH = 0.
259 max_x_noflow_SOUTH = 0.
260 min_y_noflow_WEST = 0.
261 max_y_noflow_WEST = 0.
262 min_y_noflow_EAST = 0.
263 max_y_noflow_EAST = 0.
264 min_x_noStress_NORTH = 0.
265 max_x_noStress_NORTH = 0.
266 min_x_noStress_SOUTH = 0.
267 max_x_noStress_SOUTH = 0.
268 min_y_noStress_WEST = 0.
269 max_y_noStress_WEST = 0.
270 min_y_noStress_EAST = 0.
271 max_y_noStress_EAST = 0.
272 min_x_FluxBdry_NORTH = 0.
273 max_x_FluxBdry_NORTH = 0.
274 min_x_FluxBdry_SOUTH = 0.
275 max_x_FluxBdry_SOUTH = 0.
276 min_y_FluxBdry_WEST = 0.
277 max_y_FluxBdry_WEST = 0.
278 min_y_FluxBdry_EAST = 0.
279 max_y_FluxBdry_EAST = 0.
280 min_x_Dirich_NORTH = 0.
281 max_x_Dirich_NORTH = 0.
282 min_x_Dirich_SOUTH = 0.
283 max_x_Dirich_SOUTH = 0.
284 min_y_Dirich_WEST = 0.
285 max_y_Dirich_WEST = 0.
286 min_y_Dirich_EAST = 0.
287 max_y_Dirich_EAST = 0.
288 min_y_CFBC_WEST = 0.
289 max_y_CFBC_WEST = 0.
290 min_y_CFBC_EAST = 0.
291 max_y_CFBC_EAST = 0.
292 flux_bdry_val_SOUTH = 0.
293 flux_bdry_val_NORTH = 0.
294 flux_bdry_val_WEST = 0.
295 flux_bdry_val_EAST = 0.
296
297 STREAMICE_NS_periodic = .FALSE.
298 STREAMICE_EW_periodic = .FALSE.
299
300 WRITE(msgBuf,'(A)') 'STREAMICE_READPARMS: opening data.streamice'
301 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
302 & SQUEEZE_RIGHT , 1)
303 CALL OPEN_COPY_DATA_FILE(
304 I 'data.streamice', 'STREAMICE_READPARMS',
305 O iUnit,
306 I myThid )
307
308 C Read parameters from open data file
309 READ(UNIT=iUnit,NML=STREAMICE_PARM01)
310 WRITE(msgBuf,'(A)')
311 & 'STREAMICE_READPARMS: read first param block'
312 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
313 & SQUEEZE_RIGHT , 1)
314
315 IF (TRIM(STREAMICEthickInit) .eq. "PARAM") THEN
316 READ(UNIT=iUnit,NML=STREAMICE_PARM02)
317 WRITE(msgBuf,'(A)')
318 & 'STREAMICE_READPARMS: read second param block'
319 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
320 & SQUEEZE_RIGHT , 1)
321 ENDIF
322
323 #ifdef ALLOW_STREAMICE_2DTRACER
324 READ(UNIT=iUnit,NML=STREAMICE_PARMTRACER)
325 WRITE(msgBuf,'(A)')
326 & 'STREAMICE_READPARMS: read tracer param block'
327 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
328 & SQUEEZE_RIGHT , 1)
329 #endif
330
331 #ifdef ALLOW_PETSC
332 READ(UNIT=iUnit,NML=STREAMICE_PARMPETSC)
333 WRITE(msgBuf,'(A)')
334 & 'STREAMICE_READPARMS: read petsc param block'
335 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
336 & SQUEEZE_RIGHT , 1)
337 #endif
338
339
340 READ(UNIT=iUnit,NML=STREAMICE_PARM03)
341 WRITE(msgBuf,'(A)')
342 & 'STREAMICE_READPARMS: read third param block'
343 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
344 & SQUEEZE_RIGHT , 1)
345 CLOSE(iUnit)
346
347
348 #ifdef ALLOW_STREAMICE_FLUX_CONTROL
349
350 CALL OPEN_COPY_DATA_FILE(
351 I 'data.strmctrlflux', 'STREAMICE_READPARMS',
352 O iUnit,
353 I myThid )
354
355
356 READ(UNIT=iUnit,NML=STREAMICE_PARMFLUXCTRL)
357 WRITE(msgBuf,'(A)')
358 & 'STREAMICE_READPARMS: read flux_ctrl param block'
359 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
360 & SQUEEZE_RIGHT , 1)
361 CLOSE(iUnit)
362 #endif
363
364
365
366 streamice_nstep_velocity = NINT (streamice_vel_update / deltaT)
367
368 C- Set Output type flags :
369
370 #ifdef ALLOW_MNC
371 IF (useMNC) THEN
372 IF ( .NOT.outputTypesInclusive
373 & .AND. STREAMICE_tave_mnc ) STREAMICE_tave_mdsio = .FALSE.
374 IF ( .NOT.outputTypesInclusive
375 & .AND. STREAMICE_dump_mnc ) STREAMICE_dump_mdsio = .FALSE.
376 ENDIF
377 #endif
378
379 _END_MASTER(myThid)
380
381 C-- Everyone else must wait for the parameters to be loaded
382 _BARRIER
383
384 #endif /* ALLOW_STREAMICE */
385
386 RETURN
387 END

  ViewVC Help
Powered by ViewVC 1.1.22