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

Last change on this file since 4741 was 4741, checked in by suehring, 4 years ago

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

  • Property svn:keywords set to Id
File size: 6.1 KB
Line 
1!> @file calc_mean_profile.f90
2!--------------------------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
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.
8!
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.
12!
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/>.
15!
16!
17! Copyright 1997-2020 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: calc_mean_profile.f90 4741 2020-10-14 14:32:50Z suehring $
27! Add option to force calculation of horizontal mean profiles independent on data output
28!
29! 4542 2020-05-19 15:45:12Z raasch
30! file re-formatted to follow the PALM coding standard
31!
32! 4360 2020-01-07 11:25:50Z suehring
33! Introduction of wall_flags_total_0, which currently sets bits based on static
34! topography information used in wall_flags_static_0
35!
36! 4329 2019-12-10 15:46:36Z motisi
37! Renamed wall_flags_0 to wall_flags_static_0
38!
39! 4182 2019-08-22 15:20:23Z scharf
40! Corrected "Former revisions" section
41!
42! 3655 2019-01-07 16:51:22Z knoop
43! nopointer option removed
44!
45! 1365 2014-04-22 15:03:56Z boeske
46! Initial revision
47!
48! Description:
49! ------------
50!> Calculate the horizontally averaged vertical temperature profile (pr=4 in case
51!> of potential temperature, 44 in case of virtual potential temperature, and 64
52!> in case of density (ocean runs)).
53!------------------------------------------------------------------------------!
54 MODULE calc_mean_profile_mod
55
56
57    PRIVATE
58    PUBLIC calc_mean_profile
59
60    INTERFACE calc_mean_profile
61       MODULE PROCEDURE calc_mean_profile
62    END INTERFACE calc_mean_profile
63
64 CONTAINS
65
66!--------------------------------------------------------------------------------------------------!
67! Description:
68! ------------
69!> @todo Missing subroutine description.
70!--------------------------------------------------------------------------------------------------!
71    SUBROUTINE calc_mean_profile( var, pr, force_calc )
72
73       USE control_parameters,                                                                     &
74           ONLY:  intermediate_timestep_count
75
76       USE indices,                                                                                &
77           ONLY:  ngp_2dh_s_inner, nxl, nxr, nyn, nys, nzb, nzb, nzt, wall_flags_total_0
78
79       USE kinds
80
81       USE pegrid
82
83       USE statistics,                                                                             &
84           ONLY:  flow_statistics_called, hom, sums, sums_l
85
86
87       IMPLICIT NONE
88
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
92       INTEGER(iwp) ::  i                  !<
93       INTEGER(iwp) ::  j                  !<
94       INTEGER(iwp) ::  k                  !<
95       INTEGER(iwp) ::  pr                 !<
96!$     INTEGER(iwp) ::  omp_get_thread_num !<
97       INTEGER(iwp) ::  tn                 !<
98
99       REAL(wp), DIMENSION(:,:,:), POINTER ::  var
100
101!
102!--    Computation of the horizontally averaged profile of variable var, unless already done by the
103!--    relevant call from flow_statistics. The calculation is done only for the first respective
104!--    intermediate timestep in order to spare communication time and to produce identical model
105!--    results with jobs which are calling flow_statistics at different time intervals. At
106!--    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
117
118       IF ( ( .NOT. flow_statistics_called  .AND.  intermediate_timestep_count <= 1 ) .OR.         &
119            force_calc_l )  THEN
120
121!
122!--       Horizontal average of variable var
123          tn           =   0  ! Default thread number in case of one thread
124          !$OMP PARALLEL PRIVATE( i, j, k, tn )
125!$        tn = omp_get_thread_num()
126          sums_l(:,pr,tn) = 0.0_wp
127          !$OMP DO
128          DO  i = nxl, nxr
129             DO  j =  nys, nyn
130                DO  k = nzb, nzt+1
131                   sums_l(k,pr,tn) = sums_l(k,pr,tn) + var(k,j,i) * MERGE( 1.0_wp, 0.0_wp,         &
132                                                            BTEST( wall_flags_total_0(k,j,i), 22 ) )
133                ENDDO
134             ENDDO
135          ENDDO
136          !$OMP END PARALLEL
137
138          DO  i = 1, threads_per_task-1
139             sums_l(:,pr,0) = sums_l(:,pr,0) + sums_l(:,pr,i)
140          ENDDO
141
142#if defined( __parallel )
143
144          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
145          CALL MPI_ALLREDUCE( sums_l(nzb,pr,0), sums(nzb,pr), nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d,&
146                              ierr )
147
148#else
149
150          sums(:,pr) = sums_l(:,pr,0)
151
152#endif
153
154          DO  k = nzb, nzt+1
155             IF ( ngp_2dh_s_inner(k,0) /= 0 )  THEN
156                hom(k,1,pr,0) = sums(k,pr) / ngp_2dh_s_inner(k,0)
157             ENDIF
158          ENDDO
159
160       ENDIF
161
162
163    END SUBROUTINE calc_mean_profile
164
165 END MODULE calc_mean_profile_mod
Note: See TracBrowser for help on using the repository browser.