Changeset 3545


Ignore:
Timestamp:
Nov 21, 2018 11:19:41 AM (5 years ago)
Author:
gronemeier
Message:

removed debug output; removed rans_mode from namelist; altered order of check_parameter-calls of modules

Location:
palm/trunk
Files:
4 edited

Legend:

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

    r3529 r3545  
    2525! -----------------
    2626! $Id$
     27! Call tcm_check_parameters before other modules
     28!
     29! 3529 2018-11-15 21:03:15Z gronemeier
    2730! Save time zone in variable run_zone, change date format into YYYY-MM-DD
    2831!
     
    15131516
    15141517!-- Check the module settings
     1518    CALL tcm_check_parameters
    15151519    IF ( biometeorology )       CALL bio_check_parameters
    15161520    IF ( bulk_cloud_model )     CALL bcm_check_parameters
     
    15241528    IF ( calculate_spectra )    CALL spectra_check_parameters
    15251529    CALL stg_check_parameters
    1526     CALL tcm_check_parameters
    15271530    IF ( urban_surface )        CALL usm_check_parameters
    15281531    IF ( wind_turbine )         CALL wtm_check_parameters
  • palm/trunk/SOURCE/parin.f90

    r3525 r3545  
    2525! -----------------
    2626! $Id$
     27! remove rans_mode from initialization_parameters
     28!
     29! 3525 2018-11-14 16:06:14Z kanani
    2730! Changes related to clean-up of biometeorology (dom_dwd_user)
    2831!
     
    623626             q_vertical_gradient, q_vertical_gradient_level,                   &
    624627             random_generator, random_heatflux, rans_const_c, rans_const_sigma,&
    625              rans_mode,                                                        &
    626628             rayleigh_damping_factor, rayleigh_damping_height,                 &
    627629             recycling_width, recycling_yshift,                                &
     
    695697             q_vertical_gradient, q_vertical_gradient_level,                   &
    696698             random_generator, random_heatflux, rans_const_c, rans_const_sigma,&
    697              rans_mode,                                                        &
    698699             rayleigh_damping_factor, rayleigh_damping_height,                 &
    699700             recycling_width, recycling_yshift,                                &
  • palm/trunk/SOURCE/turbulence_closure_mod.f90

    r3430 r3545  
    2525! -----------------
    2626! $Id$
     27! - Set rans_mode according to value of turbulence_closure
     28! - removed debug output
     29!
     30! 3430 2018-10-25 13:36:23Z maronga
    2731! Added support for buildings in the dynamic SGS model
    2832!
     
    160164!> @todo test initialization for all possibilities
    161165!>       add OpenMP directives whereever possible
    162 !>       remove debug output variables (dummy1, dummy2, dummy3)
    163166!> @todo Check for random disturbances
    164167!> @note <Enter notes on the module>
     
    251254    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  l_wall !< near-wall mixing length
    252255
    253     !> @todo remove debug variables
    254     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET :: &
    255        diss_prod1, diss_adve1, diss_diff1, &
    256        diss_prod2, diss_adve2, diss_diff2, &
    257        diss_prod3, diss_adve3, diss_diff3, &
    258        dummy1, dummy2, dummy3
    259 
    260256
    261257    PUBLIC c_0, rans_const_c, rans_const_sigma
     
    404400! ------------
    405401!> Check parameters routine for turbulence closure module.
    406 !> @todo remove rans_mode from initialization namelist and rework checks
    407 !>   The way it is implemented at the moment, the user has to set two variables
    408 !>   so that the RANS mode is working. It would be better if only one parameter
    409 !>   has to be set.
    410 !>   2018-06-18, gronemeier
    411402!------------------------------------------------------------------------------!
    412403 SUBROUTINE tcm_check_parameters
     
    419410!
    420411!-- Define which turbulence closure is going to be used
     412    SELECT CASE ( TRIM( turbulence_closure ) )
     413
     414       CASE ( 'dynamic' )
     415          les_dynamic = .TRUE.
     416
     417       CASE ( 'Moeng_Wyngaard' )
     418          les_mw = .TRUE.
     419
     420       CASE ( 'TKE-l' )
     421          rans_tke_l = .TRUE.
     422          rans_mode = .TRUE.
     423
     424       CASE ( 'TKE-e' )
     425          rans_tke_e = .TRUE.
     426          rans_mode = .TRUE.
     427
     428       CASE DEFAULT
     429          message_string = 'Unknown turbulence closure: ' //                &
     430                           TRIM( turbulence_closure )
     431          CALL message( 'tcm_check_parameters', 'PA0500', 1, 2, 0, 6, 0 )
     432
     433    END SELECT
     434!
     435!-- Set variables for RANS mode or LES mode
    421436    IF ( rans_mode )  THEN
    422 
    423437!
    424438!--    Assign values to constants for RANS mode
     
    432446       c_4 = rans_const_c(4)
    433447
    434        SELECT CASE ( TRIM( turbulence_closure ) )
    435 
    436           CASE ( 'TKE-l' )
    437              rans_tke_l = .TRUE.
    438 
    439           CASE ( 'TKE-e' )
    440              rans_tke_e = .TRUE.
    441 
    442           CASE DEFAULT
    443              message_string = 'Unknown turbulence closure: ' //                &
    444                               TRIM( turbulence_closure )
    445              CALL message( 'tcm_check_parameters', 'PA0500', 1, 2, 0, 6, 0 )
    446 
    447        END SELECT
    448 
    449448       IF ( turbulent_inflow .OR. turbulent_outflow )  THEN
    450449          message_string = 'turbulent inflow/outflow is not yet '//            &
     
    459458
    460459    ELSE
    461 
    462        c_0 = 0.1_wp !according to Lilly (1967) and Deardorff (1980)
     460!
     461!--    LES mode
     462       c_0 = 0.1_wp    !according to Lilly (1967) and Deardorff (1980)
    463463
    464464       dsig_e = 1.0_wp !assure to use K_m to calculate TKE instead
    465465                       !of K_e which is used in RANS mode
    466 
    467        SELECT CASE ( TRIM( turbulence_closure ) )
    468 
    469           CASE ( 'Moeng_Wyngaard' )
    470              les_mw = .TRUE.
    471 
    472           CASE ( 'dynamic' )
    473              les_dynamic = .TRUE.
    474 
    475           CASE DEFAULT
    476              !> @todo rework this part so that only one call of this error exists
    477              message_string = 'Unknown turbulence closure: ' //                &
    478                               TRIM( turbulence_closure )
    479              CALL message( 'tcm_check_parameters', 'PA0500', 1, 2, 0, 6, 0 )
    480 
    481        END SELECT
    482466
    483467    ENDIF
     
    502486       CASE ( 'diss' )
    503487          unit = 'm2/s3'
    504 
    505        CASE ( 'diss1', 'diss2',                         &                      !> @todo remove later
    506               'diss_prod1', 'diss_adve1', 'diss_diff1', &
    507               'diss_prod2', 'diss_adve2', 'diss_diff2', &
    508               'diss_prod3', 'diss_adve3', 'diss_diff3', 'dummy3'  )
    509           unit = 'debug output'
    510488
    511489       CASE ( 'kh', 'km' )
     
    544522
    545523       CASE ( 'diss', 'diss_xy', 'diss_xz', 'diss_yz' )
    546           grid_x = 'x'
    547           grid_y = 'y'
    548           grid_z = 'zu'
    549 
    550        CASE ( 'diss1', 'diss2',                         &                       !> @todo remove later
    551               'diss_prod1', 'diss_adve1', 'diss_diff1', &
    552               'diss_prod2', 'diss_adve2', 'diss_diff2', &
    553               'diss_prod3', 'diss_adve3', 'diss_diff3', 'dummy3' )
    554524          grid_x = 'x'
    555525          grid_y = 'y'
     
    741711    INTEGER(iwp) ::  nzt_do    !< vertical output index (top)
    742712
    743     LOGICAL ::  found   !< flag if output variable is found
     713    LOGICAL ::  found     !< flag if output variable is found
    744714    LOGICAL ::  resorted  !< flag if output is already resorted
    745715
    746     REAL(wp) ::  fill_value = -999.0_wp  !< value for the _FillValue attribute
     716    REAL(wp) ::  fill_value = -9999.0_wp  !< value for the _FillValue attribute
    747717
    748718    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !< local
     
    842812    LOGICAL ::  resorted  !< flag if output is already resorted
    843813
    844     REAL(wp) ::  fill_value = -999.0_wp  !< value for the _FillValue attribute
     814    REAL(wp) ::  fill_value = -9999.0_wp  !< value for the _FillValue attribute
    845815
    846816    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf   !< local
     
    889859             to_be_resorted => km_av
    890860          ENDIF
    891 
    892        CASE ( 'dummy3' )                                                        !> @todo remove later
    893           IF ( av == 0 )  THEN
    894              to_be_resorted => dummy3
    895           ENDIF
    896 
    897        CASE ( 'diss1' )                                                         !> @todo remove later
    898           IF ( av == 0 )  THEN
    899              to_be_resorted => dummy1
    900           ENDIF
    901 
    902        CASE ( 'diss2' )                                                         !> @todo remove later
    903           IF ( av == 0 )  THEN
    904              to_be_resorted => dummy2
    905           ENDIF
    906 
    907        CASE ( 'diss_prod1' )                                                    !> @todo remove later
    908           IF ( av == 0 )  THEN
    909              to_be_resorted => diss_prod1
    910           ENDIF
    911 
    912        CASE ( 'diss_adve1' )                                                    !> @todo remove later
    913           IF ( av == 0 )  THEN
    914              to_be_resorted => diss_adve1
    915           ENDIF
    916 
    917        CASE ( 'diss_diff1' )                                                    !> @todo remove later
    918           IF ( av == 0 )  THEN
    919              to_be_resorted => diss_diff1
    920           ENDIF
    921 
    922        CASE ( 'diss_prod2' )                                                    !> @todo remove later
    923           IF ( av == 0 )  THEN
    924              to_be_resorted => diss_prod2
    925           ENDIF
    926 
    927        CASE ( 'diss_adve2' )                                                    !> @todo remove later
    928           IF ( av == 0 )  THEN
    929              to_be_resorted => diss_adve2
    930           ENDIF
    931 
    932        CASE ( 'diss_diff2' )                                                    !> @todo remove later
    933           IF ( av == 0 )  THEN
    934              to_be_resorted => diss_diff2
    935           ENDIF
    936 
    937        CASE ( 'diss_prod3' )                                                    !> @todo remove later
    938           IF ( av == 0 )  THEN
    939              to_be_resorted => diss_prod3
    940           ENDIF
    941 
    942        CASE ( 'diss_adve3' )                                                    !> @todo remove later
    943           IF ( av == 0 )  THEN
    944              to_be_resorted => diss_adve3
    945           ENDIF
    946 
    947        CASE ( 'diss_diff3' )                                                    !> @todo remove later
    948           IF ( av == 0 )  THEN
    949              to_be_resorted => diss_diff3
    950           ENDIF
    951861         
    952862       CASE DEFAULT
     
    993903    ALLOCATE( kh(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    994904    ALLOCATE( km(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    995 
    996     ALLOCATE( dummy1(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )                           !> @todo remove later
    997     ALLOCATE( dummy2(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    998     ALLOCATE( dummy3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    999     ALLOCATE( diss_adve1(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    1000     ALLOCATE( diss_adve2(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    1001     ALLOCATE( diss_adve3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    1002     ALLOCATE( diss_prod1(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    1003     ALLOCATE( diss_prod2(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    1004     ALLOCATE( diss_prod3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    1005     ALLOCATE( diss_diff1(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    1006     ALLOCATE( diss_diff2(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    1007     ALLOCATE( diss_diff3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    1008     dummy1 = 0.0_wp
    1009     dummy2 = 0.0_wp
    1010     dummy3 = 0.0_wp
    1011     diss_adve1 = 0.0_wp
    1012     diss_adve2 = 0.0_wp
    1013     diss_adve3 = 0.0_wp
    1014     diss_prod1 = 0.0_wp
    1015     diss_prod2 = 0.0_wp
    1016     diss_prod3 = 0.0_wp
    1017     diss_diff1 = 0.0_wp
    1018     diss_diff2 = 0.0_wp
    1019     diss_diff3 = 0.0_wp
    1020905
    1021906#if defined( __nopointer )
     
    1095980!-- Initialize mixing length
    1096981    CALL tcm_init_mixing_length
    1097     dummy3 = l_wall                 !> @todo remove later
    1098982
    1099983!
     
    11431027                   kh   = 0.01_wp   ! there must exist an initial diffusion, because
    11441028                   km   = 0.01_wp   ! otherwise no TKE would be produced by the
    1145                                      ! production terms, as long as not yet
    1146                                      ! e = (u*/cm)**2 at k=nzb+1
     1029                                    ! production terms, as long as not yet
     1030                                    ! e = (u*/cm)**2 at k=nzb+1
    11471031                ELSE
    11481032                   kh   = 0.00001_wp
     
    23352219    INTEGER(iwp) ::  tn      !< task number of openmp task
    23362220
    2337 !    INTEGER(iwp) :: pis = 32 !< debug variable, print from i=pis                !> @todo remove later
    2338 !    INTEGER(iwp) :: pie = 32 !< debug variable, print until i=pie               !> @todo remove later
    2339 !    INTEGER(iwp) :: pjs = 26 !< debug variable, print from j=pjs                !> @todo remove later
    2340 !    INTEGER(iwp) :: pje = 26 !< debug variable, print until j=pje               !> @todo remove later
    2341 !    INTEGER(iwp) :: pkb = 1  !< debug variable, print from k=pkb                !> @todo remove later
    2342 !    INTEGER(iwp) :: pkt = 7  !< debug variable, print until k=pkt               !> @todo remove later
    2343 
    2344     REAL(wp), DIMENSION(nzb:nzt+1) :: dum_adv   !< debug variable               !> @todo remove later
    2345     REAL(wp), DIMENSION(nzb:nzt+1) :: dum_pro   !< debug variable               !> @todo remove later
    2346     REAL(wp), DIMENSION(nzb:nzt+1) :: dum_dif   !< debug variable               !> @todo remove later
    2347 
    2348 !5555 FORMAT(A,7(1X,E12.5))   !> @todo remove later
    2349 
    23502221!
    23512222!-- If required, compute prognostic equation for turbulent kinetic
     
    23682239       ENDIF
    23692240
    2370        dum_adv = tend(:,j,i)                                                    !> @todo remove later
    2371 
    23722241       CALL production_e( i, j, .FALSE. )
    2373 
    2374        dum_pro = tend(:,j,i) - dum_adv                                          !> @todo remove later
    23752242
    23762243       IF ( .NOT. humidity )  THEN
     
    23832250          CALL diffusion_e( i, j, vpt, pt_reference )
    23842251       ENDIF
    2385 
    2386        dum_dif = tend(:,j,i) - dum_adv - dum_pro                                !> @todo remove later
    23872252
    23882253!
     
    24232288       ENDIF
    24242289
    2425 !        if ( i >= pis .and. i <= pie .and. j >= pjs .and. j <= pje ) then        !> @todo remove later
    2426 !           WRITE(9, *) '------'
    2427 !           WRITE(9, '(A,F8.3,1X,F8.3,1X,I2)') 't, dt, int_ts:', simulated_time, dt_3d, intermediate_timestep_count
    2428 !           WRITE(9, *) 'i:', i
    2429 !           WRITE(9, *) 'j:', j
    2430 !           WRITE(9, *) 'k:', pkb, ' - ', pkt
    2431 !           WRITE(9, *) '---'
    2432 !           WRITE(9, *) 'e:'
    2433 !           WRITE(9, 5555) 'adv :', dum_adv(pkb:pkt)
    2434 !           WRITE(9, 5555) 'pro :', dum_pro(pkb:pkt)
    2435 !           WRITE(9, 5555) 'dif :', dum_dif(pkb:pkt)
    2436 !           WRITE(9, 5555) 'tend:', tend(pkb:pkt,j,i)
    2437 !           WRITE(9, 5555) 'e_p :', e_p(pkb:pkt,j,i)
    2438 !           WRITE(9, 5555) 'e   :', e(pkb:pkt,j,i)
    2439 !           FLUSH(9)
    2440 !        endif
    2441 
    24422290    ENDIF   ! TKE equation
    24432291
     
    24452293!-- If required, compute prognostic equation for TKE dissipation rate
    24462294    IF ( rans_tke_e )  THEN
    2447 
    24482295!
    24492296!--    Tendency-terms for dissipation
     
    24602307          CALL advec_s_up( i, j, diss )
    24612308       ENDIF
    2462 
    2463        IF ( intermediate_timestep_count == 1 )  diss_adve1(:,j,i) = tend(:,j,i) !> @todo remove later
    2464        IF ( intermediate_timestep_count == 2 )  diss_adve2(:,j,i) = tend(:,j,i)
    2465        IF ( intermediate_timestep_count == 3 )  diss_adve3(:,j,i) = tend(:,j,i)
    2466 
    24672309!
    24682310!--    Production of TKE dissipation rate
    24692311       CALL production_e( i, j, .TRUE. )
    2470 
    2471        IF ( intermediate_timestep_count == 1 )  diss_prod1(:,j,i) = tend(:,j,i) - diss_adve1(:,j,i) !> @todo remove later
    2472        IF ( intermediate_timestep_count == 2 )  diss_prod2(:,j,i) = tend(:,j,i) - diss_adve2(:,j,i)
    2473        IF ( intermediate_timestep_count == 3 )  diss_prod3(:,j,i) = tend(:,j,i) - diss_adve3(:,j,i)
    2474 
    2475        dum_pro = tend(:,j,i) - dum_adv                                          !> @todo remove later
    2476 
    24772312!
    24782313!--    Diffusion term of TKE dissipation rate
    24792314       CALL diffusion_diss( i, j )
    2480 
    2481        IF ( intermediate_timestep_count == 1 )  diss_diff1(:,j,i) = tend(:,j,i) - diss_adve1(:,j,i) - diss_prod1(:,j,i) !> @todo remove later
    2482        IF ( intermediate_timestep_count == 2 )  diss_diff2(:,j,i) = tend(:,j,i) - diss_adve2(:,j,i) - diss_prod2(:,j,i)
    2483        IF ( intermediate_timestep_count == 3 )  diss_diff3(:,j,i) = tend(:,j,i) - diss_adve3(:,j,i) - diss_prod3(:,j,i)
    2484 !        IF ( intermediate_timestep_count == 3 )  dummy3(:,j,i) = km(:,j,i)
    2485 
    2486        dum_dif = tend(:,j,i) - dum_adv - dum_pro                                !> @todo remove later
    2487 
    24882315!
    24892316!--    Additional sink term for flows through plant canopies
     
    25222349       ENDIF
    25232350
    2524        IF ( intermediate_timestep_count == 1 )  dummy1(:,j,i) = diss_p(:,j,i)   !> @todo remove later
    2525        IF ( intermediate_timestep_count == 2 )  dummy2(:,j,i) = diss_p(:,j,i)
    2526 
    2527 !        if ( i >= pis .and. i <= pie .and. j >= pjs .and. j <= pje ) then        !> @todo remove later
    2528 !           WRITE(9, *) '---'
    2529 !           WRITE(9, *) 'diss:'
    2530 !           WRITE(9, 5555) 'adv   :', dum_adv(pkb:pkt)
    2531 !           WRITE(9, 5555) 'pro   :', dum_pro(pkb:pkt)
    2532 !           WRITE(9, 5555) 'dif   :', dum_dif(pkb:pkt)
    2533 !           WRITE(9, 5555) 'tend  :', tend(pkb:pkt,j,i)
    2534 !           WRITE(9, 5555) 'diss_p:', diss_p(pkb:pkt,j,i)
    2535 !           WRITE(9, 5555) 'diss  :', diss(pkb:pkt,j,i)
    2536 !           WRITE(9, *) '---'
    2537 !           WRITE(9, 5555) 'km    :', km(pkb:pkt,j,i)
    2538 !           flush(9)
    2539 !        endif
    2540 
    25412351    ENDIF   ! dissipation equation
    25422352
     
    25862396    INTEGER(iwp) ::  flag_nr !< number of masking flag
    25872397
    2588     REAL(wp)     ::  def         !<
     2398    REAL(wp)     ::  def         !< ( du_i/dx_j + du_j/dx_i ) * du_i/dx_j
    25892399    REAL(wp)     ::  flag        !< flag to mask topography
    2590     REAL(wp)     ::  k1          !<
    2591     REAL(wp)     ::  k2          !<
     2400    REAL(wp)     ::  k1          !< temporary factor
     2401    REAL(wp)     ::  k2          !< temporary factor
    25922402    REAL(wp)     ::  km_neutral  !< diffusion coefficient assuming neutral conditions - used to compute shear production at surfaces
    2593     REAL(wp)     ::  theta       !<
    2594     REAL(wp)     ::  temp        !<
     2403    REAL(wp)     ::  theta       !< virtual potential temperature
     2404    REAL(wp)     ::  temp        !< theta * Exner-function
    25952405    REAL(wp)     ::  sign_dir    !< sign of wall-tke flux, depending on wall orientation
    25962406    REAL(wp)     ::  usvs        !< momentum flux u"v"
     
    32563066    INTEGER(iwp) ::  flag_nr !< number of masking flag
    32573067
    3258     REAL(wp)     ::  def         !<
     3068    REAL(wp)     ::  def         !< ( du_i/dx_j + du_j/dx_i ) * du_i/dx_j
    32593069    REAL(wp)     ::  flag        !< flag to mask topography
    3260     REAL(wp)     ::  k1          !<
    3261     REAL(wp)     ::  k2          !<
     3070    REAL(wp)     ::  k1          !< temporary factor
     3071    REAL(wp)     ::  k2          !< temporary factor
    32623072    REAL(wp)     ::  km_neutral  !< diffusion coefficient assuming neutral conditions - used to compute shear production at surfaces
    3263     REAL(wp)     ::  theta       !<
    3264     REAL(wp)     ::  temp        !<
     3073    REAL(wp)     ::  theta       !< virtual potential temperature
     3074    REAL(wp)     ::  temp        !< theta * Exner-function
    32653075    REAL(wp)     ::  sign_dir    !< sign of wall-tke flux, depending on wall orientation
    32663076    REAL(wp)     ::  usvs        !< momentum flux u"v"
     
    33763186       ENDDO
    33773187!
    3378 !--          Compute gradients at east- and west-facing walls
     3188!--    Compute gradients at east- and west-facing walls
    33793189       DO  l = 2, 3
    33803190          surf_s = surf_def_v(l)%start_index(j,i)
     
    33953205          ENDDO
    33963206!
    3397 !--             Natural surfaces
     3207!--       Natural surfaces
    33983208          surf_s = surf_lsm_v(l)%start_index(j,i)
    33993209          surf_e = surf_lsm_v(l)%end_index(j,i)
     
    34133223          ENDDO
    34143224!
    3415 !--             Urban surfaces
     3225!--       Urban surfaces
    34163226          surf_s = surf_usm_v(l)%start_index(j,i)
    34173227          surf_e = surf_usm_v(l)%end_index(j,i)
     
    34323242       ENDDO
    34333243!
    3434 !--          Compute gradients at upward-facing surfaces
     3244!--    Compute gradients at upward-facing surfaces
    34353245       surf_s = surf_def_h(0)%start_index(j,i)
    34363246       surf_e = surf_def_h(0)%end_index(j,i)
     
    34983308       IF ( .NOT. diss_production )  THEN
    34993309
    3500 !--       Compute temdency for TKE-production from shear
     3310!--       Compute tendency for TKE-production from shear
    35013311          tend(k,j,i) = tend(k,j,i) + km(k,j,i) * def * flag
    35023312
     
    35113321    ENDDO
    35123322
    3513 
    35143323!
    35153324!-- If required, calculate TKE production by buoyancy
     
    35223331!--          So far in the ocean no special treatment of density flux
    35233332!--          in the bottom and top surface layer
    3524 
    35253333             DO  k = nzb+1, nzt
    35263334                tmp_flux(k) = kh(k,j,i) * ( prho(k+1,j,i) - prho(k-1,j,i) ) * dd2zu(k)
     
    42664074    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var  !< temperature
    42674075#else
    4268     REAL(wp), DIMENSION(:,:,:), POINTER ::  var     !< temperature
     4076    REAL(wp), DIMENSION(:,:,:), POINTER ::  var  !< temperature
    42694077#endif
    42704078
     
    43234131    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var  !< temperature
    43244132#else
    4325     REAL(wp), DIMENSION(:,:,:), POINTER ::  var     !< temperature
     4133    REAL(wp), DIMENSION(:,:,:), POINTER ::  var  !< temperature
    43264134#endif
    43274135
     
    43764184                surf_usm_h, surf_usm_v
    43774185
    4378     INTEGER(iwp) ::  i                   !< loop index
    4379     INTEGER(iwp) ::  j                   !< loop index
    4380     INTEGER(iwp) ::  k                   !< loop index
    4381     INTEGER(iwp) ::  m                   !< loop index
    4382     INTEGER(iwp) ::  n                   !< loop index
    4383 
    4384     REAL(wp) ::  var_reference       !< reference temperature
     4186    INTEGER(iwp) ::  i          !< loop index
     4187    INTEGER(iwp) ::  j          !< loop index
     4188    INTEGER(iwp) ::  k          !< loop index
     4189    INTEGER(iwp) ::  m          !< loop index
     4190    INTEGER(iwp) ::  n          !< loop index
     4191
     4192    REAL(wp) ::  var_reference  !< reference temperature
    43854193
    43864194#if defined( __nopointer )
     
    47184526    REAL(wp)     ::  dwdz        !< Gradient of w-component in z-direction
    47194527
    4720     REAL(wp)     ::  flag                !< topography flag
     4528    REAL(wp)     ::  flag        !< topography flag
    47214529   
    47224530    REAL(wp)     ::  uc(-1:1,-1:1)  !< u on grid center
  • palm/trunk/TESTS/cases/rans_tkee/INPUT/rans_tkee_p3d

    r3541 r3545  
    2727         time_utc_init    = 0.0,
    2828
    29          rans_mode = .T.,
    3029         turbulence_closure = 'TKE-e',
    3130
Note: See TracChangeset for help on using the changeset viewer.