Ignore:
Timestamp:
Apr 22, 2014 3:03:56 PM (10 years ago)
Author:
boeske
Message:

large scale forcing enabled

File:
1 edited

Legend:

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

    r1343 r1365  
    2020! Current revisions:
    2121! ------------------
    22 !
    23 !
     22! Reset sums_ls_l to zero at each timestep
     23! +sums_ls_l
     24! Calculation of reference state (previously in subroutine calc_mean_profile)
     25
    2426! Former revisions:
    2527! -----------------
     
    126128
    127129    USE arrays_3d,                                                             &
    128         ONLY:  diss, e_p, nr_p, prho, pt, pt_p, ql, ql_c, ql_v, ql_vp, qr_p,   &
    129                q_p, rho, sa_p, tend, u, u_p, v, vpt, v_p, w_p
    130 
    131     USE buoyancy_mod,                                                          &
     130        ONLY:  diss, e_p, nr_p, prho, pt, pt_p, q, ql, ql_c, ql_v, ql_vp, qr_p,&
     131               q_p, ref_state, rho, sa_p, tend, u, u_p, v, vpt, v_p, w_p
     132
     133    USE calc_mean_profile_mod,                                                 &
    132134        ONLY:  calc_mean_profile
    133135
     
    149151               intermediate_timestep_count_max, large_scale_forcing,           &
    150152               loop_optimization, lsf_surf, lsf_vert, masks, mid,              &
    151                netcdf_data_format, neutral, nr_timesteps_this_run, ocean,      &
    152                on_device, passive_scalar, prandtl_layer, precipitation,        &
     153               netcdf_data_format, neutral, nr_timesteps_this_run, nudging,    &
     154               ocean, on_device, passive_scalar, prandtl_layer, precipitation, &
    153155               prho_reference, pt_reference, pt_slope_offset, random_heatflux, &
    154156               run_coupled, simulated_time, simulated_time_chr,                &
     
    181183        ONLY:  ls_forcing_surf, ls_forcing_vert
    182184
     185    USE nudge_mod,                                                             &
     186        ONLY:  calc_tnudge
     187
    183188    USE particle_attributes,                                                   &
    184189        ONLY:  particle_advection, particle_advection_start, wang_kernel
     
    194199
    195200    USE statistics,                                                            &
    196         ONLY:  flow_statistics_called, hom, pr_palm
     201        ONLY:  flow_statistics_called, hom, pr_palm, sums_ls_l
    197202
    198203    USE user_actions_mod,                                                      &
     
    253258!--    Determine ug, vg and w_subs in dependence on data from external file
    254259!--    LSF_DATA
    255        IF ( large_scale_forcing .AND. lsf_vert ) THEN
     260       IF ( large_scale_forcing .AND. lsf_vert )  THEN
    256261           CALL ls_forcing_vert ( simulated_time )
     262           sums_ls_l = 0.0_wp
    257263       ENDIF
    258264
     
    283289!--          buoyancy terms (WARNING: only the respective last call of
    284290!--          calc_mean_profile defines the reference state!)
    285              IF ( .NOT. neutral )  CALL calc_mean_profile( pt, 4, 'time_int' )
    286              IF ( ocean         )  CALL calc_mean_profile( rho, 64, 'time_int' )
    287              IF ( humidity      )  CALL calc_mean_profile( vpt, 44, 'time_int' )
     291             IF ( .NOT. neutral )  THEN
     292                CALL calc_mean_profile( pt, 4 )
     293                ref_state(:)  = hom(:,1,4,0) ! this is used in the buoyancy term
     294             ENDIF
     295             IF ( ocean )  THEN
     296                CALL calc_mean_profile( rho, 64 )
     297                ref_state(:)  = hom(:,1,64,0)
     298             ENDIF
     299             IF ( humidity )  THEN
     300                CALL calc_mean_profile( vpt, 44 )
     301                ref_state(:)  = hom(:,1,44,0)
     302             ENDIF
     303
    288304          ENDIF
    289305
     
    291307          IF ( ( ws_scheme_mom .OR. ws_scheme_sca )  .AND.  &
    292308               intermediate_timestep_count == 1 )  CALL ws_statistics
     309!
     310!--       In case of nudging calculate current nudging time scale and horizontal
     311!--       means of u,v,pt and q
     312          IF ( nudging )  THEN
     313             CALL calc_tnudge( simulated_time )
     314             CALL calc_mean_profile( u, 1 )
     315             CALL calc_mean_profile( v, 2 )
     316             CALL calc_mean_profile( pt, 4 )
     317             CALL calc_mean_profile( q, 41 )
     318          ENDIF
    293319
    294320!
Note: See TracChangeset for help on using the changeset viewer.