Ignore:
Timestamp:
Apr 23, 2019 1:24:29 PM (5 years ago)
Author:
raasch
Message:

pointer attribute removed from scalar 3d-array for performance reasons

File:
1 edited

Legend:

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

    r3665 r3927  
    2525! -----------------
    2626! $Id$
     27! pointer attribute removed from scalar 3d-array for performance reasons
     28!
     29! 3665 2019-01-10 08:28:24Z raasch
    2730! unused variables removed
    2831!
     
    128131
    129132       USE indices,                                                            &
    130            ONLY:  nxl, nxr, nyn, nys, nzb, nzt
     133           ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt
    131134
    132135       USE kinds
     
    142145       REAL(wp)     ::  gv  !< local additional advective velocity
    143146
    144        REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
     147       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk
    145148 
    146149
     
    195198
    196199       USE indices,                                                            &
    197            ONLY:  nzb, nzt
     200           ONLY:  nxlg, nxrg, nyng, nysg, nzb, nzt
    198201
    199202       USE kinds
     
    209212       REAL(wp)     ::  gv  !< local additional advective velocity
    210213
    211        REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
     214       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk
    212215
    213216
Note: See TracChangeset for help on using the changeset viewer.