Changeset 4741 for palm/trunk/SOURCE


Ignore:
Timestamp:
Oct 14, 2020 2:32:50 PM (4 years ago)
Author:
suehring
Message:

radiation: Add option to force calculation of horizontal mean profiles independent on data output

Location:
palm/trunk/SOURCE
Files:
2 edited

Legend:

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

    r4542 r4741  
    2020! Current revisions:
    2121! -----------------
    22 ! 
    23 ! 
     22!
     23!
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! Add option to force calculation of horizontal mean profiles independent on data output
     28!
     29! 4542 2020-05-19 15:45:12Z raasch
    2730! file re-formatted to follow the PALM coding standard
    2831!
     
    6669!> @todo Missing subroutine description.
    6770!--------------------------------------------------------------------------------------------------!
    68     SUBROUTINE calc_mean_profile( var, pr )
     71    SUBROUTINE calc_mean_profile( var, pr, force_calc )
    6972
    7073       USE control_parameters,                                                                     &
     
    8487       IMPLICIT NONE
    8588
     89       LOGICAL, OPTIONAL ::  force_calc             !< passed flag used to force calculation of mean profiles independend on data output
     90       LOGICAL           ::  force_calc_l = .FALSE. !< control flag
     91
    8692       INTEGER(iwp) ::  i                  !<
    8793       INTEGER(iwp) ::  j                  !<
     
    99105!--    results with jobs which are calling flow_statistics at different time intervals. At
    100106!--    initialization, intermediate_timestep_count = 0 is considered as well.
     107!--    Note, calc_mean_profile is also called from the radiation. Especially during the spinup when
     108!--    no data output is called, the values in hom do not necessarily reflect horizontal mean.
     109!--    The same is also for nested simulations during the spinup, where hom is initialized on a
     110!--    ealier point in time than the initialization via the parent domain takes place, meaning
     111!--    that hom does not necessarily reflect the horizontal mean during the spinup, too.
     112!--    In order to force the computation of horizontal mean profiles independent on data output,
     113!--    i.e. independent on flow_statistics, add a special control flag.
     114       IF ( PRESENT( force_calc ) )  THEN
     115          IF ( force_calc )  force_calc_l = .TRUE.
     116       ENDIF
    101117
    102        IF ( .NOT. flow_statistics_called  .AND.  intermediate_timestep_count <= 1 )  THEN
     118       IF ( ( .NOT. flow_statistics_called  .AND.  intermediate_timestep_count <= 1 ) .OR.         &
     119            force_calc_l )  THEN
    103120
    104121!
  • palm/trunk/SOURCE/radiation_model_mod.f90

    r4717 r4741  
    2828! -----------------
    2929! $Id$
     30! Add option to force calculation of horizontal mean profiles independent on data output
     31!
     32! 4717 2020-09-30 22:27:40Z pavelkrc
    3033! Fixes and optimizations of OpenMP parallelization, formatting of OpenMP
    3134! directives (J. Resler)
     
    42404243!
    42414244!--       Calculate mean pt profile.
    4242           CALL calc_mean_profile( pt, 4 )
     4245          CALL calc_mean_profile( pt, 4, .TRUE. )
    42434246          pt_av = hom(:, 1, 4, 0)
    42444247
    42454248          IF ( humidity )  THEN
    4246              CALL calc_mean_profile( q, 41 )
     4249             CALL calc_mean_profile( q, 41, .TRUE. )
    42474250             q_av  = hom(:, 1, 41, 0)
    42484251          ENDIF
     
    42534256          IF ( bulk_cloud_model )  THEN
    42544257
    4255              CALL calc_mean_profile( ql, 54 )
     4258             CALL calc_mean_profile( ql, 54, .TRUE. )
    42564259             ! average ql is now in hom(:, 1, 54, 0)
    42574260             ql_av = hom(:, 1, 54, 0)
Note: See TracChangeset for help on using the changeset viewer.