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

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

Bugfix in output of time-averaged plant-canopy quanities; Output of plant-canopy data only where tall canopy is defined; land-surface model: fix wrong location strings; tests: update urban test case; all source code files: copyright update

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