Ignore:
Timestamp:
Sep 24, 2025, 3:12:42 PM (2 months ago)
Author:
rkazeroni
Message:

For GPU porting of alpale_th and alpale_wk routines:

  • Put routine into module (speeds up source-to-source transformation)
  • Add "horizontal" comment to specify possible names of horizontal variables
  • Move declaration of variables with SAVE attributes from the compute routine to the module
  • Move one-time instructions (allocate, getin, print) to a dedicated routine_first
Location:
LMDZ6/trunk/libf/phylmd
Files:
3 edited

Legend:

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

    r5390 r5833  
    22! $Id$
    33!
     4!$gpum horizontal klon
     5MODULE alpale_th_mod
     6  PRIVATE
     7
     8  LOGICAL, SAVE                                              :: first = .TRUE.
     9  !$OMP THREADPRIVATE(first)
     10  LOGICAL, SAVE                                              :: multiply_proba_notrig = .FALSE.
     11  !$OMP THREADPRIVATE(multiply_proba_notrig)
     12  REAL, SAVE                                                 :: random_notrig_max=1.
     13  !$OMP THREADPRIVATE(random_notrig_max)
     14  REAL, SAVE                                                 :: cv_feed_area
     15  !$OMP THREADPRIVATE(cv_feed_area)
     16
     17  PUBLIC alpale_th, alpale_th_first
     18
     19  CONTAINS
     20
     21SUBROUTINE alpale_th_first()
     22
     23  USE alpale_mod, ONLY: iflag_clos_bl
     24  USE ioipsl_getin_p_mod, ONLY : getin_p
     25
     26  IMPLICIT NONE
     27
     28  IF (first) THEN
     29    CALL getin_p('multiply_proba_notrig',multiply_proba_notrig)
     30    IF (iflag_clos_bl .LT. 3) THEN
     31      random_notrig_max=1.
     32      CALL getin_p('random_notrig_max',random_notrig_max)
     33    ELSEIF (iflag_clos_bl .EQ. 3) THEN  ! (iflag_clos_bl .LT. 3)
     34      cv_feed_area = 1.e10   ! m2
     35      CALL getin_p('cv_feed_area', cv_feed_area)
     36    ENDIF  !! (iflag_clos_bl .LT. 3)
     37    first = .FALSE.
     38  ENDIF
     39
     40END SUBROUTINE alpale_th_first
     41
    442SUBROUTINE alpale_th ( dtime, lmax_th, t_seri, cell_area,  &
    543                       cin, s2, n2, strig,  &
     
    1856
    1957  USE dimphy
    20   USE ioipsl_getin_p_mod, ONLY : getin_p
    2158  USE print_control_mod, ONLY: mydebug=>debug , lunout, prt_level
    22   USE alpale_mod
     59  USE alpale_mod, ONLY: iflag_clos_bl, iflag_coupl, iflag_trig_bl, s_trig, tau_trig_deep, tau_trig_shallow
    2360  IMPLICIT NONE
    2461
     
    5087!----------------
    5188  INTEGER                                                    :: i
    52   LOGICAL, SAVE                                              :: first = .TRUE.
    53   LOGICAL, SAVE                                              :: multiply_proba_notrig = .FALSE.
    54   REAL, SAVE                                                 :: random_notrig_max=1.
    55   REAL, SAVE                                                 :: cv_feed_area
    5689  REAL                                                       :: birth_number
    5790  REAL, DIMENSION(klon)                                      :: ale_bl_ref
    5891  REAL, DIMENSION(klon)                                      :: tau_trig
    59 !
    60     !$OMP THREADPRIVATE(multiply_proba_notrig)
    61     !$OMP THREADPRIVATE(random_notrig_max)
    62     !$OMP THREADPRIVATE(cv_feed_area)
    63     !$OMP THREADPRIVATE(first)
    64 !
     92
    6593 REAL umexp  ! expression of (1.-exp(-x))/x valid for all x, especially when x->0
    6694 REAL x
    6795!
    68      CHARACTER (LEN=20) :: modname='alpale_th'
     96     CHARACTER (LEN=20), PARAMETER :: modname='alpale_th'
    6997     CHARACTER (LEN=80) :: abort_message
    7098     
     
    84112!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    85113!
    86 
    87     IF (first) THEN
    88       CALL getin_p('multiply_proba_notrig',multiply_proba_notrig)
    89       IF (iflag_clos_bl .LT. 3) THEN
    90          random_notrig_max=1.
    91          CALL getin_p('random_notrig_max',random_notrig_max)
    92       ELSEIF (iflag_clos_bl .EQ. 3) THEN  ! (iflag_clos_bl .LT. 3)
    93          cv_feed_area = 1.e10   ! m2
    94          CALL getin_p('cv_feed_area', cv_feed_area)
    95       ENDIF  !! (iflag_clos_bl .LT. 3)
    96       first=.FALSE.
    97     ENDIF
    98114
    99115!!
     
    344360   END SUBROUTINE alpale_th
    345361
     362END MODULE alpale_th_mod
  • LMDZ6/trunk/libf/phylmd/alpale_wk.f90

    r5274 r5833  
     1!$gpum horizontal klon
     2MODULE alpale_wk_mod
     3  PRIVATE
     4
     5  LOGICAL, SAVE                                              :: first = .TRUE.
     6  !$OMP THREADPRIVATE(first)
     7  REAL, ALLOCATABLE, SAVE, DIMENSION(:)                      :: cellrad
     8  !$OMP THREADPRIVATE(cellrad)
     9
     10  PUBLIC alpale_wk, alpale_wk_first
     11
     12  CONTAINS
     13
     14SUBROUTINE alpale_wk_first(cell_area)
     15
     16  USE dimphy, ONLY: klon
     17  USE yomcst_mod_h, ONLY: rpi
     18
     19  IMPLICIT NONE
     20  REAL, DIMENSION(klon), INTENT(IN)     :: cell_area
     21
     22  IF (first) THEN
     23    ALLOCATE (cellrad(klon))
     24  !  Compute pseudo grid-cell radius cellrad, such that pi*cellrad^2=cell_area
     25    print *,'alpale_wk: cell_area(1) ',cell_area(1)
     26    cellrad(:)=sqrt(cell_area(:)/rpi)
     27    first = .FALSE.
     28  ENDIF
     29
     30END SUBROUTINE alpale_wk_first
     31
    132SUBROUTINE alpale_wk ( dtime, cell_area, zoccur, sigmaw, wdens, fip ,  &
    233                       fip_cond)
     
    3970!----------------
    4071  INTEGER                                                    :: i
    41   LOGICAL, SAVE                                              :: first = .TRUE.
    42   !$OMP THREADPRIVATE(first)
    43   REAL, ALLOCATABLE, SAVE, DIMENSION(:)                      :: cellrad
    44   !$OMP THREADPRIVATE(cellrad)
    4572  REAL, DIMENSION(klon)                                      :: wkrad
    4673  REAL, DIMENSION(klon)                                      :: proba_gf
    47 
    48 IF (first) THEN
    49   ALLOCATE (cellrad(klon))
    50 !  Compute pseudo grid-cell radius cellrad, such that pi*cellrad^2=cell_area
    51   print *,'alpale_wk: cell_area(1) ',cell_area(1)
    52   cellrad(:)=sqrt(cell_area(:)/rpi)
    53   first = .FALSE.
    54 ENDIF
    5574
    5675!  Compute wake radius
     
    82101   END SUBROUTINE alpale_wk
    83102
     103END MODULE alpale_wk_mod
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r5828 r5833  
    2525  &      fl_ebil, fl_cor_ebil
    2626    USE ajsec_mod, ONLY: ajsec, ajsec_convv2
     27    USE alpale_th_mod, ONLY: alpale_th, alpale_th_first
     28    USE alpale_wk_mod, ONLY: alpale_wk, alpale_wk_first
    2729    USE assert_m, only: assert
    2830    USE change_srf_frac_mod
     
    36583660       IF (iflag_alp_wk_cond .GT. 0.) THEN
    36593661
     3662         CALL alpale_wk_first(cell_area)
    36603663         CALL alpale_wk(phys_tstep, cell_area, wake_k, wake_s, wake_dens, wake_fip_0, &
    36613664                        wake_fip)
     
    38443847          !
    38453848!
     3849          CALL alpale_th_first()
    38463850          CALL alpale_th( phys_tstep, lmax_th, t_seri, cell_area,  &
    38473851                          cin, s2, n2, strig, &
Note: See TracChangeset for help on using the changeset viewer.