Ignore:
Timestamp:
Jun 9, 2017 11:57:32 AM (7 years ago)
Author:
suehring
Message:

Enable restarts with USM with different number of PEs; some bugfixes in new surface structure in USM; formatting adjustments and descriptions in surface_mod

File:
1 edited

Legend:

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

    r2256 r2269  
    2525! -----------------
    2626! $Id$
     27! Formatting and description adjustments
     28!
     29! 2256 2017-06-07 13:58:08Z suehring
    2730! Enable heating at downward-facing surfaces
    2831!
     
    3336! Description:
    3437! ------------
    35 !> Surface module contains defines derived data structures to treat surface-
     38!> Surface module defines derived data structures to treat surface-
    3639!> bounded grid cells. Three different types of surfaces are defined:
    37 !> default surfaces, natural surfaces, and urban surfaces. Moreover, the module
    38 !> encompasses the initialization of near-surface grid cells, and handles reading
    39 !> and writing restart data.
     40!> default surfaces, natural surfaces, and urban surfaces. The module
     41!> encompasses the allocation and initialization of surface arrays, and handles
     42!> reading and writing restart data.
    4043!> In addition, a further derived data structure is defined, in order to set
    41 !> boundary conditions at surfaces.   
     44!> boundary conditions at surfaces. 
    4245!------------------------------------------------------------------------------!
    4346 MODULE surface_mod
     
    16021605       IMPLICIT NONE
    16031606
    1604        CHARACTER(LEN=1)             ::  dum
    1605 
    1606        INTEGER(iwp)                 ::  i
    1607        INTEGER(iwp)                 ::  j
    1608        INTEGER(iwp)                 ::  l
    1609        INTEGER(iwp)                 ::  m
    1610        INTEGER(iwp), DIMENSION(0:3) ::  mm
    1611 
    1612        TYPE(surf_type), DIMENSION(0:2) ::  surf_h
    1613        TYPE(surf_type), DIMENSION(0:3) ::  surf_v
     1607       CHARACTER(LEN=1)             ::  dum  !< dummy string to create output-variable name
     1608
     1609       INTEGER(iwp)                 ::  i    !< running index x-direction
     1610       INTEGER(iwp)                 ::  j    !< running index y-direction
     1611       INTEGER(iwp)                 ::  l    !< index surface type orientation
     1612       INTEGER(iwp)                 ::  m    !< running index for surface elements on individual surface array
     1613       INTEGER(iwp), DIMENSION(0:3) ::  mm   !< running index for surface elements on gathered surface array
     1614
     1615       TYPE(surf_type), DIMENSION(0:2) ::  surf_h !< gathered horizontal surfaces, contains all surface types
     1616       TYPE(surf_type), DIMENSION(0:3) ::  surf_v !< gathered vertical surfaces, contains all surface types
    16141617
    16151618!
     
    20882091!> respective surface types within this routine. This allows e.g. changing the
    20892092!> surface type after reading the restart data, which might be required in case
    2090 !> of cyclic-filling a simulation.
     2093!> of cyclic_fill mode.
    20912094!------------------------------------------------------------------------------!
    20922095    SUBROUTINE surface_read_restart_data( ii,                                  &
     
    21352138
    21362139       LOGICAL                         ::  horizontal_surface !< flag indicating horizontal surfaces
    2137        LOGICAL                         ::  vertical_surface   !< flag indicating vertical surfaces
    21382140       LOGICAL                         ::  surf_match_def     !< flag indicating that surface element is of default type
    21392141       LOGICAL                         ::  surf_match_lsm     !< flag indicating that surface element is of natural type
    21402142       LOGICAL                         ::  surf_match_usm     !< flag indicating that surface element is of urban type
     2143       LOGICAL                         ::  vertical_surface   !< flag indicating vertical surfaces
    21412144
    21422145       TYPE(surf_type), DIMENSION(0:2) ::  surf_h             !< horizontal surface type on file
Note: See TracChangeset for help on using the changeset viewer.