source: palm/trunk/SOURCE/calc_mean_profile.f90 @ 4859

Last change on this file since 4859 was 4828, checked in by Giersch, 3 years ago

Copyright updated to year 2021, interface pmc_sort removed to accelarate the nesting code

  • Property svn:keywords set to Id
File size: 6.2 KB
RevLine 
[1873]1!> @file calc_mean_profile.f90
[4542]2!--------------------------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1365]4!
[4542]5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
[1365]8!
[4542]9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
[1365]12!
[4542]13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
[1365]15!
[4542]16!
[4828]17! Copyright 1997-2021 Leibniz Universitaet Hannover
[4542]18!--------------------------------------------------------------------------------------------------!
[1365]19!
20! Current revisions:
21! -----------------
[4741]22!
[4750]23!
[1365]24! Former revisions:
25! -----------------
26! $Id: calc_mean_profile.f90 4828 2021-01-05 11:21:41Z raasch $
[4750]27! Bugfix for last commit
28!
29! 4743 2020-10-14 16:40:58Z suehring
[4741]30! Add option to force calculation of horizontal mean profiles independent on data output
31!
32! 4542 2020-05-19 15:45:12Z raasch
[4542]33! file re-formatted to follow the PALM coding standard
34!
35! 4360 2020-01-07 11:25:50Z suehring
[4346]36! Introduction of wall_flags_total_0, which currently sets bits based on static
37! topography information used in wall_flags_static_0
[4542]38!
[4346]39! 4329 2019-12-10 15:46:36Z motisi
[4329]40! Renamed wall_flags_0 to wall_flags_static_0
[4542]41!
[4329]42! 4182 2019-08-22 15:20:23Z scharf
[4182]43! Corrected "Former revisions" section
[4542]44!
[4182]45! 3655 2019-01-07 16:51:22Z knoop
[3636]46! nopointer option removed
[4542]47!
[4182]48! 1365 2014-04-22 15:03:56Z boeske
49! Initial revision
[1365]50!
51! Description:
52! ------------
[1682]53!> Calculate the horizontally averaged vertical temperature profile (pr=4 in case
54!> of potential temperature, 44 in case of virtual potential temperature, and 64
55!> in case of density (ocean runs)).
[1365]56!------------------------------------------------------------------------------!
[1682]57 MODULE calc_mean_profile_mod
[1365]58
[4542]59
[1365]60    PRIVATE
61    PUBLIC calc_mean_profile
62
63    INTERFACE calc_mean_profile
64       MODULE PROCEDURE calc_mean_profile
65    END INTERFACE calc_mean_profile
66
67 CONTAINS
68
[4542]69!--------------------------------------------------------------------------------------------------!
[1682]70! Description:
71! ------------
72!> @todo Missing subroutine description.
[4542]73!--------------------------------------------------------------------------------------------------!
[4741]74    SUBROUTINE calc_mean_profile( var, pr, force_calc )
[1365]75
[4542]76       USE control_parameters,                                                                     &
[3241]77           ONLY:  intermediate_timestep_count
[1365]78
[4542]79       USE indices,                                                                                &
80           ONLY:  ngp_2dh_s_inner, nxl, nxr, nyn, nys, nzb, nzb, nzt, wall_flags_total_0
[1365]81
82       USE kinds
83
84       USE pegrid
85
[4542]86       USE statistics,                                                                             &
[1365]87           ONLY:  flow_statistics_called, hom, sums, sums_l
88
89
90       IMPLICIT NONE
[4542]91
[4741]92       LOGICAL, OPTIONAL ::  force_calc             !< passed flag used to force calculation of mean profiles independend on data output
93       LOGICAL           ::  force_calc_l = .FALSE. !< control flag
94
[1682]95       INTEGER(iwp) ::  i                  !<
96       INTEGER(iwp) ::  j                  !<
97       INTEGER(iwp) ::  k                  !<
[4542]98       INTEGER(iwp) ::  pr                 !<
[3241]99!$     INTEGER(iwp) ::  omp_get_thread_num !<
[1682]100       INTEGER(iwp) ::  tn                 !<
[4542]101
[1365]102       REAL(wp), DIMENSION(:,:,:), POINTER ::  var
103
104!
[4542]105!--    Computation of the horizontally averaged profile of variable var, unless already done by the
106!--    relevant call from flow_statistics. The calculation is done only for the first respective
107!--    intermediate timestep in order to spare communication time and to produce identical model
108!--    results with jobs which are calling flow_statistics at different time intervals. At
[2696]109!--    initialization, intermediate_timestep_count = 0 is considered as well.
[4741]110!--    Note, calc_mean_profile is also called from the radiation. Especially during the spinup when
111!--    no data output is called, the values in hom do not necessarily reflect horizontal mean.
112!--    The same is also for nested simulations during the spinup, where hom is initialized on a
113!--    ealier point in time than the initialization via the parent domain takes place, meaning
114!--    that hom does not necessarily reflect the horizontal mean during the spinup, too.
115!--    In order to force the computation of horizontal mean profiles independent on data output,
116!--    i.e. independent on flow_statistics, add a special control flag.
117       IF ( PRESENT( force_calc ) )  THEN
[4743]118          force_calc_l = force_calc
119       ELSE
120          force_calc_l = .FALSE.
[4741]121       ENDIF
[2696]122
[4741]123       IF ( ( .NOT. flow_statistics_called  .AND.  intermediate_timestep_count <= 1 ) .OR.         &
124            force_calc_l )  THEN
[1365]125
126!
127!--       Horizontal average of variable var
128          tn           =   0  ! Default thread number in case of one thread
129          !$OMP PARALLEL PRIVATE( i, j, k, tn )
130!$        tn = omp_get_thread_num()
131          sums_l(:,pr,tn) = 0.0_wp
132          !$OMP DO
133          DO  i = nxl, nxr
134             DO  j =  nys, nyn
[2232]135                DO  k = nzb, nzt+1
[4542]136                   sums_l(k,pr,tn) = sums_l(k,pr,tn) + var(k,j,i) * MERGE( 1.0_wp, 0.0_wp,         &
137                                                            BTEST( wall_flags_total_0(k,j,i), 22 ) )
[1365]138                ENDDO
139             ENDDO
140          ENDDO
141          !$OMP END PARALLEL
142
143          DO  i = 1, threads_per_task-1
144             sums_l(:,pr,0) = sums_l(:,pr,0) + sums_l(:,pr,i)
145          ENDDO
146
147#if defined( __parallel )
148
149          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
[4542]150          CALL MPI_ALLREDUCE( sums_l(nzb,pr,0), sums(nzb,pr), nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d,&
151                              ierr )
[1365]152
153#else
154
155          sums(:,pr) = sums_l(:,pr,0)
156
157#endif
158
[1738]159          DO  k = nzb, nzt+1
160             IF ( ngp_2dh_s_inner(k,0) /= 0 )  THEN
161                hom(k,1,pr,0) = sums(k,pr) / ngp_2dh_s_inner(k,0)
162             ENDIF
163          ENDDO
[1365]164
165       ENDIF
166
167
168    END SUBROUTINE calc_mean_profile
169
[1738]170 END MODULE calc_mean_profile_mod
Note: See TracBrowser for help on using the repository browser.