Changeset 3550 for palm/trunk/SOURCE


Ignore:
Timestamp:
Nov 21, 2018 4:01:01 PM (5 years ago)
Author:
gronemeier
Message:

calculate diss production same in vector and cache optimization; move boundary condition for e and diss to boundary_conds

File:
1 edited

Legend:

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

    r3545 r3550  
    2525! -----------------
    2626! $Id$
     27! - calculate diss production same in vector and cache optimization
     28! - move boundary condition for e and diss to boundary_conds
     29!
     30! 3545 2018-11-21 11:19:41Z gronemeier
    2731! - Set rans_mode according to value of turbulence_closure
    2832! - removed debug output
     
    19371941    REAL(wp)     ::  sbt     !< wheighting factor for sub-time step
    19381942
    1939     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) :: advec  !< advection term of TKE tendency
    1940     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) :: produc !< production term of TKE tendency
    1941 
    19421943!
    19431944!-- If required, compute prognostic equation for turbulent kinetic
     
    19821983       ENDIF
    19831984
    1984        IF ( rans_tke_e )  advec = tend
    1985 
    19861985       CALL production_e( .FALSE. )
    1987 
    1988 !
    1989 !--    Save production term for prognostic equation of TKE dissipation rate
    1990        IF ( rans_tke_e )  produc = tend - advec
    19911986
    19921987       IF ( .NOT. humidity )  THEN
     
    20242019          ENDDO
    20252020       ENDDO
    2026 
    2027 !
    2028 !--    Use special boundary condition in case of TKE-e closure
    2029        !> @todo do the same for usm and lsm surfaces
    2030        !>   2018-06-05, gronemeier
    2031        IF ( rans_tke_e )  THEN
    2032           DO  i = nxl, nxr
    2033              DO  j = nys, nyn
    2034                 surf_s = surf_def_h(0)%start_index(j,i)
    2035                 surf_e = surf_def_h(0)%end_index(j,i)
    2036                 DO  m = surf_s, surf_e
    2037                    k = surf_def_h(0)%k(m)
    2038                    e_p(k,j,i) = surf_def_h(0)%us(m)**2 / c_0**2
    2039                 ENDDO
    2040              ENDDO
    2041           ENDDO
    2042        ENDIF
    20432021
    20442022!
     
    21102088          ENDIF
    21112089       ENDIF
    2112 
    21132090!
    21142091!--    Production of TKE dissipation rate
    2115        DO  i = nxl, nxr
    2116           DO  j = nys, nyn
    2117              DO  k = nzb+1, nzt
    2118 !                tend(k,j,i) = tend(k,j,i) + c_1 * diss(k,j,i) / ( e(k,j,i) + 1.0E-20_wp ) * produc(k)
    2119                 tend(k,j,i) = tend(k,j,i) + c_1 * c_0**4 * f / c_4               &  !> @todo needs revision
    2120                       / surf_def_h(0)%us(surf_def_h(0)%start_index(j,i))       &
    2121                       * SQRT(e(k,j,i)) * produc(k,j,i)
    2122              ENDDO
    2123           ENDDO
    2124        ENDDO
    2125 
     2092       CALL production_e( .TRUE. )
     2093!
     2094!--    Diffusion term of TKE dissipation rate
    21262095       CALL diffusion_diss
    2127 
    21282096!
    21292097!--    Additional sink term for flows through plant canopies
    2130 !        IF ( plant_canopy )  CALL pcm_tendency( ? )                            !> @query what to do with this?
    2131 
    2132 !        CALL user_actions( 'diss-tendency' )                                   !> @todo not yet implemented
     2098!        IF ( plant_canopy )  CALL pcm_tendency( ? )         !> @todo not yet implemented
     2099
     2100!        CALL user_actions( 'diss-tendency' )                !> @todo not yet implemented
    21332101
    21342102!
     
    21482116                IF ( diss_p(k,j,i) < 0.0_wp )                                  &
    21492117                   diss_p(k,j,i) = 0.1_wp * diss(k,j,i)
    2150              ENDDO
    2151           ENDDO
    2152        ENDDO
    2153 
    2154 !
    2155 !--    Use special boundary condition in case of TKE-e closure
    2156        DO  i = nxl, nxr
    2157           DO  j = nys, nyn
    2158              surf_s = surf_def_h(0)%start_index(j,i)
    2159              surf_e = surf_def_h(0)%end_index(j,i)
    2160              DO  m = surf_s, surf_e
    2161                 k = surf_def_h(0)%k(m)
    2162                 diss_p(k,j,i) = surf_def_h(0)%us(m)**3 / kappa * ddzu(k)
    21632118             ENDDO
    21642119          ENDDO
     
    23152270!
    23162271!--    Additional sink term for flows through plant canopies
    2317 !        IF ( plant_canopy )  CALL pcm_tendency( i, j, ? )                      !> @todo not yet implemented
    2318 
    2319 !        CALL user_actions( i, j, 'diss-tendency' )                             !> @todo not yet implemented
     2272!        IF ( plant_canopy )  CALL pcm_tendency( i, j, ? )     !> @todo not yet implemented
     2273
     2274!        CALL user_actions( i, j, 'diss-tendency' )            !> @todo not yet implemented
    23202275
    23212276!
     
    23612316!> @warning The case with constant_flux_layer = F and use_surface_fluxes = T is
    23622317!>          not considered well!
    2363 !> @todo Adjust production term in case of rans_tke_e simulation
    23642318!------------------------------------------------------------------------------!
    23652319 SUBROUTINE production_e( diss_production )
     
    26452599             IF ( .NOT. diss_production )  THEN
    26462600
    2647 !--             Compute temdency for TKE-production from shear
     2601!--             Compute tendency for TKE-production from shear
    26482602                tend(k,j,i) = tend(k,j,i) + km(k,j,i) * def * flag
    26492603
    26502604             ELSE
    26512605
    2652 !--             RANS mode: Compute temdency for dissipation-rate-production from shear
     2606!--             RANS mode: Compute tendency for dissipation-rate-production from shear
    26532607                tend(k,j,i) = tend(k,j,i) + km(k,j,i) * def * flag *           &
    26542608                              diss(k,j,i)/( e(k,j,i) + 1.0E-20_wp ) * c_1
     
    27032657                   IF ( .NOT. diss_production )  THEN
    27042658
    2705 !--                   Compute temdency for TKE-production from shear
     2659!--                   Compute tendency for TKE-production from shear
    27062660                      DO  k = nzb+1, nzt
    27072661                         flag = MERGE( 1.0_wp, 0.0_wp, BTEST(wall_flags_0(k,j,i),0) )
     
    27132667                   ELSE
    27142668
    2715 !--                   RANS mode: Compute temdency for dissipation-rate-production from shear
     2669!--                   RANS mode: Compute tendency for dissipation-rate-production from shear
    27162670                      DO  k = nzb+1, nzt
    27172671                         flag = MERGE( 1.0_wp, 0.0_wp, BTEST(wall_flags_0(k,j,i),0) )
     
    27772731                   IF ( .NOT. diss_production )  THEN
    27782732
    2779 !--                   Compute temdency for TKE-production from shear
     2733!--                   Compute tendency for TKE-production from shear
    27802734                      DO  k = nzb+1, nzt
    27812735                         flag = MERGE( 1.0_wp, 0.0_wp, BTEST(wall_flags_0(k,j,i),0) )
     
    27872741                   ELSE
    27882742
    2789 !--                   RANS mode: Compute temdency for dissipation-rate-production from shear
     2743!--                   RANS mode: Compute tendency for dissipation-rate-production from shear
    27902744                      DO  k = nzb+1, nzt
    27912745                         flag = MERGE( 1.0_wp, 0.0_wp, BTEST(wall_flags_0(k,j,i),0) )
     
    29922946                IF ( .NOT. diss_production )  THEN
    29932947
    2994 !--                Compute temdency for TKE-production from shear
     2948!--                Compute tendency for TKE-production from shear
    29952949                   DO  k = nzb+1, nzt
    29962950                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST(wall_flags_0(k,j,i),0) )
     
    30022956                ELSE
    30032957
    3004 !--                RANS mode: Compute temdency for dissipation-rate-production from shear
     2958!--                RANS mode: Compute tendency for dissipation-rate-production from shear
    30052959                   DO  k = nzb+1, nzt
    30062960                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST(wall_flags_0(k,j,i),0) )
     
    30312985!> @warning The case with constant_flux_layer = F and use_surface_fluxes = T is
    30322986!>          not considered well!
    3033 !> @todo non-neutral case is not yet considered for RANS mode
    30342987!------------------------------------------------------------------------------!
    30352988 SUBROUTINE production_e_ij( i, j, diss_production )
     
    33133266       ELSE
    33143267
    3315 !--       RANS mode: Compute temdency for dissipation-rate-production from shear
     3268!--       RANS mode: Compute tendency for dissipation-rate-production from shear
    33163269          tend(k,j,i) = tend(k,j,i) + km(k,j,i) * def * flag *           &
    33173270                        diss(k,j,i)/( e(k,j,i) + 1.0E-20_wp ) * c_1
     
    33593312             IF ( .NOT. diss_production )  THEN
    33603313
    3361 !--             Compute temdency for TKE-production from shear
     3314!--             Compute tendency for TKE-production from shear
    33623315                DO  k = nzb+1, nzt
    33633316                   flag = MERGE( 1.0_wp, 0.0_wp, BTEST(wall_flags_0(k,j,i),0) )
     
    33693322             ELSE
    33703323
    3371 !--             RANS mode: Compute temdency for dissipation-rate-production from shear
     3324!--             RANS mode: Compute tendency for dissipation-rate-production from shear
    33723325                DO  k = nzb+1, nzt
    33733326                   flag = MERGE( 1.0_wp, 0.0_wp, BTEST(wall_flags_0(k,j,i),0) )
     
    34283381             IF ( .NOT. diss_production )  THEN
    34293382
    3430 !--             Compute temdency for TKE-production from shear
     3383!--             Compute tendency for TKE-production from shear
    34313384                DO  k = nzb+1, nzt
    34323385                   flag = MERGE( 1.0_wp, 0.0_wp, BTEST(wall_flags_0(k,j,i),0) )
     
    34383391             ELSE
    34393392
    3440 !--             RANS mode: Compute temdency for dissipation-rate-production from shear
     3393!--             RANS mode: Compute tendency for dissipation-rate-production from shear
    34413394                DO  k = nzb+1, nzt
    34423395                   flag = MERGE( 1.0_wp, 0.0_wp, BTEST(wall_flags_0(k,j,i),0) )
     
    36373590          IF ( .NOT. diss_production )  THEN
    36383591
    3639 !--          Compute temdency for TKE-production from shear
     3592!--          Compute tendency for TKE-production from shear
    36403593             DO  k = nzb+1, nzt
    36413594                flag = MERGE( 1.0_wp, 0.0_wp, BTEST(wall_flags_0(k,j,i),0) )
     
    36473600          ELSE
    36483601
    3649 !--          RANS mode: Compute temdency for dissipation-rate-production from shear
     3602!--          RANS mode: Compute tendency for dissipation-rate-production from shear
    36503603             DO  k = nzb+1, nzt
    36513604                flag = MERGE( 1.0_wp, 0.0_wp, BTEST(wall_flags_0(k,j,i),0) )
Note: See TracChangeset for help on using the changeset viewer.