source: palm/tags/release-4.0/SOURCE/calc_mean_profile.f90 @ 1983

Last change on this file since 1983 was 1366, checked in by boeske, 10 years ago

last commit documented

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