Ignore:
Timestamp:
Sep 13, 2012 2:08:46 PM (12 years ago)
Author:
raasch
Message:

leapfrog timestep scheme and upstream-spline advection scheme completely removed from the code,
reading of dt_fixed from restart file removed

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/modules.f90

    r997 r1001  
    44! Current revisions:
    55! -----------------
    6 !
     6! -asselin_filter_factor, cut_spline_overshoot, dt_changed, last_dt_change,
     7! last_dt_change_1d, long_filter_factor, overshoot_limit_*, ups_limit_*
     8! several pointer/target arrays converted to normal ones
    79!
    810! Former revisions:
     
    343345          diss_s_v, diss_s_w, dzu_mg, dzw_mg, flux_s_e, flux_s_pt, flux_s_q,   &
    344346          flux_s_sa, flux_s_u, flux_s_v, flux_s_w, f1_mg, f2_mg, f3_mg,        &
    345           mean_inflow_profiles, pt_slope_ref, qs, qswst_remote, total_2d_a,    &
    346           total_2d_o, ts, us, z0, z0h
    347 
    348     REAL, DIMENSION(:,:), ALLOCATABLE, TARGET ::                               &
    349           qsws_1, qsws_2, qswst_1, qswst_2, rif_1, rif_2, saswsb_1, saswst_1,  &
    350           shf_1, shf_2, tswst_1, tswst_2, usws_1, usws_2, uswst_1, uswst_2,    &
    351           vsws_1, vsws_2, vswst_1, vswst_2
    352 
    353     REAL, DIMENSION(:,:), POINTER ::                                           &
    354           qsws, qsws_m, qswst, qswst_m, rif, rif_m, saswsb, saswst, shf,       &
    355           shf_m, tswst, tswst_m, usws, uswst, usws_m, uswst_m, vsws, vswst,    &
    356           vsws_m, vswst_m
     347          mean_inflow_profiles, pt_slope_ref, qs, qsws, qswst, qswst_remote,   &
     348          rif, saswsb, saswst, shf, total_2d_a, total_2d_o, ts, tswst, us,     &
     349          usws, uswst, vsws, vswst, z0, z0h
    357350
    358351    REAL, DIMENSION(:,:,:), ALLOCATABLE ::                                     &
     
    360353          diss_l_pt, diss_l_q, diss_l_sa, diss_l_u, diss_l_v, diss_l_w,        &
    361354          flux_l_e, flux_l_pt, flux_l_q, flux_l_sa, flux_l_u, flux_l_v,        &
    362           flux_l_w, lad_s, lad_u, lad_v, lad_w, lai, l_wall, p_loc, sec, sls,  &
    363           tend, u_m_l, u_m_n, u_m_r, u_m_s, v_m_l, v_m_n, v_m_r, v_m_s, w_m_l, &
    364           w_m_n, w_m_r, w_m_s
     355          flux_l_w, kh, km, lad_s, lad_u, lad_v, lad_w, lai, l_wall, p_loc,    &
     356          sec, sls, tend, u_m_l, u_m_n, u_m_r, u_m_s, v_m_l, v_m_n, v_m_r,    &
     357          v_m_s, w_m_l, w_m_n, w_m_r, w_m_s
    365358
    366359    REAL, DIMENSION(:,:,:), ALLOCATABLE, TARGET ::                             &
    367           ql_v, ql_vp
    368 
    369     REAL, DIMENSION(:,:,:), ALLOCATABLE, TARGET ::                             &
    370           e_1, e_2, e_3, kh_1, kh_2, km_1, km_2, p, prho_1, pt_1, pt_2, pt_3,  &
    371           q_1, q_2, q_3, ql_1, ql_2, rho_1, sa_1, sa_2, sa_3, u_1, u_2, u_3,   &
    372           v_1, v_2, v_3, vpt_1, vpt_2, w_1, w_2, w_3
     360          e_1, e_2, e_3, p, prho_1, pt_1, pt_2, pt_3, q_1, q_2, q_3, ql_v,     &
     361          ql_vp, ql_1, ql_2, rho_1, sa_1, sa_2, sa_3, u_1, u_2, u_3,           &
     362          v_1, v_2, v_3, vpt_1, w_1, w_2, w_3
    373363
    374364    REAL, DIMENSION(:,:,:), POINTER ::                                         &
    375           e, e_m, e_p, kh, kh_m, km, km_m, prho, pt, pt_m, pt_p, q, q_m, q_p,  &
    376           ql, ql_c, rho, sa, sa_p, te_m, tpt_m, tq_m, tsa_m, tu_m, tv_m, tw_m, &
    377           u, u_m, u_p, v, v_m, v_p, vpt, vpt_m, w, w_m, w_p
     365          e, e_p, prho, pt, pt_p, q, q_p, ql, ql_c, rho, sa, sa_p, te_m,       &
     366          tpt_m, tq_m, tsa_m, tu_m, tv_m, tw_m, u, u_p, v, v_p, vpt, w, w_p
    378367
    379368    REAL, DIMENSION(:,:,:,:), ALLOCATABLE ::  rif_wall
     
    555544                intermediate_timestep_count, intermediate_timestep_count_max, &
    556545                io_group = 0, io_blocks = 1, iran = -1234567, &
    557                 last_dt_change = 0, masks = 0, maximum_grid_level, &
     546                masks = 0, maximum_grid_level, &
    558547                maximum_parallel_io_streams = -1, max_pr_user = 0, &
    559548                mgcycles = 0, mg_cycles = -1, mg_switch_to_pe0_level = 0, mid, &
     
    605594                constant_top_salinityflux = .TRUE., &
    606595                constant_waterflux = .TRUE., create_disturbances = .TRUE., &
    607                 cut_spline_overshoot = .TRUE., &
    608596                data_output_2d_on_each_pe = .TRUE., &
    609597                dissipation_control = .FALSE., disturbance_created = .FALSE., &
    610598                do2d_at_begin = .FALSE., do3d_at_begin = .FALSE., &
    611599                do3d_compress = .FALSE., do_sum = .FALSE., &
    612                 dp_external = .FALSE., dp_smooth = .FALSE., &
    613                 dt_changed = .FALSE., dt_fixed = .FALSE., &
     600                dp_external = .FALSE., dp_smooth = .FALSE., dt_fixed = .FALSE., &
    614601                dt_3d_reached, dt_3d_reached_l, exchange_mg = .FALSE., &
    615602                first_call_lpm = .TRUE., &
     
    640627
    641628    REAL ::  advected_distance_x = 0.0, advected_distance_y = 0.0, &
    642              alpha_surface = 0.0, asselin_filter_factor = 0.1, &
    643              atmos_ocean_sign = 1.0, &
     629             alpha_surface = 0.0, atmos_ocean_sign = 1.0, &
    644630             averaging_interval = 0.0, averaging_interval_pr = 9999999.9, &
    645631             averaging_interval_sp = 9999999.9, bc_pt_t_val, bc_q_t_val, &
     
    671657             f = 0.0, fs = 0.0, g = 9.81, inflow_damping_height = 9999999.9, &
    672658             inflow_damping_width = 9999999.9, kappa = 0.4, km_constant = -1.0,&
    673              lad_surface = 0.0,  &
    674              leaf_surface_concentration = 0.0, long_filter_factor = 0.0, &
     659             lad_surface = 0.0, leaf_surface_concentration = 0.0, &
    675660             mask_scale_x = 1.0, mask_scale_y = 1.0, mask_scale_z = 1.0, &
    676661             maximum_cpu_time_allowed = 0.0,  &
    677662             molecular_viscosity = 1.461E-5, &
    678663             old_dt = 1.0E-10, omega = 7.29212E-5, omega_sor = 1.8, &
    679              overshoot_limit_e = 0.0, overshoot_limit_pt = 0.0, &
    680              overshoot_limit_u = 0.0, overshoot_limit_v = 0.0, &
    681              overshoot_limit_w = 0.0, particle_maximum_age = 9999999.9, &
     664             particle_maximum_age = 9999999.9, &
    682665             phi = 55.0, prandtl_number = 1.0, &
    683666             precipitation_amount_interval = 9999999.9, prho_reference, &
     
    710693             top_momentumflux_v = 9999999.9, top_salinityflux = 9999999.9, &
    711694             ug_surface = 0.0, u_bulk = 0.0, u_gtrans = 0.0, &
    712              ups_limit_e = 0.0, ups_limit_pt = 0.0, ups_limit_u = 0.0, &
    713              ups_limit_v = 0.0, ups_limit_w = 0.0, vg_surface = 0.0, &
     695             vg_surface = 0.0, &
    714696             v_bulk = 0.0, v_gtrans = 0.0, wall_adjustment_factor = 1.8, &
    715697             z_max_do2d = -1.0, z0h_factor = 1.0
     
    730712             skip_time_domask(max_masks) = 9999999.9, threshold(20) = 0.0, &
    731713             time_domask(max_masks) = 0.0, &
    732              tsc(10) = (/ 0.0, 1.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 /), &
     714             tsc(10) = (/ 1.0, 1.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 /), &
    733715             u_profile(100) = 9999999.9, uv_heights(100) = 9999999.9, &
    734716             v_profile(100) = 9999999.9, &
     
    10601042!------------------------------------------------------------------------------!
    10611043
    1062     INTEGER ::  current_timestep_number_1d = 0, damp_level_ind_1d, &
    1063                 last_dt_change_1d = 0
     1044    INTEGER ::  current_timestep_number_1d = 0, damp_level_ind_1d
    10641045
    10651046    LOGICAL ::  run_control_header_1d = .FALSE., stop_dt_1d = .FALSE.
     
    10691050                end_time_1d = 864000.0, old_dt_1d = 1.0E-10, &
    10701051                qs1d, simulated_time_1d = 0.0, time_pr_1d = 0.0, &
    1071                 time_run_control_1d = 0.0, ts1d, us1d, usws1d, usws1d_m, &
    1072                 vsws1d, vsws1d_m, z01d, z0h1d
    1073 
    1074 
    1075     REAL, DIMENSION(:), ALLOCATABLE ::  e1d, e1d_m, e1d_p, kh1d, kh1d_m, km1d, &
    1076                                         km1d_m, l_black, l1d, l1d_m, rif1d,    &
    1077                                         te_e, te_em, te_u, te_um, te_v, te_vm, &
    1078                                         u1d, u1d_m, u1d_p, v1d, v1d_m, v1d_p
     1052                time_run_control_1d = 0.0, ts1d, us1d, usws1d, &
     1053                vsws1d, z01d, z0h1d
     1054
     1055
     1056    REAL, DIMENSION(:), ALLOCATABLE ::  e1d, e1d_p, kh1d, km1d, l_black, l1d,  &
     1057                                        rif1d, te_e, te_em, te_u, te_um, te_v, &
     1058                                        te_vm, u1d, u1d_p, v1d, v1d_p
    10791059
    10801060    SAVE
Note: See TracChangeset for help on using the changeset viewer.