Ignore:
Timestamp:
Jun 5, 2019 1:25:35 PM (5 years ago)
Author:
raasch
Message:

all reals changed to double precision in order to work with 32-bit working precision, otherwise calculated time intervals would mostly give zero; variable child_domain_nvn eliminated

File:
1 edited

Legend:

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

    r3849 r4015  
    2525! -----------------
    2626! $Id$
     27! variable child_domain_nvn eliminated
     28!
     29! 3849 2019-04-01 16:35:16Z knoop
    2730! OpenACC port for SPEC
    2831!
     
    231234    REAL(wp), DIMENSION(1:nzt) ::  w_l_l               !<
    232235
    233     LOGICAL :: child_domain_nvn      !<
    234 
    235236
    236237    CALL cpu_log( log_point(8), 'pres', 'start' )
     
    381382
    382383!
    383 !-- Remove mean vertical velocity in case that Neumann conditions are
    384 !-- used both at bottom and top boundary, and if not a nested domain in a
    385 !-- normal nesting run. In case of vertical nesting, this must be done.
    386 !-- Therefore an auxiliary logical variable child_domain_nvn is used here, and
    387 !-- nvn stands for non-vertical nesting.
    388 !-- This cannot be done before the first initial time step because ngp_2dh_outer
     384!-- Remove mean vertical velocity in case that Neumann conditions are used both at bottom and top
     385!-- boundary. With Neumann conditions at both vertical boundaries, the solver cannot remove
     386!-- mean vertical velocities. They should be removed, because incompressibility requires that
     387!-- the vertical gradient of vertical velocity is zero. Since w=0 at the solid surface, it must be
     388!-- zero everywhere.
     389!-- This must not be done in case of a 3d-nesting child domain, because a mean vertical velocity
     390!-- can physically exist in such a domain.
     391!-- Also in case of offline nesting, mean vertical velocities may exist (and must not be removed),
     392!-- caused by horizontal divergence/convergence of the large scale flow that is prescribed at the
     393!-- side boundaries.
     394!-- The removal cannot be done before the first initial time step because ngp_2dh_outer
    389395!-- is not yet known then.
    390     child_domain_nvn = child_domain
    391     IF ( child_domain .AND. nesting_mode == 'vertical' )  THEN
    392        child_domain_nvn = .FALSE.
    393     ENDIF
    394 
    395     IF ( ibc_p_b == 1  .AND.  ibc_p_t == 1  .AND.  .NOT. nesting_offline  .AND. &
    396          .NOT. child_domain_nvn  .AND. intermediate_timestep_count /= 0 )       &
     396    IF ( ibc_p_b == 1  .AND.  ibc_p_t == 1  .AND.  .NOT. nesting_offline                           &
     397         .AND. .NOT. ( child_domain .AND. nesting_mode /= 'vertical' )                             &
     398         .AND. intermediate_timestep_count /= 0 )                                                  &
    397399    THEN
    398400       w_l = 0.0_wp;  w_l_l = 0.0_wp
     
    400402          DO  j = nys, nyn
    401403             DO  k = nzb+1, nzt
    402                 w_l_l(k) = w_l_l(k) + w(k,j,i)                                 &
    403                                      * MERGE( 1.0_wp, 0.0_wp,                  &
    404                                               BTEST( wall_flags_0(k,j,i), 3 )  &
    405                                             )
     404                w_l_l(k) = w_l_l(k) + w(k,j,i)                                                     &
     405                                     * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 3 ) )
    406406             ENDDO
    407407          ENDDO
     
    409409#if defined( __parallel )   
    410410       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    411        CALL MPI_ALLREDUCE( w_l_l(1), w_l(1), nzt, MPI_REAL, MPI_SUM, &
    412                            comm2d, ierr )
     411       CALL MPI_ALLREDUCE( w_l_l(1), w_l(1), nzt, MPI_REAL, MPI_SUM, comm2d, ierr )
    413412#else
    414413       w_l = w_l_l
     
    420419          DO  j = nysg, nyng
    421420             DO  k = nzb+1, nzt
    422                 w(k,j,i) = w(k,j,i) - w_l(k)                                   &
    423                                      * MERGE( 1.0_wp, 0.0_wp,                  &
    424                                               BTEST( wall_flags_0(k,j,i), 3 )  &
    425                                             )
     421                w(k,j,i) = w(k,j,i) - w_l(k)                                                       &
     422                                     * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 3 ) )
    426423             ENDDO
    427424          ENDDO
Note: See TracChangeset for help on using the changeset viewer.