Ignore:
Timestamp:
Feb 25, 2016 12:31:13 PM (8 years ago)
Author:
hellstea
Message:

Introduction of nested domain system

File:
1 edited

Legend:

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

    r1739 r1762  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Introduction of nested domain feature
    2222!
    2323! Former revisions:
     
    669669!-- is done). Further below the values needed within the timestep scheme
    670670!-- will be set.
     671!-- TO_DO: zeroth element added to weight_pres because in case of nesting
     672!--        pres may need to be called  outside the RK-substeps. Antti will
     673!--        check if this is really required.
    671674    ALLOCATE( weight_substep(1:intermediate_timestep_count_max), &
    672               weight_pres(1:intermediate_timestep_count_max) )
     675              weight_pres(0:intermediate_timestep_count_max) )
    673676    weight_substep = 1.0_wp
    674677    weight_pres    = 1.0_wp
     
    774777
    775778!
     779!--       Inside buildings set velocities back to zero
    776780          IF ( topography /= 'flat' )  THEN
    777              DO  i = nxl-1, nxr+1
    778                 DO  j = nys-1, nyn+1
     781             DO  i = nxlg, nxrg
     782                DO  j = nysg, nyng
    779783                   u(nzb:nzb_u_inner(j,i),j,i) = 0.0_wp
    780784                   v(nzb:nzb_v_inner(j,i),j,i) = 0.0_wp
     
    841845!--       in the limiting formula!). The original values are stored to be later
    842846!--       used for volume flow control.
    843           IF ( ibc_uv_b /= 1 )  THEN   
    844              DO  i = nxlg, nxrg
    845                 DO  j = nysg, nyng
    846                    u(nzb:nzb_u_inner(j,i)+1,j,i) = 0.0_wp
    847                    v(nzb:nzb_v_inner(j,i)+1,j,i) = 0.0_wp
    848                 ENDDO
    849              ENDDO
    850           ENDIF
     847          ! TO_DO:  Antti will check if this is really required
     848          !AH IF ( ibc_uv_b /= 1 )  THEN
     849          !AH    DO  i = nxlg, nxrg
     850          !AH       DO  j = nysg, nyng
     851          !AH          u(nzb:nzb_u_inner(j,i)+1,j,i) = 0.0_wp
     852          !AH          v(nzb:nzb_v_inner(j,i)+1,j,i) = 0.0_wp
     853          !AH       ENDDO
     854          !AH    ENDDO
     855          !AH ENDIF
    851856
    852857          IF ( humidity  .OR.  passive_scalar )  THEN
     
    16691674!
    16701675!-- Setting weighting factors for calculation of perturbation pressure
    1671 !-- and turbulent quantities from the RK substeps               
     1676!-- and turbulent quantities from the RK substeps
     1677!-- TO_DO: zeroth element is added to weight_pres because in nesting pres
     1678!--        may need to be called outside the RK-substeps
     1679    weight_pres(0) = 1.0_wp
    16721680    IF ( TRIM(timestep_scheme) == 'runge-kutta-3' )  THEN      ! for RK3-method
    16731681
Note: See TracChangeset for help on using the changeset viewer.