Ignore:
Timestamp:
Jul 16, 2018 7:45:13 AM (6 years ago)
Author:
gronemeier
Message:

merge with branch rans: update of rans mode and data output

Location:
palm/trunk
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk

  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/modules.f90

    r3120 r3129  
    2525! -----------------
    2626! $Id$
     27! add target attribute to km and kh, necessary for output in tcm_data_output_3d
     28!
     29! 3120 2018-07-11 18:30:57Z gronemeier
    2730! +les_dynamic
    2831!
     
    747750    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_v    !< 6th-order advective flux at south face of grid box - v-component
    748751    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_w    !< 6th-order advective flux at south face of grid box - w-component
    749     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  kh          !< eddy diffusivity for heat
    750     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  km          !< eddy diffusivity for momentum
     752    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  kh  !< eddy diffusivity for heat
     753    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  km  !< eddy diffusivity for momentum
    751754    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  prr         !< rain rate
    752755    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  p_loc       !< local array in multigrid/sor solver containing the pressure which is iteratively advanced in each iteration step
Note: See TracChangeset for help on using the changeset viewer.