Changeset 1567 for palm


Ignore:
Timestamp:
Mar 10, 2015 5:57:55 PM (9 years ago)
Author:
suehring
Message:

Bugfixes in monotonic limter.

Location:
palm/trunk/SOURCE
Files:
2 edited

Legend:

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

    r1563 r1567  
    2020! Current revisions:
    2121! ------------------
    22 
     22! Bugfixes in monotonic limiter.
    2323!
    2424! Former revisions:
     
    825825!
    826826!--           Calculate empirical limiter function (van Albada2 limiter).
    827               phi_l = MIN( 1.0_wp, ( 2.0_wp * rl ) /                          &
     827              phi_l = MIN( 1.0_wp, ( 2.0_wp * ABS( rl ) ) /                   &
    828828                                         ( rl**2 + 1.0_wp ) )
    829               phi_r = MIN( 1.0_wp, ( 2.0_wp * rr ) /                          &
     829              phi_r = MIN( 1.0_wp, ( 2.0_wp * ABS( rr ) ) /                   &
    830830                                         ( rr**2 + 1.0_wp ) )
    831               phi_s = MIN( 1.0_wp, ( 2.0_wp * rs ) /                          &
     831              phi_s = MIN( 1.0_wp, ( 2.0_wp * ABS( rs ) ) /                   &
    832832                                         ( rs**2 + 1.0_wp ) )
    833               phi_n = MIN( 1.0_wp, ( 2.0_wp * rn ) /                          &
     833              phi_n = MIN( 1.0_wp, ( 2.0_wp * ABS( rn ) ) /                   &
    834834                                         ( rn**2 + 1.0_wp ) )
    835               phi_d = MIN( 1.0_wp, ( 2.0_wp * rd ) /                          &
     835              phi_d = MIN( 1.0_wp, ( 2.0_wp * ABS( rd ) ) /                   &
    836836                                         ( rd**2 + 1.0_wp ) )
    837               phi_t = MIN( 1.0_wp, ( 2.0_wp * rt ) /                          &
     837              phi_t = MIN( 1.0_wp, ( 2.0_wp * ABS( rt ) ) /                   &
    838838                                         ( rt**2 + 1.0_wp ) )
    839839!
     
    847847              flux_n(k)                 = fn_1 - phi_n *                      &
    848848                                        ( fn_1 - flux_n(k)                  )
    849               flux_d                    = fd_1  !- phi_d *                      &
    850 !                                         ( fd_1 - flux_d                     )
    851               flux_t(k)                 = ft_1 !- phi_t *                      &
    852 !                                         ( ft_1 - flux_t(k)                  )
     849              flux_d                    = fd_1 - phi_d *                      &
     850                                        ( fd_1 - flux_d                     )
     851              flux_t(k)                 = ft_1 - phi_t *                      &
     852                                        ( ft_1 - flux_t(k)                  )
    853853!
    854854!--          Moreover, modify dissipation flux according to the limiter.
     
    857857             swap_diss_y_local(k,tn)   = swap_diss_y_local(k,tn)   * phi_s
    858858             diss_n(k)                 = diss_n(k)                 * phi_n
    859              diss_d                    = 0.0 !diss_d                    * phi_d
    860              diss_t(k)                 = 0.0 !diss_t(k)                 * phi_t
     859             diss_d                    = diss_d                    * phi_d
     860             diss_t(k)                 = diss_t(k)                 * phi_t
    861861
    862862          ENDIF
     
    10541054!
    10551055!--           Calculate empirical limiter function (van Albada2 limiter).
    1056               phi_l = MIN( 1.0_wp, ( 2.0_wp * rl ) /                          &
     1056              phi_l = MIN( 1.0_wp, ( 2.0_wp * ABS( rl ) ) /                   &
    10571057                                         ( rl**2 + 1.0_wp ) )
    1058               phi_r = MIN( 1.0_wp, ( 2.0_wp * rr ) /                          &
     1058              phi_r = MIN( 1.0_wp, ( 2.0_wp * ABS( rr ) ) /                   &
    10591059                                         ( rr**2 + 1.0_wp ) )
    1060               phi_s = MIN( 1.0_wp, ( 2.0_wp * rs ) /                          &
     1060              phi_s = MIN( 1.0_wp, ( 2.0_wp * ABS( rs ) ) /                   &
    10611061                                         ( rs**2 + 1.0_wp ) )
    1062               phi_n = MIN( 1.0_wp, ( 2.0_wp * rn ) /                          &
     1062              phi_n = MIN( 1.0_wp, ( 2.0_wp * ABS( rn ) ) /                   &
    10631063                                         ( rn**2 + 1.0_wp ) )
    1064               phi_d = MIN( 1.0_wp, ( 2.0_wp * rd ) /                          &
     1064              phi_d = MIN( 1.0_wp, ( 2.0_wp * ABS( rd ) ) /                   &
    10651065                                         ( rd**2 + 1.0_wp ) )
    1066               phi_t = MIN( 1.0_wp, ( 2.0_wp * rt ) /                          &
     1066              phi_t = MIN( 1.0_wp, ( 2.0_wp * ABS( rt ) ) /                   &
    10671067                                         ( rt**2 + 1.0_wp ) )
    10681068!
     
    11301130                                          ( flux_t(k) + diss_t(k) )           &
    11311131                                  * weight_substep(intermediate_timestep_count)
    1132              ENDDO
     1132                ENDDO
    11331133             
    11341134             CASE ( 'sa' )
     
    29612961!
    29622962!--                Calculate empirical limiter function (van Albada2 limiter).
    2963                    phi_l = MIN( 1.0_wp, ( 2.0_wp * rl ) /                     &
     2963                   phi_l = MIN( 1.0_wp, ( 2.0_wp * ABS( rl ) ) /              &
    29642964                                        ( rl**2 + 1.0_wp ) )
    2965                    phi_r = MIN( 1.0_wp, ( 2.0_wp * rr ) /                     &
     2965                   phi_r = MIN( 1.0_wp, ( 2.0_wp * ABS( rr ) ) /              &
    29662966                                        ( rr**2 + 1.0_wp ) )
    2967                    phi_s = MIN( 1.0_wp, ( 2.0_wp * rs ) /                     &
     2967                   phi_s = MIN( 1.0_wp, ( 2.0_wp * ABS( rs ) ) /              &
    29682968                                        ( rs**2 + 1.0_wp ) )
    2969                    phi_n = MIN( 1.0_wp, ( 2.0_wp * rn ) /                     &
     2969                   phi_n = MIN( 1.0_wp, ( 2.0_wp * ABS( rn ) ) /              &
    29702970                                        ( rn**2 + 1.0_wp ) )
    2971                    phi_d = MIN( 1.0_wp, ( 2.0_wp * rd ) /                     &
     2971                   phi_d = MIN( 1.0_wp, ( 2.0_wp * ABS( rd ) ) /              &
    29722972                                        ( rd**2 + 1.0_wp ) )
    2973                    phi_t = MIN( 1.0_wp, ( 2.0_wp * rt ) /                     &
     2973                   phi_t = MIN( 1.0_wp, ( 2.0_wp * ABS( rt ) ) /              &
    29742974                                        ( rt**2 + 1.0_wp ) )
    29752975!
     
    31863186!
    31873187!--                Calculate empirical limiter function (van Albada2 limiter).
    3188                    phi_l = MIN( 1.0_wp, ( 2.0_wp * rl ) /                     &
     3188                   phi_l = MIN( 1.0_wp, ( 2.0_wp * ABS( rl ) ) /              &
    31893189                                        ( rl**2 + 1.0_wp ) )
    3190                    phi_r = MIN( 1.0_wp, ( 2.0_wp * rr ) /                     &
     3190                   phi_r = MIN( 1.0_wp, ( 2.0_wp * ABS( rr ) ) /              &
    31913191                                        ( rr**2 + 1.0_wp ) )
    3192                    phi_s = MIN( 1.0_wp, ( 2.0_wp * rs ) /                     &
     3192                   phi_s = MIN( 1.0_wp, ( 2.0_wp * ABS( rs ) ) /              &
    31933193                                        ( rs**2 + 1.0_wp ) )
    3194                    phi_n = MIN( 1.0_wp, ( 2.0_wp * rn ) /                     &
     3194                   phi_n = MIN( 1.0_wp, ( 2.0_wp * ABS( rn ) ) /              &
    31953195                                        ( rn**2 + 1.0_wp ) )
    3196                    phi_d = MIN( 1.0_wp, ( 2.0_wp * rd ) /                     &
     3196                   phi_d = MIN( 1.0_wp, ( 2.0_wp * ABS( rd ) ) /              &
    31973197                                        ( rd**2 + 1.0_wp ) )
    3198                    phi_t = MIN( 1.0_wp, ( 2.0_wp * rt ) /                     &
     3198                   phi_t = MIN( 1.0_wp, ( 2.0_wp * ABS( rt ) ) /              &
    31993199                                        ( rt**2 + 1.0_wp ) )
    32003200!
     
    36993699!
    37003700!--                Calculate empirical limiter function (van Albada2 limiter).
    3701                    phi_l = MIN( 1.0_wp, ( 2.0_wp * rl ) /                     &
     3701                   phi_l = MIN( 1.0_wp, ( 2.0_wp * ABS( rl ) ) /              &
    37023702                                        ( rl**2 + 1.0_wp ) )
    3703                    phi_r = MIN( 1.0_wp, ( 2.0_wp * rr ) /                     &
     3703                   phi_r = MIN( 1.0_wp, ( 2.0_wp * ABS( rr ) ) /              &
    37043704                                        ( rr**2 + 1.0_wp ) )
    3705                    phi_s = MIN( 1.0_wp, ( 2.0_wp * rs ) /                     &
     3705                   phi_s = MIN( 1.0_wp, ( 2.0_wp * ABS( rs ) ) /              &
    37063706                                        ( rs**2 + 1.0_wp ) )
    3707                    phi_n = MIN( 1.0_wp, ( 2.0_wp * rn ) /                     &
     3707                   phi_n = MIN( 1.0_wp, ( 2.0_wp * ABS( rn ) ) /              &
    37083708                                        ( rn**2 + 1.0_wp ) )
    3709                    phi_d = MIN( 1.0_wp, ( 2.0_wp * rd ) /                     &
     3709                   phi_d = MIN( 1.0_wp, ( 2.0_wp * ABS( rd ) ) /              &
    37103710                                        ( rd**2 + 1.0_wp ) )
    3711                    phi_t = MIN( 1.0_wp, ( 2.0_wp * rt ) /                     &
     3711                   phi_t = MIN( 1.0_wp, ( 2.0_wp * ABS( rt ) ) /              &
    37123712                                        ( rt**2 + 1.0_wp ) )
    37133713!
  • palm/trunk/SOURCE/flow_statistics.f90

    r1558 r1567  
    2121! Current revisions:
    2222! -----------------
    23 !
     23! Reverse modifications made for monotonic limiter.
    2424!
    2525! Former revisions:
     
    146146        ONLY:   average_count_pr, cloud_droplets, cloud_physics, do_sum,       &
    147147                dt_3d, g, humidity, icloud_scheme, kappa, large_scale_forcing, &
    148                 large_scale_subsidence, max_pr_user, message_string,           &
    149                 monotonic_adjustment, ocean,                                   &
     148                large_scale_subsidence, max_pr_user, message_string, ocean,    &
    150149                passive_scalar, precipitation, simulated_time,                 &
    151150                use_subsidence_tendencies, use_surface_fluxes, use_top_fluxes, &
     
    285284       ENDIF
    286285
    287        IF ( ws_scheme_sca .AND. .NOT. monotonic_adjustment                    &
    288            .AND. sr == 0 )  THEN
     286       IF ( ws_scheme_sca .AND. sr == 0 )  THEN
    289287
    290288          DO  i = 0, threads_per_task-1
     
    807805!--             but so far there is no other suitable place to calculate)
    808806                IF ( ocean )  THEN
    809                    IF( .NOT. ws_scheme_sca .OR. monotonic_adjustment .OR.      &
    810                              sr /= 0 )  THEN
     807                   IF( .NOT. ws_scheme_sca .OR. sr /= 0 )  THEN
    811808                      pts = 0.5_wp * ( sa(k,j,i)   - hom(k,1,23,sr) +          &
    812809                                       sa(k+1,j,i) - hom(k+1,1,23,sr) )
     
    859856                      ENDIF
    860857                   ELSE
    861                       IF( .NOT. ws_scheme_sca .OR. monotonic_adjustment .OR.   &
    862                                 sr /= 0 )  THEN
     858                      IF( .NOT. ws_scheme_sca .OR. sr /= 0 )  THEN
    863859                         pts = 0.5_wp * ( vpt(k,j,i)   - hom(k,1,44,sr) +      &
    864860                                          vpt(k+1,j,i) - hom(k+1,1,44,sr) )
    865861                         sums_l(k,46,tn) = sums_l(k,46,tn) + pts * w(k,j,i) *  &
    866862                                                             rmask(j,i,sr)
    867                       ELSE IF ( ws_scheme_sca .AND. .NOT. monotonic_adjustment &
    868                                 .AND. sr == 0 )  THEN
     863                      ELSE IF ( ws_scheme_sca .AND. sr == 0 )  THEN
    869864                         sums_l(k,46,tn) = ( 1.0_wp + 0.61_wp *                &
    870865                                             hom(k,1,41,sr) ) *                &
     
    878873!--             Passive scalar flux
    879874                IF ( passive_scalar .AND. ( .NOT. ws_scheme_sca                &
    880                      .OR. monotonic_adjustment .OR. sr /= 0 ) )  THEN
     875                     .OR. sr /= 0 ) )  THEN
    881876                   pts = 0.5_wp * ( q(k,j,i)   - hom(k,1,41,sr) +              &
    882877                                    q(k+1,j,i) - hom(k+1,1,41,sr) )
     
    922917
    923918       ENDIF
    924        IF ( .NOT. ws_scheme_sca .OR. monotonic_adjustment .OR. sr /= 0 )  THEN
     919       IF ( .NOT. ws_scheme_sca .OR. sr /= 0 )  THEN
    925920         !$OMP DO
    926921         DO  i = nxl, nxr
     
    15331528        ONLY :  average_count_pr, cloud_droplets, cloud_physics, do_sum,       &
    15341529                dt_3d, g, humidity, icloud_scheme, kappa, large_scale_forcing, &
    1535                 large_scale_subsidence, max_pr_user, message_string,           &
    1536                 monotonic_adjustment, ocean,                                   &
     1530                large_scale_subsidence, max_pr_user, message_string, ocean,    &
    15371531                passive_scalar, precipitation, simulated_time,                 &
    15381532                use_subsidence_tendencies, use_surface_fluxes, use_top_fluxes, &
     
    16721666       ENDIF
    16731667
    1674        IF ( ws_scheme_sca .AND. .NOT. monotonic_adjustment .AND. sr == 0 )  THEN
     1668       IF ( ws_scheme_sca .AND. sr == 0 )  THEN
    16751669
    16761670          DO  i = 0, threads_per_task-1
     
    24952489       IF ( ocean )  THEN
    24962490
    2497           IF( .NOT. ws_scheme_sca .OR. monotonic_adjustment .OR. sr /= 0 )  THEN
     2491          IF( .NOT. ws_scheme_sca .OR. sr /= 0 )  THEN
    24982492
    24992493             !$acc parallel loop gang present( hom, rflags_invers, rmask, sa, sums_l, w ) create( s1 )
     
    26372631          ELSE
    26382632
    2639              IF( .NOT. ws_scheme_sca .OR. monotonic_adjustment .OR.  sr /= 0 )  THEN
     2633             IF( .NOT. ws_scheme_sca .OR.  sr /= 0 )  THEN
    26402634
    26412635                !$acc parallel loop gang present( hom, rflags_invers, rmask, sums_l, vpt, w ) create( s1 )
     
    26692663!
    26702664!--    Passive scalar flux
    2671        IF ( passive_scalar  .AND.  ( .NOT. ws_scheme_sca .OR. monotonic_adjustment &
    2672                                      .OR.  sr /= 0 ) )  THEN
     2665       IF ( passive_scalar  .AND.  ( .NOT. ws_scheme_sca  .OR.  sr /= 0 ) )  THEN
    26732666
    26742667          !$acc parallel loop gang present( hom, q, rflags_invers, rmask, sums_l, w ) create( s1 )
     
    27242717       ENDIF
    27252718
    2726        IF ( .NOT. ws_scheme_sca .OR. monotonic_adjustment .OR.  sr /= 0 )  THEN
     2719       IF ( .NOT. ws_scheme_sca .OR.  sr /= 0 )  THEN
    27272720
    27282721          !$OMP DO
Note: See TracChangeset for help on using the changeset viewer.