Changeset 3038 for palm


Ignore:
Timestamp:
May 24, 2018 10:54:00 AM (6 years ago)
Author:
gronemeier
Message:

updated variable description

File:
1 edited

Legend:

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

    r2967 r3038  
    2525! -----------------
    2626! $Id$
     27! updated variable descriptions
     28!
     29! 2967 2018-04-13 11:22:08Z raasch
    2730! bugfix: missing parallel cpp-directives added
    28 ! 
     31!
    2932! 2946 2018-04-04 17:01:23Z suehring
    3033! Remove unused module load
    31 ! 
     34!
    3235! 2945 2018-04-04 16:27:14Z suehring
    33 ! - Bugfix in parallelization of synthetic turbulence generator in case the 
    34 !   z-dimension is not an integral divisor of the number of processors along 
     36! - Bugfix in parallelization of synthetic turbulence generator in case the
     37!   z-dimension is not an integral divisor of the number of processors along
    3538!   the x- and y-dimension
    36 ! - Revision in control mimic in case of RAN-LES nesting 
    37 ! 
     39! - Revision in control mimic in case of RAN-LES nesting
     40!
    3841! 2938 2018-03-27 15:52:42Z suehring
    39 ! Apply turbulence generator at all non-cyclic lateral boundaries in case of 
    40 ! realistic Inifor large-scale forcing or RANS-LES nesting 
    41 ! 
     42! Apply turbulence generator at all non-cyclic lateral boundaries in case of
     43! realistic Inifor large-scale forcing or RANS-LES nesting
     44!
    4245! 2936 2018-03-27 14:49:27Z suehring
    43 ! variable named found has been introduced for checking if restart data was found, 
    44 ! reading of restart strings has been moved completely to read_restart_data_mod, 
    45 ! redundant skipping function has been removed, stg_read/write_restart_data 
    46 ! have been renamed to stg_r/wrd_global, stg_rrd_global is called in 
     46! variable named found has been introduced for checking if restart data was found,
     47! reading of restart strings has been moved completely to read_restart_data_mod,
     48! redundant skipping function has been removed, stg_read/write_restart_data
     49! have been renamed to stg_r/wrd_global, stg_rrd_global is called in
    4750! read_restart_data_mod now, flag syn_turb_gen_prerun and marker *** end stg
    48 ! *** have been removed (Giersch), strings and their respective lengths are 
    49 ! written out and read now in case of restart runs to get rid of prescribed 
    50 ! character lengths (Giersch), CASE DEFAULT was added if restart data is read 
    51 ! 
     51! *** have been removed (Giersch), strings and their respective lengths are
     52! written out and read now in case of restart runs to get rid of prescribed
     53! character lengths (Giersch), CASE DEFAULT was added if restart data is read
     54!
    5255! 2841 2018-02-27 15:02:57Z suehring
    5356! Bugfix: wrong placement of include 'mpif.h' corrected
    54 ! 
     57!
    5558! 2836 2018-02-26 13:40:05Z Giersch
    56 ! The variables synthetic_turbulence_generator and 
     59! The variables synthetic_turbulence_generator and
    5760! use_synthetic_turbulence_generator have been abbreviated + syn_turb_gen_prerun
    5861! flag is used to define if module related parameters were outputted as restart
    59 ! data 
    60 ! 
     62! data
     63!
    6164! 2716 2017-12-29 16:35:59Z kanani
    6265! Corrected "Former revisions" section
    63 ! 
     66!
    6467! 2696 2017-12-14 17:12:51Z kanani
    6568! Change in file header (GPL part)
     
    6871! unit number for file containing turbulence generator data changed to 90
    6972! bugfix: preprocessor directives added for MPI specific code
    70 ! 
     73!
    7174! 2576 2017-10-24 13:49:46Z Giersch
    72 ! Definition of a new function called stg_skip_global to skip module 
     75! Definition of a new function called stg_skip_global to skip module
    7376! parameters during reading restart data
    74 ! 
     77!
    7578! 2563 2017-10-19 15:36:10Z Giersch
    7679! stg_read_restart_data is called in stg_parin in the case of a restart run
    77 ! 
     80!
    7881! 2259 2017-06-08 09:09:11Z gronemeier
    7982! Initial revision
    8083!
    81 ! 
     84!
    8285!
    8386! Authors:
     
    148151    LOGICAL :: use_syn_turb_gen = .FALSE.           !< switch to use synthetic turbulence generator
    149152
    150     INTEGER(iwp) ::  id_stg_left        !< left lateral boundary core id in case of turbulence generator 
    151     INTEGER(iwp) ::  id_stg_north       !< north lateral boundary core id in case of turbulence generator 
    152     INTEGER(iwp) ::  id_stg_right       !< right lateral boundary core id in case of turbulence generator 
    153     INTEGER(iwp) ::  id_stg_south       !< south lateral boundary core id in case of turbulence generator 
     153    INTEGER(iwp) ::  id_stg_left        !< left lateral boundary core id in case of turbulence generator
     154    INTEGER(iwp) ::  id_stg_north       !< north lateral boundary core id in case of turbulence generator
     155    INTEGER(iwp) ::  id_stg_right       !< right lateral boundary core id in case of turbulence generator
     156    INTEGER(iwp) ::  id_stg_south       !< south lateral boundary core id in case of turbulence generator
    154157    INTEGER(iwp) ::  stg_type_xz        !< MPI type for full z range
    155158    INTEGER(iwp) ::  stg_type_xz_small  !< MPI type for small z range
     
    158161    INTEGER(iwp) ::  merg               !< maximum length scale (in gp)
    159162    INTEGER(iwp) ::  mergp              !< merg + nbgp
    160     INTEGER(iwp) ::  nzb_x_stg          !<
    161     INTEGER(iwp) ::  nzt_x_stg          !<
    162     INTEGER(iwp) ::  nzb_y_stg          !<
    163     INTEGER(iwp) ::  nzt_y_stg          !<
     163    INTEGER(iwp) ::  nzb_x_stg          !< lower bound of z coordinate (required for transposing z on PEs along x)
     164    INTEGER(iwp) ::  nzt_x_stg          !< upper bound of z coordinate (required for transposing z on PEs along x)
     165    INTEGER(iwp) ::  nzb_y_stg          !< lower bound of z coordinate (required for transposing z on PEs along y)
     166    INTEGER(iwp) ::  nzt_y_stg          !< upper bound of z coordinate (required for transposing z on PEs along y)
    164167
    165168    REAL(wp) :: mc_factor    !< mass flux correction factor
     
    325328    IF ( use_syn_turb_gen )  THEN
    326329
    327        IF ( .NOT. forcing  .AND.  .NOT. nest_domain )  THEN 
     330       IF ( .NOT. forcing  .AND.  .NOT. nest_domain )  THEN
    328331
    329332          IF ( INDEX( initializing_actions, 'set_constant_profiles' ) == 0     &
     
    446449    REAL(wp) :: lwy     !< length scale for w in y direction
    447450    REAL(wp) :: lwz     !< length scale for w in z direction
    448     REAL(wp) :: nnz     !< increment used to determine processor decomposition of z-axis along x and y direction 
     451    REAL(wp) :: nnz     !< increment used to determine processor decomposition of z-axis along x and y direction
    449452    REAL(wp) :: zz      !< height
    450453
     
    482485    nzt_x_stg = ( myidx + 1 ) * INT( nnz )
    483486
    484     IF ( MOD( nz , pdims(1) ) /= 0  .AND.  myidx == id_stg_right )             & 
     487    IF ( MOD( nz , pdims(1) ) /= 0  .AND.  myidx == id_stg_right )             &
    485488       nzt_x_stg = nzt_x_stg + myidx * ( nnz - INT( nnz ) )
    486489!        nzt_x_stg = myidx * nnz + MOD( nz , pdims(1) )
     
    493496
    494497       IF ( MOD( nz , pdims(2) ) /= 0  .AND.  myidy == id_stg_north )          &
    495           nzt_y_stg = nzt_y_stg + myidy * ( nnz - INT( nnz ) ) 
     498          nzt_y_stg = nzt_y_stg + myidy * ( nnz - INT( nnz ) )
    496499!           nzt_y_stg = myidy * nnz + MOD( nz , pdims(2) )
    497500    ENDIF
     
    503506    extent = 1 * realsize
    504507!
    505 !-- Set-up MPI datatyp to involve all cores for turbulence generation at yz 
    506 !-- layer 
     508!-- Set-up MPI datatyp to involve all cores for turbulence generation at yz
     509!-- layer
    507510!-- stg_type_yz: yz-slice with vertical bounds nzb:nzt+1
    508511    CALL MPI_TYPE_CREATE_SUBARRAY( 2, [nzt-nzb+2,nyng-nysg+1],                 &
     
    529532    ENDDO
    530533!
    531 !-- Set-up MPI datatyp to involve all cores for turbulence generation at xz 
    532 !-- layer 
     534!-- Set-up MPI datatyp to involve all cores for turbulence generation at xz
     535!-- layer
    533536!-- stg_type_xz: xz-slice with vertical bounds nzb:nzt+1
    534537    IF ( forcing  .OR.  ( nest_domain .AND.  rans_mode_parent  .AND.           &
     
    615618
    616619       CLOSE( 90 )
    617    
     620
    618621    ELSE
    619622!
    620 !--    Set-up defaul length scales. Assume exponentially decreasing length 
    621 !--    scales and isotropic turbulence. 
    622 !--    Typical length (time) scales of 100 m (s) should be a good compromise 
    623 !--    between all stratrifications. Near-surface variances are fixed to 
     623!--    Set-up defaul length scales. Assume exponentially decreasing length
     624!--    scales and isotropic turbulence.
     625!--    Typical length (time) scales of 100 m (s) should be a good compromise
     626!--    between all stratrifications. Near-surface variances are fixed to
    624627!--    0.1 m2/s2, vertical fluxes are one order of magnitude smaller.
    625 !--    Vertical fluxes 
     628!--    Vertical fluxes
    626629       length_scale_surface = 100.0_wp
    627630       r_ii_0               = 0.1_wp
     
    683686!
    684687!-- Assign initial profiles
    685     IF ( .NOT. forcing  .AND.  .NOT.  nest_domain )  THEN 
     688    IF ( .NOT. forcing  .AND.  .NOT.  nest_domain )  THEN
    686689       u_init = mean_inflow_profiles(:,1)
    687690       v_init = mean_inflow_profiles(:,2)
     
    959962    IMPLICIT NONE
    960963
    961     LOGICAL, INTENT(OUT)  ::  found 
     964    LOGICAL, INTENT(OUT)  ::  found
    962965
    963966
    964967    found = .TRUE.
    965  
     968
    966969
    967970    SELECT CASE ( restart_string(1:length) )
     
    974977       CASE DEFAULT
    975978
    976           found = .FALSE.   
     979          found = .FALSE.
    977980
    978981    END SELECT
     
    11661169!--    This correction factor insures that the mass flux is preserved at the
    11671170!--    inflow boundary
    1168        IF ( .NOT. forcing  .AND.  .NOT. nest_domain )  THEN 
     1171       IF ( .NOT. forcing  .AND.  .NOT. nest_domain )  THEN
    11691172          mc_factor_l = 0.0_wp
    11701173          mc_factor   = 0.0_wp
     
    12101213             DO  k = nzb+1, nzt
    12111214                volume_flow_l = volume_flow_l + u(k,j,i) * dzw(k) * dy         &
    1212                                      * MERGE( 1.0_wp, 0.0_wp,                  &   
     1215                                     * MERGE( 1.0_wp, 0.0_wp,                  &
    12131216                                              BTEST( wall_flags_0(k,j,i), 1 ) )
    12141217
    12151218                mc_factor_l = mc_factor_l     + ( u(k,j,i) + dist_yz(k,j,1) )  &
    12161219                                                         * dzw(k) * dy         &
    1217                                      * MERGE( 1.0_wp, 0.0_wp,                  &   
     1220                                     * MERGE( 1.0_wp, 0.0_wp,                  &
    12181221                                              BTEST( wall_flags_0(k,j,i), 1 ) )
    12191222             ENDDO
     
    13291332          DO  k = nzb+1, nzt
    13301333             volume_flow_l = volume_flow_l + v(k,j,i) * dzw(k) * dx            &
    1331                                   * MERGE( 1.0_wp, 0.0_wp,                     &   
     1334                                  * MERGE( 1.0_wp, 0.0_wp,                     &
    13321335                                           BTEST( wall_flags_0(k,j,i), 2 ) )
    13331336
    13341337             mc_factor_l = mc_factor_l     + ( v(k,j,i) + dist_xz(k,i,2) )     &
    13351338                                                      * dzw(k) * dx            &
    1336                                   * MERGE( 1.0_wp, 0.0_wp,                     &   
     1339                                  * MERGE( 1.0_wp, 0.0_wp,                     &
    13371340                                           BTEST( wall_flags_0(k,j,i), 2 ) )
    13381341          ENDDO
Note: See TracChangeset for help on using the changeset viewer.