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

Last change on this file since 1738 was 1738, checked in by raasch, 8 years ago

bugfixes for calculations in statistical regions which do not contain grid points in the lowest vertical levels, mean surface level height considered in the calculation of the characteristic vertical velocity

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