Ignore:
Timestamp:
Oct 7, 2020 1:25:11 PM (4 years ago)
Author:
schwenkel
Message:

Move exchange_horiz from time_integration to modules

File:
1 edited

Legend:

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

    r4671 r4731  
    2424! -----------------
    2525! $Id$
     26! Move exchange_horiz from time_integration to modules
     27!
     28! 4671 2020-09-09 20:27:58Z pavelkrc
    2629! Implementation of downward facing USM and LSM surfaces
    2730!
     
    14701473! Description:
    14711474! ------------
    1472 !> Control of microphysics for all grid points
    1473 !--------------------------------------------------------------------------------------------------!
    1474     SUBROUTINE bcm_exchange_horiz
     1475!> Exchange ghostpoints
     1476!--------------------------------------------------------------------------------------------------!
     1477    SUBROUTINE bcm_exchange_horiz( location )
    14751478
    14761479       USE exchange_horiz_mod,                                                                     &
    14771480           ONLY:  exchange_horiz
    14781481
    1479 
    1480        IF ( .NOT. microphysics_sat_adjust  .AND.  ( intermediate_timestep_count == 1  .OR.         &
    1481             call_microphysics_at_all_substeps ) )                                                  &
    1482        THEN
    1483           IF ( microphysics_morrison )  THEN
    1484              CALL exchange_horiz( nc, nbgp )
    1485              CALL exchange_horiz( qc, nbgp )
    1486           ENDIF
    1487           IF ( microphysics_seifert ) THEN
    1488              CALL exchange_horiz( qr, nbgp )
    1489              CALL exchange_horiz( nr, nbgp )
    1490           ENDIF
    1491           IF ( microphysics_ice_phase ) THEN
    1492              CALL exchange_horiz( qi, nbgp )
    1493              CALL exchange_horiz( ni, nbgp )
    1494           ENDIF
    1495           CALL exchange_horiz( q, nbgp )
    1496           CALL exchange_horiz( pt, nbgp )
    1497        ENDIF
    1498 
     1482       CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
     1483
     1484       SELECT CASE ( location )
     1485
     1486          CASE ( 'before_prognostic_equation' )
     1487
     1488             IF ( .NOT. microphysics_sat_adjust  .AND.  ( intermediate_timestep_count == 1  .OR.   &
     1489                  call_microphysics_at_all_substeps ) )                                            &
     1490             THEN
     1491                IF ( microphysics_morrison )  THEN
     1492                   CALL exchange_horiz( nc, nbgp )
     1493                   CALL exchange_horiz( qc, nbgp )
     1494                ENDIF
     1495                IF ( microphysics_seifert ) THEN
     1496                   CALL exchange_horiz( qr, nbgp )
     1497                   CALL exchange_horiz( nr, nbgp )
     1498                ENDIF
     1499                IF ( microphysics_ice_phase ) THEN
     1500                   CALL exchange_horiz( qi, nbgp )
     1501                   CALL exchange_horiz( ni, nbgp )
     1502                ENDIF
     1503                CALL exchange_horiz( q, nbgp )
     1504                CALL exchange_horiz( pt, nbgp )
     1505             ENDIF
     1506
     1507          CASE ( 'after_prognostic_equation' )
     1508
     1509             IF ( collision_turbulence )  THEN
     1510                CALL exchange_horiz( diss, nbgp )
     1511             ENDIF
     1512             IF ( microphysics_morrison )  THEN
     1513                CALL exchange_horiz( qc_p, nbgp )
     1514                CALL exchange_horiz( nc_p, nbgp )
     1515             ENDIF
     1516             IF ( microphysics_seifert )  THEN
     1517                CALL exchange_horiz( qr_p, nbgp )
     1518                CALL exchange_horiz( nr_p, nbgp )
     1519             ENDIF
     1520             IF ( microphysics_ice_phase )  THEN
     1521                CALL exchange_horiz( qi_p, nbgp )
     1522                CALL exchange_horiz( ni_p, nbgp )
     1523             ENDIF
     1524
     1525          CASE ( 'after_anterpolation' )
     1526
     1527             IF ( microphysics_morrison )  THEN
     1528                CALL exchange_horiz( qc, nbgp )
     1529                CALL exchange_horiz( nc, nbgp )
     1530             ENDIF
     1531             IF ( microphysics_seifert )  THEN
     1532                CALL exchange_horiz( qr, nbgp )
     1533                CALL exchange_horiz( nr, nbgp )
     1534             ENDIF
     1535             IF ( microphysics_ice_phase )  THEN
     1536                CALL exchange_horiz( qi, nbgp )
     1537                CALL exchange_horiz( ni, nbgp )
     1538             ENDIF
     1539
     1540       END SELECT
    14991541
    15001542    END SUBROUTINE bcm_exchange_horiz
    1501 
    15021543
    15031544
Note: See TracChangeset for help on using the changeset viewer.