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

Last change on this file since 2000 was 2000, checked in by knoop, 8 years ago

Forced header and separation lines into 80 columns

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