Ignore:
Timestamp:
Sep 24, 2018 3:42:55 PM (6 years ago)
Author:
knoop
Message:

Modularization of all bulk cloud physics code components

File:
1 edited

Legend:

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

    r3268 r3274  
    2525! -----------------
    2626! $Id$
     27! Modularization of all bulk cloud physics code components
     28!
     29! 3268 2018-09-21 13:45:37Z sward
    2730! Cleaned up agent pointer assignment in output routine
    2831!
     
    7780    USE, INTRINSIC ::  ISO_C_BINDING
    7881
    79     USE constants,                                                             &
     82    USE basic_constants_and_equations_mod,                                     &
    8083        ONLY:  pi
    8184
     
    26892692
    26902693       USE arrays_3d,                                                          &
    2691            ONLY:  u, v, pt, hyp
     2694           ONLY:  u, v, pt, hyp, exner
    26922695
    26932696!       USE chemistry_model_mod,                                                &
     
    27612764!
    27622765!--                Calculate temperature at agent position
    2763                    agents(nl)%t = pt(kl,jl,il) *                               &
    2764                                   ( hyp(kl) / 100000.0_wp )**0.286_wp
     2766                   agents(nl)%t = pt(kl,jl,il) * exner(kl)
    27652767! !
    27662768! !--                Get PM10 concentration at agent position, if possible
     
    41074109    SUBROUTINE mas_timestep_social_forces ( mode, nl, ip, jp )
    41084110
    4109 !       USE constants,                                                          &
    4110 !           ONLY:  pi
    4111 
    41124111       IMPLICIT NONE
    41134112
Note: See TracChangeset for help on using the changeset viewer.