Ignore:
Timestamp:
Sep 23, 2025, 4:32:02 PM (2 months ago)
Author:
rkazeroni
Message:

For GPU porting of call_cloud_optics_prop routine:

  • Add "horizontal" comment to specify possible names of horizontal variables
  • Put routine into module (speeds up source-to-source transformation)
  • Move declaration of variable with SAVE attribute outside of the compute routine to the module
  • Record event with a 2D "first" array instead of a scalar to enable GPU porting
  • Perform reduction on this "first" array and print (once) outside of the compute routine since this cannot be done on GPU in the current form
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/lmdz_cloud_optics_prop_ini.f90

    r5646 r5828  
    3333  REAL, PARAMETER :: k_ice0=0.005 ! units=m2/g
    3434  REAL, PARAMETER :: df=1.66 ! diffusivity factor
     35  LOGICAL, SAVE, ALLOCATABLE :: first(:,:)  ! Test, if the cloud optical depth exceeds the necessary threshold
     36!$OMP THREADPRIVATE(first)
    3537!$OMP THREADPRIVATE(prt_level, lunout, flag_aerosol, iflag_t_glace)
    3638!$OMP THREADPRIVATE(iflag_rei, novlp, iflag_ice_thermo) 
     
    4547CONTAINS
    4648
    47   SUBROUTINE cloud_optics_prop_ini(klon, prt_level_in, lunout_in, flag_aerosol_in, &
     49  SUBROUTINE cloud_optics_prop_ini(klon, klev, prt_level_in, lunout_in, flag_aerosol_in, &
    4850       & ok_cdnc_in, bl95_b0_in, &
    4951       & bl95_b1_in, latitude_deg_in, rpi_in, rg_in, rd_in, zepsec_in, novlp_in, &
     
    5355
    5456    IMPLICIT NONE
    55     INTEGER, INTENT(IN) :: klon
     57    INTEGER, INTENT(IN) :: klon, klev
    5658    INTEGER, INTENT(IN) :: prt_level_in, lunout_in
    5759    INTEGER, INTENT(IN) :: flag_aerosol_in
     
    6466
    6567    ALLOCATE(latitude_deg(klon))
     68    ALLOCATE(first(klon, klev))
     69    first(:,:) = .FALSE.
    6670
    6771    prt_level = prt_level_in
Note: See TracChangeset for help on using the changeset viewer.