SUBROUTINE parin !------------------------------------------------------------------------------! ! Actual revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Id: parin.f90 110 2007-10-05 05:13:14Z raasch $ ! ! 108 2007-08-24 15:10:38Z letzel ! +e_init, top_momentumflux_u|v in inipar, +dt_coupling in d3par ! ! 95 2007-06-02 16:48:38Z raasch ! +bc_sa_t, bottom_salinityflux, ocean, sa_surface, sa_vertical_gradient, ! sa_vertical_gradient_level, top_salinityflux in inipar, ! sa_init is allocated ! ! 87 2007-05-22 15:46:47Z raasch ! Size of hom increased by the maximum number of user-defined profiles, ! var_hom renamed pr_palm ! ! 82 2007-04-16 15:40:52Z raasch ! +return_addres, return_username in envpar ! ! 75 2007-03-22 09:54:05Z raasch ! +dt_max, netcdf_64bit_3d, precipitation_amount_interval in d3par, ! +loop_optimization, pt_reference in inipar, -data_output_ts, ! moisture renamed humidity ! ! 20 2007-02-26 00:12:32Z raasch ! +top_heatflux, use_top_fluxes in inipar ! ! -netcdf_64bit_3d ! ! 3 2007-02-13 11:30:58Z raasch ! +netcdf_64bit_3d in d3par, ! RCS Log replace by Id keyword, revision history cleaned up ! ! Revision 1.57 2007/02/11 13:11:22 raasch ! Values of environment variables are now read from file ENVPAR instead of ! reading them with a system call, + NAMELIST envpar ! ! Revision 1.1 1997/07/24 11:22:50 raasch ! Initial revision ! ! ! Description: ! ------------ ! This subroutine reads variables controling the run from the NAMELIST files !------------------------------------------------------------------------------! USE arrays_3d USE averaging USE control_parameters USE grid_variables USE indices USE model_1d USE pegrid USE profil_parameter USE statistics IMPLICIT NONE INTEGER :: idum NAMELIST /inipar/ adjust_mixing_length, alpha_surface, bc_e_b, bc_lr, & bc_ns, bc_p_b, bc_p_t, bc_pt_b, bc_pt_t, bc_q_b, & bc_q_t,bc_s_b, bc_s_t, bc_sa_t, bc_uv_b, bc_uv_t, & bottom_salinityflux, building_height, & building_length_x, building_length_y, building_wall_left, & building_wall_south, cloud_droplets, cloud_physics, & conserve_volume_flow, cut_spline_overshoot, damp_level_1d, & dissipation_1d, dt, dt_pr_1d, dt_run_control_1d, dx, dy, dz, & dz_max, dz_stretch_factor, dz_stretch_level, e_init, e_min, & end_time_1d, & fft_method, galilei_transformation, grid_matching, humidity, & inflow_disturbance_begin, inflow_disturbance_end, & initializing_actions, km_constant, km_damp_max, & long_filter_factor, loop_optimization, mixing_length_1d, & momentum_advec, netcdf_precision, npex, npey, nsor_ini, nx, ny, & nz, ocean, omega, outflow_damping_width, overshoot_limit_e, & overshoot_limit_pt, overshoot_limit_u, overshoot_limit_v, & overshoot_limit_w, passive_scalar, phi, prandtl_layer, & precipitation, pt_reference, pt_surface, & pt_surface_initial_change, pt_vertical_gradient, & pt_vertical_gradient_level, q_surface, q_surface_initial_change, & q_vertical_gradient, q_vertical_gradient_level, radiation, & random_generator, random_heatflux, rif_max, rif_min, & roughness_length, sa_surface, sa_vertical_gradient, & sa_vertical_gradient_level, scalar_advec, statistic_regions, & surface_heatflux, surface_pressure, surface_scalarflux, & surface_waterflux, s_surface, s_surface_initial_change, & s_vertical_gradient, s_vertical_gradient_level, top_heatflux, & top_momentumflux_u, top_momentumflux_v, top_salinityflux, & timestep_scheme, topography, ug_surface, & ug_vertical_gradient, ug_vertical_gradient_level, ups_limit_e, & ups_limit_pt, ups_limit_u, ups_limit_v, ups_limit_w, & use_surface_fluxes, use_top_fluxes, use_ug_for_galilei_tr, & use_upstream_for_tke, vg_surface, vg_vertical_gradient, & vg_vertical_gradient_level, wall_adjustment, wall_heatflux NAMELIST /d3par/ averaging_interval, averaging_interval_pr, & call_psolver_at_all_substeps, cfl_factor, & create_disturbances, cross_normalized_x, & cross_normalized_y, cross_profiles, cross_ts_uymax, & cross_ts_uymin, cross_xtext, cycle_mg, data_output, & data_output_format, data_output_pr, & data_output_2d_on_each_pe, disturbance_amplitude, & disturbance_energy_limit, disturbance_level_b, & disturbance_level_t, do2d_at_begin, do3d_at_begin, & do3d_compress, do3d_comp_prec, dt, dt_averaging_input, & dt_averaging_input_pr, dt_coupling, dt_data_output, & dt_data_output_av, dt_disturb, dt_dopr, & dt_dopr_listing, dt_dots, dt_do2d_xy, dt_do2d_xz, & dt_do2d_yz, dt_do3d, dt_max, dt_restart, dt_run_control,& end_time, force_print_header, mg_cycles, & mg_switch_to_pe0_level, netcdf_64bit, netcdf_64bit_3d, & ngsrb, normalizing_region, nsor, nz_do3d, omega_sor, & prandtl_number, precipitation_amount_interval, & profile_columns, profile_rows, psolver, & rayleigh_damping_factor, rayleigh_damping_height, & residual_limit, restart_time, section_xy, section_xz, & section_yz, skip_time_data_output, & skip_time_data_output_av, skip_time_dopr, & skip_time_dosp, skip_time_do2d_xy, skip_time_do2d_xz, & skip_time_do2d_yz, skip_time_do3d, & termination_time_needed, use_prior_plot1d_parameters, & z_max_do1d, z_max_do1d_normalized, z_max_do2d NAMELIST /envpar/ host, maximum_cpu_time_allowed, revision, return_addres,& return_username, run_identifier, tasks_per_node, & write_binary #if defined( __parallel ) ! !-- Preliminary determination of processor-id which is needed here to open the !-- input files belonging to the corresponding processor and to produce !-- messages by PE0 only (myid and myid_char are later determined in !-- init_pegrid) CALL MPI_COMM_RANK( comm_palm, myid, ierr ) WRITE (myid_char,'(''_'',I4.4)') myid ! !-- Since on IBM machines the process rank may be changed when the final !-- communicator is defined, save the preliminary processor-id for opening !-- the binary output file for restarts (unit 14), because otherwise !-- a mismatch occurs when reading this file in the next job myid_char_14 = myid_char #endif ! !-- Open the NAMELIST-file which is send with this job CALL check_open( 11 ) ! !-- Read the control parameters for initialization. !-- The namelist "inipar" must be provided in the NAMELIST-file. If this is !-- not the case and the file contains - instead of "inipar" - any other !-- namelist, a read error is created on t3e and control is transferred !-- to the statement with label 10. Therefore, on t3e machines one can not !-- distinguish between errors produced by a wrong "inipar" namelist or !-- because this namelist is totally missing. READ ( 11, inipar, ERR=10, END=11 ) GOTO 12 10 IF ( myid == 0 ) THEN PRINT*, '+++ parin: errors in \$inipar' PRINT*, ' or no \$inipar-namelist found (CRAY-machines only)' ENDIF CALL local_stop 11 IF ( myid == 0 ) THEN PRINT*, '+++ parin: no \$inipar-namelist found' ENDIF CALL local_stop ! !-- If required, read control parameters from restart file (produced by !-- a prior run) 12 IF ( TRIM( initializing_actions ) == 'read_restart_data' ) THEN CALL read_var_list ! !-- Increment the run count runnr = runnr + 1 ENDIF ! !-- Definition of names of areas used for computing statistics. They must !-- be defined at this place, because they are allowed to be redefined by !-- the user in user_parin. region = 'total domain' ! !-- Read runtime parameters given by the user for this run (namelist "d3par"). !-- The namelist "d3par" can be omitted. In that case, default values are !-- used for the parameters. READ ( 11, d3par, END=20 ) ! !-- Read control parameters for optionally used model software packages 20 CALL package_parin ! !-- Read user-defined variables CALL user_parin ! !-- Check in case of initial run, if the grid point numbers are well defined !-- and allocate some arrays which are already needed in init_pegrid or !-- check_parameters. During restart jobs, these arrays will be allocated !-- in read_var_list. All other arrays are allocated in init_3d_model. IF ( TRIM( initializing_actions ) /= 'read_restart_data' ) THEN IF ( nx <= 0 ) THEN IF ( myid == 0 ) THEN PRINT*, '+++ parin: no value or wrong value given for nx: nx=', nx ENDIF CALL local_stop ENDIF IF ( ny <= 0 ) THEN IF ( myid == 0 ) THEN PRINT*, '+++ parin: no value or wrong value given for ny: ny=', ny ENDIF CALL local_stop ENDIF IF ( nz <= 0 ) THEN IF ( myid == 0 ) THEN PRINT*, '+++ parin: no value or wrong value given for nz: nz=', nz ENDIF CALL local_stop ENDIF ALLOCATE( ug(0:nz+1), vg(0:nz+1), & pt_init(0:nz+1), q_init(0:nz+1), sa_init(0:nz+1), & u_init(0:nz+1), v_init(0:nz+1), & hom(0:nz+1,2,pr_palm+max_pr_user,0:statistic_regions) ) hom = 0.0 ENDIF ! !-- NAMELIST-file is not needed anymore CALL close_file( 11 ) ! !-- Read values of environment variables (this NAMELIST file is generated by !-- mrun) OPEN ( 90, FILE='ENVPAR', STATUS='OLD', FORM='FORMATTED', ERR=30 ) READ ( 90, envpar, ERR=31, END=32 ) CLOSE ( 90 ) RETURN 30 IF ( myid == 0 ) THEN PRINT*, '+++ parin: WARNING: local file ENVPAR not found' PRINT*, ' some variables for steering may not be properly set' ENDIF RETURN 31 IF ( myid == 0 ) THEN PRINT*, '+++ parin: WARNING: errors in local file ENVPAR' PRINT*, ' some variables for steering may not be properly set' ENDIF RETURN 32 IF ( myid == 0 ) THEN PRINT*, '+++ parin: WARNING: no envpar-NAMELIST found in local file ', & 'ENVPAR' PRINT*, ' some variables for steering may not be properly set' ENDIF END SUBROUTINE parin