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/lpm_boundary_conds.f90

    r2101 r2232  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Adjustments to new topography and surface concept
     23! Rename character range into location, as range is an intrinsic.
    2324!
    2425! Former revisions:
     
    7879!> (see offset_ocean_*)
    7980!------------------------------------------------------------------------------!
    80  SUBROUTINE lpm_boundary_conds( range )
     81 SUBROUTINE lpm_boundary_conds( location )
    8182 
    8283
     
    9495
    9596    USE indices,                                                               &
    96         ONLY:  nxl, nxr, nyn, nys, nz, nzb_s_inner
     97        ONLY:  nxl, nxr, nyn, nys, nz, nzb, nzb_max, wall_flags_0
    9798
    9899    USE kinds
     
    107108    IMPLICIT NONE
    108109
    109     CHARACTER (LEN=*) ::  range     !<
     110    CHARACTER (LEN=*) ::  location     !<
    110111   
    111112    INTEGER(iwp) ::  inc            !< dummy for sorting algorithmus
     
    118119    INTEGER(iwp) ::  j2             !< grid index (x) of current particle position
    119120    INTEGER(iwp) ::  j3             !< grid index (x) of intermediate particle position
     121    INTEGER(iwp) ::  k_wall         !< vertical index of topography top
    120122    INTEGER(iwp) ::  n              !< particle number
    121123    INTEGER(iwp) ::  t_index        !< running index for intermediate particle timesteps in reflection algorithmus
     
    167169
    168170
    169     IF ( range == 'bottom/top' )  THEN
     171    IF ( location == 'bottom/top' )  THEN
    170172
    171173!
     
    232234       ENDDO
    233235
    234     ELSEIF ( range == 'walls' )  THEN
     236    ELSEIF ( location == 'walls' )  THEN
    235237
    236238
     
    281283          ENDIF
    282284!
    283 !--       Walls aligned in xy layer at which particle can be possiblly reflected
    284           zwall1 = zw(nzb_s_inner(j2,i2))
    285           zwall2 = zw(nzb_s_inner(j1,i1))
    286           zwall3 = zw(nzb_s_inner(j1,i2))
    287           zwall4 = zw(nzb_s_inner(j2,i1))
     285!--       Walls aligned in xy layer at which particle can be possiblly reflected.
     286!--       The construct of MERGE and BTEST is used to determine the topography-
     287!--       top index (former nzb_s_inner).
     288          zwall1 = zw( MAXLOC(                                                 &
     289                          MERGE( 1, 0,                                         &
     290                                 BTEST( wall_flags_0(nzb:nzb_max,j2,i2), 12 )  &
     291                               ), DIM = 1                                      &
     292                             ) - 1 )                                             
     293          zwall2 = zw( MAXLOC(                                                 &
     294                          MERGE( 1, 0,                                         &
     295                                 BTEST( wall_flags_0(nzb:nzb_max,j1,i1), 12 )  &
     296                               ), DIM = 1                                      &
     297                             ) - 1 ) 
     298          zwall3 = zw( MAXLOC(                                                 &
     299                          MERGE( 1, 0,                                         &
     300                                 BTEST( wall_flags_0(nzb:nzb_max,j1,i2), 12 )  &
     301                               ), DIM = 1                                      &
     302                             ) - 1 ) 
     303          zwall4 = zw( MAXLOC(                                                 &
     304                          MERGE( 1, 0,                                         &
     305                                 BTEST( wall_flags_0(nzb:nzb_max,j2,i1), 12 )  &
     306                               ), DIM = 1                                      &
     307                             ) - 1 ) 
    288308!
    289309!--       Initialize flags to check if particle reflection is necessary
     
    469489!--             constant is required, as the particle position do not
    470490!--             necessarily exactly match the wall location due to rounding
    471 !--             errors.   
     491!--             errors. At first, determine index of topography top at (j3,i3) 
     492                k_wall = MAXLOC(                                               &
     493                            MERGE( 1, 0,                                       &
     494                                 BTEST( wall_flags_0(nzb:nzb_max,j3,i3), 12 )  &
     495                                 ), DIM = 1                                    &
     496                               ) - 1 
    472497                IF ( ABS( pos_x - xwall ) < eps      .AND.                     &
    473                      pos_z <= zw(nzb_s_inner(j3,i3)) .AND.                     &
     498                     pos_z <= zw(k_wall)            .AND.                     &
    474499                     reach_x(t_index)                .AND.                     &
    475500                     .NOT. reflect_x )  THEN
     
    504529!
    505530!--             Check if a particle needs to be reflected at any xz-wall. If
    506 !--             necessary, carry out reflection.
     531!--             necessary, carry out reflection. At first, determine index of
     532!--             topography top at (j3,i3) 
     533                k_wall = MAXLOC(                                               &
     534                            MERGE( 1, 0,                                       &
     535                                 BTEST( wall_flags_0(nzb:nzb_max,j3,i3), 12 )  &
     536                                 ), DIM = 1                                    &
     537                               ) - 1 
    507538                IF ( ABS( pos_y - ywall ) < eps      .AND.                     &
    508                      pos_z <= zw(nzb_s_inner(j3,i3)) .AND.                     &
     539                     pos_z <= zw(k_wall)            .AND.                     &
    509540                     reach_y(t_index)                .AND.                     &
    510541                     .NOT. reflect_y ) THEN
     
    525556!
    526557!--             Check if a particle needs to be reflected at any xy-wall. If
    527 !--             necessary, carry out reflection.
     558!--             necessary, carry out reflection. 
    528559                IF ( downwards .AND. reach_z(t_index) .AND.                    &
    529560                     .NOT. reflect_z )  THEN
    530                    IF ( pos_z - zw(nzb_s_inner(j3,i3)) < eps ) THEN
     561!
     562!--                Determine index of topography top at (j3,i3) and chick if
     563!--                particle is below. 
     564                   k_wall = MAXLOC(                                            &
     565                          MERGE( 1, 0,                                         &
     566                                   BTEST( wall_flags_0(nzb:nzb_max,j3,i3), 12 )&
     567                               ), DIM = 1                                      &
     568                                  ) - 1 
     569                   IF ( pos_z - zw(k_wall) < eps ) THEN
    531570 
    532                       pos_z = MAX( 2.0_wp * zw(nzb_s_inner(j3,i3)) - pos_z,    &
    533                                    zw(nzb_s_inner(j3,i3)) )
     571                      pos_z = MAX( 2.0_wp * zw(k_wall) - pos_z,    &
     572                                   zw(k_wall) )
    534573
    535574                      particles(n)%speed_z = - particles(n)%speed_z
Note: See TracChangeset for help on using the changeset viewer.