Ignore:
Timestamp:
Aug 24, 2020 4:02:40 PM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/inflow_turbulence.f90

    r4429 r4646  
    11!> @file inflow_turbulence.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    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.
    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/>.
     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.
     8!
     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.
     12!
     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/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
    2120! -----------------
    22 ! 
    23 ! 
     21!
     22!
    2423! Former revisions:
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4429 2020-02-27 15:24:30Z raasch
    2729! bugfix: cpp-directives added for serial mode
    28 ! 
     30!
    2931! 4360 2020-01-07 11:25:50Z suehring
    3032! use y_shift instead of old parameter recycling_yshift
    31 ! 
     33!
    3234! 4297 2019-11-21 10:37:50Z oliver.maas
    33 ! changed recycling_yshift so that the y-shift can be a multiple of PE
    34 ! instead of y-shift of a half domain width
    35 ! 
     35! changed recycling_yshift so that the y-shift can be a multiple of PE instead of y-shift of a half
     36! domain width
     37!
    3638! 4183 2019-08-23 07:33:16Z oliver.maas
    37 ! simplified steering of recycling of absolute values by initialization
    38 ! parameter recycling_method_for_thermodynamic_quantities
    39 ! 
     39! simplified steering of recycling of absolute values by initialization parameter
     40! recycling_method_for_thermodynamic_quantities
     41!
    4042! 4182 2019-08-22 15:20:23Z scharf
    4143! Corrected "Former revisions" section
    42 ! 
     44!
    4345! 4172 2019-08-20 11:55:33Z oliver.maas
    4446! added optional recycling of absolute values for pt and q
    45 ! 
     47!
    4648! 3655 2019-01-07 16:51:22Z knoop
    4749! Corrected "Former revisions" section
     
    5153! Description:
    5254! ------------
    53 !> Imposing turbulence at the respective inflow using the turbulence
    54 !> recycling method of Kataoka and Mizuno (2002).
    55 !------------------------------------------------------------------------------!
     55!> Imposing turbulence at the respective inflow using the turbulence recycling method of
     56!> Kataoka and Mizuno (2002).
     57!--------------------------------------------------------------------------------------------------!
    5658 SUBROUTINE inflow_turbulence
    57  
    58 
    59     USE arrays_3d,                                                             &
     59
     60
     61    USE arrays_3d,                                                                                 &
    6062        ONLY:  e, inflow_damping_factor, mean_inflow_profiles, pt, q, s, u, v, w
    61        
    62 #if defined( __parallel )
    63     USE control_parameters,                                                    &
    64         ONLY:  humidity, passive_scalar, recycling_plane, y_shift,             &
    65                recycling_method_for_thermodynamic_quantities
     63
     64#if defined( __parallel )
     65    USE control_parameters,                                                                        &
     66        ONLY:  humidity, passive_scalar, recycling_method_for_thermodynamic_quantities,            &
     67               recycling_plane, y_shift
     68
    6669#else
    67     USE control_parameters,                                                    &
    68         ONLY:  humidity, passive_scalar, recycling_plane,                      &
    69                recycling_method_for_thermodynamic_quantities
    70 #endif
    71        
    72     USE cpulog,                                                                &
     70    USE control_parameters,                                                                        &
     71        ONLY:  humidity, passive_scalar, recycling_method_for_thermodynamic_quantities,            &
     72               recycling_plane
     73
     74#endif
     75
     76    USE cpulog,                                                                                    &
    7377        ONLY:  cpu_log, log_point
    74        
    75     USE indices,                                                               &
     78
     79    USE indices,                                                                                   &
    7680        ONLY:  nbgp, nxl, ny, nyn, nys, nyng, nysg, nzb, nzt
    77        
     81
    7882    USE kinds
    79    
     83
    8084    USE pegrid
    8185
    8286
    8387    IMPLICIT NONE
    84    
     88
    8589    INTEGER(iwp) ::  i        !< loop index
    8690    INTEGER(iwp) ::  j        !< loop index
     
    9498#endif
    9599
    96     REAL(wp), DIMENSION(nzb:nzt+1,7,nbgp)           ::                         &
    97        avpr               !< stores averaged profiles at recycling plane
    98     REAL(wp), DIMENSION(nzb:nzt+1,7,nbgp)           ::                         &
    99        avpr_l             !< auxiliary variable to calculate avpr
    100     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,7,nbgp) ::                         &
    101        inflow_dist        !< turbulence signal of vars, added at inflow boundary
    102 #if defined( __parallel )
    103     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,7,nbgp) ::                         &
    104        local_inflow_dist  !< auxiliary variable for inflow_dist, used for y-shift
    105 #endif
    106    
     100    REAL(wp), DIMENSION(nzb:nzt+1,7,nbgp) ::  avpr               !< stores averaged profiles at recycling plane
     101    REAL(wp), DIMENSION(nzb:nzt+1,7,nbgp) ::  avpr_l             !< auxiliary variable to calculate avpr
     102
     103    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,7,nbgp) ::  inflow_dist        !< turbulence signal of vars, added at inflow boundary
     104#if defined( __parallel )
     105    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,7,nbgp) ::  local_inflow_dist  !< auxiliary variable for inflow_dist, used for y-shift
     106#endif
     107
    107108    CALL cpu_log( log_point(40), 'inflow_turbulence', 'start' )
    108    
     109
    109110!
    110111!-- Carry out spanwise averaging in the recycling plane
     
    119120#if defined( __parallel )
    120121    IF ( myidx == id_recycling )  THEN
    121        
     122
    122123       DO  l = 1, nbgp
    123124          DO  j = nys, nyn
     
    129130                avpr_l(k,4,l) = avpr_l(k,4,l) + pt(k,j,i)
    130131                avpr_l(k,5,l) = avpr_l(k,5,l) + e(k,j,i)
    131                 IF ( humidity )                                                &
    132                    avpr_l(k,6,l) = avpr_l(k,6,l) + q(k,j,i)
    133                 IF ( passive_scalar )                                          &
    134                    avpr_l(k,7,l) = avpr_l(k,7,l) + s(k,j,i)
     132                IF ( humidity )  avpr_l(k,6,l) = avpr_l(k,6,l) + q(k,j,i)
     133                IF ( passive_scalar )  avpr_l(k,7,l) = avpr_l(k,7,l) + s(k,j,i)
    135134
    136135             ENDDO
     
    143142!-- Now, averaging over all PEs
    144143    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    145     CALL MPI_ALLREDUCE( avpr_l(nzb,1,1), avpr(nzb,1,1), ngp_pr, MPI_REAL,      &
    146                         MPI_SUM, comm2d, ierr )
     144    CALL MPI_ALLREDUCE( avpr_l(nzb,1,1), avpr(nzb,1,1), ngp_pr, MPI_REAL, MPI_SUM, comm2d, ierr )
    147145
    148146#else
     
    156154             avpr_l(k,4,l) = avpr_l(k,4,l) + pt(k,j,i)
    157155             avpr_l(k,5,l) = avpr_l(k,5,l) + e(k,j,i)
    158              IF ( humidity )                                                   &
    159                 avpr_l(k,6,l) = avpr_l(k,6,l) + q(k,j,i)
    160              IF ( passive_scalar )                                             &
    161                 avpr_l(k,7,l) = avpr_l(k,7,l) + s(k,j,i)
    162 
    163           ENDDO
    164        ENDDO
    165        i = i + 1
     156             IF ( humidity )  avpr_l(k,6,l) = avpr_l(k,6,l) + q(k,j,i)
     157             IF ( passive_scalar )  avpr_l(k,7,l) = avpr_l(k,7,l) + s(k,j,i)
     158
     159          ENDDO
     160       ENDDO
     161       i = i + 1
    166162    ENDDO
    167    
     163
    168164    avpr = avpr_l
    169165#endif
     
    171167    avpr = avpr / ( ny + 1 )
    172168!
    173 !-- Calculate the disturbances at the recycling plane
    174 !-- for recycling of absolute quantities, the disturbance is defined as the absolute value
    175 !-- (and not as the deviation from the mean profile)
     169!-- Calculate the disturbances at the recycling plane for recycling of absolute quantities, the
     170!-- disturbance is defined as the absolute value (and not as the deviation from the mean profile).
    176171    i = recycling_plane
    177172
     
    184179                inflow_dist(k,j,2,l) = v(k,j,i)   - avpr(k,2,l)
    185180                inflow_dist(k,j,3,l) = w(k,j,i)   - avpr(k,3,l)
    186                 IF ( TRIM( recycling_method_for_thermodynamic_quantities )     &
    187                    == 'turbulent_fluctuation' )  THEN
     181                IF ( TRIM( recycling_method_for_thermodynamic_quantities )                         &
     182                     == 'turbulent_fluctuation' )  THEN
    188183                   inflow_dist(k,j,4,l) = pt(k,j,i) - avpr(k,4,l)
    189                 ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities ) &
    190                    == 'absolute_value' )  THEN
     184                ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )                     &
     185                         == 'absolute_value' )  THEN
    191186                   inflow_dist(k,j,4,l) = pt(k,j,i)
    192187                ENDIF
    193188                inflow_dist(k,j,5,l) = e(k,j,i)   - avpr(k,5,l)
    194189                IF ( humidity ) THEN
    195                    IF ( TRIM( recycling_method_for_thermodynamic_quantities )  &
    196                       == 'turbulent_fluctuation' )  THEN
     190                   IF ( TRIM( recycling_method_for_thermodynamic_quantities )                      &
     191                        == 'turbulent_fluctuation' )  THEN
    197192                      inflow_dist(k,j,6,l) = q(k,j,i) - avpr(k,6,l)
    198                    ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )  &
    199                       == 'absolute_value' )  THEN
     193                   ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )                  &
     194                            == 'absolute_value' )  THEN
    200195                      inflow_dist(k,j,6,l) = q(k,j,i)
    201196                   ENDIF
    202197                ENDIF
    203                 IF ( passive_scalar )                                          &
     198                IF ( passive_scalar )                                                              &
    204199                   inflow_dist(k,j,7,l) = s(k,j,i) - avpr(k,7,l)
    205200            ENDDO
     
    216211             inflow_dist(k,j,2,l) = v(k,j,i)   - avpr(k,2,l)
    217212             inflow_dist(k,j,3,l) = w(k,j,i)   - avpr(k,3,l)
    218              IF ( TRIM( recycling_method_for_thermodynamic_quantities )        &
     213             IF ( TRIM( recycling_method_for_thermodynamic_quantities )                            &
    219214                   == 'turbulent_fluctuation' )  THEN
    220215                inflow_dist(k,j,4,l) = pt(k,j,i) - avpr(k,4,l)
    221              ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )    &
    222                    == 'absolute_value' )  THEN
     216             ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )                        &
     217                      == 'absolute_value' )  THEN
    223218                inflow_dist(k,j,4,l) = pt(k,j,i)
    224219             ENDIF
    225220             inflow_dist(k,j,5,l) = e(k,j,i)   - avpr(k,5,l)
    226221             IF ( humidity )  THEN
    227                 IF ( TRIM( recycling_method_for_thermodynamic_quantities )     &
    228                       == 'turbulent_fluctuation' )  THEN
     222                IF ( TRIM( recycling_method_for_thermodynamic_quantities )                         &
     223                     == 'turbulent_fluctuation' )  THEN
    229224                   inflow_dist(k,j,6,l) = q(k,j,i) - avpr(k,6,l)
    230                 ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities ) &
    231                       == 'absolute_value' )  THEN
     225                ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )                     &
     226                         == 'absolute_value' )  THEN
    232227                   inflow_dist(k,j,6,l) = q(k,j,i)
    233228                ENDIF
    234229             ENDIF
    235              IF ( passive_scalar )                                             &
     230             IF ( passive_scalar )                                                                 &
    236231                inflow_dist(k,j,7,l) = s(k,j,i) - avpr(k,7,l)
    237              
     232
    238233          ENDDO
    239234       ENDDO
     
    247242    IF ( myidx == id_recycling  .AND.  myidx /= id_inflow )  THEN
    248243
    249        CALL MPI_SEND( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL,            &
    250                       id_inflow, 1, comm1dx, ierr )
     244       CALL MPI_SEND( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL, id_inflow, 1, comm1dx, ierr )
    251245
    252246    ELSEIF ( myidx /= id_recycling  .AND.  myidx == id_inflow )  THEN
    253247
    254248       inflow_dist = 0.0_wp
    255        CALL MPI_RECV( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL,            &
    256                       id_recycling, 1, comm1dx, status, ierr )
     249       CALL MPI_RECV( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL, id_recycling, 1, comm1dx,      &
     250                      status, ierr )
    257251
    258252    ENDIF
     
    262256!-- Shift inflow_dist in positive y direction by a number of
    263257!-- PEs equal to y_shift
    264     IF ( ( y_shift /= 0 ) .AND. myidx == id_inflow ) THEN
    265 
    266 !
    267 !--    Calculate the ID of the PE which sends data to this PE (prev) and of the
    268 !--    PE which receives data from this PE (next).
     258    IF ( ( y_shift /= 0 )  .AND.  myidx == id_inflow ) THEN
     259
     260!
     261!--    Calculate the ID of the PE which sends data to this PE (prev) and of the PE which receives
     262!--    data from this PE (next).
    269263       prev = MODULO(myidy - y_shift , pdims(2))
    270264       next = MODULO(myidy + y_shift , pdims(2))
    271        
     265
    272266       local_inflow_dist = 0.0_wp
    273267
    274        CALL MPI_SENDRECV( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL,        &
    275                           next, 1, local_inflow_dist(nzb,nysg,1,1), ngp_ifd,   &
    276                           MPI_REAL, prev, 1, comm1dy, status, ierr )
     268       CALL MPI_SENDRECV( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL, next, 1,                   &
     269                          local_inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL, prev, 1, comm1dy,    &
     270                          status, ierr )
    277271
    278272       inflow_dist = local_inflow_dist
     
    289283          DO  k = nzb, nzt + 1
    290284
    291              u(k,j,-nbgp+1:0) = mean_inflow_profiles(k,1) +                    &
    292                         inflow_dist(k,j,1,1:nbgp) * inflow_damping_factor(k)
    293              v(k,j,-nbgp:-1)  = mean_inflow_profiles(k,2) +                    &
    294                         inflow_dist(k,j,2,1:nbgp) * inflow_damping_factor(k)
    295              w(k,j,-nbgp:-1)  =                                                &
    296                         inflow_dist(k,j,3,1:nbgp) * inflow_damping_factor(k)
    297              IF ( TRIM( recycling_method_for_thermodynamic_quantities )        &
     285             u(k,j,-nbgp+1:0) = mean_inflow_profiles(k,1) +                                        &
     286                                inflow_dist(k,j,1,1:nbgp) * inflow_damping_factor(k)
     287             v(k,j,-nbgp:-1)  = mean_inflow_profiles(k,2) +                                        &
     288                                inflow_dist(k,j,2,1:nbgp) * inflow_damping_factor(k)
     289             w(k,j,-nbgp:-1)  = inflow_dist(k,j,3,1:nbgp) * inflow_damping_factor(k)
     290             IF ( TRIM( recycling_method_for_thermodynamic_quantities )                            &
    298291                   == 'turbulent_fluctuation' )  THEN
    299                 pt(k,j,-nbgp:-1) = mean_inflow_profiles(k,4) +                 &
    300                 inflow_dist(k,j,4,1:nbgp) * inflow_damping_factor(k)
    301              ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )    &
    302                    == 'absolute_value' )  THEN
     292                pt(k,j,-nbgp:-1) = mean_inflow_profiles(k,4) +                                     &
     293                                   inflow_dist(k,j,4,1:nbgp) * inflow_damping_factor(k)
     294             ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )                        &
     295                      == 'absolute_value' )  THEN
    303296                pt(k,j,-nbgp:-1) = inflow_dist(k,j,4,1:nbgp)
    304297             ENDIF
    305              e(k,j,-nbgp:-1)  = mean_inflow_profiles(k,5) +                    &
    306                         inflow_dist(k,j,5,1:nbgp) * inflow_damping_factor(k)
     298             e(k,j,-nbgp:-1)  = mean_inflow_profiles(k,5) +                                        &
     299                                inflow_dist(k,j,5,1:nbgp) * inflow_damping_factor(k)
    307300             e(k,j,-nbgp:-1)  = MAX( e(k,j,-nbgp:-1), 0.0_wp )
    308301             IF ( humidity )  THEN
    309                 IF ( TRIM( recycling_method_for_thermodynamic_quantities )     &
     302                IF ( TRIM( recycling_method_for_thermodynamic_quantities )                         &
    310303                      == 'turbulent_fluctuation' )  THEN
    311                    q(k,j,-nbgp:-1)  = mean_inflow_profiles(k,6) +              &
    312                       inflow_dist(k,j,6,1:nbgp) * inflow_damping_factor(k)
    313                 ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities ) &
    314                       == 'absolute_value' )  THEN
     304                   q(k,j,-nbgp:-1)  = mean_inflow_profiles(k,6) +                                  &
     305                                      inflow_dist(k,j,6,1:nbgp) * inflow_damping_factor(k)
     306                ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )                     &
     307                         == 'absolute_value' )  THEN
    315308                   q(k,j,-nbgp:-1)  = inflow_dist(k,j,6,1:nbgp)
    316309                ENDIF
    317310             ENDIF
    318              IF ( passive_scalar )                                             &
    319                 s(k,j,-nbgp:-1)  = mean_inflow_profiles(k,7) +                 &
    320                         inflow_dist(k,j,7,1:nbgp) * inflow_damping_factor(k)
    321                        
    322           ENDDO
    323        ENDDO
    324 
    325     ENDIF
    326 
    327 
    328     CALL cpu_log( log_point(40), 'inflow_turbulence', 'stop' )
     311             IF ( passive_scalar )                                                                 &
     312                s(k,j,-nbgp:-1)  = mean_inflow_profiles(k,7) +                                     &
     313                                   inflow_dist(k,j,7,1:nbgp) * inflow_damping_factor(k)
     314
     315          ENDDO
     316       ENDDO
     317
     318    ENDIF
     319
     320
     321    CALL  cpu_log( log_point(40), 'inflow_turbulence', 'stop' )
    329322
    330323
Note: See TracChangeset for help on using the changeset viewer.