/[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.5 - (show annotations) (download)
Wed Jun 4 13:08:52 2014 UTC (10 years ago) by dgoldberg
Branch: MAIN
CVS Tags: checkpoint64y
Changes since 1.4: +31 -25 lines
changes for time dependent forcing

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

  ViewVC Help
Powered by ViewVC 1.1.22