Ignore:
Timestamp:
Dec 16, 2019 8:17:03 AM (4 years ago)
Author:
Giersch
Message:

Topography closed channel flow with symmetric boundaries implemented, ID tag in radiation module corrected

File:
1 edited

Legend:

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

    r4329 r4340  
    2525! -----------------
    2626! $Id$
     27! Topography closed channel flow with symmetric boundaries implemented
     28!
     29! 4329 2019-12-10 15:46:36Z motisi
    2730! Renamed wall_flags_0 to wall_flags_static_0
    2831!
     
    132135               momentum_advec, number_stretch_level_end,                       &
    133136               number_stretch_level_start, ocean_mode, psolver, scalar_advec,  &
    134                topography, use_surface_fluxes
     137               symmetry_flag, topography, use_surface_fluxes
    135138         
    136139    USE grid_variables,                                                        &
     
    360363!--    the first u/v- and w-level (k=0) are defined at same height (z=0).
    361364!--    The second u-level (k=1) corresponds to the top of the
    362 !--    Prandtl-layer.
    363        IF ( ibc_uv_b == 0 .OR. ibc_uv_b == 2 ) THEN
     365!--    Prandtl-layer. In case of symmetric boundaries (closed channel flow),
     366!--    the first grid point is always at z=0.
     367       IF ( ibc_uv_b == 0 .OR. ibc_uv_b == 2 .OR.                              &
     368            topography == 'closed_channel' ) THEN
    364369          zu(0) = 0.0_wp
    365370       ELSE
     
    379384!--    The default value of dz_stretch_level_start is negative, thus the first
    380385!--    condition is always true. Hence, the second condition is necessary.
    381        DO  k = 2, nzt+1
     386       DO  k = 2, nzt+1-symmetry_flag
    382387          IF ( dz_stretch_level_start(n) <= zu(k-1) .AND.                      &
    383388               dz_stretch_level_start(n) /= -9999999.9_wp ) THEN
     
    408413          ENDIF
    409414       ENDDO
     415       
     416!
     417!--    If a closed channel flow is simulated, make sure that grid structure is 
     418!--    the same for both bottom and top boundary. (Hint: Using a different dz
     419!--    at the bottom and at the top makes no sense due to symmetric boundaries
     420!--    where dz should be equal. Therefore, different dz at the bottom and top 
     421!--    causes an abort (see check_parameters).)
     422       IF ( topography == 'closed_channel' ) THEN
     423          zu(nzt+1) = zu(nzt) + dz(1) * 0.5_wp
     424       ENDIF
    410425
    411426!
     
    413428!--    corresponding u-levels. In case of dirichlet bc for u and v at the
    414429!--    ground the first u- and w-level (k=0) are defined at same height (z=0).
    415 !--    The top w-level is extrapolated linearly.
     430!--    Per default, the top w-level is extrapolated linearly. In case of
     431!--    a closed channel flow, zu(nzt+1) and zw(nzt) must be set explicitely.
     432!--    (Hint: Using a different dz at the bottom and at the top makes no sense
     433!--    due to symmetric boundaries where dz should be equal. Therefore,
     434!--    different dz at the bottom and top causes an abort (see
     435!--    check_parameters).)
    416436       zw(0) = 0.0_wp
    417        DO  k = 1, nzt
     437       DO  k = 1, nzt-symmetry_flag
    418438          zw(k) = ( zu(k) + zu(k+1) ) * 0.5_wp
    419439       ENDDO
    420        zw(nzt+1) = zw(nzt) + 2.0_wp * ( zu(nzt+1) - zw(nzt) )
     440       IF ( topography == 'closed_channel' ) THEN
     441          zw(nzt)   = zw(nzt-1) + dz(1)
     442          zw(nzt+1) = zw(nzt) + dz(1)
     443       ELSE
     444          zw(nzt+1) = zw(nzt) + 2.0_wp * ( zu(nzt+1) - zw(nzt) )
     445       ENDIF
    421446
    422447    ELSE
     
    18171842!   
    18181843!--       Initialilize 3D topography array, used later for initializing flags
    1819           topo(nzb+1:nzt+1,:,:) = IBSET( topo(nzb+1:nzt+1,:,:), 0 )
     1844          topo(nzb+1:nzt+1,:,:) = IBSET( topo(nzb+1:nzt+1,:,:), 0 )
     1845         
     1846       CASE ( 'closed_channel' )
     1847!   
     1848!--       Initialilize 3D topography array, used later for initializing flags
     1849          topo(nzb+1:nzt,:,:) = IBSET( topo(nzb+1:nzt,:,:), 0 )
    18201850
    18211851       CASE ( 'single_building' )
     
    22382268!--    is applicable. If this is not possible, abort.
    22392269       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
    2240           IF ( TRIM( topography ) /= 'single_building' .AND.                   &
     2270          IF ( TRIM( topography ) /= 'closed_channel' .AND.                    &
     2271               TRIM( topography ) /= 'single_building' .AND.                   &
    22412272               TRIM( topography ) /= 'single_street_canyon' .AND.              &
    22422273               TRIM( topography ) /= 'tunnel'  .AND.                           &
     
    22502281               'is not set. Its default value is & only valid for ',           &
    22512282               '"topography" = ''single_building'', ''tunnel'' ',              &
    2252                '''single_street_canyon'' & or ''read_from_file''.',            &
     2283               '''single_street_canyon'', ''closed_channel'' & or ',           &
     2284               '''read_from_file''.',                                          &
    22532285               '& Choose ''cell_edge'' or ''cell_center''.'
    22542286             CALL message( 'init_grid', 'PA0239', 1, 2, 0, 6, 0 )
     
    23442376!
    23452377!--          scalar grid
    2346              IF ( BTEST( topo(k,j,i), 0 ) )                                 &
     2378             IF ( BTEST( topo(k,j,i), 0 ) )                                    &
    23472379                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 0 )
    23482380!
    23492381!--          u grid
    2350              IF ( BTEST( topo(k,j,i),   0 )  .AND.                          &
    2351                   BTEST( topo(k,j,i-1), 0 ) )                               &
     2382             IF ( BTEST( topo(k,j,i),   0 )  .AND.                             &
     2383                  BTEST( topo(k,j,i-1), 0 ) )                                  &
    23522384                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 1 )
    23532385!
    23542386!--          v grid
    2355              IF ( BTEST( topo(k,j,i),   0 )  .AND.                          &
    2356                   BTEST( topo(k,j-1,i), 0 ) )                               &
     2387             IF ( BTEST( topo(k,j,i),   0 )  .AND.                             &
     2388                  BTEST( topo(k,j-1,i), 0 ) )                                  &
    23572389                 wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 2 )
    23582390
     
    23622394!
    23632395!--          w grid
    2364              IF ( BTEST( topo(k,j,i),   0 )  .AND.                          &
    2365                   BTEST( topo(k+1,j,i), 0 ) )                               &
     2396             IF ( BTEST( topo(k,j,i),   0 )  .AND.                             &
     2397                  BTEST( topo(k+1,j,i), 0 ) )                                  &
    23662398                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 3 )
    23672399          ENDDO
    2368           wall_flags_static_0(nzt+1,j,i) = IBSET( wall_flags_static_0(nzt+1,j,i), 3 )
     2400         
     2401          IF ( topography /= 'closed_channel' ) THEN
     2402             wall_flags_static_0(nzt+1,j,i) = IBSET( wall_flags_static_0(nzt+1,j,i), 3 )
     2403          ENDIF
    23692404
    23702405       ENDDO
     
    24792514!
    24802515!--       Flags indicating downward facing walls
    2481           DO k = nzb+1, nzt
     2516          DO k = nzb+1, nzt+1
    24822517!
    24832518!--          Scalar grid
Note: See TracChangeset for help on using the changeset viewer.