/[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.7 - (show annotations) (download)
Fri Sep 5 14:25:11 2014 UTC (9 years, 8 months ago) by dgoldberg
Branch: MAIN
Changes since 1.6: +12 -3 lines
extensive changes to s/r's to (a) allow for coupling with shelfice and (b) modularize the convergence check in streamice_vel_solve

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

  ViewVC Help
Powered by ViewVC 1.1.22