/[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.18 - (show annotations) (download)
Wed Aug 9 15:23:36 2017 UTC (6 years, 8 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, HEAD
Changes since 1.17: +10 -2 lines
replace CLOSE(nmlfileUnit) with CLOSE(nmlfileUnit,STATUS='DELETE') to remove
scratchfiles after closing, except for SINGLE_DISK_IO, when everything
stays the same

1 C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_readparms.F,v 1.17 2016/11/29 14:22:20 dgoldberg Exp $
2 C $Name: BASE $
3
4 C this needs changes
5
6 #include "STREAMICE_OPTIONS.h"
7
8 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
9 CBOP 0
10 SUBROUTINE STREAMICE_READPARMS( myThid )
11
12 C !DESCRIPTION:
13 C Initialize STREAMICE variables and constants.
14
15 C !USES:
16 IMPLICIT NONE
17 #include "SIZE.h"
18 #include "EEPARAMS.h"
19 #include "PARAMS.h"
20 #include "STREAMICE.h"
21 #include "STREAMICE_BDRY.h"
22 !#ifdef ALLOW_STREAMICE_FLUX_CONTROL
23 !#include "STREAMICE_CTRL_FLUX.h"
24 !#endif
25
26 C !INPUT PARAMETERS:
27 INTEGER myThid
28 CEOP
29
30 #ifdef ALLOW_STREAMICE
31
32 C !LOCAL VARIABLES:
33 C msgBuf :: Informational/error message buffer
34 C iUnit :: Work variable for IO unit number
35 CHARACTER*(MAX_LEN_MBUF) msgBuf
36 INTEGER iUnit, iarr, tarr
37
38 NAMELIST /STREAMICE_PARM01/
39 & streamice_density, streamice_density_ocean_avg,
40 & streamice_density_firn,
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, streamice_err_norm,
45 & streamice_max_cg_iter, streamice_max_nl_iter,
46 & streamice_maxcgiter_cpl, streamice_maxnliter_cpl,
47 & STREAMICEthickInit,
48 & STREAMICEsigcoordInit,
49 & STREAMICEsigcoordFile,
50 & STREAMICEthickFile,
51 & STREAMICEcalveMaskFile,
52 & STREAMICEcostMaskFile,
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 & STREAMICEuFluxTimeDepFile, STREAMICEvFluxTimeDepFile,
88 & STREAMICEGlenConstFile, STREAMICEGlenConstConfig,
89 & STREAMICE_ppm_driving_stress,
90 & STREAMICE_h_ctrl_const_surf,
91 & streamice_wgt_drift,streamice_wgt_surf,streamice_wgt_vel,
92 & streamice_wgt_avthick, streamice_wgt_tikh,
93 & streamice_addl_backstress,
94 & streamice_smooth_gl_width,
95 & streamice_adot_uniform,
96 & streamice_firn_correction,
97 & STREAMICE_apply_firn_correction,
98 & STREAMICE_ADV_SCHEME, streamice_forcing_period,
99 & STREAMICE_chkfixedptconvergence,
100 & STREAMICE_chkresidconvergence,
101 & STREAMICE_alt_driving_stress,
102 #ifdef STREAMICE_FLOWLINE_BUTTRESS
103 & streamice_buttr_width,
104 & useStreamiceFlowlineButtr,
105 #endif
106 & STREAMICE_allow_cpl
107 #ifdef ALLOW_OPENAD
108 & ,streamice_smooth_thick_adjoint
109 #endif
110
111 #ifdef ALLOW_STREAMICE_2DTRACER
112 NAMELIST /STREAMICE_PARMTRACER/
113 & STREAMICETrac2DBCxFile,
114 & STREAMICETrac2DBCyFile,
115 & STREAMICETrac2DINITFile
116 #endif
117
118 #ifdef ALLOW_PETSC
119 NAMELIST /STREAMICE_PARMPETSC/
120 & PETSC_PRECOND_TYPE, PETSC_SOLVER_TYPE,
121 & streamice_use_petsc
122 #endif
123
124 #if (defined (ALLOW_OPENAD) && defined (ALLOW_STREAMICE_OAD_FP))
125 NAMELIST /STREAMICE_PARMOAD/
126 & streamice_nonlin_tol_adjoint
127 #ifdef ALLOW_PETSC
128 & ,STREAMICE_OAD_petsc_reuse,
129 & PETSC_PRECOND_OAD
130 #endif
131 #endif
132
133 !#ifdef ALLOW_STREAMICE_FLUX_CONTROL
134 ! NAMELIST /STREAMICE_PARMFLUXCTRL/
135 ! & n_fluxes, n_epochs,
136 ! & streamice_ctrl_flux_id,
137 ! & streamice_ctrl_flux_scaleVel
138 !#endif
139
140 NAMELIST /STREAMICE_PARM02/
141 & shelf_max_draft,
142 & shelf_min_draft,
143 & shelf_edge_pos,
144 & shelf_slope_scale,
145 & shelf_flat_width,
146 & flow_dir
147
148 NAMELIST /STREAMICE_PARM03/
149 & min_x_noflow_NORTH, max_x_noflow_NORTH,
150 & min_x_noflow_SOUTH, max_x_noflow_SOUTH,
151 & min_y_noflow_WEST, max_y_noflow_WEST,
152 & min_y_noflow_EAST, max_y_noflow_EAST,
153 & min_x_noStress_NORTH, max_x_noStress_NORTH,
154 & min_x_noStress_SOUTH, max_x_noStress_SOUTH,
155 & min_y_noStress_WEST, max_y_noStress_WEST,
156 & min_y_noStress_EAST, max_y_noStress_EAST,
157 & min_x_FluxBdry_NORTH, max_x_FluxBdry_NORTH,
158 & min_x_FluxBdry_SOUTH, max_x_FluxBdry_SOUTH,
159 & min_y_FluxBdry_WEST, max_y_FluxBdry_WEST,
160 & min_y_FluxBdry_EAST, max_y_FluxBdry_EAST,
161 & min_x_Dirich_NORTH, max_x_Dirich_NORTH,
162 & min_x_Dirich_SOUTH, max_x_Dirich_SOUTH,
163 & min_y_Dirich_WEST, max_y_Dirich_WEST,
164 & min_y_Dirich_EAST, max_y_Dirich_EAST,
165 & min_x_CFBC_NORTH, max_x_CFBC_NORTH,
166 & min_x_CFBC_SOUTH, max_x_CFBC_SOUTH,
167 & min_y_CFBC_WEST, max_y_CFBC_WEST,
168 & min_y_CFBC_EAST, max_y_CFBC_EAST,
169 & flux_bdry_val_SOUTH, flux_bdry_val_NORTH,
170 & flux_bdry_val_WEST, flux_bdry_val_EAST,
171 & STREAMICE_NS_periodic, STREAMICE_EW_periodic
172
173 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
174
175 IF ( .NOT.useStreamIce ) THEN
176 C- pkg STREAMICE is not used
177 _BEGIN_MASTER(myThid)
178 C- Track pkg activation status:
179 STREAMICEisOn = .FALSE.
180 C print a (weak) warning if data.streamice is found
181 CALL PACKAGES_UNUSED_MSG( 'useStreamIce', ' ', ' ' )
182 _END_MASTER(myThid)
183 RETURN
184 ENDIF
185
186 _BEGIN_MASTER(myThid)
187
188 C This routine has been called by the main model so we set our
189 C internal flag to indicate we are in business
190 STREAMICEisOn = .TRUE.
191
192 C-- Default values for STREAMICE
193
194 streamice_density = 917.
195 streamice_density_ocean_avg = 1024.
196 streamice_density_firn = streamice_density
197 B_glen_isothermal = 9.461e-18 ! Pa (-1/3) a
198 n_glen = 3.
199 eps_glen_min = 1.0e-12
200 eps_u_min = 1.0e-6
201 C_basal_fric_const = 31.71 ! Pa (m/a)-1n
202 n_basal_friction = 1.
203 streamice_vel_update = deltaT ! seconds
204 streamice_cg_tol = 1e-6
205 streamice_nonlin_tol = 1e-6
206 streamice_nonlin_tol_fp = 1.e-14
207 streamice_err_norm = 0.
208 #if (defined (ALLOW_OPENAD) && defined (ALLOW_STREAMICE_OAD_FP))
209 streamice_nonlin_tol_adjoint = 1.e-14
210 #ifdef ALLOW_PETSC
211 PETSC_PRECOND_OAD = 'MUMPS'
212 STREAMICE_OAD_petsc_reuse =.false.
213 #endif
214 #endif
215 streamice_max_cg_iter = 2000
216 streamice_max_nl_iter = 100
217 streamice_maxcgiter_cpl = 0
218 streamice_maxnliter_cpl = 0
219 #ifdef ALLOW_OPENAD
220 streamice_smooth_thick_adjoint = 0
221 #endif
222 ! streamice_n_sub_regularize = 4
223 streamice_CFL_factor = .5
224 streamice_adjDump = 0.
225 streamice_bg_surf_slope_x = .0
226 streamice_bg_surf_slope_y = 0.
227 streamice_kx_b_init = 1.
228 streamice_ky_b_init = 1.
229 streamice_wgt_drift = 0.
230 streamice_wgt_tikh = 0.
231 streamice_wgt_surf = 0.
232 streamice_wgt_vel = 0.
233 streamice_wgt_avthick = 0.
234 streamice_addl_backstress = 0.0
235 streamice_smooth_gl_width = 0.0
236 streamice_adot_uniform = 0.0
237 streamice_forcing_period = 0
238 streamice_firn_correction = 0.
239 #ifdef STREAMICE_FLOWLINE_BUTTRESS
240 streamice_buttr_width = 1000000000.
241 #endif
242 STREAMICE_apply_firn_correction = .false.
243
244 STREAMICEthickInit = 'FILE'
245 STREAMICEthickFile = ' '
246 STREAMICEcalveMaskFile = ' '
247 STREAMICEsigcoordInit = 'UNIFORM'
248 STREAMICEsigcoordFile = ' '
249 STREAMICEbasalTracConfig = 'UNIFORM'
250 STREAMICEBdotConfig = ''
251 STREAMICEBdotFile = ''
252 STREAMICEBdotTimeDepFile = ' '
253 STREAMICEbasalTracFile = ' '
254 STREAMICEvelOptimFile = ''
255 STREAMICEtopogFile = ''
256 STREAMICEhmaskFile = ''
257 STREAMICEHBCyFile = ''
258 STREAMICEHBCxFile = ''
259 STREAMICEuNormalStressFile = ''
260 STREAMICEvNormalStressFile = ''
261 STREAMICEuShearStressFile = ''
262 STREAMICEvShearStressFile = ''
263 STREAMICEuNormalTimeDepFile = ' '
264 STREAMICEvNormalTimeDepFile = ' '
265 STREAMICEuShearTimeDepFile = ' '
266 STREAMICEvShearTimeDepFile = ' '
267 STREAMICEuFluxTimeDepFile = ' '
268 STREAMICEvFluxTimeDepFile = ' '
269
270 #ifdef ALLOW_STREAMICE_2DTRACER
271 STREAMICETrac2DBCxFile = ''
272 STREAMICETrac2DBCyFile = ''
273 STREAMICETrac2DInitFile = ''
274 #endif
275 STREAMICEuFaceBdryFile = ''
276 STREAMICEvFaceBdryFile = ''
277 STREAMICEuDirichValsFile = ''
278 STREAMICEvDirichValsFile = ''
279 STREAMICEuMassFluxFile = ''
280 STREAMICEvMassFluxFile = ''
281 STREAMICEGlenConstFile = ''
282 STREAMICEcostMaskFile = ''
283 STREAMICEGlenConstConfig = 'UNIFORM'
284 #ifdef ALLOW_PETSC
285 PETSC_PRECOND_TYPE = 'PCBJACOBI'
286 PETSC_SOLVER_TYPE = 'KSPCG'
287 streamice_use_petsc = .true.
288 #endif
289 STREAMICE_ADV_SCHEME = ''
290
291 !#ifdef ALLOW_STREAMICE_FLUX_CONTROL
292 ! n_fluxes = 0
293 ! n_epochs = 0
294 ! DO iarr=1,n_fluxes_max
295 ! streamice_ctrl_flux_id(iarr) = 0
296 ! DO tarr=1,n_epochs_max
297 ! streamice_ctrl_flux_scaleVel(iarr,tarr) = 0. _d 0
298 ! ENDDO
299 ! ENDDO
300 !#endif
301
302 STREAMICE_tave_mdsio = .TRUE.
303 STREAMICE_dump_mdsio = .TRUE.
304 STREAMICE_dump_mnc = .FALSE.
305 STREAMICE_tave_mnc = .FALSE.
306 ! STREAMICE_GL_regularize = .FALSE.
307 STREAMICE_move_front = .FALSE.
308 STREAMICE_calve_to_mask = .FALSE.
309 ! STREAMICE_geom_file_setup = .FALSE.
310 ! STREAMICE_construct_matrix = .TRUE.
311 STREAMICE_lower_cg_tol = .FALSE.
312 STREAMICE_diagnostic_only = .FALSE.
313 #ifdef STREAMICE_FLOWLINE_BUTTRESS
314 useStreamiceFlowlineButtr=.FALSE.
315 #endif
316 STREAMICE_ppm_driving_stress = .FALSE.
317 STREAMICE_chkfixedptconvergence = .true.
318 STREAMICE_chkresidconvergence = .true.
319 STREAMICE_alt_driving_stress = .FALSE.
320 STREAMICE_h_ctrl_const_surf = .FALSE.
321 STREAMICE_allow_cpl = .false.
322 ! STREAMICE_hybrid_stress= .FALSE.
323
324 min_x_noflow_NORTH = 0.
325 max_x_noflow_NORTH = 0.
326 min_x_noflow_SOUTH = 0.
327 max_x_noflow_SOUTH = 0.
328 min_y_noflow_WEST = 0.
329 max_y_noflow_WEST = 0.
330 min_y_noflow_EAST = 0.
331 max_y_noflow_EAST = 0.
332 min_x_noStress_NORTH = 0.
333 max_x_noStress_NORTH = 0.
334 min_x_noStress_SOUTH = 0.
335 max_x_noStress_SOUTH = 0.
336 min_y_noStress_WEST = 0.
337 max_y_noStress_WEST = 0.
338 min_y_noStress_EAST = 0.
339 max_y_noStress_EAST = 0.
340 min_x_FluxBdry_NORTH = 0.
341 max_x_FluxBdry_NORTH = 0.
342 min_x_FluxBdry_SOUTH = 0.
343 max_x_FluxBdry_SOUTH = 0.
344 min_y_FluxBdry_WEST = 0.
345 max_y_FluxBdry_WEST = 0.
346 min_y_FluxBdry_EAST = 0.
347 max_y_FluxBdry_EAST = 0.
348 min_x_Dirich_NORTH = 0.
349 max_x_Dirich_NORTH = 0.
350 min_x_Dirich_SOUTH = 0.
351 max_x_Dirich_SOUTH = 0.
352 min_y_Dirich_WEST = 0.
353 max_y_Dirich_WEST = 0.
354 min_y_Dirich_EAST = 0.
355 max_y_Dirich_EAST = 0.
356 min_y_CFBC_WEST = 0.
357 max_y_CFBC_WEST = 0.
358 min_y_CFBC_EAST = 0.
359 max_y_CFBC_EAST = 0.
360 flux_bdry_val_SOUTH = 0.
361 flux_bdry_val_NORTH = 0.
362 flux_bdry_val_WEST = 0.
363 flux_bdry_val_EAST = 0.
364
365 STREAMICE_NS_periodic = .FALSE.
366 STREAMICE_EW_periodic = .FALSE.
367
368 WRITE(msgBuf,'(A)') 'STREAMICE_READPARMS: opening data.streamice'
369 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
370 & SQUEEZE_RIGHT , 1)
371 CALL OPEN_COPY_DATA_FILE(
372 I 'data.streamice', 'STREAMICE_READPARMS',
373 O iUnit,
374 I myThid )
375
376 C Read parameters from open data file
377 READ(UNIT=iUnit,NML=STREAMICE_PARM01)
378 WRITE(msgBuf,'(A)')
379 & 'STREAMICE_READPARMS: read first param block'
380 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
381 & SQUEEZE_RIGHT , 1)
382
383 IF (TRIM(STREAMICEthickInit) .eq. "PARAM") THEN
384 READ(UNIT=iUnit,NML=STREAMICE_PARM02)
385 WRITE(msgBuf,'(A)')
386 & 'STREAMICE_READPARMS: read second param block'
387 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
388 & SQUEEZE_RIGHT , 1)
389 ENDIF
390
391 #ifdef ALLOW_STREAMICE_2DTRACER
392 READ(UNIT=iUnit,NML=STREAMICE_PARMTRACER)
393 WRITE(msgBuf,'(A)')
394 & 'STREAMICE_READPARMS: read tracer param block'
395 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
396 & SQUEEZE_RIGHT , 1)
397 #endif
398
399 #ifdef ALLOW_PETSC
400 READ(UNIT=iUnit,NML=STREAMICE_PARMPETSC)
401 WRITE(msgBuf,'(A)')
402 & 'STREAMICE_READPARMS: read petsc param block'
403 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
404 & SQUEEZE_RIGHT , 1)
405 #endif
406
407 #if (defined (ALLOW_OPENAD) && defined (ALLOW_STREAMICE_OAD_FP))
408 READ(UNIT=iUnit,NML=STREAMICE_PARMOAD)
409 WRITE(msgBuf,'(A)')
410 & 'STREAMICE_READPARMS: read oad parm block'
411 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
412 & SQUEEZE_RIGHT , 1)
413 #endif
414
415 READ(UNIT=iUnit,NML=STREAMICE_PARM03)
416 WRITE(msgBuf,'(A)')
417 & 'STREAMICE_READPARMS: read third param block'
418 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
419 & SQUEEZE_RIGHT , 1)
420 #ifdef SINGLE_DISK_IO
421 CLOSE(iUnit)
422 #else
423 CLOSE(iUnit,STATUS='DELETE')
424 #endif /* SINGLE_DISK_IO */
425
426 !#ifdef ALLOW_STREAMICE_FLUX_CONTROL
427 !
428 ! CALL OPEN_COPY_DATA_FILE(
429 ! I 'data.strmctrlflux', 'STREAMICE_READPARMS',
430 ! O iUnit,
431 ! I myThid )
432 !
433 ! READ(UNIT=iUnit,NML=STREAMICE_PARMFLUXCTRL)
434 ! WRITE(msgBuf,'(A)')
435 ! & 'STREAMICE_READPARMS: read flux_ctrl param block'
436 ! CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
437 ! & SQUEEZE_RIGHT , 1)
438 !#ifdef SINGLE_DISK_IO
439 ! CLOSE(iUnit)
440 !#else
441 ! CLOSE(iUnit,STATUS='DELETE')
442 !#endif /* SINGLE_DISK_IO */
443 !#endif
444
445 streamice_nstep_velocity = NINT (streamice_vel_update / deltaT)
446
447 C- Set Output type flags :
448
449 #ifdef ALLOW_MNC
450 IF (useMNC) THEN
451 IF ( .NOT.outputTypesInclusive
452 & .AND. STREAMICE_tave_mnc ) STREAMICE_tave_mdsio = .FALSE.
453 IF ( .NOT.outputTypesInclusive
454 & .AND. STREAMICE_dump_mnc ) STREAMICE_dump_mdsio = .FALSE.
455 ENDIF
456 #endif
457
458 _END_MASTER(myThid)
459
460 C-- Everyone else must wait for the parameters to be loaded
461 _BARRIER
462
463 #endif /* ALLOW_STREAMICE */
464
465 RETURN
466 END

  ViewVC Help
Powered by ViewVC 1.1.22