SUBROUTINE read_var_list !------------------------------------------------------------------------------! ! Actual revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Log: read_var_list.f90,v $ ! Revision 1.34 2006/08/22 14:14:27 raasch ! +dz_max ! ! Revision 1.33 2006/08/04 15:04:08 raasch ! +first_call_advec_particles, time_dopts, use_upstream_for_tke ! ! Revision 1.32 2006/02/23 12:53:31 raasch ! +building parameters, conserve_volume_flow, dissipation_1d, e_min, ! mixing_length_1d, topography, ! -average_count_pl, time_average_pr, ! nt_anz renamed current_timestep_number, ..pl.. renamed ..do.. ! ! Revision 1.31 2005/06/29 09:12:49 steinfeld ! +ug_surface, ug_vertical_gradient, ug_vertical_gradient_level, ! ug_vertical_gradient_level_ind, vg_surface, vg_vertical_gradient, ! vg_vertical_gradient_level, vg_vertical_gradient_level_ind; ! allocation of the new arrays ug and vg ! ! Revision 1.30 2005/06/26 20:09:42 raasch ! +cloud_droplets ! ! Revision 1.29 2005/05/18 15:55:12 raasch ! +netcdf_precision ! ! Revision 1.28 2005/03/26 21:01:00 raasch ! +bc_lr, bc_ns, inflow_disturbance_begin, inflow_disturbance_end, km_damp_max, ! outflow_damping_width ! ! Revision 1.27 2004/04/30 12:49:56 raasch ! +grid_matching, impulse_advec renamed momentum_advec ! ! Revision 1.26 2004/01/28 15:27:33 raasch ! at and bt replaced by array tsc ! ! Revision 1.25 2003/10/29 09:10:41 raasch ! +last_dt_change ! ! Revision 1.24 2003/03/14 13:47:15 raasch ! +random_generator ! ! Revision 1.23 2002/12/19 16:18:27 raasch ! Array hom, which was formerly read in init_3d_model, will now be allocated ! and read here, binary version incremented to 2.2, +time_restart, ! STOP statement replaced by call of subroutine local_stop ! ! Revision 1.22 2002/04/16 08:21:06 raasch ! +bc_s_b, bc_s_t, surface_scalarflux, s_surface, s_surface_initial_change, ! s_vertical_gradient, s_vertical_gradient_level ! ! Revision 1.21 2001/08/21 10:01:23 raasch ! +wall_adjustment ! ! Revision 1.20 2001/03/30 07:51:25 raasch ! Translation of remaining German identifiers (variables, subroutines, etc.), ! runtime and package parameters are not read from unit 13 any more ! ! Revision 1.19 2001/01/29 12:35:03 raasch ! +passive_scalar ! ! Revision 1.18 2001/01/25 07:24:28 raasch ! +fft_method, use_surface_fluxes ! ! Revision 1.17 2001/01/05 15:16:18 raasch ! +average_count_sp, time_dosp ! ! Revision 1.16 2000/12/28 13:38:46 raasch ! Module dvrp_variables removed, -particle_transport ! ! Revision 1.15 2000/04/27 06:57:04 raasch ! +dt_dvrp, dvrp_filecount, npex, npey, threshold, time_dvrp ! -dt_plisos, dt_plpart, time_plisos, time_plpart, ! all comments translated into English, old revision remarks deleted ! ! Revision 1.14 2000/04/13 13:06:16 schroeter ! Einlesen der Initialisierungsparameter fuer Rechnungen ! mit Feuchte/Wolkenphysik ! ! Revision 1.13 2000/01/10 10:06:32 10:06:32 raasch (Siegfried Raasch) ! +use_ug_for_galilei_tr ! ! Revision 1.1 1998/03/18 20:18:48 raasch ! Initial revision ! ! ! Description: ! ------------ ! Reading values of control variables from restart-file (binary format) !------------------------------------------------------------------------------! USE arrays_3d USE averaging USE grid_variables USE indices USE model_1d USE pegrid USE profil_parameter USE statistics USE control_parameters IMPLICIT NONE CHARACTER (LEN=10) :: binary_version, version_on_file CHARACTER (LEN=30) :: variable_chr CALL check_open( 13 ) ! !-- Make version number check first READ ( 13 ) version_on_file binary_version = '3.0' IF ( TRIM( version_on_file ) /= TRIM( binary_version ) ) THEN IF ( myid == 0 ) THEN PRINT*, '+++ read_var_list: version mismatch concerning control', & ' variables' PRINT*, ' version on file = "', & TRIM( version_on_file ), '"' PRINT*, ' version on program = "', & TRIM( binary_version ), '"' ENDIF CALL local_stop ENDIF ! !-- Read vertical number of gridpoints and number of different areas used !-- for computing statistics. Allocate arrays depending on these values, !-- which are needed for the following read instructions. READ ( 13 ) variable_chr IF ( TRIM( variable_chr ) /= 'nz' ) THEN PRINT*, '+++ read_var_list: nz not found in data from prior run on PE ',& myid CALL local_stop ENDIF READ ( 13 ) nz READ ( 13 ) variable_chr IF ( TRIM( variable_chr ) /= 'statistic_regions' ) THEN PRINT*, '+++ read_var_list: statistic_regions not found in data from ', & 'prior run on PE ', myid CALL local_stop ENDIF READ ( 13 ) statistic_regions ALLOCATE( ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1), v_init(0:nz+1), & pt_init(0:nz+1), q_init(0:nz+1), & hom(0:nz+1,2,var_hom,0:statistic_regions) ) ! !-- Now read all control parameters: !-- Caution: When the following read instructions have been changed, the !-- ------- version number stored in the variable binary_version has to be !-- increased. The same changes must also be done in write_var_list. READ ( 13 ) variable_chr DO WHILE ( TRIM( variable_chr ) /= '*** end ***' ) SELECT CASE ( TRIM( variable_chr ) ) CASE ( 'adjust_mixing_length' ) READ ( 13 ) adjust_mixing_length CASE ( 'advected_distance_x' ) READ ( 13 ) advected_distance_x CASE ( 'advected_distance_y' ) READ ( 13 ) advected_distance_y CASE ( 'alpha_surface' ) READ ( 13 ) alpha_surface CASE ( 'average_count_pr' ) READ ( 13 ) average_count_pr CASE ( 'average_count_sp' ) READ ( 13 ) average_count_sp CASE ( 'average_count_3d' ) READ ( 13 ) average_count_3d CASE ( 'bc_e_b' ) READ ( 13 ) bc_e_b CASE ( 'bc_lr' ) READ ( 13 ) bc_lr CASE ( 'bc_ns' ) READ ( 13 ) bc_ns CASE ( 'bc_p_b' ) READ ( 13 ) bc_p_b CASE ( 'bc_p_t' ) READ ( 13 ) bc_p_t CASE ( 'bc_pt_b' ) READ ( 13 ) bc_pt_b CASE ( 'bc_pt_t' ) READ ( 13 ) bc_pt_t CASE ( 'bc_pt_t_val' ) READ ( 13 ) bc_pt_t_val CASE ( 'bc_q_b' ) READ ( 13 ) bc_q_b CASE ( 'bc_q_t' ) READ ( 13 ) bc_q_t CASE ( 'bc_q_t_val' ) READ ( 13 ) bc_q_t_val CASE ( 'bc_s_b' ) READ ( 13 ) bc_s_b CASE ( 'bc_s_t' ) READ ( 13 ) bc_s_t CASE ( 'bc_uv_b' ) READ ( 13 ) bc_uv_b CASE ( 'bc_uv_t' ) READ ( 13 ) bc_uv_t CASE ( 'building_height' ) READ ( 13 ) building_height CASE ( 'building_length_x' ) READ ( 13 ) building_length_x CASE ( 'building_length_y' ) READ ( 13 ) building_length_y CASE ( 'building_wall_left' ) READ ( 13 ) building_wall_left CASE ( 'building_wall_south' ) READ ( 13 ) building_wall_south CASE ( 'cloud_droplets' ) READ ( 13 ) cloud_droplets CASE ( 'cloud_physics' ) READ ( 13 ) cloud_physics CASE ( 'conserve_volume_flow' ) READ ( 13 ) conserve_volume_flow CASE ( 'current_timestep_number' ) READ ( 13 ) current_timestep_number CASE ( 'cut_spline_overshoot' ) READ ( 13 ) cut_spline_overshoot CASE ( 'damp_level_1d' ) READ ( 13 ) damp_level_1d CASE ( 'dissipation_1d' ) READ ( 13 ) dissipation_1d CASE ( 'dt_fixed' ) READ ( 13 ) dt_fixed CASE ( 'dt_pr_1d' ) READ ( 13 ) dt_pr_1d CASE ( 'dt_run_control_1d' ) READ ( 13 ) dt_run_control_1d CASE ( 'dt_3d' ) READ ( 13 ) dt_3d CASE ( 'dvrp_filecount' ) READ ( 13 ) dvrp_filecount CASE ( 'dx' ) READ ( 13 ) dx CASE ( 'dy' ) READ ( 13 ) dy CASE ( 'dz' ) READ ( 13 ) dz CASE ( 'dz_max' ) READ ( 13 ) dz_max CASE ( 'dz_stretch_factor' ) READ ( 13 ) dz_stretch_factor CASE ( 'dz_stretch_level' ) READ ( 13 ) dz_stretch_level CASE ( 'e_min' ) READ ( 13 ) e_min CASE ( 'end_time_1d' ) READ ( 13 ) end_time_1d CASE ( 'fft_method' ) READ ( 13 ) fft_method CASE ( 'first_call_advec_particles' ) READ ( 13 ) first_call_advec_particles CASE ( 'galilei_transformation' ) READ ( 13 ) galilei_transformation CASE ( 'grid_matching' ) READ ( 13 ) grid_matching CASE ( 'hom' ) READ ( 13 ) hom CASE ( 'inflow_disturbance_begin' ) READ ( 13 ) inflow_disturbance_begin CASE ( 'inflow_disturbance_end' ) READ ( 13 ) inflow_disturbance_end CASE ( 'km_constant' ) READ ( 13 ) km_constant CASE ( 'km_damp_max' ) READ ( 13 ) km_damp_max CASE ( 'last_dt_change' ) READ ( 13 ) last_dt_change CASE ( 'long_filter_factor' ) READ ( 13 ) long_filter_factor CASE ( 'mixing_length_1d' ) READ ( 13 ) mixing_length_1d CASE ( 'moisture' ) READ ( 13 ) moisture CASE ( 'momentum_advec' ) READ ( 13 ) momentum_advec CASE ( 'netcdf_precision' ) READ ( 13 ) netcdf_precision CASE ( 'npex' ) READ ( 13 ) npex CASE ( 'npey' ) READ ( 13 ) npey CASE ( 'nsor_ini' ) READ ( 13 ) nsor_ini CASE ( 'nx' ) READ ( 13 ) nx CASE ( 'ny' ) READ ( 13 ) ny CASE ( 'old_dt' ) READ ( 13 ) old_dt CASE ( 'omega' ) READ ( 13 ) omega CASE ( 'outflow_damping_width' ) READ ( 13 ) outflow_damping_width CASE ( 'overshoot_limit_e' ) READ ( 13 ) overshoot_limit_e CASE ( 'overshoot_limit_pt' ) READ ( 13 ) overshoot_limit_pt CASE ( 'overshoot_limit_u' ) READ ( 13 ) overshoot_limit_u CASE ( 'overshoot_limit_v' ) READ ( 13 ) overshoot_limit_v CASE ( 'overshoot_limit_w' ) READ ( 13 ) overshoot_limit_w CASE ( 'passive_scalar' ) READ ( 13 ) passive_scalar CASE ( 'phi' ) READ ( 13 ) phi CASE ( 'prandtl_layer' ) READ ( 13 ) prandtl_layer CASE ( 'precipitation' ) READ ( 13 ) precipitation CASE ( 'pt_init' ) READ ( 13 ) pt_init CASE ( 'pt_surface' ) READ ( 13 ) pt_surface CASE ( 'pt_surface_initial_change' ) READ ( 13 ) pt_surface_initial_change CASE ( 'pt_vertical_gradient' ) READ ( 13 ) pt_vertical_gradient CASE ( 'pt_vertical_gradient_level' ) READ ( 13 ) pt_vertical_gradient_level CASE ( 'pt_vertical_gradient_level_ind' ) READ ( 13 ) pt_vertical_gradient_level_ind CASE ( 'q_init' ) READ ( 13 ) q_init CASE ( 'q_surface' ) READ ( 13 ) q_surface CASE ( 'q_surface_initial_change' ) READ ( 13 ) q_surface_initial_change CASE ( 'q_vertical_gradient' ) READ ( 13 ) q_vertical_gradient CASE ( 'q_vertical_gradient_level' ) READ ( 13 ) q_vertical_gradient_level CASE ( 'q_vertical_gradient_level_ind' ) READ ( 13 ) q_vertical_gradient_level_ind CASE ( 'radiation' ) READ ( 13 ) radiation CASE ( 'random_generator' ) READ ( 13 ) random_generator CASE ( 'random_heatflux' ) READ ( 13 ) random_heatflux CASE ( 'rif_max' ) READ ( 13 ) rif_max CASE ( 'rif_min' ) READ ( 13 ) rif_min CASE ( 'roughness_length' ) READ ( 13 ) roughness_length CASE ( 'runnr' ) READ ( 13 ) runnr CASE ( 'scalar_advec' ) READ ( 13 ) scalar_advec CASE ( 'simulated_time' ) READ ( 13 ) simulated_time CASE ( 'surface_heatflux' ) READ ( 13 ) surface_heatflux CASE ( 'surface_pressure' ) READ ( 13 ) surface_pressure CASE ( 'surface_scalarflux' ) READ ( 13 ) surface_scalarflux CASE ( 'surface_waterflux' ) READ ( 13 ) surface_waterflux CASE ( 's_surface' ) READ ( 13 ) s_surface CASE ( 's_surface_initial_change' ) READ ( 13 ) s_surface_initial_change CASE ( 's_vertical_gradient' ) READ ( 13 ) s_vertical_gradient CASE ( 's_vertical_gradient_level' ) READ ( 13 ) s_vertical_gradient_level CASE ( 'time_disturb' ) READ ( 13 ) time_disturb CASE ( 'time_dopr' ) READ ( 13 ) time_dopr CASE ( 'time_dopr_av' ) READ ( 13 ) time_dopr_av CASE ( 'time_dopr_listing' ) READ ( 13 ) time_dopr_listing CASE ( 'time_dopts' ) READ ( 13 ) time_dopts CASE ( 'time_dosp' ) READ ( 13 ) time_dosp CASE ( 'time_dots' ) READ ( 13 ) time_dots CASE ( 'time_do2d_xy' ) READ ( 13 ) time_do2d_xy CASE ( 'time_do2d_xz' ) READ ( 13 ) time_do2d_xz CASE ( 'time_do2d_yz' ) READ ( 13 ) time_do2d_yz CASE ( 'time_do3d' ) READ ( 13 ) time_do3d CASE ( 'time_do_av' ) READ ( 13 ) time_do_av CASE ( 'time_do_sla' ) READ ( 13 ) time_do_sla CASE ( 'time_dvrp' ) READ ( 13 ) time_dvrp CASE ( 'time_restart' ) READ ( 13 ) time_restart CASE ( 'time_run_control' ) READ ( 13 ) time_run_control CASE ( 'timestep_scheme' ) READ ( 13 ) timestep_scheme CASE ( 'topography' ) READ ( 13 ) topography CASE ( 'tsc' ) READ ( 13 ) tsc CASE ( 'u_init' ) READ ( 13 ) u_init CASE ( 'u_max' ) READ ( 13 ) u_max CASE ( 'u_max_ijk' ) READ ( 13 ) u_max_ijk CASE ( 'ug' ) READ ( 13 ) ug CASE ( 'ug_surface' ) READ ( 13 ) ug_surface CASE ( 'ug_vertical_gradient' ) READ ( 13 ) ug_vertical_gradient CASE ( 'ug_vertical_gradient_level' ) READ ( 13 ) ug_vertical_gradient_level CASE ( 'ug_vertical_gradient_level_ind' ) READ ( 13 ) ug_vertical_gradient_level_ind CASE ( 'ups_limit_e' ) READ ( 13 ) ups_limit_e CASE ( 'ups_limit_pt' ) READ ( 13 ) ups_limit_pt CASE ( 'ups_limit_u' ) READ ( 13 ) ups_limit_u CASE ( 'ups_limit_v' ) READ ( 13 ) ups_limit_v CASE ( 'ups_limit_w' ) READ ( 13 ) ups_limit_w CASE ( 'use_surface_fluxes' ) READ ( 13 ) use_surface_fluxes CASE ( 'use_ug_for_galilei_tr' ) READ ( 13 ) use_ug_for_galilei_tr CASE ( 'use_upstream_for_tke' ) READ ( 13 ) use_upstream_for_tke CASE ( 'v_init' ) READ ( 13 ) v_init CASE ( 'v_max' ) READ ( 13 ) v_max CASE ( 'v_max_ijk' ) READ ( 13 ) v_max_ijk CASE ( 'vg' ) READ ( 13 ) vg CASE ( 'vg_surface' ) READ ( 13 ) vg_surface CASE ( 'vg_vertical_gradient' ) READ ( 13 ) vg_vertical_gradient CASE ( 'vg_vertical_gradient_level' ) READ ( 13 ) vg_vertical_gradient_level CASE ( 'vg_vertical_gradient_level_ind' ) READ ( 13 ) vg_vertical_gradient_level_ind CASE ( 'wall_adjustment' ) READ ( 13 ) wall_adjustment CASE ( 'w_max' ) READ ( 13 ) w_max CASE ( 'w_max_ijk' ) READ ( 13 ) w_max_ijk CASE ( 'time-series-quantities' ) READ ( 13 ) cross_ts_uymax, cross_ts_uymax_computed, & cross_ts_uymin, cross_ts_uymin_computed CASE DEFAULT PRINT*, '+++ read_var_list: unknown variable named "', & TRIM( variable_chr ), '" found in' PRINT*, ' data from prior run on PE ', myid CALL local_stop END SELECT ! !-- Read next string READ ( 13 ) variable_chr ENDDO END SUBROUTINE read_var_list