Ignore:
Timestamp:
Feb 23, 2007 4:53:48 AM (17 years ago)
Author:
raasch
Message:

preliminary version of modified boundary conditions at top

File:
1 edited

Legend:

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

    r4 r19  
    55! Actual revisions:
    66! -----------------
    7 !
     7! +constant_top_heatflux, top_heatflux, use_top_fluxes, +arrays for top fluxes,
     8! +nzt_diff, default of bc_pt_t renamed "initial_gradient"
     9! Bugfix: p is not a pointer
    810!
    911! Former revisions:
     
    7577
    7678    REAL, DIMENSION(:,:), ALLOCATABLE, TARGET ::                               &
    77           qsws_1, qsws_2, rif_1, rif_2, shf_1, shf_2, usws_1, usws_2,          &
    78           vsws_1, vsws_2
     79          qsws_1, qsws_2, qswst_1, qswst_2, rif_1, rif_2, shf_1, shf_2,        &
     80          tswst_1, tswst_2, usws_1, usws_2, vsws_1, vsws_2
    7981
    8082    REAL, DIMENSION(:,:), POINTER ::                                           &
    81           qsws, qsws_m, rif, rif_m, shf, shf_m, usws, usws_m, vsws, vsws_m
     83          qsws, qsws_m, qswst, qswst_m, rif, rif_m, shf, shf_m, tswst,         &
     84          tswst_m, usws, usws_m, vsws, vsws_m
    8285
    8386    REAL, DIMENSION(:,:,:), ALLOCATABLE ::                                     &
     
    8891
    8992    REAL, DIMENSION(:,:,:), ALLOCATABLE, TARGET ::                             &
    90           e_1, e_2, e_3, kh_1, kh_2, km_1, km_2, pt_1, pt_2, pt_3, q_1, q_2,   &
    91           q_3, ql_1, ql_2, u_1, u_2, u_3, v_1, v_2, v_3, vpt_1, vpt_2, w_1,    &
    92           w_2, w_3
     93          e_1, e_2, e_3, kh_1, kh_2, km_1, km_2, p, pt_1, pt_2, pt_3, q_1,     &
     94          q_2, q_3, ql_1, ql_2, u_1, u_2, u_3, v_1, v_2, v_3, vpt_1, vpt_2,    &
     95          w_1, w_2, w_3
    9396
    9497    REAL, DIMENSION(:,:,:), POINTER ::                                         &
    95           e, e_m, e_p, kh, kh_m, km, km_m, p, pt, pt_m, pt_p, q, q_m, q_p, ql, &
     98          e, e_m, e_p, kh, kh_m, km, km_m, pt, pt_m, pt_p, q, q_m, q_p, ql,    &
    9699          ql_c, te_m, tpt_m, tq_m, tu_m, tv_m, tw_m, u, u_m, u_p, v, v_m, v_p, &
    97100          vpt, vpt_m, w, w_m, w_p
     
    201204                            scalar_advec = 'pw-scheme'
    202205    CHARACTER (LEN=20)  ::  bc_e_b = 'neumann', bc_lr = 'cyclic', &
    203                             bc_ns = 'cyclic', &
    204                             bc_p_b = 'neumann', bc_p_t = 'dirichlet', &
    205                             bc_pt_b = 'dirichlet', bc_pt_t = 'neumann', &
     206                            bc_ns = 'cyclic', bc_p_b = 'neumann', &
     207                            bc_p_t = 'dirichlet', bc_pt_b = 'dirichlet', &
     208                            bc_pt_t = 'initial_gradient', &
    206209                            bc_q_b = 'dirichlet', bc_q_t = 'neumann', &
    207210                            bc_s_b = 'dirichlet', bc_s_t = 'neumann', &
     
    263266                cloud_droplets = .FALSE., cloud_physics = .FALSE., &
    264267                conserve_volume_flow = .FALSE., constant_diffusion = .FALSE., &
    265                 constant_heatflux = .TRUE., constant_waterflux = .TRUE., &
    266                 create_disturbances = .TRUE., cut_spline_overshoot = .TRUE., &
     268                constant_heatflux = .TRUE., constant_top_heatflux = .TRUE., &
     269                constant_waterflux = .TRUE., create_disturbances = .TRUE., &
     270                cut_spline_overshoot = .TRUE., &
    267271                data_output_2d_on_each_pe = .TRUE., do2d_at_begin = .FALSE., &
    268272                do3d_at_begin = .FALSE., do3d_compress = .FALSE., &
     
    270274                disturbance_created = .FALSE., &
    271275                first_call_advec_particles = .TRUE., &
    272                 force_print_header = .FALSE., galilei_transformation = .FALSE., &
     276                force_print_header = .FALSE., galilei_transformation = .FALSE.,&
    273277                inflow_l = .FALSE., inflow_n = .FALSE., inflow_r = .FALSE., &
    274278                inflow_s = .FALSE., iso2d_output = .FALSE., &
     
    281285                random_heatflux = .FALSE., run_control_header = .FALSE., &
    282286                sloping_surface = .FALSE., stop_dt = .FALSE., &
    283                 terminate_run = .FALSE., use_prior_plot1d_parameters = .FALSE., &
    284                 use_surface_fluxes = .FALSE., use_ug_for_galilei_tr = .TRUE., &
     287                terminate_run = .FALSE., use_prior_plot1d_parameters = .FALSE.,&
     288                use_surface_fluxes = .FALSE., use_top_fluxes = .FALSE., &
     289                use_ug_for_galilei_tr = .TRUE., &
    285290                use_upstream_for_tke = .FALSE., wall_adjustment = .TRUE.
    286291
     
    336341             time_do_sla = 0.0, time_dvrp = 0.0, time_prel = 0.0, &
    337342             time_restart = 9999999.9, time_run_control = 0.0, &
    338              ug_surface = 0.0, u_gtrans = 0.0, ups_limit_e = 0.0, &
    339              ups_limit_pt = 0.0, ups_limit_u = 0.0, ups_limit_v = 0.0, &
    340              ups_limit_w = 0.0, vg_surface = 0.0, v_gtrans = 0.0, &
    341              wall_adjustment_factor = 1.8, z_max_do1d = -1.0, &
     343             top_heatflux = 9999999.9, ug_surface = 0.0, u_gtrans = 0.0, &
     344             ups_limit_e = 0.0, ups_limit_pt = 0.0, ups_limit_u = 0.0, &
     345             ups_limit_v = 0.0, ups_limit_w = 0.0, vg_surface = 0.0, &
     346             v_gtrans = 0.0, wall_adjustment_factor = 1.8, z_max_do1d = -1.0, &
    342347             z_max_do1d_normalized = -1.0, z_max_do2d = -1.0
    343348
     
    500505    INTEGER ::  ngp_sums, nnx, nx = 0, nxa, nxl, nxr, nxra, nny, ny = 0, nya,  &
    501506                nyn, nyna, nys, nnz, nz = 0, nza, nzb, nzb_diff, nzt, nzta,    &
    502                 uxrp = 0, vynp = 0
     507                nzt_diff, uxrp = 0, vynp = 0
    503508
    504509    INTEGER, DIMENSION(:), ALLOCATABLE ::                                      &
Note: See TracChangeset for help on using the changeset viewer.