Ignore:
Timestamp:
May 7, 2019 12:32:52 PM (5 years ago)
Author:
monakurppa
Message:

Remove salsa calls from prognostic_equations and correct a bug in the salsa deposition for urban and land surface models

File:
1 edited

Legend:

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

    r3931 r3956  
    2525! -----------------
    2626! $Id$
     27! Removed salsa calls.
     28!
     29! 3931 2019-04-24 16:34:28Z schwenkel
    2730! Correct/complete module_interface introduction for chemistry model
    2831!
     
    464467#endif
    465468
    466     USE salsa_mod,                                                             &
    467         ONLY:  aerosol_mass, aerosol_number, dt_salsa, last_salsa_time,        &
    468                nbins_aerosol, ncomponents_mass, ngases_salsa,                  &
    469                salsa_boundary_conds, salsa_diagnostics, salsa_driver,          &
    470                salsa_gas, salsa_gases_from_chem, skip_time_do_salsa
    471 
    472469    USE statistics,                                                            &
    473470        ONLY:  hom
     
    518515    INTEGER(iwp) ::  i                   !<
    519516    INTEGER(iwp) ::  i_omp_start         !<
    520     INTEGER(iwp) ::  ib                  !< index for aerosol size bins (salsa)
    521     INTEGER(iwp) ::  ic                  !< index for chemical compounds (salsa)
    522     INTEGER(iwp) ::  icc                 !< additional index for chemical compounds (salsa)
    523     INTEGER(iwp) ::  ig                  !< index for gaseous compounds (salsa)
    524517    INTEGER(iwp) ::  j                   !<
    525518    INTEGER(iwp) ::  k                   !<
     
    550543!
    551544!-- Module Inferface for exchange horiz after non_advective_processes but before
    552 !-- advection. Therefore, non_advective_processes must not run for ghost points.
     545!-- advection. Therefore, non_advective_processes must not run for ghost points.
     546    !$OMP END PARALLEL
    553547    CALL module_interface_exchange_horiz()
    554     !$OMP END PARALLEL
    555 
    556 !
    557 !-- Run SALSA and aerosol dynamic processes. SALSA is run with a longer time
    558 !-- step. The exchange of ghost points is required after this update of the
    559 !-- concentrations of aerosol number and mass
    560     IF ( salsa )  THEN
    561 
    562        IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
    563           IF ( ( time_since_reference_point - last_salsa_time ) >= dt_salsa )  &
    564           THEN
    565              CALL cpu_log( log_point_s(90), 'salsa processes ', 'start' )
    566              !$OMP PARALLEL PRIVATE (i,j)
    567 !
    568 !--          Call salsa processes
    569              !$OMP DO
    570              DO  i = nxl, nxr
    571                 DO  j = nys, nyn
    572                    CALL salsa_diagnostics( i, j )
    573                    CALL salsa_driver( i, j, 3 )
    574                    CALL salsa_diagnostics( i, j )
    575                 ENDDO
    576              ENDDO
    577              !$OMP END PARALLEL
    578 
    579              CALL cpu_log( log_point_s(90), 'salsa processes ', 'stop' )
    580 
    581              CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'start' )
    582 !
    583 !--          Exchange ghost points and decycle if needed.
    584              DO  ib = 1, nbins_aerosol
    585                 CALL exchange_horiz( aerosol_number(ib)%conc, nbgp )
    586                 CALL salsa_boundary_conds( aerosol_number(ib)%conc,            &
    587                                            aerosol_number(ib)%init )
    588                 DO  ic = 1, ncomponents_mass
    589                    icc = ( ic - 1 ) * nbins_aerosol + ib
    590                    CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp )
    591                    CALL salsa_boundary_conds( aerosol_mass(icc)%conc,          &
    592                                               aerosol_mass(icc)%init )
    593                 ENDDO
    594              ENDDO
    595 
    596              IF ( .NOT. salsa_gases_from_chem )  THEN
    597                 DO  ig = 1, ngases_salsa
    598                    CALL exchange_horiz( salsa_gas(ig)%conc, nbgp )
    599                    CALL salsa_boundary_conds( salsa_gas(ig)%conc,              &
    600                                               salsa_gas(ig)%init )
    601                 ENDDO
    602              ENDIF
    603              CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'stop' )
    604              last_salsa_time = time_since_reference_point
    605 
    606           ENDIF
    607 
    608        ENDIF
    609 
    610     ENDIF
    611 
    612548!
    613549!-- Loop over all prognostic equations
     
    11531089
    11541090    INTEGER(iwp) ::  i     !<
    1155     INTEGER(iwp) ::  ib    !< index for aerosol size bins (salsa)
    1156     INTEGER(iwp) ::  ic    !< index for chemical compounds (salsa)
    1157     INTEGER(iwp) ::  icc   !< additional index for chemical compounds (salsa)
    1158     INTEGER(iwp) ::  ig    !< index for gaseous compounds (salsa)
    11591091    INTEGER(iwp) ::  j     !<
    11601092    INTEGER(iwp) ::  k     !<
     
    11681100    ENDIF
    11691101!
    1170 !-- Run SALSA and aerosol dynamic processes. SALSA is run with a longer time
    1171 !-- step. The exchange of ghost points is required after this update of the
    1172 !-- concentrations of aerosol number and mass
    1173     IF ( salsa )  THEN
    1174        IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
    1175           IF ( ( time_since_reference_point - last_salsa_time ) >= dt_salsa )  &
    1176           THEN
    1177              CALL cpu_log( log_point_s(90), 'salsa processes ', 'start' )
    1178              !$OMP PARALLEL PRIVATE (i,j)
    1179              !$OMP DO
    1180 !
    1181 !--          Call salsa processes
    1182              DO  i = nxl, nxr
    1183                 DO  j = nys, nyn
    1184                    CALL salsa_diagnostics( i, j )
    1185                    CALL salsa_driver( i, j, 3 )
    1186                    CALL salsa_diagnostics( i, j )
    1187                 ENDDO
    1188              ENDDO
    1189              !$OMP END PARALLEL
    1190 
    1191              CALL cpu_log( log_point_s(90), 'salsa processes ', 'stop' )
    1192              CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'start' )
    1193 !
    1194 !--          Exchange ghost points and decycle if needed.
    1195              DO  ib = 1, nbins_aerosol
    1196                 CALL exchange_horiz( aerosol_number(ib)%conc, nbgp )
    1197                 CALL salsa_boundary_conds( aerosol_number(ib)%conc,            &
    1198                                            aerosol_number(ib)%init )
    1199                 DO  ic = 1, ncomponents_mass
    1200                    icc = ( ic - 1 ) * nbins_aerosol + ib
    1201                    CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp )
    1202                    CALL salsa_boundary_conds( aerosol_mass(icc)%conc,          &
    1203                                               aerosol_mass(icc)%init )
    1204                 ENDDO
    1205              ENDDO
    1206              IF ( .NOT. salsa_gases_from_chem )  THEN
    1207                 DO  ig = 1, ngases_salsa
    1208                    CALL exchange_horiz( salsa_gas(ig)%conc, nbgp )
    1209                    CALL salsa_boundary_conds( salsa_gas(ig)%conc,              &
    1210                                               salsa_gas(ig)%init )
    1211                 ENDDO
    1212              ENDIF
    1213              CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'stop' )
    1214              last_salsa_time = time_since_reference_point
    1215           ENDIF
    1216        ENDIF
    1217     ENDIF
    1218 
    1219 !
    12201102!-- Calculate non advective processes for all other modules
    12211103    CALL module_interface_non_advective_processes
    12221104!
    12231105!-- Module Inferface for exchange horiz after non_advective_processes but before
    1224 !-- advection. Therefore, non_advective_processes must not run for ghost points.     
     1106!-- advection. Therefore, non_advective_processes must not run for ghost points.
    12251107    CALL module_interface_exchange_horiz()
    1226    
    12271108!
    12281109!-- u-velocity component
Note: See TracChangeset for help on using the changeset viewer.