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

Last change on this file since 2232 was 2232, checked in by suehring, 7 years ago

Adjustments according new topography and surface-modelling concept implemented

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