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_v.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, vynp eliminated
    88!
    99! Former revisions:
     
    6363       REAL, DIMENSION(:,:),   POINTER ::  vsws
    6464       REAL, DIMENSION(:,:,:), POINTER ::  km, u, v, w
    65        REAL, DIMENSION(nzb:nzt+1,nys:nyn+vynp,nxl:nxr) ::  vsus
     65       REAL, DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr) ::  vsus
    6666
    6767!
     
    6969!--    if neccessary
    7070       IF ( topography /= 'flat' )  THEN
    71           CALL wall_fluxes( vsus, 0.0, 1.0, 0.0, 0.0, 0, vynp, nzb_v_inner, &
     71          CALL wall_fluxes( vsus, 0.0, 1.0, 0.0, 0.0, nzb_v_inner, &
    7272                            nzb_v_outer, wall_v )
    7373       ENDIF
    7474
    7575       DO  i = nxl, nxr
    76           DO  j = nys, nyn+vynp
     76          DO  j = nys, nyn
    7777!
    7878!--          Compute horizontal diffusion
Note: See TracChangeset for help on using the changeset viewer.