1 | SUBROUTINE parin |
---|
2 | |
---|
3 | !------------------------------------------------------------------------------! |
---|
4 | ! Actual revisions: |
---|
5 | ! ----------------- |
---|
6 | ! |
---|
7 | ! |
---|
8 | ! Former revisions: |
---|
9 | ! ----------------- |
---|
10 | ! $Log: parin.f90,v $ |
---|
11 | ! Revision 1.57 2007/02/11 13:11:22 raasch |
---|
12 | ! Values of environment variables are now read from file ENVPAR instead of |
---|
13 | ! reading them with a system call, + NAMELIST envpar |
---|
14 | ! |
---|
15 | ! Revision 1.56 2006/08/22 14:13:56 raasch |
---|
16 | ! +dz_max in inipar |
---|
17 | ! |
---|
18 | ! Revision 1.55 2006/08/04 14:53:43 raasch |
---|
19 | ! +use_upstream_for_tke |
---|
20 | ! |
---|
21 | ! Revision 1.54 2006/03/17 08:45:44 raasch |
---|
22 | ! +skip_time_data_output_av |
---|
23 | ! |
---|
24 | ! Revision 1.53 2006/02/23 12:46:19 raasch |
---|
25 | ! parameters for 2d/3d averaging, |
---|
26 | ! +conserve_volume_flow, dissipation_1d, e_min, mixing_length_1d, topography, & |
---|
27 | ! wall_heatflux in inipar, |
---|
28 | ! +data_output, netcdf_64bit, skip_time_dosp, skip_time_dopr, etc. in d3par, |
---|
29 | ! allocation of nanz_2dh and nanz_3d moved to init_3d_model, ebene renamed |
---|
30 | ! section, average_period_pr1d removed, average_period_pl1d renamed |
---|
31 | ! averaging_interval_pr, dt_average renamed dt_averaging_input_pr, |
---|
32 | ! +parameters for single building topography settings |
---|
33 | ! |
---|
34 | ! Revision 1.52 2005/06/29 10:21:15 steinfeld |
---|
35 | ! +ug_surface, ug_vertical_gradient, ug_vertical_gradient_level, |
---|
36 | ! vg_surface, vg_vertical_gradient, vg_vertical_gradient_level in inipar; |
---|
37 | ! arrays ug and vg are allocated during initialization runs |
---|
38 | ! |
---|
39 | ! Revision 1.51 2005/06/26 20:06:26 raasch |
---|
40 | ! +cloud_droplets in inipar |
---|
41 | ! |
---|
42 | ! Revision 1.50 2005/05/18 15:40:49 raasch |
---|
43 | ! +netcdf_precision in inipar, +data_output_format in d3par |
---|
44 | ! |
---|
45 | ! Revision 1.49 2005/04/23 09:35:23 raasch |
---|
46 | ! fcl_factor renamed cfl_factor |
---|
47 | ! |
---|
48 | ! Revision 1.48 2005/03/26 20:42:17 raasch |
---|
49 | ! +bc_lr, bc_ns, call_psolver_at_all_substeps, inflow_disturbance_begin, & |
---|
50 | ! inflow_disturbance_end, km_damp_max, outflow_damping_width in inipar |
---|
51 | ! |
---|
52 | ! Revision 1.47 2004/04/30 12:32:06 raasch |
---|
53 | ! +grid_matching in inipar, impulse_advec renamed momentum_advec |
---|
54 | ! |
---|
55 | ! Revision 1.46 2003/10/29 09:03:06 raasch |
---|
56 | ! +mg_cycles, mg_switch_to_pe0_level in d3par |
---|
57 | ! |
---|
58 | ! Revision 1.45 2003/03/16 09:42:23 raasch |
---|
59 | ! Two underscores (_) are placed in front of all define-strings |
---|
60 | ! |
---|
61 | ! Revision 1.44 2003/03/14 13:45:24 raasch |
---|
62 | ! +random_generator in inipar |
---|
63 | ! |
---|
64 | ! Revision 1.43 2003/03/12 16:35:55 raasch |
---|
65 | ! Reading of environment variable tasks_per_node moved from poisfft_hybrid |
---|
66 | ! to here |
---|
67 | ! |
---|
68 | ! Revision 1.42 2002/12/19 15:55:31 raasch |
---|
69 | ! Saving preliminary process-id-string for opening unit 14 (binary output for |
---|
70 | ! restart). Array hom is allocated during first run only, allocation during |
---|
71 | ! restart runs will now be done in read_var_list. |
---|
72 | ! +dt_restart, restart_time in d3par, STOP statement replaced by call of |
---|
73 | ! subroutine local_stop |
---|
74 | ! |
---|
75 | ! Revision 1.41 2002/04/16 08:10:50 raasch |
---|
76 | ! +bc_s_b, bc_s_t, surface_scalarflux, s_surface, s_surface_initial_change, |
---|
77 | ! s_vertical_gradient, s_vertical_gradient_level in inipar |
---|
78 | ! |
---|
79 | ! Revision 1.40 2001/08/21 09:54:27 raasch |
---|
80 | ! MPI_COMM_WORLD replaced by comm_palm, +wall_adjustment in inipar |
---|
81 | ! |
---|
82 | ! Revision 1.39 2001/07/20 13:10:07 raasch |
---|
83 | ! +cycle_mg, ngsrb, residual_limit in d3par |
---|
84 | ! |
---|
85 | ! Revision 1.38 2001/03/30 07:43:55 raasch |
---|
86 | ! Translation of remaining German identifiers (variables, subroutines, etc.), |
---|
87 | ! namelist d3par can also be omitted in the initial run |
---|
88 | ! |
---|
89 | ! Revision 1.37 2001/01/29 12:30:26 raasch |
---|
90 | ! +passive_scalar in inipar |
---|
91 | ! |
---|
92 | ! Revision 1.36 2001/01/25 07:17:39 raasch |
---|
93 | ! +fft_method, use_surface_fluxes in inipar |
---|
94 | ! |
---|
95 | ! Revision 1.35 2001/01/02 17:32:13 raasch |
---|
96 | ! Unit 11 closed at the end of the subroutine |
---|
97 | ! |
---|
98 | ! Revision 1.34 2000/12/28 13:24:51 raasch |
---|
99 | ! Call of package_parin. dt_dvrp and threshold moved |
---|
100 | ! from d3par to other namelists in subroutine package_parin |
---|
101 | ! |
---|
102 | ! Revision 1.33 2000/04/27 06:55:20 raasch |
---|
103 | ! +npex, npey in initial parameter list, comments have to be translated yet, |
---|
104 | ! -dt_plisos, dt_plpart, +dt_dvrp, threshold, in run-time parameter list, |
---|
105 | ! all comments translated into English, old revision remarks deleted |
---|
106 | ! |
---|
107 | ! Revision 1.32 2000/04/13 13:03:06 schroeter |
---|
108 | ! Erweitern der Parameterlist fuer Wolkenphysik |
---|
109 | ! |
---|
110 | ! Revision 1.31 2000/01/10 10:05:55 10:05:55 raasch (Siegfried Raasch) |
---|
111 | ! +use_ug_for_galilei_tr |
---|
112 | ! |
---|
113 | ! Revision 1.1 1997/07/24 11:22:50 raasch |
---|
114 | ! Initial revision |
---|
115 | ! |
---|
116 | ! |
---|
117 | ! Description: |
---|
118 | ! ------------ |
---|
119 | ! This subroutine reads variables controling the run from the NAMELIST files |
---|
120 | !------------------------------------------------------------------------------! |
---|
121 | |
---|
122 | USE arrays_3d |
---|
123 | USE averaging |
---|
124 | USE control_parameters |
---|
125 | USE grid_variables |
---|
126 | USE indices |
---|
127 | USE model_1d |
---|
128 | USE pegrid |
---|
129 | USE profil_parameter |
---|
130 | USE statistics |
---|
131 | |
---|
132 | IMPLICIT NONE |
---|
133 | |
---|
134 | INTEGER :: idum |
---|
135 | |
---|
136 | |
---|
137 | NAMELIST /inipar/ adjust_mixing_length, alpha_surface, bc_e_b, bc_lr, & |
---|
138 | bc_ns, bc_p_b, bc_p_t, bc_pt_b, bc_pt_t, bc_q_b, & |
---|
139 | bc_q_t,bc_s_b, bc_s_t, bc_uv_b, bc_uv_t, & |
---|
140 | building_height, building_length_x, building_length_y, & |
---|
141 | building_wall_left, building_wall_south, & |
---|
142 | cloud_droplets, cloud_physics, conserve_volume_flow, & |
---|
143 | cut_spline_overshoot, damp_level_1d, dissipation_1d, & |
---|
144 | dt, dt_pr_1d, dt_run_control_1d, dx, dy, dz, dz_max, & |
---|
145 | dz_stretch_factor, dz_stretch_level, e_min, & |
---|
146 | end_time_1d, fft_method, galilei_transformation, & |
---|
147 | grid_matching, inflow_disturbance_begin, & |
---|
148 | inflow_disturbance_end, initializing_actions, & |
---|
149 | km_constant, km_damp_max, long_filter_factor, & |
---|
150 | mixing_length_1d, moisture, momentum_advec, & |
---|
151 | netcdf_precision, npex, npey, nsor_ini, nx, ny, nz, & |
---|
152 | omega, outflow_damping_width, overshoot_limit_e, & |
---|
153 | overshoot_limit_pt, overshoot_limit_u, & |
---|
154 | overshoot_limit_v, overshoot_limit_w, passive_scalar, & |
---|
155 | phi, prandtl_layer, precipitation, pt_surface, & |
---|
156 | pt_surface_initial_change, pt_vertical_gradient, & |
---|
157 | pt_vertical_gradient_level, q_surface, & |
---|
158 | q_surface_initial_change, q_vertical_gradient, & |
---|
159 | q_vertical_gradient_level, radiation, random_generator, & |
---|
160 | random_heatflux, rif_max, rif_min, roughness_length, & |
---|
161 | scalar_advec, statistic_regions, surface_heatflux, & |
---|
162 | surface_pressure, surface_scalarflux, surface_waterflux,& |
---|
163 | s_surface, s_surface_initial_change, & |
---|
164 | s_vertical_gradient, s_vertical_gradient_level, & |
---|
165 | timestep_scheme, topography, ug_surface, & |
---|
166 | ug_vertical_gradient, ug_vertical_gradient_level, & |
---|
167 | ups_limit_e, ups_limit_pt, ups_limit_u, ups_limit_v, & |
---|
168 | ups_limit_w, use_surface_fluxes, use_ug_for_galilei_tr, & |
---|
169 | use_upstream_for_tke, vg_surface, vg_vertical_gradient, & |
---|
170 | vg_vertical_gradient_level, wall_adjustment, & |
---|
171 | wall_heatflux |
---|
172 | |
---|
173 | |
---|
174 | NAMELIST /d3par/ averaging_interval, averaging_interval_pr, & |
---|
175 | call_psolver_at_all_substeps, cfl_factor, & |
---|
176 | create_disturbances, cross_normalized_x, & |
---|
177 | cross_normalized_y, cross_profiles, cross_ts_uymax, & |
---|
178 | cross_ts_uymin, cross_xtext, cycle_mg, data_output, & |
---|
179 | data_output_format, data_output_pr, data_output_ts, & |
---|
180 | data_output_2d_on_each_pe, disturbance_amplitude, & |
---|
181 | disturbance_energy_limit, disturbance_level_b, & |
---|
182 | disturbance_level_t, do2d_at_begin, do3d_at_begin, & |
---|
183 | do3d_compress, do3d_comp_prec, dt, dt_averaging_input, & |
---|
184 | dt_averaging_input_pr, dt_data_output, & |
---|
185 | dt_data_output_av, dt_disturb, dt_dopr, & |
---|
186 | dt_dopr_listing, dt_dots, dt_do2d_xy, dt_do2d_xz, & |
---|
187 | dt_do2d_yz, dt_do3d, dt_restart, dt_run_control, & |
---|
188 | end_time, force_print_header, mg_cycles, & |
---|
189 | mg_switch_to_pe0_level, netcdf_64bit, ngsrb, & |
---|
190 | normalizing_region, nsor, nz_do3d, omega_sor, & |
---|
191 | prandtl_number, profile_columns, profile_rows, psolver, & |
---|
192 | rayleigh_damping_factor, rayleigh_damping_height, & |
---|
193 | residual_limit, restart_time, section_xy, section_xz, & |
---|
194 | section_yz, skip_time_data_output, & |
---|
195 | skip_time_data_output_av, skip_time_dopr, & |
---|
196 | skip_time_dosp, skip_time_do2d_xy, skip_time_do2d_xz, & |
---|
197 | skip_time_do2d_yz, skip_time_do3d, & |
---|
198 | termination_time_needed, use_prior_plot1d_parameters, & |
---|
199 | z_max_do1d, z_max_do1d_normalized, z_max_do2d |
---|
200 | |
---|
201 | |
---|
202 | NAMELIST /envpar/ host, maximum_cpu_time_allowed, run_identifier, & |
---|
203 | tasks_per_node, write_binary |
---|
204 | |
---|
205 | |
---|
206 | #if defined( __parallel ) |
---|
207 | ! |
---|
208 | !-- Preliminary determination of processor-id which is needed here to open the |
---|
209 | !-- input files belonging to the corresponding processor and to produce |
---|
210 | !-- messages by PE0 only (myid and myid_char are later determined in |
---|
211 | !-- init_pegrid) |
---|
212 | CALL MPI_COMM_RANK( comm_palm, myid, ierr ) |
---|
213 | WRITE (myid_char,'(''_'',I4.4)') myid |
---|
214 | ! |
---|
215 | !-- Since on IBM machines the process rank may be changed when the final |
---|
216 | !-- communicator is defined, save the preliminary processor-id for opening |
---|
217 | !-- the binary output file for restarts (unit 14), because otherwise |
---|
218 | !-- a mismatch occurs when reading this file in the next job |
---|
219 | myid_char_14 = myid_char |
---|
220 | #endif |
---|
221 | |
---|
222 | ! |
---|
223 | !-- Open the NAMELIST-file which is send with this job |
---|
224 | CALL check_open( 11 ) |
---|
225 | |
---|
226 | ! |
---|
227 | !-- Read the control parameters for initialization. |
---|
228 | !-- The namelist "inipar" must be provided in the NAMELIST-file. If this is |
---|
229 | !-- not the case and the file contains - instead of "inipar" - any other |
---|
230 | !-- namelist, a read error is created on t3e and control is transferred |
---|
231 | !-- to the statement with label 10. Therefore, on t3e machines one can not |
---|
232 | !-- distinguish between errors produced by a wrong "inipar" namelist or |
---|
233 | !-- because this namelist is totally missing. |
---|
234 | READ ( 11, inipar, ERR=10, END=11 ) |
---|
235 | GOTO 12 |
---|
236 | 10 IF ( myid == 0 ) THEN |
---|
237 | PRINT*, '+++ parin: errors in \$inipar' |
---|
238 | PRINT*, ' or no \$inipar-namelist found (CRAY-machines only)' |
---|
239 | ENDIF |
---|
240 | CALL local_stop |
---|
241 | 11 IF ( myid == 0 ) THEN |
---|
242 | PRINT*, '+++ parin: no \$inipar-namelist found' |
---|
243 | ENDIF |
---|
244 | CALL local_stop |
---|
245 | |
---|
246 | ! |
---|
247 | !-- If required, read control parameters from restart file (produced by |
---|
248 | !-- a prior run) |
---|
249 | 12 IF ( TRIM( initializing_actions ) == 'read_restart_data' ) THEN |
---|
250 | |
---|
251 | CALL read_var_list |
---|
252 | ! |
---|
253 | !-- Increment the run count |
---|
254 | runnr = runnr + 1 |
---|
255 | |
---|
256 | ELSE |
---|
257 | ! |
---|
258 | !-- This is not a restart job. |
---|
259 | !-- Check, if the grid point numbers are well defined. |
---|
260 | IF ( nx <= 0 ) THEN |
---|
261 | IF ( myid == 0 ) THEN |
---|
262 | PRINT*, '+++ parin: no value or wrong value given for nx: nx=', nx |
---|
263 | ENDIF |
---|
264 | CALL local_stop |
---|
265 | ENDIF |
---|
266 | IF ( ny <= 0 ) THEN |
---|
267 | IF ( myid == 0 ) THEN |
---|
268 | PRINT*, '+++ parin: no value or wrong value given for ny: ny=', ny |
---|
269 | ENDIF |
---|
270 | CALL local_stop |
---|
271 | ENDIF |
---|
272 | IF ( nz <= 0 ) THEN |
---|
273 | IF ( myid == 0 ) THEN |
---|
274 | PRINT*, '+++ parin: no value or wrong value given for nz: nz=', nz |
---|
275 | ENDIF |
---|
276 | CALL local_stop |
---|
277 | ENDIF |
---|
278 | |
---|
279 | ! |
---|
280 | !-- Allocate arrays which will be already initialized in init_pegrid or |
---|
281 | !-- check_parameters. During restart jobs, these arrays will be allocated |
---|
282 | !-- in read_var_list. All other arrays are allocated in init_3d_model. |
---|
283 | ALLOCATE( ug(0:nz+1), vg(0:nz+1), & |
---|
284 | pt_init(0:nz+1), q_init(0:nz+1), u_init(0:nz+1), & |
---|
285 | v_init(0:nz+1), & |
---|
286 | hom(0:nz+1,2,var_hom,0:statistic_regions) ) |
---|
287 | hom = 0.0 |
---|
288 | |
---|
289 | ENDIF |
---|
290 | |
---|
291 | ! |
---|
292 | !-- Definition of names of areas used for computing statistics. They must |
---|
293 | !-- be defined at this place, because they are allowed to be redefined by |
---|
294 | !-- the user in user_parin. |
---|
295 | region = 'total domain' |
---|
296 | |
---|
297 | ! |
---|
298 | !-- Read runtime parameters given by the user for this run (namelist "d3par"). |
---|
299 | !-- The namelist "d3par" can be omitted. In that case, default values are |
---|
300 | !-- used for the parameters. |
---|
301 | READ ( 11, d3par, END=20 ) |
---|
302 | |
---|
303 | ! |
---|
304 | !-- Read control parameters for optionally used model software packages |
---|
305 | 20 CALL package_parin |
---|
306 | |
---|
307 | ! |
---|
308 | !-- Read user-defined variables |
---|
309 | CALL user_parin |
---|
310 | |
---|
311 | ! |
---|
312 | !-- NAMELIST-file is not needed anymore |
---|
313 | CALL close_file( 11 ) |
---|
314 | |
---|
315 | ! |
---|
316 | !-- Read values of environment variables (this NAMELIST file is generated by |
---|
317 | !-- mrun) |
---|
318 | OPEN ( 90, FILE='ENVPAR', STATUS='OLD', FORM='FORMATTED', ERR=30 ) |
---|
319 | READ ( 90, envpar, ERR=31, END=32 ) |
---|
320 | CLOSE ( 90 ) |
---|
321 | RETURN |
---|
322 | |
---|
323 | 30 IF ( myid == 0 ) THEN |
---|
324 | PRINT*, '+++ parin: WARNING: local file ENVPAR not found' |
---|
325 | PRINT*, ' some variables for steering may not be properly set' |
---|
326 | ENDIF |
---|
327 | RETURN |
---|
328 | |
---|
329 | 31 IF ( myid == 0 ) THEN |
---|
330 | PRINT*, '+++ parin: WARNING: errors in local file ENVPAR' |
---|
331 | PRINT*, ' some variables for steering may not be properly set' |
---|
332 | ENDIF |
---|
333 | RETURN |
---|
334 | |
---|
335 | 32 IF ( myid == 0 ) THEN |
---|
336 | PRINT*, '+++ parin: WARNING: no envpar-NAMELIST found in local file ', & |
---|
337 | 'ENVPAR' |
---|
338 | PRINT*, ' some variables for steering may not be properly set' |
---|
339 | ENDIF |
---|
340 | |
---|
341 | END SUBROUTINE parin |
---|