Ignore:
Timestamp:
Apr 17, 2018 10:27:57 AM (6 years ago)
Author:
kanani
Message:

Fixes for radiative transfer model

File:
1 edited

Legend:

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

    r2970 r2977  
    2626! -----------------
    2727! $Id$
     28! Implement changes from branch radiation (r2948-2971) with minor modifications,
     29! plus some formatting.
     30! (moh.hefny)
     31! Added flag to check the existence of vertical urban/land surfaces, required
     32! to activate RTM
     33!
     34! 2970 2018-04-13 15:09:23Z suehring
    2835! Remove un-necessary initialization of surface elements in old large-scale
    2936! forcing mode
     
    450457    INTEGER(iwp) ::  ns_v_on_file(0:3)                       !< total number of vertical surfaces with the same facing, required for writing restart data
    451458
     459    LOGICAL ::  vertical_surfaces_exist = .FALSE.   !< flag indicating that there are vertical urban/land surfaces
     460                                                    !< in the domain (required to activiate RTM)
     461
    452462
    453463    SAVE
     
    488498    PUBLIC bc_h, ind_pav_green, ind_veg_wall, ind_wat_win, ns_h_on_file,       &
    489499           ns_v_on_file, surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v,       &
    490            surf_usm_h, surf_usm_v, surf_type
     500           surf_usm_h, surf_usm_v, surf_type, vertical_surfaces_exist
    491501!
    492502!-- Public subroutines and functions
     
    615625    SUBROUTINE init_surface_arrays
    616626
     627
     628       USE pegrid
     629
     630
    617631       IMPLICIT NONE
    618632
     
    628642       INTEGER(iwp), DIMENSION(0:3) ::  num_lsm_v !< number of vertically-aligned natural surfaces
    629643       INTEGER(iwp), DIMENSION(0:3) ::  num_usm_v !< number of vertically-aligned urban surfaces
     644
     645       INTEGER(iwp)              ::  num_surf_v_l !< number of vertically-aligned local urban/land surfaces
     646       INTEGER(iwp)              ::  num_surf_v   !< number of vertically-aligned total urban/land surfaces
    630647
    631648       LOGICAL ::  building                       !< flag indicating building grid point
     
    920937                                               nys, nyn, nxl, nxr )
    921938       ENDDO
    922 
     939!
     940!--    Set the flag for the existence of vertical urban/land surfaces
     941       num_surf_v_l = 0
     942       DO  l = 0, 3
     943          num_surf_v_l = num_surf_v_l + surf_usm_v(l)%ns + surf_lsm_v(l)%ns
     944       ENDDO
     945
     946#if defined( __parallel )
     947       CALL MPI_ALLREDUCE( num_surf_v_l, num_surf_v, 1, MPI_INTEGER, MPI_SUM, comm2d, ierr)
     948#else
     949       num_surf_v = num_surf_v_l
     950#endif
     951       IF ( num_surf_v > 0 ) vertical_surfaces_exist = .TRUE.
     952       
    923953
    924954    END SUBROUTINE init_surface_arrays
Note: See TracChangeset for help on using the changeset viewer.