Ignore:
Timestamp:
Oct 30, 2013 11:36:58 AM (10 years ago)
Author:
heinze
Message:

Nudging and large scale forcing from external file implemented

File:
1 edited

Legend:

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

    r1240 r1241  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! Usage of nudging enabled
     23! +nudging, ntnudge, ptnudge, qnudge, tnudge, unudge, vnudge, wnudge
     24! increase pr_palm from 80 to 90 to allow for more standard profiles
     25!
     26! Enable prescribed time depenend surface fluxes and geostrophic wind read in
     27! from external file LSF_DATA
     28! +large_scale_forcing, lsf_surf, lsf_vert, nlsf, time_surf, shf_surf, qsws_surf,
     29!  pt_surf, q_surf, p_surf, time_vert, ug_vert, vg_vert, wsubs_vert
    2330!
    2431! Former revisions:
     
    434441          c_u_m, c_u_m_l, c_v_m, c_v_m_l, c_w_m, c_w_m_l, ddzu, ddzu_pres,     &
    435442          dd2zu, dzu, ddzw, dzw, hyp, inflow_damping_factor, lad, l_grid,      &
    436           nc_1d, nr_1d, ptdf_x, ptdf_y, pt_1d, pt_init, q_1d, q_init, qc_1d,   &
    437           qr_1d, rdf, rdf_sc, ref_state, sa_init, ug, u_init,                  &
    438           u_nzb_p1_for_vfc, vg, v_init, v_nzb_p1_for_vfc, w_subs, zu, zw
     443          nc_1d, nr_1d, ptdf_x, ptdf_y, p_surf, pt_surf, pt_1d, pt_init,       &
     444          qsws_surf, q_1d, q_init, q_surf, qc_1d, qr_1d, rdf, rdf_sc,          &
     445          ref_state, sa_init, shf_surf, timenudge, time_surf, time_vert, ug,   &
     446          u_init, u_nzb_p1_for_vfc, vg, v_init, v_nzb_p1_for_vfc, w_subs, zu, zw
    439447
    440448    REAL, DIMENSION(:,:), ALLOCATABLE ::                                       &
     
    443451          flux_s_e, flux_s_nr, flux_s_pt, flux_s_q, flux_s_qr, flux_s_sa,      &
    444452          flux_s_u, flux_s_v, flux_s_w, f1_mg, f2_mg, f3_mg,                   &
    445           mean_inflow_profiles, nrs, nrsws, nrswst, pt_slope_ref, qs, qsws,    &
    446           qswst, qswst_remote, qrs, qrsws, qrswst, rif, saswsb, saswst, shf,   &
    447           total_2d_a, total_2d_o, ts, tswst, us, usws, uswst, vsws, vswst, z0, &
    448           z0h
     453          mean_inflow_profiles, nrs, nrsws, nrswst, ptnudge, pt_slope_ref,     &
     454          qnudge, qs, qsws, qswst, qswst_remote, qrs, qrsws, qrswst, rif,      &
     455          saswsb, saswst, shf, tnudge, total_2d_a, total_2d_o, ts, tswst,      &
     456          ug_vert, unudge, us, usws, uswst, vnudge, vg_vert, vsws, vswst,      &
     457          wnudge, wsubs_vert, z0, z0h
    449458
    450459    REAL, DIMENSION(:,:,:), ALLOCATABLE ::                                     &
     
    478487    REAL, DIMENSION(:,:,:), ALLOCATABLE :: var_x, var_y, var_z, gamma_x,       &
    479488                                           gamma_y, gamma_z
     489
    480490
    481491    SAVE
     
    715725                maximum_parallel_io_streams = -1, max_pr_user = 0, &
    716726                mgcycles = 0, mg_cycles = -1, mg_switch_to_pe0_level = 0, mid, &
    717                 netcdf_data_format = 2, ngsrb = 2, nr_timesteps_this_run = 0, &
     727                nlsf = 1000, ntnudge = 100, netcdf_data_format = 2, ngsrb = 2, &
     728                nr_timesteps_this_run = 0, &
    718729                nsor = 20, nsor_ini = 100, n_sor, normalizing_region = 0, &
    719730                nz_do3d = -9999, pch_index = 0, prt_time_count = 0, &
     
    772783                inflow_l = .FALSE., inflow_n = .FALSE., &
    773784                inflow_r = .FALSE., inflow_s = .FALSE., &
    774                 iso2d_output = .FALSE., large_scale_subsidence = .FALSE., &
     785                iso2d_output = .FALSE., large_scale_forcing = .FALSE., &
     786                large_scale_subsidence = .FALSE., lsf_surf = .TRUE., &
     787                lsf_vert = .TRUE., lptnudge = .FALSE., lqnudge = .FALSE., &
     788                lunudge = .FALSE., lvnudge = .FALSE., lwnudge = .FALSE., &
    775789                masking_method = .FALSE., mg_switch_to_pe0 = .FALSE., &
    776                 netcdf_output = .FALSE., neutral = .FALSE., ocean = .FALSE., &
    777                 on_device = .FALSE., &
     790                netcdf_output = .FALSE., neutral = .FALSE., nudging = .FALSE., &
     791                ocean = .FALSE., on_device = .FALSE., &
    778792                outflow_l = .FALSE., outflow_n = .FALSE., outflow_r = .FALSE., &
    779793                outflow_s = .FALSE., passive_scalar = .FALSE., &
     
    16611675
    16621676    CHARACTER (LEN=40) ::  region(0:9)
    1663     INTEGER ::  pr_palm = 80, statistic_regions = 0
     1677    INTEGER ::  pr_palm = 90, statistic_regions = 0
    16641678    INTEGER ::  u_max_ijk(3), v_max_ijk(3), w_max_ijk(3)
    16651679    LOGICAL ::  flow_statistics_called = .FALSE.
Note: See TracChangeset for help on using the changeset viewer.