Ignore:
Timestamp:
Dec 14, 2017 6:46:24 PM (7 years ago)
Author:
suehring
Message:

Particle reflections at downward-facing walls; revision of particle speed interpolations at walls; bugfixes in get_topography_index and in date constants

File:
1 edited

Legend:

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

    r2696 r2698  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Bugfix in get_topography_top_index
    2323!
    2424! Former revisions:
     
    272272
    273273    USE surface_mod,                                                           &
    274         ONLY:  get_topography_top_index, surf_def_h, surf_def_v, surf_lsm_h,   &
     274        ONLY:  get_topography_top_index, get_topography_top_index_ji,          &
     275               surf_def_h, surf_def_v, surf_lsm_h,                             &
    275276               surf_lsm_v, surf_type, surf_usm_h, surf_usm_v
    276277
     
    32443245!
    32453246!--             Obtain topography top index (lower bound of RRTMG)
    3246                 k_topo = get_topography_top_index( j, i, 's' )
     3247                k_topo = get_topography_top_index_ji( j, i, 's' )
    32473248
    32483249                IF ( lw_radiation )  THEN
     
    44114412                  pc_heating_rate, lad_s, prototype_lad, usm_lad_rma       
    44124413       
    4413        USE surface_mod,                                                        &
    4414            ONLY:  get_topography_top_index, surf_lsm_h, surf_lsm_v, surf_usm_h,&
    4415                   surf_usm_v
    4416 
    44174414       IMPLICIT NONE
    44184415
     
    44484445!
    44494446!--                Find topography top index
    4450                    k_topo = get_topography_top_index( j, i, 's' )
     4447                   k_topo = get_topography_top_index_ji( j, i, 's' )
    44514448
    44524449                   DO k = nzt+1, 0, -1
     
    45534550                DO  j = ijdb(3,ids), ijdb(4,ids)
    45544551
    4555                    k_topo  = get_topography_top_index( j, i, 's' )
    4556                    k_topo2 = get_topography_top_index( j-jdir(ids), i-idir(ids), 's' )
     4552                   k_topo  = get_topography_top_index_ji( j, i, 's' )
     4553                   k_topo2 = get_topography_top_index_ji( j-jdir(ids), i-idir(ids), 's' )
    45574554
    45584555
     
    45724569             DO j = nys, nyn
    45734570!--              Find topography top index
    4574                  k_topo = get_topography_top_index( j, i, 's' )
     4571                 k_topo = get_topography_top_index_ji( j, i, 's' )
    45754572                 k = nzut - k_topo
    45764573                 nsurfl = nsurfl + 6 * k
     
    45934590!
    45944591!--                Find topography top index
    4595                    k_topo = get_topography_top_index( j, i, 's' )
     4592                   k_topo = get_topography_top_index_ji( j, i, 's' )
    45964593
    45974594                   DO k = k_topo + 1, pct(j,i)
     
    47094706               DO i = ijdb(1,ids), ijdb(2,ids)
    47104707                   DO j = ijdb(3,ids), ijdb(4,ids)
    4711                        k_topo  = get_topography_top_index( j, i, 's' )
    4712                        k_topo2 = get_topography_top_index( j-jdir(ids), i-idir(ids), 's' )
     4708                       k_topo  = get_topography_top_index_ji( j, i, 's' )
     4709                       k_topo2 = get_topography_top_index_ji( j-jdir(ids), i-idir(ids), 's' )
    47134710
    47144711                       DO k = MAX(k_topo,k_topo2)+1, nzut
     
    47274724          DO i = nxl, nxr
    47284725             DO j = nys, nyn
    4729                 k_topo = get_topography_top_index( j, i, 's' )
     4726                k_topo = get_topography_top_index_ji( j, i, 's' )
    47304727
    47314728!--             add upward surface
     
    47464743          DO i = nxl, nxr
    47474744             DO j = nys, nyn
    4748                 k_topo = get_topography_top_index( j, i, 's' )
     4745                k_topo = get_topography_top_index_ji( j, i, 's' )
    47494746!--             north
    47504747                IF ( j /= ny ) THEN
     
    47524749                   jr = min(max(j-jdir(ids),0),ny)
    47534750                   ir = min(max(i-idir(ids),0),nx)
    4754                    k_topo2 = get_topography_top_index( jr, ir, 's' )
     4751                   k_topo2 = get_topography_top_index_ji( jr, ir, 's' )
    47554752                   DO k = MAX(k_topo,k_topo2)+1, nzut
    47564753                      isurf = isurf + 1
     
    47634760                   jr = min(max(j-jdir(ids),0),ny)
    47644761                   ir = min(max(i-idir(ids),0),nx)
    4765                    k_topo2 = get_topography_top_index( jr, ir, 's' )
     4762                   k_topo2 = get_topography_top_index_ji( jr, ir, 's' )
    47664763
    47674764                   DO k = MAX(k_topo,k_topo2)+1, nzut
     
    47754772                   jr = min(max(j-jdir(ids),0),ny)
    47764773                   ir = min(max(i-idir(ids),0),nx)
    4777                    k_topo2 = get_topography_top_index( jr, ir, 's' )
     4774                   k_topo2 = get_topography_top_index_ji( jr, ir, 's' )
    47784775
    47794776                   DO k = MAX(k_topo,k_topo2)+1, nzut
     
    47874784                   jr = min(max(j-jdir(ids),0),ny)
    47884785                   ir = min(max(i-idir(ids),0),nx)
    4789                    k_topo2 = get_topography_top_index( jr, ir, 's' )
     4786                   k_topo2 = get_topography_top_index_ji( jr, ir, 's' )
    47904787
    47914788                   DO k = MAX(k_topo,k_topo2)+1, nzut
     
    52555252!
    52565253!--             Following expression equals former kk = k - nzb_s_inner(j,i)
    5257                 kk = k - get_topography_top_index( j, i, 's' )  !- lad arrays are defined flat
     5254                kk = k - get_topography_top_index_ji( j, i, 's' )  !- lad arrays are defined flat
    52585255                pc_heating_rate(kk, j, i) = (pcbinsw(ipcgb) + pcbinlw(ipcgb)) &
    52595256                    * pchf_prep(k) * pt(k, j, i) !-- = dT/dt
     
    58565853            DO i = nxl, nxr
    58575854                DO j = nys, nyn
    5858                     k = get_topography_top_index( j, i, 's' )
     5855                    k = get_topography_top_index_ji( j, i, 's' )
    58595856
    58605857                    usm_lad(k:nzut, j, i) = lad_s(0:nzut-k, j, i)
Note: See TracChangeset for help on using the changeset viewer.