source: palm/trunk/SOURCE/calc_mean_profile_mod.f90 @ 1850

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

added _mod string to several filenames to meet the naming convection for modules

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