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

    r2302 r2317  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Get topography top index via Function call
    2323!
    2424! Former revisions:
     
    278278
    279279    USE surface_mod,                                                           &
    280         ONLY:  init_bc
     280        ONLY:  get_topography_top_index, init_bc
    281281
    282282    IMPLICIT NONE
     
    17131713!--    nxl to nxr and nys to nyn on south and right model boundary, hence,
    17141714!--    use intrinsic lbound and ubound functions to infer array bounds.
    1715        DO  i = lbound(zu_s_inner, 1), ubound(zu_s_inner, 1)
    1716           DO  j = lbound(zu_s_inner, 2), ubound(zu_s_inner, 2)
     1715       DO  i = LBOUND(zu_s_inner, 1), UBOUND(zu_s_inner, 1)
     1716          DO  j = LBOUND(zu_s_inner, 2), UBOUND(zu_s_inner, 2)
    17171717!
    17181718!--          Topography height on scalar grid. Therefore, determine index of
    1719 !--          upward-facing surface element on scalar grid (bit 12).
    1720              zu_s_inner(i,j) = zu( MAXLOC( MERGE(                              &
    1721                                          1, 0, BTEST( wall_flags_0(:,j,i), 12 )&
    1722                                                 ), DIM = 1                     &
    1723                                          ) - 1                                 &
    1724                                  )
     1719!--          upward-facing surface element on scalar grid.
     1720             zu_s_inner(i,j) = zu( get_topography_top_index( j, i, 's' ) )
     1721
     1722             write(9,*)  get_topography_top_index( j, i, 's' ), MAXLOC(                                                    &
     1723                          MERGE( 1, 0,                                         &
     1724                                 BTEST( wall_flags_0(:,j,i), 12 )  &
     1725                               ), DIM = 1                                      &
     1726                          ) - 1
    17251727!
    17261728!--          Topography height on w grid. Therefore, determine index of
    1727 !--          upward-facing surface element on w grid (bit 18).
    1728              zw_w_inner(i,j) = zw( MAXLOC( MERGE(                              &
    1729                                          1, 0, BTEST( wall_flags_0(:,j,i), 18 )&
    1730                                                 ), DIM = 1                     &
    1731                                          ) - 1                                 &
    1732                                  )
     1729!--          upward-facing surface element on w grid.
     1730             zw_w_inner(i,j) = zw( get_topography_top_index( j, i, 's' ) )
    17331731          ENDDO
    17341732       ENDDO
    1735 
     1733       flush(9)
    17361734
    17371735    ENDIF
Note: See TracChangeset for help on using the changeset viewer.