Ignore:
Timestamp:
Mar 22, 2007 9:54:05 AM (17 years ago)
Author:
raasch
Message:

preliminary update for changes concerning non-cyclic boundary conditions

File:
1 edited

Legend:

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

    r57 r75  
    55! -----------------
    66! Wall functions now include diabatic conditions, call of routine wall_fluxes,
    7 ! z0 removed from argument list
     7! z0 removed from argument list, uxrp eliminated
    88!
    99! Former revisions:
     
    6565       REAL, DIMENSION(:,:),   POINTER ::  usws
    6666       REAL, DIMENSION(:,:,:), POINTER ::  km, u, v, w
    67        REAL, DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr+uxrp) ::  usvs
     67       REAL, DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr) ::  usvs
    6868
    6969!
     
    7171!--    if neccessary
    7272       IF ( topography /= 'flat' )  THEN
    73           CALL wall_fluxes( usvs, 1.0, 0.0, 0.0, 0.0, uxrp, 0, nzb_u_inner, &
     73          CALL wall_fluxes( usvs, 1.0, 0.0, 0.0, 0.0, nzb_u_inner, &
    7474                            nzb_u_outer, wall_u )
    7575       ENDIF
    7676
    77        DO  i = nxl, nxr+uxrp
     77       DO  i = nxl, nxr
    7878          DO  j = nys,nyn
    7979!
Note: See TracChangeset for help on using the changeset viewer.