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

Last change on this file since 4329 was 4329, checked in by motisi, 4 years ago

Renamed wall_flags_0 to wall_flags_static_0

  • Property svn:keywords set to Id
File size: 4.8 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 4329 2019-12-10 15:46:36Z motisi $
27! Renamed wall_flags_0 to wall_flags_static_0
28!
29! 4182 2019-08-22 15:20:23Z scharf
30! Corrected "Former revisions" section
31!
32! 3655 2019-01-07 16:51:22Z knoop
33! nopointer option removed
34!
35! 1365 2014-04-22 15:03:56Z boeske
36! Initial revision
37!
38! Description:
39! ------------
40!> Calculate the horizontally averaged vertical temperature profile (pr=4 in case
41!> of potential temperature, 44 in case of virtual potential temperature, and 64
42!> in case of density (ocean runs)).
43!------------------------------------------------------------------------------!
44 MODULE calc_mean_profile_mod
45 
46
47    PRIVATE
48    PUBLIC calc_mean_profile
49
50    INTERFACE calc_mean_profile
51       MODULE PROCEDURE calc_mean_profile
52    END INTERFACE calc_mean_profile
53
54 CONTAINS
55
56!------------------------------------------------------------------------------!
57! Description:
58! ------------
59!> @todo Missing subroutine description.
60!------------------------------------------------------------------------------!
61    SUBROUTINE calc_mean_profile( var, pr )
62
63       USE control_parameters,                                                 &
64           ONLY:  intermediate_timestep_count
65
66       USE indices,                                                            &
67           ONLY:  ngp_2dh_s_inner, nxl, nxr, nyn, nys, nzb, nzb, nzt,          &
68                  wall_flags_static_0
69
70       USE kinds
71
72       USE pegrid
73
74       USE statistics,                                                         &
75           ONLY:  flow_statistics_called, hom, sums, sums_l
76
77
78       IMPLICIT NONE
79       
80       INTEGER(iwp) ::  i                  !<
81       INTEGER(iwp) ::  j                  !<
82       INTEGER(iwp) ::  k                  !<
83       INTEGER(iwp) ::  pr                 !<
84!$     INTEGER(iwp) ::  omp_get_thread_num !<
85       INTEGER(iwp) ::  tn                 !<
86       
87       REAL(wp), DIMENSION(:,:,:), POINTER ::  var
88
89!
90!--    Computation of the horizontally averaged profile of variable var, unless
91!--    already done by the relevant call from flow_statistics. The calculation
92!--    is done only for the first respective intermediate timestep in order to
93!--    spare communication time and to produce identical model results with jobs
94!--    which are calling flow_statistics at different time intervals. At
95!--    initialization, intermediate_timestep_count = 0 is considered as well.
96
97       IF ( .NOT. flow_statistics_called  .AND.                                &
98            intermediate_timestep_count <= 1 )  THEN
99
100!
101!--       Horizontal average of variable var
102          tn           =   0  ! Default thread number in case of one thread
103          !$OMP PARALLEL PRIVATE( i, j, k, tn )
104!$        tn = omp_get_thread_num()
105          sums_l(:,pr,tn) = 0.0_wp
106          !$OMP DO
107          DO  i = nxl, nxr
108             DO  j =  nys, nyn
109                DO  k = nzb, nzt+1
110                   sums_l(k,pr,tn) = sums_l(k,pr,tn) + var(k,j,i)              &
111                                     * MERGE( 1.0_wp, 0.0_wp,                  &
112                                              BTEST( wall_flags_static_0(k,j,i), 22 ) )
113                ENDDO
114             ENDDO
115          ENDDO
116          !$OMP END PARALLEL
117
118          DO  i = 1, threads_per_task-1
119             sums_l(:,pr,0) = sums_l(:,pr,0) + sums_l(:,pr,i)
120          ENDDO
121
122#if defined( __parallel )
123
124          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
125          CALL MPI_ALLREDUCE( sums_l(nzb,pr,0), sums(nzb,pr), nzt+2-nzb,       &
126                              MPI_REAL, MPI_SUM, comm2d, ierr )
127
128#else
129
130          sums(:,pr) = sums_l(:,pr,0)
131
132#endif
133
134          DO  k = nzb, nzt+1
135             IF ( ngp_2dh_s_inner(k,0) /= 0 )  THEN
136                hom(k,1,pr,0) = sums(k,pr) / ngp_2dh_s_inner(k,0)
137             ENDIF
138          ENDDO
139
140       ENDIF
141
142
143    END SUBROUTINE calc_mean_profile
144
145 END MODULE calc_mean_profile_mod
Note: See TracBrowser for help on using the repository browser.