Ignore:
Timestamp:
Dec 14, 2017 5:12:51 PM (6 years ago)
Author:
kanani
Message:

Merge of branch palm4u into trunk

Location:
palm/trunk
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk

  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/pmc_interface_mod.f90

    r2669 r2696  
    1 MODULE pmc_interface
    2 
     1!> @file pmc_interface_mod.f90
    32!------------------------------------------------------------------------------!
    4 ! This file is part of PALM.
     3! This file is part of the PALM model system.
    54!
    65! PALM is free software: you can redistribute it and/or modify it under the
     
    2625! -----------------
    2726! $Id$
     27! - Bugfix in init_tke_factor (MS)
     28!
     29! 2669 2017-12-06 16:03:27Z raasch
    2830! file extension for nested domains changed to "_N##",
    2931! created flag file in order to enable combine_plot_fields to process nest data
     
    194196! @todo Data transfer of qc and nc is prepared but not activated
    195197!-------------------------------------------------------------------------------!
     198 MODULE pmc_interface
    196199
    197200#if defined( __nopointer )
     
    26852688             
    26862689             DO  k = k_wall + 1, nzt
    2687                 
     2690 
    26882691                kc     = kco(k) + 1
    26892692                glsf   = ( dx * dy * dzu(k) )**p13
     
    30663069                   w(k,j,i)   = MERGE( w(k,j,i), 0.0_wp,                       &
    30673070                                       BTEST( wall_flags_0(k,j,i), 3 ) )
    3068                    e(k,j,i)   = MERGE( e(k,j,i), 0.0_wp,                       &
    3069                                        BTEST( wall_flags_0(k,j,i), 0 ) )
     3071!                    e(k,j,i)   = MERGE( e(k,j,i), 0.0_wp,                       &
     3072!                                        BTEST( wall_flags_0(k,j,i), 0 ) )
    30703073                   u_p(k,j,i) = MERGE( u_p(k,j,i), 0.0_wp,                     &
    30713074                                       BTEST( wall_flags_0(k,j,i), 1 ) )
     
    30743077                   w_p(k,j,i) = MERGE( w_p(k,j,i), 0.0_wp,                     &
    30753078                                       BTEST( wall_flags_0(k,j,i), 3 ) )
    3076                    e_p(k,j,i) = MERGE( e_p(k,j,i), 0.0_wp,                     &
    3077                                        BTEST( wall_flags_0(k,j,i), 0 ) )
     3079!                    e_p(k,j,i) = MERGE( e_p(k,j,i), 0.0_wp,                     &
     3080!                                        BTEST( wall_flags_0(k,j,i), 0 ) )
    30783081                ENDDO
    30793082             ENDDO
     
    44924495      ENDIF
    44934496!
    4494 !--   Store the boundary values also into the other redundant ghost node layers
     4497!--   Store the boundary values also into the other redundant ghost node layers.
     4498!--   Please note, in case of only one ghost node layer, e.g. for the PW
     4499!--   scheme, the following loops will not be entered.
    44954500      IF ( edge == 'l' )  THEN
    44964501         DO  ibgp = -nbgp, ib
     
    47134718      ENDIF
    47144719!
    4715 !--   Store the boundary values also into the other redundant ghost node layers
     4720!--   Store the boundary values also into the other redundant ghost node layers.
     4721!--   Please note, in case of only one ghost node layer, e.g. for the PW
     4722!--   scheme, the following loops will not be entered.
    47164723      IF ( edge == 's' )  THEN
    47174724         DO  jbgp = -nbgp, jb
Note: See TracChangeset for help on using the changeset viewer.