Ignore:
Timestamp:
May 30, 2017 5:47:52 PM (7 years ago)
Author:
suehring
Message:

Adjustments according new topography and surface-modelling concept implemented

File:
1 edited

Legend:

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

    r2101 r2232  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! +Generic tunnel added
     23! +Example of setting user-defined topography
    2324!
    2425! Former revisions:
     
    5556!> Execution of user-defined grid initializing actions
    5657!------------------------------------------------------------------------------!
    57  SUBROUTINE user_init_grid( nzb_local )
     58 SUBROUTINE user_init_grid( topo_3d )
    5859 
    5960
     
    6869    IMPLICIT NONE
    6970
    70     INTEGER(iwp), DIMENSION(nysg:nyng,nxlg:nxrg) ::  nzb_local   !<
     71    INTEGER(iwp)                                           ::  k_topo      !< topography top index
     72    INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  topo_3d     !< 3D topography field
     73
     74    REAL(wp) ::  h_topo !< user-defined topography height
    7175
    7276!
     
    7882    SELECT CASE ( TRIM( topography ) )
    7983
    80        CASE ( 'flat', 'single_building', 'single_street_canyon' )
     84       CASE ( 'flat', 'single_building', 'single_street_canyon', 'tunnel' )
    8185!
    8286!--       Not allowed here since these are the standard cases used in init_grid.
     
    8892          message_string = 'topography "' // topography // '" not available yet'
    8993          CALL message( 'user_init_grid', 'UI0005', 1, 2, 0, 6, 0 )
     94!
     95!--       The user is allowed to set surface-mounted as well as non-surface
     96!--       mounted topography (e.g. overhanging structures). For both, use
     97!--       3D array topo_3d and set bit 0. The convention is: bit is zero inside
     98!--       topography, bit is 1 for atmospheric grid point.
     99!--       The following example shows how to prescribe sine-like topography
     100!--       along x-direction with amplitude of 10 * dz and wavelength 10 * dy.
     101!           DO  i = nxlg, nxrg
     102!              h_topo = 10.0_wp * dz * (SIN(3.14_wp*0.5_wp)*i*dx / ( 5.0_wp * dy ) )**2
     103!
     104!              k_topo = MINLOC( ABS( zw - h_topo ), 1 ) - 1
     105!
     106!              topo_3d(k_topo+1:nzt+1,:,i) =                                     &
     107!                                          IBSET( topo_3d(k_topo+1:nzt+1,:,i), 0 )
     108!           ENDDO
     109!
     110!           CALL exchange_horiz_int( topo_3d, nbgp )
    90111
    91112       CASE DEFAULT
     
    100121
    101122
     123
     124
    102125 END SUBROUTINE user_init_grid
    103126
Note: See TracChangeset for help on using the changeset viewer.