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/virtual_flight_mod.f90

    r3248 r3274  
    2525! -----------------
    2626! $Id$
     27! Modularization of all bulk cloud physics code components
     28!
     29! 3248 2018-09-14 09:42:06Z sward
    2730! Minor formating changes
    2831!
     
    311314    SUBROUTINE flight_init
    312315 
    313        USE constants,                                                          &
     316       USE basic_constants_and_equations_mod,                                  &
    314317           ONLY:  pi
    315318   
     
    410413   
    411414       USE control_parameters,                                                 &
    412           ONLY:  cloud_droplets, cloud_physics, humidity, neutral,             &
    413                  passive_scalar
    414          
     415          ONLY:  cloud_droplets, humidity, neutral, passive_scalar
     416
     417       USE bulk_cloud_model_mod,                                               &
     418           ONLY:  bulk_cloud_model
     419
    415420       USE netcdf_interface
    416421   
     
    441446          id_q       = num_var_fl
    442447       ENDIF
    443        IF ( cloud_physics .OR. cloud_droplets )  THEN
     448       IF ( bulk_cloud_model .OR. cloud_droplets )  THEN
    444449          num_var_fl = num_var_fl + 1 
    445450          id_ql      = num_var_fl
     
    533538
    534539       USE control_parameters,                                                 &
    535            ONLY:  cloud_droplets, cloud_physics, dt_3d, humidity, neutral,     &
     540           ONLY:  cloud_droplets, dt_3d, humidity, neutral,                    &
    536541                  passive_scalar, simulated_time
    537542                 
     
    544549       USE indices,                                                            &
    545550           ONLY:  nx, nxl, nxr, ny, nys, nyn
     551
     552       USE bulk_cloud_model_mod,                                               &
     553           ONLY:  bulk_cloud_model
    546554
    547555       USE pegrid
     
    712720!
    713721!--             Liquid water content
    714                 IF ( cloud_physics .OR. cloud_droplets )  THEN
     722                IF ( bulk_cloud_model .OR. cloud_droplets )  THEN
    715723                   CALL interpolate_xyz( ql, zu, ddzu, 1.0_wp, x, y, var_index, j, i )
    716724                   var_index = var_index + 1
Note: See TracChangeset for help on using the changeset viewer.