Changeset 3879 for palm/trunk/SOURCE


Ignore:
Timestamp:
Apr 8, 2019 8:25:23 PM (5 years ago)
Author:
knoop
Message:

Moved loop over chem_species into chem_boundary_conds_decycle

Location:
palm/trunk/SOURCE
Files:
4 edited

Legend:

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

    r3864 r3879  
    230230
    231231    USE chemistry_model_mod,                                                   &
    232         ONLY:  chem_boundary_conds 
    233              
     232        ONLY:  chem_boundary_conds
     233
    234234    USE control_parameters,                                                    &
    235235        ONLY:  air_chemistry, bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,  &
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r3878 r3879  
    289289
    290290    USE indices,                                                                                   &
    291          ONLY:  nz, nzb, nzt, nysg, nyng, nxlg, nxrg, nys, nyn, nx, nxl, nxr, ny, wall_flags_0
     291         ONLY:  nbgp, nz, nzb, nzt, nysg, nyng, nxlg, nxrg, nys, nyn, nx, nxl, nxr, ny, wall_flags_0
    292292
    293293    USE pegrid,                                                                                    &
     
    429429    INTERFACE chem_boundary_conds
    430430       MODULE PROCEDURE chem_boundary_conds
     431    END INTERFACE chem_boundary_conds
     432
     433    INTERFACE chem_boundary_conds_decycle
    431434       MODULE PROCEDURE chem_boundary_conds_decycle
    432     END INTERFACE chem_boundary_conds
     435    END INTERFACE chem_boundary_conds_decycle
    433436
    434437    INTERFACE chem_check_data_output
     
    585588
    586589
    587     PUBLIC chem_3d_data_averaging, chem_boundary_conds, chem_check_data_output, &
     590    PUBLIC chem_3d_data_averaging, chem_boundary_conds,                       &
     591            chem_boundary_conds_decycle, chem_check_data_output,              &
    588592         chem_check_data_output_pr, chem_check_parameters,                    &
    589593         chem_data_output_2d, chem_data_output_3d, chem_data_output_mask,     &
     
    871875!> x-direction
    872876!------------------------------------------------------------------------------!
    873  SUBROUTINE chem_boundary_conds_decycle( cs_3d, cs_pr_init )
     877 SUBROUTINE chem_boundary_conds_decycle()
    874878!
    875879!-- Decycling of chemistry variables: Dirichlet BCs with cyclic is frequently not
     
    887891    INTEGER(iwp) ::  k         !<
    888892    INTEGER(iwp) ::  ss        !<
     893    INTEGER(iwp) ::  lsp       !<
     894    INTEGER(iwp) ::  lsp_usr   !<
    889895    REAL(wp), DIMENSION(nzb:nzt+1) ::  cs_pr_init
    890896    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  cs_3d
    891897    REAL(wp) ::  flag !< flag to mask topography grid points
    892898
    893     flag = 0.0_wp
    894 !
    895 !-- Left and right boundaries
    896     IF ( decycle_chem_lr  .AND.  bc_lr_cyc )  THEN
    897 
    898        DO  boundary = 1, 2
    899 
    900           IF ( decycle_method(boundary) == 'dirichlet' )  THEN
    901 !   
    902 !--          Initial profile is copied to ghost and first three layers         
    903              ss = 1
    904              ee = 0
    905              IF ( boundary == 1  .AND.  nxl == 0 )  THEN
    906                 ss = nxlg
    907                 ee = nxl+2
    908              ELSEIF ( boundary == 2  .AND.  nxr == nx )  THEN
    909                 ss = nxr-2
    910                 ee = nxrg
     899    CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'start' )
     900
     901    DO  lsp = 1, nspec
     902
     903       CALL exchange_horiz( chem_species(lsp)%conc_p, nbgp )
     904       lsp_usr = 1
     905       DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
     906          IF ( TRIM(chem_species(lsp)%name) == TRIM(cs_name(lsp_usr)) )  THEN
     907
     908             cs_3d = chem_species(lsp)%conc_p
     909             cs_pr_init = chem_species(lsp)%conc_pr_init
     910
     911             flag = 0.0_wp
     912         !
     913         !-- Left and right boundaries
     914             IF ( decycle_chem_lr  .AND.  bc_lr_cyc )  THEN
     915
     916                DO  boundary = 1, 2
     917
     918                   IF ( decycle_method(boundary) == 'dirichlet' )  THEN
     919         !
     920         !--          Initial profile is copied to ghost and first three layers
     921                      ss = 1
     922                      ee = 0
     923                      IF ( boundary == 1  .AND.  nxl == 0 )  THEN
     924                         ss = nxlg
     925                         ee = nxl+2
     926                      ELSEIF ( boundary == 2  .AND.  nxr == nx )  THEN
     927                         ss = nxr-2
     928                         ee = nxrg
     929                      ENDIF
     930
     931                      DO  i = ss, ee
     932                         DO  j = nysg, nyng
     933                            DO  k = nzb+1, nzt
     934                               flag = MERGE( 1.0_wp, 0.0_wp,                            &
     935                                             BTEST( wall_flags_0(k,j,i), 0 ) )
     936                               cs_3d(k,j,i) = cs_pr_init(k) * flag
     937                            ENDDO
     938                         ENDDO
     939                      ENDDO
     940
     941                 ELSEIF ( decycle_method(boundary) == 'neumann' )  THEN
     942         !
     943         !--          The value at the boundary is copied to the ghost layers to simulate
     944         !--          an outlet with zero gradient
     945                      ss = 1
     946                      ee = 0
     947                      IF ( boundary == 1  .AND.  nxl == 0 )  THEN
     948                         ss = nxlg
     949                         ee = nxl-1
     950                         copied = nxl
     951                      ELSEIF ( boundary == 2  .AND.  nxr == nx )  THEN
     952                         ss = nxr+1
     953                         ee = nxrg
     954                         copied = nxr
     955                      ENDIF
     956
     957                       DO  i = ss, ee
     958                         DO  j = nysg, nyng
     959                            DO  k = nzb+1, nzt
     960                               flag = MERGE( 1.0_wp, 0.0_wp,                            &
     961                                             BTEST( wall_flags_0(k,j,i), 0 ) )
     962                              cs_3d(k,j,i) = cs_3d(k,j,copied) * flag
     963                            ENDDO
     964                         ENDDO
     965                      ENDDO
     966
     967                   ELSE
     968                      WRITE(message_string,*)                                           &
     969                                          'unknown decycling method: decycle_method (', &
     970                              boundary, ') ="' // TRIM( decycle_method(boundary) ) // '"'
     971                      CALL message( 'chem_boundary_conds_decycle', 'CM0431',           &
     972                                    1, 2, 0, 6, 0 )
     973                   ENDIF
     974                ENDDO
    911975             ENDIF
    912 
    913              DO  i = ss, ee
    914                 DO  j = nysg, nyng
    915                    DO  k = nzb+1, nzt
    916                       flag = MERGE( 1.0_wp, 0.0_wp,                            &
    917                                     BTEST( wall_flags_0(k,j,i), 0 ) )
    918                       cs_3d(k,j,i) = cs_pr_init(k) * flag
    919                    ENDDO
     976         !
     977         !-- South and north boundaries
     978             IF ( decycle_chem_ns  .AND.  bc_ns_cyc )  THEN
     979
     980                DO  boundary = 3, 4
     981
     982                   IF ( decycle_method(boundary) == 'dirichlet' )  THEN
     983         !
     984         !--          Initial profile is copied to ghost and first three layers
     985                      ss = 1
     986                      ee = 0
     987                      IF ( boundary == 3  .AND.  nys == 0 )  THEN
     988                         ss = nysg
     989                         ee = nys+2
     990                      ELSEIF ( boundary == 4  .AND.  nyn == ny )  THEN
     991                         ss = nyn-2
     992                         ee = nyng
     993                      ENDIF
     994
     995                      DO  i = nxlg, nxrg
     996                         DO  j = ss, ee
     997                            DO  k = nzb+1, nzt
     998                               flag = MERGE( 1.0_wp, 0.0_wp,                            &
     999                                             BTEST( wall_flags_0(k,j,i), 0 ) )
     1000                               cs_3d(k,j,i) = cs_pr_init(k) * flag
     1001                            ENDDO
     1002                         ENDDO
     1003                      ENDDO
     1004
     1005
     1006                 ELSEIF ( decycle_method(boundary) == 'neumann' )  THEN
     1007         !
     1008         !--          The value at the boundary is copied to the ghost layers to simulate
     1009         !--          an outlet with zero gradient
     1010                      ss = 1
     1011                      ee = 0
     1012                      IF ( boundary == 3  .AND.  nys == 0 )  THEN
     1013                         ss = nysg
     1014                         ee = nys-1
     1015                         copied = nys
     1016                      ELSEIF ( boundary == 4  .AND.  nyn == ny )  THEN
     1017                         ss = nyn+1
     1018                         ee = nyng
     1019                         copied = nyn
     1020                      ENDIF
     1021
     1022                       DO  i = nxlg, nxrg
     1023                         DO  j = ss, ee
     1024                            DO  k = nzb+1, nzt
     1025                               flag = MERGE( 1.0_wp, 0.0_wp,                            &
     1026                                             BTEST( wall_flags_0(k,j,i), 0 ) )
     1027                               cs_3d(k,j,i) = cs_3d(k,copied,i) * flag
     1028                            ENDDO
     1029                         ENDDO
     1030                      ENDDO
     1031
     1032                   ELSE
     1033                      WRITE(message_string,*)                                           &
     1034                                          'unknown decycling method: decycle_method (', &
     1035                              boundary, ') ="' // TRIM( decycle_method(boundary) ) // '"'
     1036                      CALL message( 'chem_boundary_conds_decycle', 'CM0432',           &
     1037                                    1, 2, 0, 6, 0 )
     1038                   ENDIF
    9201039                ENDDO
    921              ENDDO
    922 
    923         ELSEIF ( decycle_method(boundary) == 'neumann' )  THEN
    924 !
    925 !--          The value at the boundary is copied to the ghost layers to simulate
    926 !--          an outlet with zero gradient
    927              ss = 1
    928              ee = 0
    929              IF ( boundary == 1  .AND.  nxl == 0 )  THEN
    930                 ss = nxlg
    931                 ee = nxl-1
    932                 copied = nxl
    933              ELSEIF ( boundary == 2  .AND.  nxr == nx )  THEN
    934                 ss = nxr+1
    935                 ee = nxrg
    936                 copied = nxr
    9371040             ENDIF
    9381041
    939               DO  i = ss, ee
    940                 DO  j = nysg, nyng
    941                    DO  k = nzb+1, nzt
    942                       flag = MERGE( 1.0_wp, 0.0_wp,                            &
    943                                     BTEST( wall_flags_0(k,j,i), 0 ) )
    944                      cs_3d(k,j,i) = cs_3d(k,j,copied) * flag
    945                    ENDDO
    946                 ENDDO
    947              ENDDO
    948 
    949           ELSE
    950              WRITE(message_string,*)                                           &
    951                                  'unknown decycling method: decycle_method (', &
    952                      boundary, ') ="' // TRIM( decycle_method(boundary) ) // '"'
    953              CALL message( 'chem_boundary_conds_decycle', 'CM0431',           &
    954                            1, 2, 0, 6, 0 )
    9551042          ENDIF
     1043
     1044          lsp_usr = lsp_usr + 1
     1045
    9561046       ENDDO
    957     ENDIF
    958 !
    959 !-- South and north boundaries
    960     IF ( decycle_chem_ns  .AND.  bc_ns_cyc )  THEN
    961 
    962        DO  boundary = 3, 4
    963 
    964           IF ( decycle_method(boundary) == 'dirichlet' )  THEN
    965 !   
    966 !--          Initial profile is copied to ghost and first three layers         
    967              ss = 1
    968              ee = 0
    969              IF ( boundary == 3  .AND.  nys == 0 )  THEN
    970                 ss = nysg
    971                 ee = nys+2
    972              ELSEIF ( boundary == 4  .AND.  nyn == ny )  THEN
    973                 ss = nyn-2
    974                 ee = nyng
    975              ENDIF
    976 
    977              DO  i = nxlg, nxrg
    978                 DO  j = ss, ee
    979                    DO  k = nzb+1, nzt
    980                       flag = MERGE( 1.0_wp, 0.0_wp,                            &
    981                                     BTEST( wall_flags_0(k,j,i), 0 ) )
    982                       cs_3d(k,j,i) = cs_pr_init(k) * flag
    983                    ENDDO
    984                 ENDDO
    985              ENDDO
    986 
    987 
    988         ELSEIF ( decycle_method(boundary) == 'neumann' )  THEN
    989 !
    990 !--          The value at the boundary is copied to the ghost layers to simulate
    991 !--          an outlet with zero gradient
    992              ss = 1
    993              ee = 0
    994              IF ( boundary == 3  .AND.  nys == 0 )  THEN
    995                 ss = nysg
    996                 ee = nys-1
    997                 copied = nys
    998              ELSEIF ( boundary == 4  .AND.  nyn == ny )  THEN
    999                 ss = nyn+1
    1000                 ee = nyng
    1001                 copied = nyn
    1002              ENDIF
    1003 
    1004               DO  i = nxlg, nxrg
    1005                 DO  j = ss, ee
    1006                    DO  k = nzb+1, nzt
    1007                       flag = MERGE( 1.0_wp, 0.0_wp,                            &
    1008                                     BTEST( wall_flags_0(k,j,i), 0 ) )
    1009                       cs_3d(k,j,i) = cs_3d(k,copied,i) * flag
    1010                    ENDDO
    1011                 ENDDO
    1012              ENDDO
    1013 
    1014           ELSE
    1015              WRITE(message_string,*)                                           &
    1016                                  'unknown decycling method: decycle_method (', &
    1017                      boundary, ') ="' // TRIM( decycle_method(boundary) ) // '"'
    1018              CALL message( 'chem_boundary_conds_decycle', 'CM0432',           &
    1019                            1, 2, 0, 6, 0 )
    1020           ENDIF
    1021        ENDDO
    1022     ENDIF
     1047
     1048    ENDDO
     1049
     1050    CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'stop' )
     1051
    10231052 END SUBROUTINE chem_boundary_conds_decycle
    10241053
  • palm/trunk/SOURCE/prognostic_equations.f90

    r3878 r3879  
    4141!
    4242! 3840 2019-03-29 10:35:52Z knoop
    43 ! added USE chem_gasphase_mod for nvar, nspec and spc_names
     43! added USE chem_gasphase_mod for nspec, nspec and spc_names
    4444!
    4545! 3820 2019-03-27 11:53:41Z forkel
     
    388388
    389389    USE chem_modules,                                                          &
    390         ONLY:  call_chem_at_all_substeps, chem_gasphase_on, cs_name,           &
    391                deposition_dry, chem_species
     390        ONLY:  chem_gasphase_on, deposition_dry, chem_species
    392391
    393392    USE chem_gasphase_mod,                                                     &
    394         ONLY:  nspec, nvar, spc_names
     393        ONLY:  nspec, spc_names
    395394
    396395    USE chemistry_model_mod,                                                   &
    397         ONLY:  chem_boundary_conds, chem_prognostic_equations
     396        ONLY:  chem_boundary_conds_decycle, chem_prognostic_equations
    398397
    399398    USE control_parameters,                                                    &
     
    520519    LOGICAL      ::  loop_start          !<
    521520    INTEGER(iwp) ::  lsp
    522     INTEGER(iwp) ::  lsp_usr             !< lsp running index for chem spcs
    523521
    524522
     
    538536    !$OMP END PARALLEL
    539537
    540     IF ( air_chemistry )  THEN
    541 !
    542 !--    Loop over chemical species       
    543        CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'start' )
    544        DO  lsp = 1, nspec
    545           CALL exchange_horiz( chem_species(lsp)%conc, nbgp )   
    546           lsp_usr = 1 
    547           DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
    548              IF ( TRIM(chem_species(lsp)%name) == TRIM(cs_name(lsp_usr)) )  THEN
    549 
    550                 CALL chem_boundary_conds( chem_species(lsp)%conc_p,                                 &
    551                                           chem_species(lsp)%conc_pr_init )
    552              
    553              ENDIF
    554              lsp_usr = lsp_usr +1
    555           ENDDO
    556 
    557 
    558        ENDDO
    559        CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'stop' )
    560 
    561     ENDIF
     538    IF ( air_chemistry )  CALL chem_boundary_conds_decycle
    562539!
    563540!-- Run SALSA and aerosol dynamic processes. SALSA is run with a longer time
     
    11421119!
    11431120!--          Loop over chemical species
    1144              DO  lsp = 1, nvar                         
     1121             DO  lsp = 1, nspec
    11451122                CALL chem_prognostic_equations( chem_species(lsp)%conc_p,      &
    11461123                                     chem_species(lsp)%conc,                   &
     
    19241901!
    19251902!--    Loop over chemical species
    1926        DO  lsp = 1, nvar                         
     1903       DO  lsp = 1, nspec
    19271904          CALL chem_prognostic_equations( chem_species(lsp)%conc_p,            &
    19281905                                          chem_species(lsp)%conc,              &
  • palm/trunk/SOURCE/time_integration.f90

    r3876 r3879  
    3838!
    3939! 3833 2019-03-28 15:04:04Z forkel
    40 ! added USE chem_gasphase_mod, replaced nspec by nvar since fixed compounds are not integrated
     40! added USE chem_gasphase_mod, replaced nspec by nspec since fixed compounds are not integrated
    4141!
    4242! 3820 2019-03-27 11:53:41Z forkel
     
    506506
    507507    USE chem_gasphase_mod,                                                                         &
    508         ONLY:  nvar
     508        ONLY:  nspec
    509509
    510510    USE chem_modules,                                                                              &
    511         ONLY:  bc_cs_t_val, cs_name, emissions_anthropogenic, nspec_out, chem_species
     511        ONLY:  bc_cs_t_val, emissions_anthropogenic, nspec_out, chem_species
    512512
    513513    USE chemistry_model_mod,                                                                       &
    514         ONLY:  chem_boundary_conds
     514        ONLY:  chem_boundary_conds_decycle
    515515
    516516    USE control_parameters,                                                                        &
     
    680680    INTEGER(iwp)      ::  icc       !< additional index for aerosol mass bins
    681681    INTEGER(iwp)      ::  ig        !< index for salsa gases
    682     INTEGER(iwp)      ::  lsp
    683     INTEGER(iwp)      ::  lsp_usr   !<
    684682    INTEGER(iwp)      ::  n         !< loop counter for chemistry species
    685683
     
    859857           bc_q_t_val  = ( q_init(nzt+1) - q_init(nzt) ) / dzu(nzt+1)
    860858           IF ( air_chemistry )  THEN
    861               DO  lsp = 1, nvar
    862                  bc_cs_t_val = (  chem_species(lsp)%conc_pr_init(nzt+1)                            &
    863                                 - chem_species(lsp)%conc_pr_init(nzt) )                            &
     859              DO  n = 1, nspec
     860                 bc_cs_t_val = (  chem_species(n)%conc_pr_init(nzt+1)                            &
     861                                - chem_species(n)%conc_pr_init(nzt) )                            &
    864862                               / dzu(nzt+1)
    865863              ENDDO
     
    10361034          ENDIF
    10371035          IF ( passive_scalar )  CALL exchange_horiz( s_p, nbgp )
    1038           IF ( air_chemistry )  THEN
    1039              DO  lsp = 1, nvar
    1040                 CALL exchange_horiz( chem_species(lsp)%conc_p, nbgp )
    1041 !
    1042 !--             kanani: Push chem_boundary_conds after CALL boundary_conds
    1043                 lsp_usr = 1
    1044                 DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
    1045                    IF ( TRIM(chem_species(lsp)%name) == TRIM(cs_name(lsp_usr)) )  THEN
    1046                       CALL chem_boundary_conds( chem_species(lsp)%conc_p,                          &
    1047                                                 chem_species(lsp)%conc_pr_init )
    1048                    ENDIF
    1049                    lsp_usr = lsp_usr + 1
    1050                 ENDDO
    1051              ENDDO
    1052           ENDIF
     1036          IF ( air_chemistry  )  CALL chem_boundary_conds_decycle
    10531037
    10541038          IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
     
    11331117
    11341118                IF ( air_chemistry )  THEN
    1135                    DO  n = 1, nvar     
     1119                   DO  n = 1, nspec
    11361120                      CALL exchange_horiz( chem_species(n)%conc, nbgp )
    11371121                   ENDDO
Note: See TracChangeset for help on using the changeset viewer.