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

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

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