Changeset 151 for palm/trunk/SOURCE/modules.f90
- Timestamp:
- Mar 7, 2008 1:42:18 PM (17 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/modules.f90
r150 r151 5 5 ! Actual revisions: 6 6 ! ----------------- 7 ! +hor_index_bounds, hor_index_bounds_previous_run, numprocs_previous_run, 8 ! nx_on_file, ny_on_file, offset_ocean_* 7 ! +hor_index_bounds, hor_index_bounds_previous_run, id_inflow, 8 ! inflow_damping_*, mean_inflow_profiles, numprocs_previous_run, nx_on_file, 9 ! ny_on_file, offset_ocean_*, recycling_plane, recycling_width, turbulent_inflow 9 10 ! -myid_char_14 10 11 ! … … 115 116 116 117 REAL, DIMENSION(:), ALLOCATABLE :: & 117 ddzu, dd2zu, dzu, ddzw, dzw, hyp, km_damp_x, km_damp_y, lad, l_grid,&118 pt_init, q_init, rdf, sa_init, ug, u_init, u_nzb_p1_for_vfc, vg,&119 v_init, v_nzb_p1_for_vfc, zu, zw118 ddzu, dd2zu, dzu, ddzw, dzw, hyp, inflow_damping_factor, km_damp_x, & 119 km_damp_y, lad, l_grid, pt_init, q_init, rdf, sa_init, ug, u_init, & 120 u_nzb_p1_for_vfc, vg, v_init, v_nzb_p1_for_vfc, zu, zw 120 121 121 122 REAL, DIMENSION(:,:), ALLOCATABLE :: & 122 c_u, c_v, c_w, dzu_mg, dzw_mg, f1_mg, f2_mg, f3_mg, pt_slope_ref,&123 qs, qswst_remote, ts, us, z0123 c_u, c_v, c_w, dzu_mg, dzw_mg, f1_mg, f2_mg, f3_mg, & 124 mean_inflow_profiles, pt_slope_ref, qs, qswst_remote, ts, us, z0 124 125 125 126 REAL, DIMENSION(:,:), ALLOCATABLE, TARGET :: & … … 309 310 nsor_ini = 100, n_sor, normalizing_region = 0, & 310 311 nz_do1d, nz_do3d = -9999, outflow_damping_width = -1, & 311 prt_time_count = 0, r unnr = 0, skip_do_avs= 0, &312 terminate_coupled = 0, terminate_coupled_remote= 0, &313 t imestep_count = 0312 prt_time_count = 0, recycling_plane, runnr = 0, & 313 skip_do_avs = 0, terminate_coupled = 0, & 314 terminate_coupled_remote = 0, timestep_count = 0 314 315 315 316 INTEGER :: dist_nxl(0:1), dist_nxr(0:1), dist_nyn(0:1), dist_nys(0:1), & … … 357 358 random_heatflux = .FALSE., run_control_header = .FALSE., & 358 359 sloping_surface = .FALSE., stop_dt = .FALSE., & 359 terminate_run = .FALSE., use_prior_plot1d_parameters = .FALSE.,& 360 use_reference = .FALSE., use_surface_fluxes = .FALSE., & 361 use_top_fluxes = .FALSE., use_ug_for_galilei_tr = .TRUE., & 362 use_upstream_for_tke = .FALSE., wall_adjustment = .TRUE. 360 terminate_run = .FALSE., turbulent_inflow = .FALSE., & 361 use_prior_plot1d_parameters = .FALSE., use_reference = .FALSE.,& 362 use_surface_fluxes = .FALSE., use_top_fluxes = .FALSE., & 363 use_ug_for_galilei_tr = .TRUE., use_upstream_for_tke = .FALSE.,& 364 wall_adjustment = .TRUE. 363 365 364 366 LOGICAL :: data_output_xy(0:1) = .FALSE., data_output_xz(0:1) = .FALSE., & … … 392 394 dz_stretch_level = 100000.0, e_init = 0.0, e_min = 0.0, & 393 395 end_time = 0.0, & 394 f = 0.0, fs = 0.0, g = 9.81, kappa = 0.4, km_constant = -1.0, & 396 f = 0.0, fs = 0.0, g = 9.81, inflow_damping_height = 9999999.9, & 397 inflow_damping_width = 9999999.9, kappa = 0.4, km_constant = -1.0,& 395 398 km_damp_max = -1.0, lad_surface = 0.0, long_filter_factor = 0.0, & 396 399 maximum_cpu_time_allowed = 0.0, molecular_viscosity = 1.461E-5, & … … 405 408 q_surface = 0.0, q_surface_initial_change = 0.0, & 406 409 rayleigh_damping_factor = -1.0, rayleigh_damping_height = -1.0, & 407 residual_limit = 1.0E-4, restart_time = 9999999.9, rho_reference, & 408 rho_surface, rif_max = 1.0, & 410 recycling_width = 9999999.9, residual_limit = 1.0E-4, & 411 restart_time = 9999999.9, rho_reference, rho_surface, & 412 rif_max = 1.0, & 409 413 rif_min = -5.0, roughness_length = 0.1, sa_surface = 35.0, & 410 414 simulated_time = 0.0, simulated_time_at_begin, sin_alpha_surface, & … … 961 965 #endif 962 966 CHARACTER(LEN=5) :: myid_char = '' 963 INTEGER :: myid=0, npex = -1, npey = -1, numprocs = 1,&964 numprocs _previous_run = -1,&967 INTEGER :: id_inflow, myid=0, npex = -1, npey = -1, & 968 numprocs = 1, numprocs_previous_run = -1, & 965 969 tasks_per_node = -9999, threads_per_task = 1 966 970
Note: See TracChangeset
for help on using the changeset viewer.