Changeset 4542 for palm/trunk/SOURCE/calc_mean_profile.f90
- Timestamp:
- May 19, 2020 3:45:12 PM (5 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/calc_mean_profile.f90
r4360 r4542 1 1 !> @file calc_mean_profile.f90 2 !------------------------------------------------------------------------------ !2 !--------------------------------------------------------------------------------------------------! 3 3 ! This file is part of the PALM model system. 4 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. 5 ! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General 6 ! Public License as published by the Free Software Foundation, either version 3 of the License, or 7 ! (at your option) any later version. 9 8 ! 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 FOR12 ! A PARTICULAR PURPOSE. See the GNU GeneralPublic License for more details.9 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the 10 ! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General 11 ! Public License for more details. 13 12 ! 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/>. 13 ! You should have received a copy of the GNU General Public License along with PALM. If not, see 14 ! <http://www.gnu.org/licenses/>. 15 ! 16 16 ! 17 17 ! Copyright 1997-2020 Leibniz Universitaet Hannover 18 !------------------------------------------------------------------------------ !18 !--------------------------------------------------------------------------------------------------! 19 19 ! 20 20 ! Current revisions: … … 25 25 ! ----------------- 26 26 ! $Id$ 27 ! file re-formatted to follow the PALM coding standard 28 ! 29 ! 4360 2020-01-07 11:25:50Z suehring 27 30 ! Introduction of wall_flags_total_0, which currently sets bits based on static 28 31 ! topography information used in wall_flags_static_0 29 ! 32 ! 30 33 ! 4329 2019-12-10 15:46:36Z motisi 31 34 ! Renamed wall_flags_0 to wall_flags_static_0 32 ! 35 ! 33 36 ! 4182 2019-08-22 15:20:23Z scharf 34 37 ! Corrected "Former revisions" section 35 ! 38 ! 36 39 ! 3655 2019-01-07 16:51:22Z knoop 37 40 ! nopointer option removed 38 ! 41 ! 39 42 ! 1365 2014-04-22 15:03:56Z boeske 40 43 ! Initial revision … … 47 50 !------------------------------------------------------------------------------! 48 51 MODULE calc_mean_profile_mod 49 52 50 53 51 54 PRIVATE … … 58 61 CONTAINS 59 62 60 !------------------------------------------------------------------------------ !63 !--------------------------------------------------------------------------------------------------! 61 64 ! Description: 62 65 ! ------------ 63 66 !> @todo Missing subroutine description. 64 !------------------------------------------------------------------------------ !67 !--------------------------------------------------------------------------------------------------! 65 68 SUBROUTINE calc_mean_profile( var, pr ) 66 69 67 USE control_parameters, &70 USE control_parameters, & 68 71 ONLY: intermediate_timestep_count 69 72 70 USE indices, & 71 ONLY: ngp_2dh_s_inner, nxl, nxr, nyn, nys, nzb, nzb, nzt, & 72 wall_flags_total_0 73 USE indices, & 74 ONLY: ngp_2dh_s_inner, nxl, nxr, nyn, nys, nzb, nzb, nzt, wall_flags_total_0 73 75 74 76 USE kinds … … 76 78 USE pegrid 77 79 78 USE statistics, &80 USE statistics, & 79 81 ONLY: flow_statistics_called, hom, sums, sums_l 80 82 81 83 82 84 IMPLICIT NONE 83 85 84 86 INTEGER(iwp) :: i !< 85 87 INTEGER(iwp) :: j !< 86 88 INTEGER(iwp) :: k !< 87 INTEGER(iwp) :: pr !< 89 INTEGER(iwp) :: pr !< 88 90 !$ INTEGER(iwp) :: omp_get_thread_num !< 89 91 INTEGER(iwp) :: tn !< 90 92 91 93 REAL(wp), DIMENSION(:,:,:), POINTER :: var 92 94 93 95 ! 94 !-- Computation of the horizontally averaged profile of variable var, unless 95 !-- already done by the relevant call from flow_statistics. The calculation 96 !-- is done only for the first respective intermediate timestep in order to 97 !-- spare communication time and to produce identical model results with jobs 98 !-- which are calling flow_statistics at different time intervals. At 96 !-- Computation of the horizontally averaged profile of variable var, unless already done by the 97 !-- relevant call from flow_statistics. The calculation is done only for the first respective 98 !-- intermediate timestep in order to spare communication time and to produce identical model 99 !-- results with jobs which are calling flow_statistics at different time intervals. At 99 100 !-- initialization, intermediate_timestep_count = 0 is considered as well. 100 101 101 IF ( .NOT. flow_statistics_called .AND. & 102 intermediate_timestep_count <= 1 ) THEN 102 IF ( .NOT. flow_statistics_called .AND. intermediate_timestep_count <= 1 ) THEN 103 103 104 104 ! … … 112 112 DO j = nys, nyn 113 113 DO k = nzb, nzt+1 114 sums_l(k,pr,tn) = sums_l(k,pr,tn) + var(k,j,i) & 115 * MERGE( 1.0_wp, 0.0_wp, & 116 BTEST( wall_flags_total_0(k,j,i), 22 ) ) 114 sums_l(k,pr,tn) = sums_l(k,pr,tn) + var(k,j,i) * MERGE( 1.0_wp, 0.0_wp, & 115 BTEST( wall_flags_total_0(k,j,i), 22 ) ) 117 116 ENDDO 118 117 ENDDO … … 127 126 128 127 IF ( collective_wait ) CALL MPI_BARRIER( comm2d, ierr ) 129 CALL MPI_ALLREDUCE( sums_l(nzb,pr,0), sums(nzb,pr), nzt+2-nzb, 130 MPI_REAL, MPI_SUM, comm2d,ierr )128 CALL MPI_ALLREDUCE( sums_l(nzb,pr,0), sums(nzb,pr), nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d,& 129 ierr ) 131 130 132 131 #else
Note: See TracChangeset
for help on using the changeset viewer.