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

Last change on this file since 1952 was 1874, checked in by maronga, 8 years ago

last commit documented

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