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

    r5646 r5828  
    11! $Id$
    22MODULE lmdz_cloud_optics_prop
     3  PRIVATE
     4
     5  LOGICAL, SAVE :: first_first = .TRUE.
     6  !$OMP THREADPRIVATE(first_first)
     7
     8  PUBLIC cloud_optics_prop, cloud_optics_prop_post
    39
    410CONTAINS
     11
     12SUBROUTINE cloud_optics_prop_post()
     13  USE lmdz_cloud_optics_prop_ini, ONLY: novlp
     14  USE lmdz_cloud_optics_prop_ini, ONLY: first
     15  IMPLICIT NONE
     16
     17  IF (first_first) THEN
     18    IF (ANY(first)) THEN
     19      IF (novlp==1) THEN
     20        WRITE (*, *) 'Hypothese de recouvrement: MAXIMUM_ &
     21                &                                             &
     22                &                                          RANDOM'
     23        first_first = .FALSE.
     24      ELSEIF (novlp==2) THEN
     25        WRITE (*, *) 'Hypothese de recouvrement: MAXIMUM'
     26        first_first = .FALSE.
     27      ELSEIF (novlp==3) THEN
     28        WRITE (*, *) 'Hypothese de recouvrement: RANDOM'
     29        first_first = .FALSE.
     30      ENDIF
     31    ENDIF
     32  ENDIF
     33
     34END SUBROUTINE cloud_optics_prop_post
    535
    636SUBROUTINE cloud_optics_prop(klon, klev, paprs, pplay, temp, radocond, picefra, pclc, &
     
    2959  USE lmdz_cloud_optics_prop_ini , ONLY : rei_coef, rei_min_temp
    3060  USE lmdz_cloud_optics_prop_ini , ONLY : zepsec, novlp, iflag_ice_thermo, ok_new_lscp
     61  USE lmdz_cloud_optics_prop_ini , ONLY : first
    3162 
    3263
     
    115146  ! Local variables
    116147  !----------------
    117 
    118   LOGICAL, SAVE :: first = .TRUE.
    119   !$OMP THREADPRIVATE(first)
    120148  INTEGER flag_max
    121149
     
    652680
    653681          IF (novlp.EQ.2) THEN
    654             IF (first) THEN
    655               WRITE (*, *) 'Hypothese de recouvrement: MAXIMUM'
    656               first = .FALSE.
     682            IF (first_first) THEN
     683              first(i,k) = .TRUE.
    657684            ENDIF
    658685            flag_max = -1.
     
    661688
    662689          IF (novlp.EQ.3) THEN
    663             IF (first) THEN
    664               WRITE (*, *) 'Hypothese de recouvrement: RANDOM'
    665               first = .FALSE.
     690            IF (first_first) THEN
     691              first(i,k) = .TRUE.
    666692            ENDIF
    667693            flag_max = 1.
     
    670696
    671697          IF (novlp.EQ.1) THEN
    672             IF (first) THEN
    673               WRITE (*, *) 'Hypothese de recouvrement: MAXIMUM_ &
    674                 &                                             &
    675                 &                                          RANDOM'
    676               first = .FALSE.
     698            IF (first_first) THEN
     699              first(i,k) = .TRUE.
    677700            ENDIF
    678701            flag_max = 1.
     
    767790  ENDIF !ok_cdnc
    768791
    769   first=.false. !to be sure
    770 
    771792  RETURN
    772793
Note: See TracChangeset for help on using the changeset viewer.