Changeset 3379 for palm


Ignore:
Timestamp:
Oct 19, 2018 12:38:28 PM (5 years ago)
Author:
knoop
Message:

Added topography flags to subroutine init_pt_anomaly

File:
1 edited

Legend:

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

    r3035 r3379  
    2525! -----------------
    2626! $Id$
     27! Added topography flags
     28!
     29! 3035 2018-05-24 09:35:20Z schwenkel
    2730! Add option to initialize warm air bubble close to surface
    2831!
     
    7073!------------------------------------------------------------------------------!
    7174 SUBROUTINE init_pt_anomaly
    72  
     75
    7376
    7477    USE arrays_3d,                                                             &
    7578        ONLY:  pt, zu
    7679
    77     USE control_parameters   
    78        
     80    USE control_parameters
     81
    7982    USE grid_variables,                                                        &
    8083        ONLY:  dx, dy
    8184
    8285    USE indices,                                                               &
    83         ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nzb, nzt
    84        
     86        ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nzb, nzt, wall_flags_0
     87
    8588    USE kinds
    8689
     
    9396    INTEGER(iwp) ::  k  !< grid index along z
    9497    INTEGER(iwp) ::  kc !< center index along z
    95    
     98
    9699    REAL(wp)     ::  amount                               !< amount of temperature perturbation
    97100    REAL(wp)     ::  bubble_center_y                      !< center of bubble in y
     
    99102    REAL(wp)     ::  bubble_sigma_y = 300.0               !< width of bubble in y
    100103    REAL(wp)     ::  bubble_sigma_z = 150.0               !< width of bubble in z
     104    REAL(wp)     ::  flag                                 !< flag to mask topography grid points
    101105    REAL(wp)     ::  initial_temperature_difference = 0.4 !< temperature perturbation for bubble in K
    102106    REAL(wp)     ::  radius                               !< radius of pt anomaly
     
    105109    REAL(wp)     ::  y                                    !< y dimension of pt anomaly
    106110    REAL(wp)     ::  z                                    !< z dimension of pt anomaly
    107    
    108    
     111
     112
    109113!
    110114!-- Defaults: radius rc, strength z,
     
    114118    jc =  ic
    115119    kc =  nzt / 2
    116    
     120
    117121    IF ( INDEX( initializing_actions, 'initialize_ptanom' ) /= 0 )  THEN
    118122!
     
    121125          DO  j = nys, nyn
    122126             DO  k = nzb+1, nzt
     127!
     128!--             Predetermine flag to mask topography
     129                flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
     130
    123131                x = ( i - ic ) * dx
    124132                y = ( j - jc ) * dy
     
    131139                ENDIF
    132140
    133                 pt(k,j,i) = pt(k,j,i) + amount
     141                pt(k,j,i) = pt(k,j,i) + amount * flag
    134142
    135143             ENDDO
    136144          ENDDO
    137145       ENDDO
    138        
     146
    139147!
    140148!-- Initialize warm air bubble close to surface and homogenous elegonated
     
    144152!--    Calculate y-center of model domain
    145153       bubble_center_y = ( ny + 1.0 ) * dy / 2.0
    146    
     154
    147155!
    148156!--    Compute perturbation for potential temperaure
    149157       DO  i = nxl, nxr
    150158          DO  j = nys, nyn
    151              DO  k = nzb+1, nzt
     159             DO  k = nzb+1, nzt
     160!
     161!--             Predetermine flag to mask topography
     162                flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
     163
    152164                pt(k,j,i) = pt(k,j,i) +                                        &
    153165                               EXP( -0.5 * ( (j* dy  - bubble_center_y) /      &
     
    155167                               EXP( -0.5 * ( (zu(k)  - bubble_center_z) /      &
    156168                                                       bubble_sigma_z)**2) *   &
    157                                initial_temperature_difference
     169                               initial_temperature_difference * flag
    158170             ENDDO
    159171          ENDDO
Note: See TracChangeset for help on using the changeset viewer.