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

    r2299 r2317  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Get topography top index via Function call
    2323!
    2424! Former revisions:
     
    169169
    170170    USE indices,                                                               &
    171         ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt,           &
    172                wall_flags_0
     171        ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt
    173172
    174173    USE kinds
     
    200199        ONLY:  rrtmg_sw
    201200#endif
    202 
    203 
     201    USE surface_mod,                                                           &
     202        ONLY:  get_topography_top_index
    204203
    205204    IMPLICIT NONE
     
    11861185!
    11871186!--          Obtain vertical index of topography top
    1188              k = MAXLOC(                                                       &
    1189                         MERGE( 1, 0,                                           &
    1190                                BTEST( wall_flags_0(:,j,i), 12 )                &
    1191                              ), DIM = 1                                        &
    1192                        ) - 1
     1187             k = get_topography_top_index( j, i, 's' )
    11931188
    11941189             exn1 = (hyp(k+1) / 100000.0_wp )**0.286_wp
     
    12431238!--          Obtain vertical index of topography top. So far it is identical to
    12441239!--          nzb.
    1245              k = MAXLOC(                                                       &
    1246                         MERGE( 1, 0,                                           &
    1247                                BTEST( wall_flags_0(:,j,i), 12 )                &
    1248                              ), DIM = 1                                        &
    1249                        ) - 1
     1240             k = get_topography_top_index( j, i, 's' )
    12501241
    12511242             rad_net(j,i)      = net_radiation
Note: See TracChangeset for help on using the changeset viewer.