Ignore:
Timestamp:
Jul 20, 2017 5:27:19 PM (7 years ago)
Author:
suehring
Message:

get topograpyh top index via function call

File:
1 edited

Legend:

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

    r2233 r2317  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Get topography top index via Function call
    2323!
    2424! Former revisions:
     
    9898
    9999    USE indices,                                                               &
    100         ONLY:  nxl, nxr, nyn, nys, nz, nzb, nzb_max, wall_flags_0
     100        ONLY:  nxl, nxr, nyn, nys, nz, nzb
    101101
    102102    USE kinds
     
    108108
    109109    USE pegrid
     110
     111    USE surface_mod,                                                           &
     112        ONLY:  get_topography_top_index
    110113
    111114    IMPLICIT NONE
     
    289292!--       The construct of MERGE and BTEST is used to determine the topography-
    290293!--       top index (former nzb_s_inner).
    291           zwall1 = zw( MAXLOC(                                                 &
    292                           MERGE( 1, 0,                                         &
    293                                  BTEST( wall_flags_0(nzb:nzb_max,j2,i2), 12 )  &
    294                                ), DIM = 1                                      &
    295                              ) - 1 )                                             
    296           zwall2 = zw( MAXLOC(                                                 &
    297                           MERGE( 1, 0,                                         &
    298                                  BTEST( wall_flags_0(nzb:nzb_max,j1,i1), 12 )  &
    299                                ), DIM = 1                                      &
    300                              ) - 1 ) 
    301           zwall3 = zw( MAXLOC(                                                 &
    302                           MERGE( 1, 0,                                         &
    303                                  BTEST( wall_flags_0(nzb:nzb_max,j1,i2), 12 )  &
    304                                ), DIM = 1                                      &
    305                              ) - 1 ) 
    306           zwall4 = zw( MAXLOC(                                                 &
    307                           MERGE( 1, 0,                                         &
    308                                  BTEST( wall_flags_0(nzb:nzb_max,j2,i1), 12 )  &
    309                                ), DIM = 1                                      &
    310                              ) - 1 ) 
     294          zwall1 = zw( get_topography_top_index( j2, i2, 's' ) )                                             
     295          zwall2 = zw( get_topography_top_index( j1, i1, 's' ) )
     296          zwall3 = zw( get_topography_top_index( j1, i2, 's' ) )
     297          zwall4 = zw( get_topography_top_index( j2, i1, 's' ) )
    311298!
    312299!--       Initialize flags to check if particle reflection is necessary
     
    493480!--             necessarily exactly match the wall location due to rounding
    494481!--             errors. At first, determine index of topography top at (j3,i3) 
    495                 k_wall = MAXLOC(                                               &
    496                             MERGE( 1, 0,                                       &
    497                                  BTEST( wall_flags_0(nzb:nzb_max,j3,i3), 12 )  &
    498                                  ), DIM = 1                                    &
    499                                ) - 1 
     482                k_wall = get_topography_top_index( j3, i3, 's' )
    500483                IF ( ABS( pos_x - xwall ) < eps      .AND.                     &
    501484                     pos_z <= zw(k_wall)             .AND.                     &
     
    534517!--             necessary, carry out reflection. At first, determine index of
    535518!--             topography top at (j3,i3) 
    536                 k_wall = MAXLOC(                                               &
    537                             MERGE( 1, 0,                                       &
    538                                  BTEST( wall_flags_0(nzb:nzb_max,j3,i3), 12 )  &
    539                                  ), DIM = 1                                    &
    540                                ) - 1 
     519                k_wall = get_topography_top_index( j3, i3, 's' )
    541520                IF ( ABS( pos_y - ywall ) < eps      .AND.                     &
    542521                     pos_z <= zw(k_wall)             .AND.                     &
     
    565544!--                Determine index of topography top at (j3,i3) and chick if
    566545!--                particle is below. 
    567                    k_wall = MAXLOC(                                            &
    568                           MERGE( 1, 0,                                         &
    569                                    BTEST( wall_flags_0(nzb:nzb_max,j3,i3), 12 )&
    570                                ), DIM = 1                                      &
    571                                   ) - 1 
     546                   k_wall = get_topography_top_index( j3, i3, 's' )
    572547                   IF ( pos_z - zw(k_wall) < eps ) THEN
    573548 
Note: See TracChangeset for help on using the changeset viewer.