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/advec_ws.f90

    r2329 r2696  
    11!> @file advec_ws.f90
    22!------------------------------------------------------------------------------!
    3 ! This file is part of PALM.
     3! This file is part of the PALM model system.
    44!
    55! PALM is free software: you can redistribute it and/or modify it under the
     
    2525! -----------------
    2626! $Id$
     27! Implement advection for TKE-dissipation in case of RANS-TKE-e closure (TG)
     28! Allocate advc_flags_1/2 within ws_init_flags instead of init_grid
     29! Change argument list for exchange_horiz_2d_int (MS)
     30!
     31! 2329 2017-08-03 14:24:56Z knoop
    2732! Bugfix concerning density in divergence correction close to buildings
    2833!
     
    247252
    248253       USE arrays_3d,                                                          &
    249            ONLY:  diss_l_e, diss_l_nc, diss_l_nr, diss_l_pt, diss_l_q,         &
    250                   diss_l_qc, diss_l_qr, diss_l_s, diss_l_sa, diss_l_u,         &
    251                   diss_l_v, diss_l_w, flux_l_e, flux_l_nc, flux_l_nr,          &
    252                   flux_l_pt, flux_l_q, flux_l_qc, flux_l_qr, flux_l_s,         &
    253                   flux_l_sa, flux_l_u, flux_l_v, flux_l_w, diss_s_e,           &
    254                   diss_s_nc,  diss_s_nr, diss_s_pt, diss_s_q, diss_s_qc,       &
    255                   diss_s_qr, diss_s_s, diss_s_sa, diss_s_u, diss_s_v,          &
    256                   diss_s_w, flux_s_e, flux_s_nc, flux_s_nr, flux_s_pt,         &
    257                   flux_s_q, flux_s_qc, flux_s_qr, flux_s_s, flux_s_sa,         &
    258                   flux_s_u, flux_s_v, flux_s_w
     254           ONLY:  diss_l_diss, diss_l_e, diss_l_nc, diss_l_nr, diss_l_pt,      &
     255                  diss_l_q, diss_l_qc, diss_l_qr, diss_l_s, diss_l_sa,         &
     256                  diss_l_u, diss_l_v, diss_l_w, flux_l_diss, flux_l_e,         &
     257                  flux_l_nc, flux_l_nr, flux_l_pt, flux_l_q, flux_l_qc,        &
     258                  flux_l_qr, flux_l_s, flux_l_sa, flux_l_u, flux_l_v,          &
     259                  flux_l_w, diss_s_diss, diss_s_e, diss_s_nc,  diss_s_nr,      &
     260                  diss_s_pt, diss_s_q, diss_s_qc, diss_s_qr, diss_s_s,         &
     261                  diss_s_sa, diss_s_u, diss_s_v,  diss_s_w, flux_s_diss,       &
     262                  flux_s_e, flux_s_nc, flux_s_nr, flux_s_pt, flux_s_q,         &
     263                  flux_s_qc, flux_s_qr, flux_s_s, flux_s_sa, flux_s_u,         &
     264                  flux_s_v, flux_s_w
    259265
    260266       USE constants,                                                          &
     
    265271           ONLY:  cloud_physics, humidity, loop_optimization,                  &
    266272                  passive_scalar, microphysics_morrison, microphysics_seifert, &
    267                   ocean, ws_scheme_mom, ws_scheme_sca
     273                  ocean, rans_tke_e, ws_scheme_mom, ws_scheme_sca
    268274
    269275       USE indices,                                                            &
     
    378384                       diss_l_pt(nzb+1:nzt,nys:nyn,0:threads_per_task-1),      &
    379385                       diss_l_e(nzb+1:nzt,nys:nyn,0:threads_per_task-1) )
     386
     387             IF ( rans_tke_e )  THEN
     388                ALLOCATE( flux_s_diss(nzb+1:nzt,0:threads_per_task-1),         &
     389                          diss_s_diss(nzb+1:nzt,0:threads_per_task-1) )
     390                ALLOCATE( flux_l_diss(nzb+1:nzt,nys:nyn,0:threads_per_task-1), &
     391                          diss_l_diss(nzb+1:nzt,nys:nyn,0:threads_per_task-1) )
     392             ENDIF
    380393
    381394             IF ( humidity )  THEN
     
    437450
    438451       USE control_parameters,                                                 &
    439            ONLY:  inflow_l, inflow_n, inflow_r, inflow_s, momentum_advec,      &
     452           ONLY:  force_bound_l, force_bound_n, force_bound_r, force_bound_s,  &
     453                  inflow_l, inflow_n, inflow_r, inflow_s, momentum_advec,      &
    440454                  nest_bound_l, nest_bound_n, nest_bound_r, nest_bound_s,      &
    441455                  outflow_l, outflow_n, outflow_r, outflow_s, scalar_advec
    442456
    443457       USE indices,                                                            &
    444            ONLY:  advc_flags_1, advc_flags_2, nbgp, nxl, nxlu, nxr, nyn, nys,  &
    445                   nysv, nzb, nzt, wall_flags_0
     458           ONLY:  advc_flags_1, advc_flags_2, nbgp, nxl, nxlg, nxlu, nxr, nxrg,&
     459                  nyn, nyng, nys, nysg, nysv, nzb, nzt, wall_flags_0
    446460
    447461       USE kinds
     
    458472       LOGICAL      ::  flag_set !< steering variable for advection flags
    459473   
    460 
     474       ALLOCATE( advc_flags_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                  &
     475                 advc_flags_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     476       advc_flags_1 = 0
     477       advc_flags_2 = 0
    461478       IF ( scalar_advec == 'ws-scheme' )  THEN
    462479!
     
    474491                    .OR.  .NOT. BTEST(wall_flags_0(k,j,i+2),0)                 &   
    475492                    .OR.  .NOT. BTEST(wall_flags_0(k,j,i-1),0) )               &
    476                       .OR.  ( ( inflow_l .OR. outflow_l .OR. nest_bound_l )    &
     493                      .OR.  ( ( inflow_l .OR. outflow_l .OR. nest_bound_l  .OR.&
     494                                force_bound_l )                                &
    477495                            .AND.  i == nxl   )                                &
    478                       .OR.  ( ( inflow_r .OR. outflow_r .OR. nest_bound_r )    &
     496                      .OR.  ( ( inflow_r .OR. outflow_r .OR. nest_bound_r  .OR.&
     497                                force_bound_r )                                &
    479498                            .AND.  i == nxr   ) )                              &
    480499                   THEN
     
    491510                            )                                                  &
    492511                                                    .OR.                       &
    493                             ( ( inflow_r .OR. outflow_r .OR. nest_bound_r )    &
     512                            ( ( inflow_r .OR. outflow_r .OR. nest_bound_r  .OR.&
     513                                force_bound_r )                                &
    494514                              .AND. i == nxr-1 )    .OR.                       &
    495                             ( ( inflow_l .OR. outflow_l .OR. nest_bound_l )    &
    496                               .AND. i == nxlu  ) )                             &
     515                            ( ( inflow_l .OR. outflow_l .OR. nest_bound_l  .OR.&
     516                                force_bound_l )                                &
     517                              .AND. i == nxlu  ) )                             & ! why not nxl+1
    497518                   THEN
    498519                      advc_flags_1(k,j,i) = IBSET( advc_flags_1(k,j,i), 1 )
     
    511532                    .OR.  .NOT. BTEST(wall_flags_0(k,j+2,i),0)                 &   
    512533                    .OR.  .NOT. BTEST(wall_flags_0(k,j-1,i),0))                &
    513                       .OR.  ( ( inflow_s .OR. outflow_s .OR. nest_bound_s )    &
     534                      .OR.  ( ( inflow_s .OR. outflow_s .OR. nest_bound_s  .OR.&
     535                                force_bound_s )                                &
    514536                            .AND.  j == nys   )                                &
    515                       .OR.  ( ( inflow_n .OR. outflow_n .OR. nest_bound_n )    &
     537                      .OR.  ( ( inflow_n .OR. outflow_n .OR. nest_bound_n  .OR.&
     538                                force_bound_n )                                &
    516539                            .AND.  j == nyn   ) )                              &
    517540                   THEN
     
    530553                            )                                                  &
    531554                                                    .OR.                       &
    532                             ( ( inflow_s .OR. outflow_s .OR. nest_bound_s )    &
    533                               .AND. j == nysv  )    .OR.                       &
    534                             ( ( inflow_n .OR. outflow_n .OR. nest_bound_n )    &
     555                            ( ( inflow_s .OR. outflow_s .OR. nest_bound_s  .OR.&
     556                                force_bound_s )                                &
     557                              .AND. j == nysv  )    .OR.                       & ! why not nys+1
     558                            ( ( inflow_n .OR. outflow_n .OR. nest_bound_n  .OR.&
     559                                force_bound_n )                                &
    535560                              .AND. j == nyn-1 ) )                             &         
    536561                   THEN
     
    620645!--                WS1 (9), WS3 (10), WS5 (11)
    621646                   IF ( .NOT. BTEST(wall_flags_0(k,j,i+1),1)  .OR.             &
    622                             ( ( inflow_l .OR. outflow_l .OR. nest_bound_l )    &
     647                            ( ( inflow_l .OR. outflow_l .OR. nest_bound_l  .OR.&
     648                                force_bound_l )                                &
    623649                              .AND. i <= nxlu  )    .OR.                       &
    624                             ( ( inflow_r .OR. outflow_r .OR. nest_bound_r )    &
     650                            ( ( inflow_r .OR. outflow_r .OR. nest_bound_r  .OR.&
     651                                force_bound_r )                                &
    625652                              .AND. i == nxr   ) )                             &
    626653                   THEN
     
    630657                              .NOT. BTEST(wall_flags_0(k,j,i-1),1) )           &
    631658                                                        .OR.                   &
    632                             ( ( inflow_r .OR. outflow_r .OR. nest_bound_r )    &
     659                            ( ( inflow_r .OR. outflow_r .OR. nest_bound_r  .OR.&
     660                                force_bound_r )                                &
    633661                              .AND. i == nxr-1 )    .OR.                       &
    634                             ( ( inflow_l .OR. outflow_l .OR. nest_bound_l )    &
     662                            ( ( inflow_l .OR. outflow_l .OR. nest_bound_l  .OR.&
     663                                force_bound_l )                                &
    635664                              .AND. i == nxlu+1) )                             &
    636665                   THEN
     
    652681!--                WS1 (12), WS3 (13), WS5 (14)
    653682                   IF ( .NOT. BTEST(wall_flags_0(k,j+1,i),1)   .OR.            &
    654                             ( ( inflow_s .OR. outflow_s .OR. nest_bound_s )    &
     683                            ( ( inflow_s .OR. outflow_s .OR. nest_bound_s  .OR.&
     684                                force_bound_s )                                &
    655685                              .AND. j == nys   )    .OR.                       &
    656                             ( ( inflow_n .OR. outflow_n .OR. nest_bound_n )    &
     686                            ( ( inflow_n .OR. outflow_n .OR. nest_bound_n  .OR.&
     687                                force_bound_n )                                &
    657688                              .AND. j == nyn   ) )                             &
    658689                   THEN
     
    662693                              .NOT. BTEST(wall_flags_0(k,j-1,i),1) )           &
    663694                                                        .OR.                   &
    664                             ( ( inflow_s .OR. outflow_s .OR. nest_bound_s )    &
     695                            ( ( inflow_s .OR. outflow_s .OR. nest_bound_s  .OR.&
     696                                force_bound_s )                                &
    665697                              .AND. j == nysv  )    .OR.                       &
    666                             ( ( inflow_n .OR. outflow_n .OR. nest_bound_n )    &
     698                            ( ( inflow_n .OR. outflow_n .OR. nest_bound_n  .OR.&
     699                                force_bound_n )                                &
    667700                              .AND. j == nyn-1 ) )                             &
    668701                   THEN
     
    746779!--                WS1 (18), WS3 (19), WS5 (20)
    747780                   IF ( .NOT. BTEST(wall_flags_0(k,j,i+1),2)  .OR.             &
    748                             ( ( inflow_l .OR. outflow_l .OR. nest_bound_l )    &
     781                            ( ( inflow_l .OR. outflow_l .OR. nest_bound_l  .OR.&
     782                                force_bound_l )                                &
    749783                              .AND. i == nxl   )    .OR.                       &
    750                             ( ( inflow_r .OR. outflow_r .OR. nest_bound_r )    &
     784                            ( ( inflow_r .OR. outflow_r .OR. nest_bound_r  .OR.&
     785                                force_bound_r )                                &
    751786                              .AND. i == nxr   ) )                             &
    752787                  THEN
     
    758793                              .NOT. BTEST(wall_flags_0(k,j,i-1),2)             &
    759794                                                    .OR.                       &
    760                             ( ( inflow_r .OR. outflow_r .OR. nest_bound_r )    &
     795                            ( ( inflow_r .OR. outflow_r .OR. nest_bound_r  .OR.&
     796                                force_bound_r )                                &
    761797                              .AND. i == nxr-1 )    .OR.                       &
    762                             ( ( inflow_l .OR. outflow_l .OR. nest_bound_l )    &
     798                            ( ( inflow_l .OR. outflow_l .OR. nest_bound_l  .OR.&
     799                                force_bound_l )                                &
    763800                              .AND. i == nxlu  ) )                             &
    764801                   THEN
     
    780817!--                WS1 (21), WS3 (22), WS5 (23)
    781818                   IF ( .NOT. BTEST(wall_flags_0(k,j+1,i),2) .OR.              &
    782                             ( ( inflow_s .OR. outflow_s .OR. nest_bound_s )    &
     819                            ( ( inflow_s .OR. outflow_s .OR. nest_bound_s  .OR.&
     820                                force_bound_s )                                &
    783821                              .AND. j <= nysv  )    .OR.                       &
    784                             ( ( inflow_n .OR. outflow_n .OR. nest_bound_n )    &
     822                            ( ( inflow_n .OR. outflow_n .OR. nest_bound_n  .OR.&
     823                                force_bound_n )                                &
    785824                              .AND. j == nyn   ) )                             &
    786825                   THEN
     
    790829                              .NOT. BTEST(wall_flags_0(k,j-1,i),2) )           &
    791830                                                        .OR.                   &
    792                             ( ( inflow_s .OR. outflow_s .OR. nest_bound_s )    &
     831                            ( ( inflow_s .OR. outflow_s .OR. nest_bound_s  .OR.&
     832                                force_bound_s )                                &
    793833                              .AND. j == nysv+1)    .OR.                       &
    794                             ( ( inflow_n .OR. outflow_n .OR. nest_bound_n )    &
     834                            ( ( inflow_n .OR. outflow_n .OR. nest_bound_n  .OR.&
     835                                force_bound_n )                                &
    795836                              .AND. j == nyn-1 ) )                             &
    796837                   THEN
     
    873914!--                WS1 (27), WS3 (28), WS5 (29)
    874915                   IF ( .NOT. BTEST(wall_flags_0(k,j,i+1),3) .OR.              &
    875                             ( ( inflow_l .OR. outflow_l .OR. nest_bound_l )    &
     916                            ( ( inflow_l .OR. outflow_l .OR. nest_bound_l  .OR.&
     917                                force_bound_l )                                &
    876918                              .AND. i == nxl   )    .OR.                       &
    877                             ( ( inflow_r .OR. outflow_r .OR. nest_bound_r )    &
     919                            ( ( inflow_r .OR. outflow_r .OR. nest_bound_r  .OR.&
     920                                force_bound_r )                                &
    878921                              .AND. i == nxr   ) )                             &
    879922                   THEN
     
    883926                              .NOT. BTEST(wall_flags_0(k,j,i-1),3) )           &
    884927                                                        .OR.                   &
    885                             ( ( inflow_r .OR. outflow_r .OR. nest_bound_r )    &
     928                            ( ( inflow_r .OR. outflow_r .OR. nest_bound_r  .OR.&
     929                                force_bound_r )                                &
    886930                              .AND. i == nxr-1 )    .OR.                       &
    887                             ( ( inflow_l .OR. outflow_l .OR. nest_bound_l )    &
     931                            ( ( inflow_l .OR. outflow_l .OR. nest_bound_l  .OR.&
     932                                force_bound_l )                                &
    888933                              .AND. i == nxlu  ) )                             &
    889934                   THEN
     
    905950!--                WS1 (30), WS3 (31), WS5 (32)
    906951                   IF ( .NOT. BTEST(wall_flags_0(k,j+1,i),3) .OR.              &
    907                             ( ( inflow_s .OR. outflow_s .OR. nest_bound_s )    &
     952                            ( ( inflow_s .OR. outflow_s .OR. nest_bound_s  .OR.&
     953                                force_bound_s )                                &
    908954                              .AND. j == nys   )    .OR.                       &
    909                             ( ( inflow_n .OR. outflow_n .OR. nest_bound_n )    &
     955                            ( ( inflow_n .OR. outflow_n .OR. nest_bound_n  .OR.&
     956                                force_bound_n )                                &
    910957                              .AND. j == nyn   ) )                             &
    911958                   THEN
     
    915962                              .NOT. BTEST(wall_flags_0(k,j-1,i),3) )           &
    916963                                                        .OR.                   &
    917                             ( ( inflow_s .OR. outflow_s .OR. nest_bound_s )    &
     964                            ( ( inflow_s .OR. outflow_s .OR. nest_bound_s  .OR.&
     965                                force_bound_s )                                &
    918966                              .AND. j == nysv  )    .OR.                       &
    919                             ( ( inflow_n .OR. outflow_n .OR. nest_bound_n )    &
     967                            ( ( inflow_n .OR. outflow_n .OR. nest_bound_n  .OR.&
     968                                force_bound_n )                                &
    920969                              .AND. j == nyn-1 ) )                             &
    921970                   THEN
     
    10031052!
    10041053!--       Exchange ghost points for advection flags
    1005           CALL exchange_horiz_int( advc_flags_1, nbgp )
    1006           CALL exchange_horiz_int( advc_flags_2, nbgp )
     1054          CALL exchange_horiz_int( advc_flags_1, nys, nyn, nxl, nxr, nzt, nbgp )
     1055          CALL exchange_horiz_int( advc_flags_2, nys, nyn, nxl, nxr, nzt, nbgp )
    10071056!
    10081057!--       Set boundary flags at inflow and outflow boundary in case of
    10091058!--       non-cyclic boundary conditions.
    1010          IF ( inflow_l .OR. outflow_l .OR. nest_bound_l )  THEN
     1059          IF ( inflow_l      .OR.  outflow_l  .OR.                             &
     1060               nest_bound_l  .OR.  force_bound_l )  THEN
    10111061             advc_flags_1(:,:,nxl-1) = advc_flags_1(:,:,nxl)
    10121062             advc_flags_2(:,:,nxl-1) = advc_flags_2(:,:,nxl)
    1013          ENDIF
    1014 
    1015          IF ( inflow_r .OR. outflow_r .OR. nest_bound_r )  THEN
     1063          ENDIF
     1064
     1065          IF ( inflow_r      .OR.  outflow_r  .OR.                             &
     1066               nest_bound_r  .OR.  force_bound_r )  THEN
    10161067            advc_flags_1(:,:,nxr+1) = advc_flags_1(:,:,nxr)
    10171068            advc_flags_2(:,:,nxr+1) = advc_flags_2(:,:,nxr)
    10181069          ENDIF
    10191070
    1020           IF ( inflow_n .OR. outflow_n .OR. nest_bound_n )  THEN
     1071          IF ( inflow_n      .OR.  outflow_n  .OR.                             &
     1072               nest_bound_n  .OR.  force_bound_n )  THEN
    10211073             advc_flags_1(:,nyn+1,:) = advc_flags_1(:,nyn,:)
    10221074             advc_flags_2(:,nyn+1,:) = advc_flags_2(:,nyn,:)
    10231075          ENDIF
    10241076
    1025           IF ( inflow_s .OR. outflow_s  .OR. nest_bound_s )  THEN
     1077          IF ( inflow_s      .OR.  outflow_s  .OR.                             &
     1078               nest_bound_s  .OR.  force_bound_s )  THEN
    10261079             advc_flags_1(:,nys-1,:) = advc_flags_1(:,nys,:)
    10271080             advc_flags_2(:,nys-1,:) = advc_flags_2(:,nys,:)
Note: See TracChangeset for help on using the changeset viewer.