Ignore:
Timestamp:
Mar 3, 2021 3:39:08 PM (3 years ago)
Author:
suehring
Message:

Remove offset in terrain-following masked output and allow only mask_k_over_surface >= 1

File:
1 edited

Legend:

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

    r4873 r4895  
    2626! -----------------
    2727! $Id$
     28! Remove offset in terrain-following masked output
     29!
     30! 4873 2021-02-12 17:12:17Z monakurppa
    2831! local namelist parameter added to switch off the module although the respective module namelist
    2932! appears in the namelist file
     
    1251312516    INTEGER(iwp) ::  kk             !< loop index for masked output in z-direction
    1251412517    INTEGER(iwp) ::  mid            !< masked output running index
    12515     INTEGER(iwp) ::  ktt            !< k index of highest terrain surface
     12518    INTEGER(iwp) ::  ktt            !< k index of lowest non-terrain grid point
    1251612519
    1251712520    LOGICAL ::  found      !<
     
    1255412557                   DO  j = 1, mask_size_l(mid,2)
    1255512558!
    12556 !--                   Get k index of the highest terraing surface
     12559!--                   Get k index of the lowest non-terrain grid point
    1255712560                      im = mask_i(mid,i)
    1255812561                      jm = mask_j(mid,j)
    12559                       ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )), &
    12560                                                     DIM = 1 ) - 1
     12562                      ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 ) ),        &
     12563                                    DIM = 1 ) - 1
    1256112564                      DO  k = 1, mask_size_l(mid,3)
    12562                          kk = MIN( ktt+mask_k(mid,k), nzt+1 )
    12563 !
    12564 !--                      Set value if not in building
     12565                         kk = MIN( ktt + mask_k(mid,k) - 1, nzt+1 )
     12566!
     12567!--                      Set value if not in building, else set fill value
    1256512568                         IF ( BTEST( wall_flags_total_0(kk,jm,im), 6 ) )  THEN
    1256612569                            local_pf(i,j,k) = fill_value
     
    1260912612                   DO  j = 1, mask_size_l(mid,2)
    1261012613!
    12611 !--                   Get k index of the highest terraing surface
     12614!--                   Get k index of the lowest non-terrain grid point
    1261212615                      im = mask_i(mid,i)
    1261312616                      jm = mask_j(mid,j)
    12614                       ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )), &
    12615                                                     DIM = 1 ) - 1
     12617                      ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )),         &
     12618                                           DIM = 1 ) - 1
    1261612619                      DO  k = 1, mask_size_l(mid,3)
    12617                          kk = MIN( ktt+mask_k(mid,k), nzt+1 )
    12618 !
    12619 !--                      Set value if not in building
     12620                         kk = MIN( ktt + mask_k(mid,k) - 1, nzt+1 )
     12621!
     12622!--                      Set value if not in building, else set fill value
    1262012623                         IF ( BTEST( wall_flags_total_0(kk,jm,im), 6 ) )  THEN
    1262112624                            local_pf(i,j,k) = fill_value
     
    1269012693                      DO  j = 1, mask_size_l(mid,2)
    1269112694!
    12692 !--                      Get k index of the highest terraing surface
     12695!--                      Get k index of the lowest non-terrain grid point
    1269312696                         im = mask_i(mid,i)
    1269412697                         jm = mask_j(mid,j)
    12695                          ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )), &
    12696                                                        DIM = 1 ) - 1
     12698                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )),      &
     12699                                       DIM = 1 ) - 1
    1269712700                         DO  k = 1, mask_size_l(mid,3)
    12698                             kk = MIN( ktt+mask_k(mid,k), nzt+1 )
    12699 !
    12700 !--                         Set value if not in building
     12701                            kk = MIN( ktt + mask_k(mid,k) - 1, nzt+1 )
     12702!
     12703!--                         Set value if not in building, else set fill value
    1270112704                            IF ( BTEST( wall_flags_total_0(kk,jm,im), 6 ) )  THEN
    1270212705                               local_pf(i,j,k) = fill_value
     
    1274012743                      DO  j = 1, mask_size_l(mid,2)
    1274112744!
    12742 !--                      Get k index of the highest terraing surface
     12745!--                      Get k index of the lowest non-terrain grid point
    1274312746                         im = mask_i(mid,i)
    1274412747                         jm = mask_j(mid,j)
    12745                          ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )), &
    12746                                                        DIM = 1 ) - 1
     12748                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )),      &
     12749                                       DIM = 1 ) - 1
    1274712750                         DO  k = 1, mask_size_l(mid,3)
    12748                             kk = MIN( ktt+mask_k(mid,k), nzt+1 )
    12749 !
    12750 !--                         Set value if not in building
     12751                            kk = MIN( ktt + mask_k(mid,k) - 1, nzt+1 )
     12752!
     12753!--                         Set value if not in building, else set fill value
    1275112754                            IF ( BTEST( wall_flags_total_0(kk,jm,im), 6 ) )  THEN
    1275212755                               local_pf(i,j,k) = fill_value
     
    1278812791                      DO  j = 1, mask_size_l(mid,2)
    1278912792!
    12790 !--                      Get k index of the highest terraing surface
     12793!--                      Get k index of the lowest non-terrain grid point
    1279112794                         im = mask_i(mid,i)
    1279212795                         jm = mask_j(mid,j)
    12793                          ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )), &
    12794                                                        DIM = 1 ) - 1
     12796                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )),      &
     12797                                       DIM = 1 ) - 1
    1279512798                         DO  k = 1, mask_size_l(mid,3)
    12796                             kk = MIN( ktt+mask_k(mid,k), nzt+1 )
    12797 !
    12798 !--                         Set value if not in building
     12799                            kk = MIN( ktt + mask_k(mid,k) - 1, nzt+1 )
     12800!
     12801!--                         Set value if not in building, else set fill value
    1279912802                            IF ( BTEST( wall_flags_total_0(kk,jm,im), 6 ) )  THEN
    1280012803                               local_pf(i,j,k) = fill_value
     
    1284012843                      DO  j = 1, mask_size_l(mid,2)
    1284112844!
    12842 !--                      Get k index of the highest terraing surface
     12845!--                      Get k index of the lowest non-terrain grid point
    1284312846                         im = mask_i(mid,i)
    1284412847                         jm = mask_j(mid,j)
    12845                          ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )), &
    12846                                                        DIM = 1 ) - 1
     12848                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )),      &
     12849                                       DIM = 1 ) - 1
    1284712850                         DO  k = 1, mask_size_l(mid,3)
    12848                             kk = MIN( ktt+mask_k(mid,k), nzt+1 )
    12849 !
    12850 !--                         Set value if not in building
     12851                            kk = MIN( ktt + mask_k(mid,k) - 1, nzt+1 )
     12852!
     12853!--                         Set value if not in building, else set fill value
    1285112854                            IF ( BTEST( wall_flags_total_0(kk,jm,im), 6 ) )  THEN
    1285212855                               local_pf(i,j,k) = fill_value
     
    1289212895                      DO  j = 1, mask_size_l(mid,2)
    1289312896!
    12894 !--                      Get k index of the highest terraing surface
     12897!--                      Get k index of the lowest non-terrain grid point
    1289512898                         im = mask_i(mid,i)
    1289612899                         jm = mask_j(mid,j)
    12897                          ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )), &
    12898                                                        DIM = 1 ) - 1
     12900                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 ) ),    &
     12901                                       DIM = 1 ) - 1
    1289912902                         DO  k = 1, mask_size_l(mid,3)
    12900                             kk = MIN( ktt+mask_k(mid,k), nzt+1 )
    12901 !
    12902 !--                         Set value if not in building
     12903                            kk = MIN( ktt + mask_k(mid,k) - 1, nzt+1 )
     12904!
     12905!--                         Set value if not in building, else set fill value
    1290312906                            IF ( BTEST( wall_flags_total_0(kk,jm,im), 6 ) )  THEN
    1290412907                               local_pf(i,j,k) = fill_value
     
    1294412947                      DO  j = 1, mask_size_l(mid,2)
    1294512948!
    12946 !--                      Get k index of the highest terraing surface
     12949!--                      Get k index of the lowest non-terrain grid point
    1294712950                         im = mask_i(mid,i)
    1294812951                         jm = mask_j(mid,j)
    12949                          ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )), &
    12950                                                        DIM = 1 ) - 1
     12952                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )),      &
     12953                                       DIM = 1 ) - 1
    1295112954                         DO  k = 1, mask_size_l(mid,3)
    12952                             kk = MIN( ktt+mask_k(mid,k), nzt+1 )
    12953 !
    12954 !--                         Set value if not in building
     12955                            kk = MIN( ktt + mask_k(mid,k) - 1, nzt+1 )
     12956!
     12957!--                         Set value if not in building, else set fill value
    1295512958                            IF ( BTEST( wall_flags_total_0(kk,jm,im), 6 ) )  THEN
    1295612959                               local_pf(i,j,k) = fill_value
     
    1299412997                         DO  j = 1, mask_size_l(mid,2)
    1299512998   !
    12996    !--                      Get k index of the highest terraing surface
     12999   !--                      Get k index of the lowest non-terrain grid point
    1299713000                            im = mask_i(mid,i)
    1299813001                            jm = mask_j(mid,j)
    12999                             ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )), &
    13000                                                           DIM = 1 ) - 1
     13002                            ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )),   &
     13003                                          DIM = 1 ) - 1
    1300113004                            DO  k = 1, mask_size_l(mid,3)
    13002                                kk = MIN( ktt+mask_k(mid,k), nzt+1 )
     13005                               kk = MIN( ktt + mask_k(mid,k) - 1, nzt+1 )
    1300313006   !
    13004    !--                         Set value if not in building
     13007   !--                         Set value if not in building, else set fill value
    1300513008                               IF ( BTEST( wall_flags_total_0(kk,jm,im), 6 ) )  THEN
    1300613009                                  local_pf(i,j,k) = fill_value
     
    1304713050                      DO  j = 1, mask_size_l(mid,2)
    1304813051!
    13049 !--                      Get k index of the highest terraing surface
     13052!--                      Get k index of the lowest non-terrain grid point
    1305013053                         im = mask_i(mid,i)
    1305113054                         jm = mask_j(mid,j)
    13052                          ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )), &
    13053                                           DIM = 1 ) - 1
     13055                         ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )),      &
     13056                                       DIM = 1 ) - 1
    1305413057                         DO  k = 1, mask_size_l(mid,3)
    13055                             kk = MIN( ktt+mask_k(mid,k), nzt+1 )
    13056 !
    13057 !--                         Set value if not in building
     13058                            kk = MIN( ktt + mask_k(mid,k) - 1, nzt+1 )
     13059!
     13060!--                         Set value if not in building, else set fill value
    1305813061                            IF ( BTEST( wall_flags_total_0(kk,jm,im), 6 ) )  THEN
    1305913062                               local_pf(i,j,k) = fill_value
     
    1309313096             DO  j = 1, mask_size_l(mid,2)
    1309413097!
    13095 !--             Get k index of the highest terraing surface
     13098!--             Get k index of the lowest non-terrain grid point
    1309613099                im = mask_i(mid,i)
    1309713100                jm = mask_j(mid,j)
    13098                 ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )), &
    13099                                  DIM = 1 ) - 1
     13101                ktt = MINLOC( MERGE( 1, 0, BTEST( wall_flags_total_0(:,jm,im), 5 )), DIM = 1 ) - 1
    1310013102                DO  k = 1, mask_size_l(mid,3)
    13101                    kk = MIN( ktt+mask_k(mid,k), nzt+1 )
    13102 !
    13103 !--                Set value if not in building
     13103                   kk = MIN( ktt + mask_k(mid,k) - 1, nzt+1 )
     13104!
     13105!--                Set value if not in building, else set fill value
    1310413106                   IF ( BTEST( wall_flags_total_0(kk,jm,im), 6 ) )  THEN
    1310513107                      local_pf(i,j,k) = fill_value
Note: See TracChangeset for help on using the changeset viewer.