Ignore:
Timestamp:
Oct 26, 2015 4:17:44 PM (9 years ago)
Author:
maronga
Message:

various bugfixes and modifications of the atmosphere-land-surface-radiation interaction. Completely re-written routine to calculate surface fluxes (surface_layer_fluxes.f90) that replaces prandtl_fluxes. Minor formatting corrections and renamings

File:
1 edited

Legend:

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

    r1683 r1691  
    1414! PALM. If not, see <http://www.gnu.org/licenses/>.
    1515!
    16 ! Copyright 1997-2014 Leibniz Universitaet Hannover
     16! Copyright 1997-2015 Leibniz Universitaet Hannover
    1717!--------------------------------------------------------------------------------!
    1818!
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Renamed Obukhov length. Added ol, removed rif. Increased number of profiles
     22! (pr_palm). Changed default values for dissipation_1d to 'detering' and
     23! (mixing_length_1d to 'blackadar'. Added most_method. rif_min and rif_max
     24! renamed to zeta_min and zeta_max and new values assigned.
    2225!
    2326! Former revisions:
     
    300303!
    301304!
     305!------------------------------------------------------------------------------!
     306! Description:
     307! ------------
     308!> Definition of all variables
     309!>
     310!> @todo Add description for each variable
     311!------------------------------------------------------------------------------!
     312
     313
     314!------------------------------------------------------------------------------!
    302315! Description:
    303316! ------------
     
    338351          flux_s_e, flux_s_nr, flux_s_pt, flux_s_q, flux_s_qr, flux_s_sa,      &
    339352          flux_s_u, flux_s_v, flux_s_w, f1_mg, f2_mg, f3_mg,                   &
    340           mean_inflow_profiles, nrs, nrsws, nrswst, ptnudge, pt_slope_ref,     &
     353          mean_inflow_profiles, nrs, nrsws, nrswst,                            &
     354          ol,                                                                  & !< Obukhov length
     355          ptnudge, pt_slope_ref,                                               &
    341356          qnudge, qs, qsws, qswst, qswst_remote, qrs, qrsws, qrswst, rif,      &
    342357          saswsb, saswst, shf, tnudge, td_lsa_lpt, td_lsa_q, td_sub_lpt,       &
     
    390405    USE kinds
    391406
    392     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  lwp_av, precipitation_rate_av,   &
    393                                           qsws_av, shf_av,ts_av, us_av, z0_av, &
    394                                           z0h_av
     407    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  lwp_av,                & !> Avg. liquid water path
     408                                              precipitation_rate_av, & !> Avg. of precipitation rate
     409                                              ol_av,                 & !> Avg. of Obukhov length
     410                                              qsws_av,               & !> Avg. of surface moisture flux
     411                                              shf_av,                & !> Avg. of surface heat flux
     412                                              ts_av,                 & !> Avg. of characteristic temperature scale
     413                                              us_av,                 & !> Avg. of friction velocity
     414                                              z0_av,                 & !> Avg. of roughness length for momentum
     415                                              z0h_av                   !> Avg. of roughness length for heat and moisture
    395416
    396417    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::                         &
     
    541562    CHARACTER (LEN=2)    ::  coupling_char = ''
    542563    CHARACTER (LEN=5)    ::  write_binary = 'false'
    543     CHARACTER (LEN=8)    ::  run_date, run_time
     564    CHARACTER (LEN=8)    ::  most_method = 'lookup', & !< NAMELIST parameter defining method to be used to calculate Okukhov length,
     565                             run_date,               & !<
     566                             run_time                  !<
    544567    CHARACTER (LEN=9)    ::  simulated_time_chr
    545568    CHARACTER (LEN=11)   ::  topography_grid_convention = ' '
     
    563586                             coupling_mode = 'uncoupled', &
    564587                             coupling_mode_remote = 'uncoupled', &
    565                              dissipation_1d = 'as_in_3d_model', &
     588                             dissipation_1d = 'detering', &
    566589                             fft_method = 'system-specific', &
    567                              mixing_length_1d = 'as_in_3d_model', &
     590                             mixing_length_1d = 'blackadar', &
    568591                             random_generator = 'numerical-recipes', &
    569592                             reference_state = 'initial_profile', &
     
    653676                cloud_top_radiation = .FALSE., &
    654677                conserve_volume_flow = .FALSE., constant_diffusion = .FALSE., &
     678                constant_flux_layer = .TRUE., &
    655679                constant_heatflux = .TRUE., constant_top_heatflux = .TRUE., &
    656680                constant_top_momentumflux = .FALSE., &
     
    679703                outflow_l = .FALSE., outflow_n = .FALSE., outflow_r = .FALSE., &
    680704                outflow_s = .FALSE., passive_scalar = .FALSE., &
    681                 prandtl_layer = .TRUE., &
    682705                precipitation = .FALSE., &
    683706                random_heatflux = .FALSE., recycling_yshift = .FALSE.,&
     
    745768                 recycling_width = 9999999.9_wp, residual_limit = 1.0E-4_wp, &
    746769                 restart_time = 9999999.9_wp, rho_reference, rho_surface, &
    747                  rif_max = 1.0_wp, rif_min = -5.0_wp, roughness_length = 0.1_wp, &
     770                 roughness_length = 0.1_wp, &
    748771                 sa_surface = 35.0_wp, &
    749772                 simulated_time = 0.0_wp, simulated_time_at_begin, sin_alpha_surface, &
     
    768791                 vg_surface = 0.0_wp, vpt_reference = 9999999.9_wp, &
    769792                 v_bulk = 0.0_wp, v_gtrans = 0.0_wp, wall_adjustment_factor = 1.8_wp, &
     793                 zeta_max = 20.0_wp,    & !< Maximum value of zeta = z/L
     794                 zeta_min = -9990.0_wp, & !< Minimum value of zeta = z/L
    770795                 z_max_do2d = -1.0_wp, z0h_factor = 1.0_wp
    771796
     
    11491174             'wpt          ', 'pt(0)        ', 'pt(zp)       ',                &
    11501175             'w"u"0        ', 'w"v"0        ', 'w"q"0        ',                &
    1151              'mo_L         ', 'q*           ',                                 &
     1176             'ol           ', 'q*           ',                                 &
    11521177             ( 'unknown      ', i9 = 1, dots_max-23 ) /)
    11531178
     
    14291454
    14301455    CHARACTER (LEN=40) ::  region(0:9)
    1431     INTEGER(iwp) ::  pr_palm = 120, statistic_regions = 0
     1456    INTEGER(iwp) ::  pr_palm = 130, statistic_regions = 0
    14321457    INTEGER(iwp) ::  u_max_ijk(3) = -1, v_max_ijk(3) = -1, w_max_ijk(3) = -1
    14331458    LOGICAL ::  flow_statistics_called = .FALSE.
Note: See TracChangeset for help on using the changeset viewer.