SUBROUTINE read_var_list !------------------------------------------------------------------------------! ! Current revisions: ! ----------------- ! Output of messages replaced by message handling routine. ! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left, ! canyon_wall_south, conserve_volume_flow_mode, coupling_start_time, ! dp_external, dp_level_b, dp_smooth, dpdxy, run_coupled, ! time_since_reference_point, topography_grid_convention, u_bulk, v_bulk ! ! Former revisions: ! ----------------- ! $Id: read_var_list.f90 291 2009-04-16 12:07:26Z raasch $ ! ! 216 2008-11-25 07:12:43Z raasch ! limitations for nx_on_file, ny_on_file removed (read_parts_of_var_list) ! ! 173 2008-05-23 20:39:38Z raasch ! +cthf, leaf_surface_concentration, scalar_exchange_coefficient ! +numprocs_previous_run, hor_index_bounds_previous_run, inflow_damping_factor, ! inflow_damping_height, inflow_damping_width, mean_inflow_profiles, ! recycling_width, turbulent_inflow, ! -cross_ts_*, npex, npey, ! hom_sum, volume_flow_area, volume_flow_initial moved from ! read_3d_binary to here, ! routines read_parts_of_var_list and skip_var_list added at the end ! ! 138 2007-11-28 10:03:58Z letzel ! +canopy_mode, drag_coefficient, lad, lad_surface, lad_vertical_gradient, ! lad_vertical_gradient_level, lad_vertical_gradient_level_ind, pch_index, ! plant_canopy, time_sort_particles ! ! 102 2007-07-27 09:09:17Z raasch ! +time_coupling, top_momentumflux_u|v ! ! 95 2007-06-02 16:48:38Z raasch ! +bc_sa_t, ocean, sa_init, sa_surface, sa_vertical_gradient, ! sa_vertical_gradient_level, bottom/top_salinity_flux ! ! 87 2007-05-22 15:46:47Z raasch ! +max_pr_user (version 3.1), var_hom renamed pr_palm ! ! 75 2007-03-22 09:54:05Z raasch ! +loop_optimization, pt_reference, moisture renamed humidity ! ! 20 2007-02-26 00:12:32Z raasch ! +top_heatflux, use_top_fluxes ! ! RCS Log replace by Id keyword, revision history cleaned up ! ! Revision 1.34 2006/08/22 14:14:27 raasch ! +dz_max ! ! Revision 1.1 1998/03/18 20:18:48 raasch ! Initial revision ! ! ! Description: ! ------------ ! Reading values of global control variables from restart-file (binary format) !------------------------------------------------------------------------------! USE arrays_3d USE averaging USE control_parameters USE grid_variables USE indices USE model_1d USE particle_attributes USE pegrid USE profil_parameter USE statistics 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.4' IF ( TRIM( version_on_file ) /= TRIM( binary_version ) ) THEN WRITE( message_string, * ) 'version mismatch concerning control ', & 'variables', & '&version on file = "', & TRIM( version_on_file ), '"', & '&version on program = "', & TRIM( binary_version ), '"' CALL message( 'read_var_list', 'PA0296', 1, 2, 0, 6, 0 ) ENDIF ! !-- Read number of PEs and horizontal index bounds of all PEs used in previous !-- run READ ( 13 ) variable_chr IF ( TRIM( variable_chr ) /= 'numprocs' ) THEN WRITE( message_string, * ) 'numprocs not found in data from prior ', & 'run on PE ', myid CALL message( 'read_var_list', 'PA0297', 1, 2, 0, 6, 0 ) ENDIF READ ( 13 ) numprocs_previous_run IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) ) THEN ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) ) ENDIF READ ( 13 ) variable_chr IF ( TRIM( variable_chr ) /= 'hor_index_bounds' ) THEN WRITE( message_string, * ) 'hor_index_bounds not found in data from ', & 'prior run on PE ', myid CALL message( 'read_var_list', 'PA0298', 1, 2, 0, 6, 0 ) ENDIF READ ( 13 ) hor_index_bounds_previous_run ! !-- 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 WRITE( message_string, * ) 'nz not found in data from prior run on PE ',& myid CALL message( 'read_var_list', 'PA0299', 1, 2, 0, 6, 0 ) ENDIF READ ( 13 ) nz READ ( 13 ) variable_chr IF ( TRIM( variable_chr ) /= 'max_pr_user' ) THEN WRITE( message_string, * ) 'max_pr_user not found in data from ', & 'prior run on PE ', myid CALL message( 'read_var_list', 'PA0300', 1, 2, 0, 6, 0 ) ENDIF READ ( 13 ) max_pr_user ! This value is checked against the number of ! user profiles given for the current run ! in routine user_parin (it has to match) READ ( 13 ) variable_chr IF ( TRIM( variable_chr ) /= 'statistic_regions' ) THEN WRITE( message_string, * ) 'statistic_regions not found in data from ', & 'prior run on PE ', myid CALL message( 'read_var_list', 'PA0301', 1, 2, 0, 6, 0 ) ENDIF READ ( 13 ) statistic_regions IF ( .NOT. ALLOCATED( ug ) ) THEN ALLOCATE( lad(0:nz+1), 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), & sa_init(0:nz+1), & hom(0:nz+1,2,pr_palm+max_pr_user,0:statistic_regions), & hom_sum(0:nz+1,pr_palm+max_pr_user,0:statistic_regions) ) ENDIF ! !-- 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_sa_t' ) READ ( 13 ) bc_sa_t CASE ( 'bc_uv_b' ) READ ( 13 ) bc_uv_b CASE ( 'bc_uv_t' ) READ ( 13 ) bc_uv_t CASE ( 'bottom_salinityflux' ) READ ( 13 ) bottom_salinityflux 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 ( 'canopy_mode' ) READ ( 13 ) canopy_mode CASE ( 'canyon_height' ) READ ( 13 ) canyon_height CASE ( 'canyon_width_x' ) READ ( 13 ) canyon_width_x CASE ( 'canyon_width_y' ) READ ( 13 ) canyon_width_y CASE ( 'canyon_wall_left' ) READ ( 13 ) canyon_wall_left CASE ( 'canyon_wall_south' ) READ ( 13 ) canyon_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 ( 'conserve_volume_flow_mode' ) READ ( 13 ) conserve_volume_flow_mode CASE ( 'coupling_start_time' ) READ ( 13 ) coupling_start_time CASE ( 'cthf' ) READ ( 13 ) cthf 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 ( 'dp_external' ) READ ( 13 ) dp_external CASE ( 'dp_level_b' ) READ ( 13 ) dp_level_b CASE ( 'dp_smooth' ) READ ( 13 ) dp_smooth CASE ( 'dpdxy' ) READ ( 13 ) dpdxy CASE ( 'drag_coefficient' ) READ ( 13 ) drag_coefficient 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 ( 'hom_sum' ) READ ( 13 ) hom_sum CASE ( 'humidity' ) READ ( 13 ) humidity CASE ( 'inflow_damping_factor' ) IF ( .NOT. ALLOCATED( inflow_damping_factor ) ) THEN ALLOCATE( inflow_damping_factor(0:nz+1) ) ENDIF READ ( 13 ) inflow_damping_factor CASE ( 'inflow_damping_height' ) READ ( 13 ) inflow_damping_height CASE ( 'inflow_damping_width' ) READ ( 13 ) inflow_damping_width 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 ( 'lad' ) READ ( 13 ) lad CASE ( 'lad_surface' ) READ ( 13 ) lad_surface CASE ( 'lad_vertical_gradient' ) READ ( 13 ) lad_vertical_gradient CASE ( 'lad_vertical_gradient_level' ) READ ( 13 ) lad_vertical_gradient_level CASE ( 'lad_vertical_gradient_level_in' ) READ ( 13 ) lad_vertical_gradient_level_ind CASE ( 'last_dt_change' ) READ ( 13 ) last_dt_change CASE ( 'leaf_surface_concentration' ) READ ( 13 ) leaf_surface_concentration CASE ( 'long_filter_factor' ) READ ( 13 ) long_filter_factor CASE ( 'loop_optimization' ) READ ( 13 ) loop_optimization CASE ( 'mean_inflow_profiles' ) IF ( .NOT. ALLOCATED( mean_inflow_profiles ) ) THEN ALLOCATE( mean_inflow_profiles(0:nz+1,5) ) ENDIF READ ( 13 ) mean_inflow_profiles CASE ( 'mixing_length_1d' ) READ ( 13 ) mixing_length_1d CASE ( 'momentum_advec' ) READ ( 13 ) momentum_advec CASE ( 'netcdf_precision' ) READ ( 13 ) netcdf_precision CASE ( 'nsor_ini' ) READ ( 13 ) nsor_ini CASE ( 'nx' ) READ ( 13 ) nx nx_on_file = nx CASE ( 'ny' ) READ ( 13 ) ny ny_on_file = ny CASE ( 'ocean' ) READ ( 13 ) ocean 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 ( 'pch_index' ) READ ( 13 ) pch_index CASE ( 'phi' ) READ ( 13 ) phi CASE ( 'plant_canopy' ) READ ( 13 ) plant_canopy CASE ( 'prandtl_layer' ) READ ( 13 ) prandtl_layer CASE ( 'precipitation' ) READ ( 13 ) precipitation CASE ( 'pt_init' ) READ ( 13 ) pt_init CASE ( 'pt_reference' ) READ ( 13 ) pt_reference 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 ( 'recycling_width' ) READ ( 13 ) recycling_width 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 ( 'run_coupled' ) READ ( 13 ) run_coupled CASE ( 'sa_init' ) READ ( 13 ) sa_init CASE ( 'sa_surface' ) READ ( 13 ) sa_surface CASE ( 'sa_vertical_gradient' ) READ ( 13 ) sa_vertical_gradient CASE ( 'sa_vertical_gradient_level' ) READ ( 13 ) sa_vertical_gradient_level CASE ( 'scalar_advec' ) READ ( 13 ) scalar_advec CASE ( 'scalar_exchange_coefficient' ) READ ( 13 ) scalar_exchange_coefficient 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_coupling' ) READ ( 13 ) time_coupling 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 ( 'time_since_reference_point' ) READ ( 13 ) time_since_reference_point CASE ( 'time_sort_particles' ) READ ( 13 ) time_sort_particles CASE ( 'timestep_scheme' ) READ ( 13 ) timestep_scheme CASE ( 'topography' ) READ ( 13 ) topography CASE ( 'topography_grid_convention' ) READ ( 13 ) topography_grid_convention CASE ( 'top_heatflux' ) READ ( 13 ) top_heatflux CASE ( 'top_momentumflux_u' ) READ ( 13 ) top_momentumflux_u CASE ( 'top_momentumflux_v' ) READ ( 13 ) top_momentumflux_v CASE ( 'top_salinityflux' ) READ ( 13 ) top_salinityflux CASE ( 'tsc' ) READ ( 13 ) tsc CASE ( 'turbulent_inflow' ) READ ( 13 ) turbulent_inflow CASE ( 'u_bulk' ) READ ( 13 ) u_bulk 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_top_fluxes' ) READ ( 13 ) use_top_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_bulk' ) READ ( 13 ) v_bulk 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 ( 'volume_flow_area' ) READ ( 13 ) volume_flow_area CASE ( 'volume_flow_initial' ) READ ( 13 ) volume_flow_initial CASE ( 'wall_adjustment' ) READ ( 13 ) wall_adjustment CASE ( 'w_max' ) READ ( 13 ) w_max CASE ( 'w_max_ijk' ) READ ( 13 ) w_max_ijk CASE DEFAULT WRITE( message_string, * ) 'unknown variable named "', & TRIM( variable_chr ), '" found in', & ' data from prior run on PE ', myid CALL message( 'read_var_list', 'PA0302', 1, 2, 0, 6, 0 ) END SELECT ! !-- Read next string READ ( 13 ) variable_chr ENDDO END SUBROUTINE read_var_list SUBROUTINE read_parts_of_var_list !------------------------------------------------------------------------------! ! Description: ! ------------ ! Skipping the global control variables from restart-file (binary format) ! except some informations needed when reading restart data from a previous ! run which used a smaller total domain or/and a different domain decomposition. !------------------------------------------------------------------------------! USE arrays_3d USE control_parameters USE indices USE pegrid USE statistics IMPLICIT NONE CHARACTER (LEN=10) :: version_on_file CHARACTER (LEN=30) :: variable_chr INTEGER :: idum, max_pr_user_on_file, nz_on_file, & statistic_regions_on_file, tmp_mpru, tmp_sr REAL, DIMENSION(:,:,:), ALLOCATABLE :: hom_sum_on_file REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: hom_on_file CALL check_open( 13 ) WRITE (9,*) 'rpovl: after check open 13' CALL local_flush( 9 ) READ ( 13 ) version_on_file ! !-- Read number of PEs and horizontal index bounds of all PEs used in previous !-- run READ ( 13 ) variable_chr IF ( TRIM( variable_chr ) /= 'numprocs' ) THEN WRITE( message_string, * ) 'numprocs not found in data from prior ', & 'run on PE ', myid CALL message( 'read_parts_of_var_list', 'PA0297', 1, 2, 0, 6, 0 ) ENDIF READ ( 13 ) numprocs_previous_run IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) ) THEN ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) ) ENDIF READ ( 13 ) variable_chr IF ( TRIM( variable_chr ) /= 'hor_index_bounds' ) THEN WRITE( message_string, * ) 'hor_index_bounds not found in data from ', & 'prior run on PE ', myid CALL message( 'read_parts_of_var_list', 'PA0298', 1, 2, 0, 6, 0 ) ENDIF READ ( 13 ) hor_index_bounds_previous_run ! !-- 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 message_string = 'nz not found in restart data file' CALL message( 'read_parts_of_var_list', 'PA0303', 1, 2, 0, 6, 0 ) ENDIF READ ( 13 ) nz_on_file IF ( nz_on_file /= nz ) THEN WRITE( message_string, * ) 'mismatch concerning number of ', & 'gridpoints along z', & '&nz on file = "', nz_on_file, '"', & '&nz from run = "', nz, '"' CALL message( 'read_parts_of_var_list', 'PA0304', 1, 2, 0, 6, 0 ) ENDIF READ ( 13 ) variable_chr IF ( TRIM( variable_chr ) /= 'max_pr_user' ) THEN message_string = 'max_pr_user not found in restart data file' CALL message( 'read_parts_of_var_list', 'PA0305', 1, 2, 0, 6, 0 ) ENDIF READ ( 13 ) max_pr_user_on_file IF ( max_pr_user_on_file /= max_pr_user ) THEN WRITE( message_string, * ) 'number of user profiles on res', & 'tart data file differs from the current ', & 'run&max_pr_user on file = "', & max_pr_user_on_file, '"', & '&max_pr_user from run = "', & max_pr_user, '"' CALL message( 'read_parts_of_var_list', 'PA0306', 0, 0, 0, 6, 0 ) tmp_mpru = MIN( max_pr_user_on_file, max_pr_user ) ELSE tmp_mpru = max_pr_user ENDIF READ ( 13 ) variable_chr IF ( TRIM( variable_chr ) /= 'statistic_regions' ) THEN message_string = 'statistic_regions not found in restart data file' CALL message( 'read_parts_of_var_list', 'PA0307', 1, 2, 0, 6, 0 ) ENDIF READ ( 13 ) statistic_regions_on_file IF ( statistic_regions_on_file /= statistic_regions ) THEN WRITE( message_string, * ) 'statistic regions on restart data file ',& 'differ from the current run', & '&statistic regions on file = "', & statistic_regions_on_file, '"', & '&statistic regions from run = "', & statistic_regions, '"', & '&statistic data may be lost!' CALL message( 'read_parts_of_var_list', 'PA0308', 0, 1, 0, 6, 0 ) tmp_sr = MIN( statistic_regions_on_file, statistic_regions ) ELSE tmp_sr = statistic_regions ENDIF ! !-- Now read and check some control parameters and skip the rest !-- The total domain of the pre-run must not be smaller than the subdomain !-- of the current run, because the mapping of data from the pre-run does !-- not work for this case. WRITE (9,*) 'wpovl: begin reading variables' CALL local_flush( 9 ) READ ( 13 ) variable_chr DO WHILE ( TRIM( variable_chr ) /= '*** end ***' ) SELECT CASE ( TRIM( variable_chr ) ) CASE ( 'average_count_pr' ) READ ( 13 ) average_count_pr IF ( average_count_pr /= 0 ) THEN WRITE( message_string, * ) 'inflow profiles not temporally ', & 'averaged. &Averaging will be done now using ', & average_count_pr, ' samples.' CALL message( 'read_parts_of_var_list', 'PA0309', & 0, 1, 0, 6, 0 ) ENDIF CASE ( 'hom' ) ALLOCATE( hom_on_file(0:nz+1,2,pr_palm+max_pr_user_on_file, & 0:statistic_regions_on_file) ) READ ( 13 ) hom_on_file hom(:,:,1:pr_palm+tmp_mpru,0:tmp_sr) = & hom_on_file(:,:,1:pr_palm+tmp_mpru,0:tmp_sr) DEALLOCATE( hom_on_file ) CASE ( 'hom_sum' ) ALLOCATE( hom_sum_on_file(0:nz+1,pr_palm+max_pr_user_on_file, & 0:statistic_regions_on_file) ) READ ( 13 ) hom_sum_on_file hom_sum(:,1:pr_palm+tmp_mpru,0:tmp_sr) = & hom_sum_on_file(:,1:pr_palm+tmp_mpru,0:tmp_sr) DEALLOCATE( hom_sum_on_file ) CASE ( 'nx' ) READ ( 13 ) nx_on_file CASE ( 'ny' ) READ ( 13 ) ny_on_file CASE DEFAULT READ ( 13 ) idum END SELECT READ ( 13 ) variable_chr ENDDO ! !-- Calculate the temporal average of vertical profiles, if neccessary IF ( average_count_pr /= 0 ) THEN hom_sum = hom_sum / REAL( average_count_pr ) ENDIF END SUBROUTINE read_parts_of_var_list SUBROUTINE skip_var_list !------------------------------------------------------------------------------! ! Description: ! ------------ ! Skipping the global control variables from restart-file (binary format) !------------------------------------------------------------------------------! IMPLICIT NONE CHARACTER (LEN=10) :: version_on_file CHARACTER (LEN=30) :: variable_chr INTEGER :: idum WRITE (9,*) 'skipvl #1' CALL local_flush( 9 ) READ ( 13 ) version_on_file WRITE (9,*) 'skipvl before variable_chr' CALL local_flush( 9 ) READ ( 13 ) variable_chr WRITE (9,*) 'skipvl after variable_chr' CALL local_flush( 9 ) DO WHILE ( TRIM( variable_chr ) /= '*** end ***' ) WRITE (9,*) 'skipvl chr = ', variable_chr CALL local_flush( 9 ) READ ( 13 ) idum READ ( 13 ) variable_chr ENDDO WRITE (9,*) 'skipvl last' CALL local_flush( 9 ) END SUBROUTINE skip_var_list