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

Last change on this file since 4180 was 4180, checked in by scharf, 6 years ago

removed comments in 'Former revisions' section that are older than 01.01.2019

  • Property svn:keywords set to Id
File size: 4.6 KB
RevLine 
[1873]1!> @file calc_mean_profile.f90
[2000]2!------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1365]4!
[2000]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.
[1365]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!
[3655]17! Copyright 1997-2019 Leibniz Universitaet Hannover
[2000]18!------------------------------------------------------------------------------!
[1365]19!
20! Current revisions:
21! -----------------
22!
[2233]23!
[1365]24! Former revisions:
25! -----------------
26! $Id: calc_mean_profile.f90 4180 2019-08-21 14:37:54Z scharf $
[3636]27! nopointer option removed
28!
[1365]29!
30! Description:
31! ------------
[1682]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)).
[1365]35!------------------------------------------------------------------------------!
[1682]36 MODULE calc_mean_profile_mod
37 
[1365]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
[1682]48!------------------------------------------------------------------------------!
49! Description:
50! ------------
51!> @todo Missing subroutine description.
52!------------------------------------------------------------------------------!
[1365]53    SUBROUTINE calc_mean_profile( var, pr )
54
55       USE control_parameters,                                                 &
[3241]56           ONLY:  intermediate_timestep_count
[1365]57
58       USE indices,                                                            &
[2232]59           ONLY:  ngp_2dh_s_inner, nxl, nxr, nyn, nys, nzb, nzb, nzt,          &
60                  wall_flags_0
[1365]61
62       USE kinds
63
64       USE pegrid
65
66       USE statistics,                                                         &
67           ONLY:  flow_statistics_called, hom, sums, sums_l
68
69
70       IMPLICIT NONE
71       
[1682]72       INTEGER(iwp) ::  i                  !<
73       INTEGER(iwp) ::  j                  !<
74       INTEGER(iwp) ::  k                  !<
75       INTEGER(iwp) ::  pr                 !<
[3241]76!$     INTEGER(iwp) ::  omp_get_thread_num !<
[1682]77       INTEGER(iwp) ::  tn                 !<
[1365]78       
79       REAL(wp), DIMENSION(:,:,:), POINTER ::  var
80
81!
82!--    Computation of the horizontally averaged profile of variable var, unless
83!--    already done by the relevant call from flow_statistics. The calculation
84!--    is done only for the first respective intermediate timestep in order to
85!--    spare communication time and to produce identical model results with jobs
[2696]86!--    which are calling flow_statistics at different time intervals. At
87!--    initialization, intermediate_timestep_count = 0 is considered as well.
88
[1365]89       IF ( .NOT. flow_statistics_called  .AND.                                &
[2696]90            intermediate_timestep_count <= 1 )  THEN
[1365]91
92!
93!--       Horizontal average of variable var
94          tn           =   0  ! Default thread number in case of one thread
95          !$OMP PARALLEL PRIVATE( i, j, k, tn )
96!$        tn = omp_get_thread_num()
97          sums_l(:,pr,tn) = 0.0_wp
98          !$OMP DO
99          DO  i = nxl, nxr
100             DO  j =  nys, nyn
[2232]101                DO  k = nzb, nzt+1
102                   sums_l(k,pr,tn) = sums_l(k,pr,tn) + var(k,j,i)              &
103                                     * MERGE( 1.0_wp, 0.0_wp,                  &
104                                              BTEST( wall_flags_0(k,j,i), 22 ) )
[1365]105                ENDDO
106             ENDDO
107          ENDDO
108          !$OMP END PARALLEL
109
110          DO  i = 1, threads_per_task-1
111             sums_l(:,pr,0) = sums_l(:,pr,0) + sums_l(:,pr,i)
112          ENDDO
113
114#if defined( __parallel )
115
116          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
117          CALL MPI_ALLREDUCE( sums_l(nzb,pr,0), sums(nzb,pr), nzt+2-nzb,       &
118                              MPI_REAL, MPI_SUM, comm2d, ierr )
119
120#else
121
122          sums(:,pr) = sums_l(:,pr,0)
123
124#endif
125
[1738]126          DO  k = nzb, nzt+1
127             IF ( ngp_2dh_s_inner(k,0) /= 0 )  THEN
128                hom(k,1,pr,0) = sums(k,pr) / ngp_2dh_s_inner(k,0)
129             ENDIF
130          ENDDO
[1365]131
132       ENDIF
133
134
135    END SUBROUTINE calc_mean_profile
136
[1738]137 END MODULE calc_mean_profile_mod
Note: See TracBrowser for help on using the repository browser.