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

    r5305 r5828  
    11! $Id$
     2MODULE nuage_mod
     3  PRIVATE
     4
     5  PUBLIC nuage, diagcld1, diagcld2
     6
     7  CONTAINS
    28
    39SUBROUTINE nuage(paprs, pplay, t, pqlwp,picefra, pclc, pcltau, pclemi, pch, pcl, pcm, &
     
    95101  REAL cldtaupi(klon, klev) ! pre-industrial cloud opt thickness for diag
    96102  REAl dzfice(klon)
     103  REAL :: pp_ratio(klon)
    97104  ! jq-end
    98105
     
    115122            CALL icefrac_lscp(klon,t(:,k),iflag_ice_thermo,distcltop(:,k),temp_cltop(:,k),zfice(:),dzfice(:))
    116123        ELSE
    117             CALL icefrac_lsc(klon,t(:,k),pplay(:,k)/paprs(:,1),zfice(:))
     124            pp_ratio(1:klon) = pplay(1:klon,k)/paprs(1:klon,1)
     125            CALL icefrac_lsc(klon,t(:,k),pp_ratio(:),zfice(:))
    118126
    119127        ENDIF
     
    257265  RETURN
    258266END SUBROUTINE nuage
     267
    259268SUBROUTINE diagcld1(paprs, pplay, rain, snow, kbot, ktop, diafra, dialiq)
    260269  USE dimphy
     
    340349  RETURN
    341350END SUBROUTINE diagcld1
     351
    342352SUBROUTINE diagcld2(paprs, pplay, t, q, diafra, dialiq)
    343353  USE dimphy
     
    431441  RETURN
    432442END SUBROUTINE diagcld2
     443
     444END MODULE nuage_mod
Note: See TracChangeset for help on using the changeset viewer.