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_advec.f90

    r2233 r2317  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! Get topography top index via Function call
    2323!
    2424! Former revisions:
     
    126126       
    127127    USE indices,                                                               &
    128         ONLY:  nzb, nzb_max, nzt, wall_flags_0
     128        ONLY:  nzb, nzt
    129129       
    130130    USE kinds
     
    140140
    141141    USE surface_mod,                                                           &
    142         ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
     142        ONLY:  get_topography_top_index, surf_def_h, surf_lsm_h, surf_usm_h
    143143
    144144    IMPLICIT NONE
     
    284284!
    285285!--       Determine vertical index of topography top
    286           k_wall = MAXLOC(                                                     &
    287                        MERGE( 1, 0,                                            &
    288                               BTEST( wall_flags_0(nzb:nzb_max,jlog,ilog), 12 ) &
    289                             ), DIM = 1                                         &
    290                          ) - 1
     286          k_wall = get_topography_top_index( jlog,ilog, 's' )
    291287
    292288          IF ( constant_flux_layer  .AND.  zv(n) - zw(k_wall) < z_p )  THEN
     
    385381!
    386382!--       Determine vertical index of topography top
    387           k_wall = MAXLOC(                                                     &
    388                        MERGE( 1, 0,                                            &
    389                               BTEST( wall_flags_0(nzb:nzb_max,jlog,ilog), 12 ) &
    390                             ), DIM = 1                                         &
    391                          ) - 1
     383          k_wall = get_topography_top_index( jlog,ilog, 's' )
    392384
    393385          IF ( constant_flux_layer  .AND.  zv(n) - zw(k_wall) < z_p )  THEN
     
    677669!
    678670!--          Determine vertical index of topography top at (j,i)
    679              k_wall = MAXLOC(                                                  &
    680                           MERGE( 1, 0,                                         &
    681                                  BTEST( wall_flags_0(nzb:nzb_max,j,i), 12 )    &
    682                                ), DIM = 1                                      &
    683                             ) - 1
     671             k_wall = get_topography_top_index( j, i, 's' )
    684672!
    685673!--          To do: Reconsider order of computations in order to avoid
     
    700688!
    701689!--          Determine vertical index of topography top at (j+1,i)
    702              k_wall = MAXLOC(                                                  &
    703                           MERGE( 1, 0,                                         &
    704                                  BTEST( wall_flags_0(nzb:nzb_max,j+1,i), 12 )  &
    705                                ), DIM = 1                                      &
    706                             ) - 1
     690             k_wall = get_topography_top_index( j+1, i, 's' )
     691
    707692             IF ( k > k_wall  .OR.  k_wall == 0 )  THEN
    708693                num_gp = num_gp + 1
     
    720705!
    721706!--          Determine vertical index of topography top at (j,i)
    722              k_wall = MAXLOC(                                                  &
    723                           MERGE( 1, 0,                                         &
    724                                  BTEST( wall_flags_0(nzb:nzb_max,j,i), 12 )    &
    725                                ), DIM = 1                                      &
    726                             ) - 1
     707             k_wall = get_topography_top_index( j, i, 's' )
     708
    727709             IF ( k+1 > k_wall  .OR.  k_wall == 0 )  THEN
    728710                num_gp = num_gp + 1
     
    740722!
    741723!--          Determine vertical index of topography top at (j+1,i)
    742              k_wall = MAXLOC(                                                  &
    743                           MERGE( 1, 0,                                         &
    744                                  BTEST( wall_flags_0(nzb:nzb_max,j+1,i), 12 )  &
    745                                ), DIM = 1                                      &
    746                             ) - 1
     724             k_wall = get_topography_top_index( j+1, i, 's' )
    747725             IF ( k+1 > k_wall  .OR.  k_wall == 0 )  THEN
    748726                num_gp = num_gp + 1
     
    760738!
    761739!--          Determine vertical index of topography top at (j,i+1)
    762              k_wall = MAXLOC(                                                  &
    763                           MERGE( 1, 0,                                         &
    764                                  BTEST( wall_flags_0(nzb:nzb_max,j,i+1), 12 )  &
    765                                ), DIM = 1                                      &
    766                             ) - 1
     740             k_wall = get_topography_top_index( j, i+1, 's' )
    767741             IF ( k > k_wall  .OR.  k_wall == 0 )  THEN
    768742                num_gp = num_gp + 1
     
    780754!
    781755!--          Determine vertical index of topography top at (j+1,i+1)
    782              k_wall = MAXLOC(                                                  &
    783                           MERGE( 1, 0,                                         &
    784                                  BTEST( wall_flags_0(nzb:nzb_max,j+1,i+1), 12 )&
    785                                ), DIM = 1                                      &
    786                             ) - 1
     756             k_wall = get_topography_top_index( j+1, i+1, 's' )
     757
    787758             IF ( k > k_wall  .OR.  k_wall == 0 )  THEN
    788759                num_gp = num_gp + 1
     
    800771!
    801772!--          Determine vertical index of topography top at (j,i+1)
    802              k_wall = MAXLOC(                                                  &
    803                           MERGE( 1, 0,                                         &
    804                                  BTEST( wall_flags_0(nzb:nzb_max,j,i+1), 12 )  &
    805                                ), DIM = 1                                      &
    806                             ) - 1
     773             k_wall = get_topography_top_index( j, i+1, 's' )
     774
    807775             IF ( k+1 > k_wall  .OR.  k_wall == 0 )  THEN
    808776                num_gp = num_gp + 1
     
    820788!
    821789!--          Determine vertical index of topography top at (j+1,i+1)
    822              k_wall = MAXLOC(                                                  &
    823                           MERGE( 1, 0,                                         &
    824                                  BTEST( wall_flags_0(nzb:nzb_max,j+1,i+1), 12 )&
    825                                ), DIM = 1                                      &
    826                             ) - 1
     790             k_wall = get_topography_top_index( j+1, i+1, 's' )
     791
    827792             IF ( k+1 > k_wall  .OR.  k_wall == 0)  THEN
    828793                num_gp = num_gp + 1
Note: See TracChangeset for help on using the changeset viewer.