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

Last change on this file since 3830 was 3655, checked in by knoop, 5 years ago

Bugfix: made "unit" and "found" intend INOUT in module interface subroutines + automatic copyright update

  • Property svn:keywords set to Id
File size: 5.5 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
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: calc_mean_profile.f90 3655 2019-01-07 16:51:22Z raasch $
27! nopointer option removed
28!
29! 3241 2018-09-12 15:02:00Z raasch
30! omp_get_thread_num now declared in openmp directive,
31! unused variable removed
32!
33! 2718 2018-01-02 08:49:38Z maronga
34! Corrected "Former revisions" section
35!
36! 2696 2017-12-14 17:12:51Z kanani
37! Change in file header (GPL part)
38! Enable usage also during initialization, required for initialization of
39! radiation and land-surface model (MS)
40!
41! 2233 2017-05-30 18:08:54Z suehring
42!
43! 2232 2017-05-30 17:47:52Z suehring
44! Adjustments to new topography concept
45!
46! 2000 2016-08-20 18:09:15Z knoop
47! Forced header and separation lines into 80 columns
48!
49! 1873 2016-04-18 14:50:06Z maronga
50! Module renamed (removed _mod)
51!
52!
53! 1850 2016-04-08 13:29:27Z maronga
54! Module renamed
55!
56!
57! 1738 2015-12-18 13:56:05Z raasch
58! bugfix: if a layer is completely filled with topography, no mean is calculated
59!
60! 1682 2015-10-07 23:56:08Z knoop
61! Code annotations made doxygen readable
62!
63! 1365 2014-04-22 15:03:56Z boeske
64! Initial revision
65!
66! Description:
67! ------------
68!> Calculate the horizontally averaged vertical temperature profile (pr=4 in case
69!> of potential temperature, 44 in case of virtual potential temperature, and 64
70!> in case of density (ocean runs)).
71!------------------------------------------------------------------------------!
72 MODULE calc_mean_profile_mod
73 
74
75    PRIVATE
76    PUBLIC calc_mean_profile
77
78    INTERFACE calc_mean_profile
79       MODULE PROCEDURE calc_mean_profile
80    END INTERFACE calc_mean_profile
81
82 CONTAINS
83
84!------------------------------------------------------------------------------!
85! Description:
86! ------------
87!> @todo Missing subroutine description.
88!------------------------------------------------------------------------------!
89    SUBROUTINE calc_mean_profile( var, pr )
90
91       USE control_parameters,                                                 &
92           ONLY:  intermediate_timestep_count
93
94       USE indices,                                                            &
95           ONLY:  ngp_2dh_s_inner, nxl, nxr, nyn, nys, nzb, nzb, nzt,          &
96                  wall_flags_0
97
98       USE kinds
99
100       USE pegrid
101
102       USE statistics,                                                         &
103           ONLY:  flow_statistics_called, hom, sums, sums_l
104
105
106       IMPLICIT NONE
107       
108       INTEGER(iwp) ::  i                  !<
109       INTEGER(iwp) ::  j                  !<
110       INTEGER(iwp) ::  k                  !<
111       INTEGER(iwp) ::  pr                 !<
112!$     INTEGER(iwp) ::  omp_get_thread_num !<
113       INTEGER(iwp) ::  tn                 !<
114       
115       REAL(wp), DIMENSION(:,:,:), POINTER ::  var
116
117!
118!--    Computation of the horizontally averaged profile of variable var, unless
119!--    already done by the relevant call from flow_statistics. The calculation
120!--    is done only for the first respective intermediate timestep in order to
121!--    spare communication time and to produce identical model results with jobs
122!--    which are calling flow_statistics at different time intervals. At
123!--    initialization, intermediate_timestep_count = 0 is considered as well.
124
125       IF ( .NOT. flow_statistics_called  .AND.                                &
126            intermediate_timestep_count <= 1 )  THEN
127
128!
129!--       Horizontal average of variable var
130          tn           =   0  ! Default thread number in case of one thread
131          !$OMP PARALLEL PRIVATE( i, j, k, tn )
132!$        tn = omp_get_thread_num()
133          sums_l(:,pr,tn) = 0.0_wp
134          !$OMP DO
135          DO  i = nxl, nxr
136             DO  j =  nys, nyn
137                DO  k = nzb, nzt+1
138                   sums_l(k,pr,tn) = sums_l(k,pr,tn) + var(k,j,i)              &
139                                     * MERGE( 1.0_wp, 0.0_wp,                  &
140                                              BTEST( wall_flags_0(k,j,i), 22 ) )
141                ENDDO
142             ENDDO
143          ENDDO
144          !$OMP END PARALLEL
145
146          DO  i = 1, threads_per_task-1
147             sums_l(:,pr,0) = sums_l(:,pr,0) + sums_l(:,pr,i)
148          ENDDO
149
150#if defined( __parallel )
151
152          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
153          CALL MPI_ALLREDUCE( sums_l(nzb,pr,0), sums(nzb,pr), nzt+2-nzb,       &
154                              MPI_REAL, MPI_SUM, comm2d, ierr )
155
156#else
157
158          sums(:,pr) = sums_l(:,pr,0)
159
160#endif
161
162          DO  k = nzb, nzt+1
163             IF ( ngp_2dh_s_inner(k,0) /= 0 )  THEN
164                hom(k,1,pr,0) = sums(k,pr) / ngp_2dh_s_inner(k,0)
165             ENDIF
166          ENDDO
167
168       ENDIF
169
170
171    END SUBROUTINE calc_mean_profile
172
173 END MODULE calc_mean_profile_mod
Note: See TracBrowser for help on using the repository browser.