Ignore:
Timestamp:
Apr 8, 2019 4:53:48 PM (5 years ago)
Author:
knoop
Message:

Implemented non_transport_physics module interfaces

File:
1 edited

Legend:

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

    r3872 r3874  
    2525! -----------------
    2626! $Id$
     27! Added non_transport_physics module interfaces and moved bcm code into it
     28!
     29! 3872 2019-04-08 15:03:06Z knoop
    2730! Moving prognostic equations of bcm into bulk_cloud_model_mod
    2831!
     
    378381               ug, u_init, u_p, v, vg, vpt, v_init, v_p, w, w_p
    379382
    380     USE bulk_cloud_model_mod,                                                  &
    381         ONLY:  call_microphysics_at_all_substeps, bulk_cloud_model,            &
    382                bcm_actions_micro, microphysics_sat_adjust
    383 
    384383    USE buoyancy_mod,                                                          &
    385384        ONLY:  buoyancy
     
    441440    USE module_interface,                                                      &
    442441        ONLY:  module_interface_actions, &
     442               module_interface_non_transport_physics, &
    443443               module_interface_prognostic_equations
    444444
     
    478478        ONLY:  wtm_tendencies
    479479
     480    IMPLICIT NONE
    480481
    481482    PRIVATE
     
    510511
    511512
    512     IMPLICIT NONE
    513 
    514513    INTEGER(iwp) ::  i                   !<
    515514    INTEGER(iwp) ::  i_omp_start         !<
     
    649648       ENDIF
    650649
    651     ENDIF
    652 
    653 !
    654 !-- If required, calculate cloud microphysics
    655     IF ( bulk_cloud_model  .AND.  .NOT. microphysics_sat_adjust  .AND.         &
    656          ( intermediate_timestep_count == 1  .OR.                              &
    657            call_microphysics_at_all_substeps ) )                               &
    658     THEN
    659        !$OMP PARALLEL PRIVATE (i,j)
    660        !$OMP DO
    661        DO  i = nxlg, nxrg
    662           DO  j = nysg, nyng
    663              CALL bcm_actions_micro( i, j )
    664            ENDDO
     650    ENDIF
     651
     652    !$OMP PARALLEL PRIVATE (i,j)
     653    !$OMP DO
     654    DO  i = nxlg, nxrg
     655       DO  j = nysg, nyng
     656!
     657!--       Calculate non transport physics for all other modules
     658          CALL module_interface_non_transport_physics( i, j )
    665659       ENDDO
    666        !$OMP END PARALLEL
    667     ENDIF
     660    ENDDO
     661    !$OMP END PARALLEL
    668662
    669663!
     
    12381232
    12391233
    1240     IMPLICIT NONE
    1241 
    12421234    INTEGER(iwp) ::  i     !<
    12431235    INTEGER(iwp) ::  ib    !< index for aerosol size bins (salsa)
     
    12991291          ENDIF
    13001292       ENDIF
    1301     ENDIF
    1302 
    1303 !
    1304 !-- If required, calculate cloud microphysical impacts
    1305     IF ( bulk_cloud_model  .AND.  .NOT. microphysics_sat_adjust  .AND.         &
    1306          ( intermediate_timestep_count == 1  .OR.                              &
    1307            call_microphysics_at_all_substeps )                                 &
    1308        )  THEN
    1309        CALL cpu_log( log_point(51), 'microphysics', 'start' )
    1310        CALL bcm_actions_micro
    1311        CALL cpu_log( log_point(51), 'microphysics', 'stop' )
    13121293    ENDIF
     1294
     1295!
     1296!-- Calculate non transport physics for all other modules
     1297    CALL module_interface_non_transport_physics
    13131298
    13141299!
Note: See TracChangeset for help on using the changeset viewer.