/[MITgcm]/MITgcm_contrib/dgoldberg/streamice/streamice_readparms.F
ViewVC logotype

Contents of /MITgcm_contrib/dgoldberg/streamice/streamice_readparms.F

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


Revision 1.7 - (show annotations) (download)
Thu Sep 27 20:29:00 2012 UTC (12 years, 9 months ago) by dgoldberg
Branch: MAIN
Changes since 1.6: +6 -2 lines
various changes

1 C $Header: /u/gcmpack/MITgcm_contrib/dgoldberg/streamice/streamice_readparms.F,v 1.6 2012/09/18 17:06:48 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
24 C !INPUT PARAMETERS:
25 INTEGER myThid
26 CEOP
27
28 #ifdef ALLOW_STREAMICE
29
30 C !LOCAL VARIABLES:
31 C msgBuf :: Informational/error message buffer
32 C iUnit :: Work variable for IO unit number
33 CHARACTER*(MAX_LEN_MBUF) msgBuf
34 INTEGER iUnit
35
36 NAMELIST /STREAMICE_PARM01/
37 & streamice_density, streamice_density_ocean_avg,
38 & A_glen_isothermal, n_glen, eps_glen_min,
39 & C_basal_fric_const, n_basal_friction,
40 & streamice_vel_update,streamice_cg_tol,streamice_nonlin_tol,
41 & streamice_nonlin_tol_fp,
42 & streamice_max_cg_iter, streamice_max_nl_iter,
43 & STREAMICE_GL_regularize,
44 & STREAMICEthickInit,
45 & STREAMICEsigcoordInit,
46 & STREAMICEsigcoordFile,
47 & STREAMICEthickFile,
48 & STREAMICEcalveMaskFile,
49 & STREAMICEison,
50 & STREAMICE_dump_mdsio, STREAMICE_tave_mdsio,
51 & STREAMICE_dump_mnc, STREAMICE_tave_mnc,
52 & STREAMICE_GL_regularize, STREAMICE_move_front,
53 & STREAMICE_calve_to_mask,
54 & STREAMICE_diagnostic_only,
55 ! & STREAMICE_construct_matrix,
56 & STREAMICE_lower_cg_tol,
57 & streamice_CFL_factor,
58 & streamice_adjDump,
59 ! & STREAMICE_hybrid_stress,
60 & streamice_bg_surf_slope_x, streamice_bg_surf_slope_y,
61 & streamice_kx_b_init, streamice_ky_b_init,
62 & STREAMICEbasalTracConfig,
63 & STREAMICEbasalTracFile,
64 & STREAMICEvelOptimFile,
65 & STREAMICE_ppm_driving_stress,
66 & STREAMICE_h_ctrl_const_surf
67
68
69 NAMELIST /STREAMICE_PARM02/
70 & shelf_max_draft,
71 & shelf_min_draft,
72 & shelf_edge_pos,
73 & shelf_slope_scale,
74 & shelf_flat_width,
75 & flow_dir
76
77 NAMELIST /STREAMICE_PARM03/
78 & min_x_noflow_NORTH, max_x_noflow_NORTH,
79 & min_x_noflow_SOUTH, max_x_noflow_SOUTH,
80 & min_y_noflow_WEST, max_y_noflow_WEST,
81 & min_y_noflow_EAST, max_y_noflow_EAST,
82 & min_x_noStress_NORTH, max_x_noStress_NORTH,
83 & min_x_noStress_SOUTH, max_x_noStress_SOUTH,
84 & min_y_noStress_WEST, max_y_noStress_WEST,
85 & min_y_noStress_EAST, max_y_noStress_EAST,
86 & min_x_FluxBdry_NORTH, max_x_FluxBdry_NORTH,
87 & min_x_FluxBdry_SOUTH, max_x_FluxBdry_SOUTH,
88 & min_y_FluxBdry_WEST, max_y_FluxBdry_WEST,
89 & min_y_FluxBdry_EAST, max_y_FluxBdry_EAST,
90 & min_x_Dirich_NORTH, max_x_Dirich_NORTH,
91 & min_x_Dirich_SOUTH, max_x_Dirich_SOUTH,
92 & min_y_Dirich_WEST, max_y_Dirich_WEST,
93 & min_y_Dirich_EAST, max_y_Dirich_EAST,
94 & min_x_CFBC_NORTH, max_x_CFBC_NORTH,
95 & min_x_CFBC_SOUTH, max_x_CFBC_SOUTH,
96 & min_y_CFBC_WEST, max_y_CFBC_WEST,
97 & min_y_CFBC_EAST, max_y_CFBC_EAST,
98 & flux_bdry_val_SOUTH, flux_bdry_val_NORTH,
99 & flux_bdry_val_WEST, flux_bdry_val_EAST,
100 & STREAMICE_NS_periodic, STREAMICE_EW_periodic
101
102 _BEGIN_MASTER(myThid)
103
104 C-- Default values for STREAMICE
105
106 streamice_density = 917.
107 streamice_density_ocean_avg = 1024.
108 A_glen_isothermal = 9.461e-18 ! Pa (-1/3) a
109 n_glen = 3.
110 eps_glen_min = 1.0e-12
111 C_basal_fric_const = 31.71 ! Pa (m/a)-1n
112 n_basal_friction = 1.
113 streamice_vel_update = 169200. ! seconds
114 streamice_cg_tol = 1e-6
115 streamice_nonlin_tol = 1e-6
116 streamice_nonlin_tol_fp = 1.e-14
117 streamice_max_cg_iter = 2000
118 streamice_max_nl_iter = 100
119 streamice_n_sub_regularize = 4
120 streamice_CFL_factor = .5
121 streamice_adjDump = 0.
122 streamice_bg_surf_slope_x = .0
123 streamice_bg_surf_slope_y = 0.
124 streamice_kx_b_init = 1.
125 streamice_ky_b_init = 1.
126
127 STREAMICEthickInit = 'FILE'
128 STREAMICEthickFile = ' '
129 STREAMICEcalveMaskFile = ' '
130 STREAMICEsigcoordInit = 'UNIFORM'
131 STREAMICEsigcoordFile = ' '
132 STREAMICEbasalTracConfig = 'UNIFORM'
133 STREAMICEbasalTracFile = ' '
134 STREAMICEvelOptimFile = ''
135
136 STREAMICEison = .TRUE.
137 STREAMICE_tave_mdsio = .TRUE.
138 STREAMICE_dump_mdsio = .TRUE.
139 STREAMICE_dump_mnc = .FALSE.
140 STREAMICE_tave_mnc = .FALSE.
141 STREAMICE_GL_regularize = .FALSE.
142 STREAMICE_move_front = .FALSE.
143 STREAMICE_calve_to_mask = .FALSE.
144 ! STREAMICE_construct_matrix = .TRUE.
145 STREAMICE_lower_cg_tol = .FALSE.
146 STREAMICE_diagnostic_only = .FALSE.
147 STREAMICE_ppm_driving_stress = .FALSE.
148 STREAMICE_h_ctrl_const_surf = .FALSE.
149 ! STREAMICE_hybrid_stress= .FALSE.
150
151 min_x_noflow_NORTH = 0.
152 max_x_noflow_NORTH = 0.
153 min_x_noflow_SOUTH = 0.
154 max_x_noflow_SOUTH = 0.
155 min_y_noflow_WEST = 0.
156 max_y_noflow_WEST = 0.
157 min_y_noflow_EAST = 0.
158 max_y_noflow_EAST = 0.
159 min_x_noStress_NORTH = 0.
160 max_x_noStress_NORTH = 0.
161 min_x_noStress_SOUTH = 0.
162 max_x_noStress_SOUTH = 0.
163 min_y_noStress_WEST = 0.
164 max_y_noStress_WEST = 0.
165 min_y_noStress_EAST = 0.
166 max_y_noStress_EAST = 0.
167 min_x_FluxBdry_NORTH = 0.
168 max_x_FluxBdry_NORTH = 0.
169 min_x_FluxBdry_SOUTH = 0.
170 max_x_FluxBdry_SOUTH = 0.
171 min_y_FluxBdry_WEST = 0.
172 max_y_FluxBdry_WEST = 0.
173 min_y_FluxBdry_EAST = 0.
174 max_y_FluxBdry_EAST = 0.
175 min_x_Dirich_NORTH = 0.
176 max_x_Dirich_NORTH = 0.
177 min_x_Dirich_SOUTH = 0.
178 max_x_Dirich_SOUTH = 0.
179 min_y_Dirich_WEST = 0.
180 max_y_Dirich_WEST = 0.
181 min_y_Dirich_EAST = 0.
182 max_y_Dirich_EAST = 0.
183 min_y_CFBC_WEST = 0.
184 max_y_CFBC_WEST = 0.
185 min_y_CFBC_EAST = 0.
186 max_y_CFBC_EAST = 0.
187 flux_bdry_val_SOUTH = 0.
188 flux_bdry_val_NORTH = 0.
189 flux_bdry_val_WEST = 0.
190 flux_bdry_val_EAST = 0.
191
192 STREAMICE_NS_periodic = .FALSE.
193 STREAMICE_EW_periodic = .FALSE.
194
195 WRITE(msgBuf,'(A)') 'STREAMICE_READPARMS: opening data.streamice'
196 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
197 & SQUEEZE_RIGHT , 1)
198 CALL OPEN_COPY_DATA_FILE(
199 I 'data.streamice', 'STREAMICE_READPARMS',
200 O iUnit,
201 I myThid )
202
203 C Read parameters from open data file
204 READ(UNIT=iUnit,NML=STREAMICE_PARM01)
205 WRITE(msgBuf,'(A)')
206 & 'STREAMICE_READPARMS: read first param block'
207 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
208 & SQUEEZE_RIGHT , 1)
209
210 IF (TRIM(STREAMICEthickInit) .eq. "PARAM") THEN
211 READ(UNIT=iUnit,NML=STREAMICE_PARM02)
212 WRITE(msgBuf,'(A)')
213 & 'STREAMICE_READPARMS: read second param block'
214 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
215 & SQUEEZE_RIGHT , 1)
216 ENDIF
217
218 READ(UNIT=iUnit,NML=STREAMICE_PARM03)
219 WRITE(msgBuf,'(A)')
220 & 'STREAMICE_READPARMS: read third param block'
221 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
222 & SQUEEZE_RIGHT , 1)
223 C Close the open data file
224 CLOSE(iUnit)
225
226 streamice_nstep_velocity = NINT (streamice_vel_update / deltaT)
227
228 C- Set Output type flags :
229
230 #ifdef ALLOW_MNC
231 IF (useMNC) THEN
232 IF ( .NOT.outputTypesInclusive
233 & .AND. STREAMICE_tave_mnc ) STREAMICE_tave_mdsio = .FALSE.
234 IF ( .NOT.outputTypesInclusive
235 & .AND. STREAMICE_dump_mnc ) STREAMICE_dump_mdsio = .FALSE.
236 ENDIF
237 #endif
238
239 _END_MASTER(myThid)
240
241 C-- Everyone else must wait for the parameters to be loaded
242 _BARRIER
243
244 #endif /* ALLOW_STREAMICE */
245
246 RETURN
247 END

  ViewVC Help
Powered by ViewVC 1.1.22