Ignore:
Timestamp:
Apr 28, 2014 12:40:45 PM (10 years ago)
Author:
heinze
Message:

Upper boundary conditions for pt and q in case of nudging adjusted

File:
1 edited

Legend:

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

    r1366 r1380  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! CALL of nudge_ref added
     23! bc_pt_t_val and bc_q_t_val are updated in case nudging is used
    2324!
    2425! Former revisions:
     
    131132
    132133    USE arrays_3d,                                                             &
    133         ONLY:  diss, e_p, nr_p, prho, pt, pt_p, q, ql, ql_c, ql_v, ql_vp, qr_p,&
    134                q_p, ref_state, rho, sa_p, tend, u, u_p, v, vpt, v_p, w_p
     134        ONLY:  diss, dzu, e_p, nr_p, prho, pt, pt_p, pt_init, q_init, q, ql,   &
     135               ql_c, ql_v, ql_vp, qr_p, q_p, ref_state, rho, sa_p, tend, u,    &
     136               u_p, v, vpt, v_p, w_p
    135137
    136138    USE calc_mean_profile_mod,                                                 &
     
    140142        ONLY:  advected_distance_x, advected_distance_y, average_count_3d,     &
    141143               average_count_sp, averaging_interval, averaging_interval_pr,    &
    142                averaging_interval_sp, bc_lr_cyc, bc_ns_cyc,                    &
    143                call_psolver_at_all_substeps, cloud_droplets, cloud_physics,    &
    144                constant_heatflux, create_disturbances, dopr_n,                 &
     144               averaging_interval_sp, bc_lr_cyc, bc_ns_cyc, bc_pt_t_val,       &
     145               bc_q_t_val, call_psolver_at_all_substeps, cloud_droplets,       &
     146               cloud_physics, constant_heatflux, create_disturbances, dopr_n,  &
    145147               constant_diffusion, coupling_mode, coupling_start_time,         &
    146148               current_timestep_number, disturbance_created,                   &
     
    176178    USE indices,                                                               &
    177179        ONLY:  i_left, i_right, j_north, j_south, nbgp, nx, nxl, nxlg, nxr,    &
    178                nxrg, nyn, nys, nzb, nzb_u_inner, nzb_v_inner
     180               nxrg, nyn, nys, nzb, nzt, nzb_u_inner, nzb_v_inner
    179181
    180182    USE interaction_droplets_ptq_mod,                                          &
     
    187189
    188190    USE nudge_mod,                                                             &
    189         ONLY:  calc_tnudge
     191        ONLY:  calc_tnudge, nudge_ref
    190192
    191193    USE particle_attributes,                                                   &
     
    267269
    268270!
     271!--    Set pt_init and q_init to the current profiles taken from
     272!--    NUDGING_DATA
     273       IF ( nudging )  THEN
     274           CALL nudge_ref ( simulated_time )
     275!
     276!--        Store temperature gradient at the top boundary for possible Neumann
     277!--        boundary condition
     278           bc_pt_t_val = ( pt_init(nzt+1) - pt_init(nzt) ) / dzu(nzt+1)
     279           bc_q_t_val  = ( q_init(nzt+1) - q_init(nzt) ) / dzu(nzt+1)
     280       ENDIF
     281
     282!
    269283!--    Execute the user-defined actions
    270284       CALL user_actions( 'before_timestep' )
     
    312326!
    313327!--       In case of nudging calculate current nudging time scale and horizontal
    314 !--       means of u,v,pt and q
     328!--       means of u, v, pt and q
    315329          IF ( nudging )  THEN
    316330             CALL calc_tnudge( simulated_time )
Note: See TracChangeset for help on using the changeset viewer.