Changeset 4731 for palm/trunk/SOURCE/salsa_mod.f90
- Timestamp:
- Oct 7, 2020 1:25:11 PM (4 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/salsa_mod.f90
r4671 r4731 26 26 ! ----------------- 27 27 ! $Id$ 28 ! Move exchange_horiz from time_integration to modules 29 ! 30 ! 4671 2020-09-09 20:27:58Z pavelkrc 28 31 ! Implementation of downward facing USM and LSM surfaces 29 32 ! … … 8332 8335 !> Routine for exchange horiz of salsa variables. 8333 8336 !------------------------------------------------------------------------------! 8334 SUBROUTINE salsa_exchange_horiz_bounds 8337 SUBROUTINE salsa_exchange_horiz_bounds ( location ) 8335 8338 8336 8339 USE cpulog, & … … 8347 8350 INTEGER(iwp) :: ig !< 8348 8351 8349 IF ( time_since_reference_point >= skip_time_do_salsa ) THEN 8350 IF ( ( time_since_reference_point - last_salsa_time ) >= dt_salsa ) THEN 8351 8352 CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'start' ) 8353 ! 8354 !-- Exchange ghost points 8355 DO ib = 1, nbins_aerosol 8356 CALL exchange_horiz( aerosol_number(ib)%conc, nbgp, & 8357 alternative_communicator = communicator_salsa ) 8358 DO ic = 1, ncomponents_mass 8359 icc = ( ic - 1 ) * nbins_aerosol + ib 8360 CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp, & 8352 CHARACTER (LEN=*), INTENT(IN) :: location !< call location string 8353 8354 SELECT CASE ( location ) 8355 8356 CASE ( 'before_prognostic_equation' ) 8357 8358 IF ( time_since_reference_point >= skip_time_do_salsa ) THEN 8359 IF ( ( time_since_reference_point - last_salsa_time ) >= dt_salsa ) THEN 8360 8361 CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'start' ) 8362 ! 8363 !-- Exchange ghost points 8364 DO ib = 1, nbins_aerosol 8365 CALL exchange_horiz( aerosol_number(ib)%conc, nbgp, & 8366 alternative_communicator = communicator_salsa ) 8367 DO ic = 1, ncomponents_mass 8368 icc = ( ic - 1 ) * nbins_aerosol + ib 8369 CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp, & 8370 alternative_communicator = communicator_salsa ) 8371 ENDDO 8372 ENDDO 8373 IF ( .NOT. salsa_gases_from_chem ) THEN 8374 DO ig = 1, ngases_salsa 8375 CALL exchange_horiz( salsa_gas(ig)%conc, nbgp, & 8376 alternative_communicator = communicator_salsa ) 8377 ENDDO 8378 ENDIF 8379 ! 8380 !-- Apply only horizontal boundary conditions 8381 CALL salsa_boundary_conditions( horizontal_conditions_only = .TRUE. ) 8382 CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'stop' ) 8383 ! 8384 !-- Update last_salsa_time 8385 last_salsa_time = time_since_reference_point 8386 ENDIF 8387 ENDIF 8388 8389 CASE ( 'after_prognostic_equation' ) 8390 8391 IF ( salsa .AND. time_since_reference_point >= skip_time_do_salsa ) THEN 8392 DO ib = 1, nbins_aerosol 8393 CALL exchange_horiz( aerosol_number(ib)%conc_p, nbgp, & 8361 8394 alternative_communicator = communicator_salsa ) 8395 DO ic = 1, ncomponents_mass 8396 icc = ( ic - 1 ) * nbins_aerosol + ib 8397 CALL exchange_horiz( aerosol_mass(icc)%conc_p, nbgp, & 8398 alternative_communicator = communicator_salsa ) 8399 ENDDO 8362 8400 ENDDO 8363 ENDDO 8364 IF ( .NOT. salsa_gases_from_chem ) THEN 8365 DO ig = 1, ngases_salsa 8366 CALL exchange_horiz( salsa_gas(ig)%conc, nbgp, & 8401 IF ( .NOT. salsa_gases_from_chem ) THEN 8402 DO ig = 1, ngases_salsa 8403 CALL exchange_horiz( salsa_gas(ig)%conc_p, nbgp, & 8404 alternative_communicator = communicator_salsa ) 8405 ENDDO 8406 ENDIF 8407 ENDIF 8408 8409 CASE ( 'after_anterpolation' ) 8410 8411 IF ( salsa .AND. time_since_reference_point >= skip_time_do_salsa ) THEN 8412 DO ib = 1, nbins_aerosol 8413 CALL exchange_horiz( aerosol_number(ib)%conc, nbgp, & 8367 8414 alternative_communicator = communicator_salsa ) 8415 DO ic = 1, ncomponents_mass 8416 icc = ( ic - 1 ) * nbins_aerosol + ib 8417 CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp, & 8418 alternative_communicator = communicator_salsa ) 8419 ENDDO 8368 8420 ENDDO 8421 IF ( .NOT. salsa_gases_from_chem ) THEN 8422 DO ig = 1, ngases_salsa 8423 CALL exchange_horiz( salsa_gas(ig)%conc, nbgp, & 8424 alternative_communicator = communicator_salsa ) 8425 ENDDO 8426 ENDIF 8369 8427 ENDIF 8370 ! 8371 !-- Apply only horizontal boundary conditions 8372 CALL salsa_boundary_conditions( horizontal_conditions_only = .TRUE. ) 8373 CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'stop' ) 8374 ! 8375 !-- Update last_salsa_time 8376 last_salsa_time = time_since_reference_point 8377 ENDIF 8378 ENDIF 8428 8429 END SELECT 8379 8430 8380 8431 END SUBROUTINE salsa_exchange_horiz_bounds 8432 8381 8433 8382 8434 !------------------------------------------------------------------------------!
Note: See TracChangeset
for help on using the changeset viewer.