Ignore:
Timestamp:
Jun 16, 2025, 7:12:42 PM (6 weeks ago)
Author:
yann meurdesoif
Message:

Convection GPU porting : Compression of active convection point is now optional (default remain to true). For GPU runs, convection is not compressed and is computed on each column. The update is done only for column where convection is active

YM

File:
1 edited

Legend:

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

    r5699 r5712  
    66  LOGICAL, SAVE :: debut = .TRUE.
    77  !$OMP THREADPRIVATE(debut)
     8  LOGICAL, SAVE :: never_compress=.FALSE.   ! if true, compression is desactivated in convection
     9  !$OMP THREADPRIVATE(never_compress)
    810
    911  PUBLIC cva_driver_pre, cva_driver_post, cva_driver
     
    3234    ! -- set simulation flags:
    3335    ! (common cvflag)
     36    never_compress = .FALSE.
     37    CALL getin_p("convection_no_compression",never_compress)
     38    IF (s2s_is_initialized()) never_compress = .TRUE.  ! for GPU, compression must be disabled
    3439    CALL cv_flag(iflag_ice_thermo)
    3540
     
    624629
    625630  INTEGER, PARAMETER                                       :: igout=1
     631  LOGICAL :: is_convect(len)   ! is convection is active on column
    626632
    627633! print *, 't1, t1_wake ',(k,t1(1,k),t1_wake(1,k),k=1,nd)
     
    878884!  gridpoints and the weights "coef_convective" (= 1. for convective gridpoints and = 0.
    879885!  elsewhere).
    880   ncum = 0
    881   coef_convective(:) = 0.
    882886  DO i = 1, len
    883887    IF (iflag1(i)==0) THEN
    884888      coef_convective(i) = 1.
    885       ncum = ncum + 1
    886       idcum(ncum) = i
     889      is_convect(i) = .TRUE.
     890    ELSE
     891      coef_convective(i) = 0.
     892      is_convect(i) = .FALSE.     
    887893    END IF
    888894  END DO
    889895
    890 ! print*,'len, ncum = ',len,ncum
     896 
     897  IF (never_compress) THEN
     898    compress = .FALSE.
     899    DO i = 1,len
     900      idcum(i) = i
     901    ENDDO
     902    ncum=len
     903  ELSE
     904    ncum = 0
     905    DO i = 1, len
     906      IF (iflag1(i)==0) THEN
     907        ncum = ncum + 1
     908        idcum(ncum) = i
     909      END IF
     910    END DO
     911   
     912    IF (ncum>0) THEN
     913!   If the fraction of convective points is larger than comp_threshold, then compression
     914!   is assumed useless.
     915      compress = ncum .lt. len*comp_threshold
     916      IF (.not. compress) THEN
     917        DO i = 1,len
     918          idcum(i) = i
     919        ENDDO
     920        ncum=len
     921      ENDIF
     922    ENDIF
     923
     924  ENDIF   
    891925
    892926  IF (ncum>0) THEN
     
    898932
    899933    IF (iflag_con==3) THEN
    900 ! print*,'ncum tv1 ',ncum,tv1
    901 ! print*,'tvp1 ',tvp1
    902 !jyg<
    903 !   If the fraction of convective points is larger than comp_threshold, then compression
    904 !   is assumed useless.
    905 !
    906   compress = ncum .lt. len*comp_threshold
    907 !
    908   IF (.not. compress) THEN
    909     DO i = 1,len
    910       idcum(i) = i
    911     ENDDO
    912   ENDIF
    913 !
    914 !>jyg
    915         if (prt_level >= 9) &
    916              PRINT *, 'cva_driver -> cv3a_compress'
     934      if (prt_level >= 9) PRINT *, 'cva_driver -> cv3a_compress'
    917935      CALL cv3a_compress(len, nloc, ncum, nd, ntra, compress, &
    918936                         iflag1, nk1, icb1, icbs1, &
     
    937955                         Ale, Alp, omega)
    938956
    939 ! print*,'tv ',tv
    940 ! print*,'tvp ',tvp
    941957
    942958    END IF
    943959
    944960    IF (iflag_con==4) THEN
    945         if (prt_level >= 9) &
    946              PRINT *, 'cva_driver -> cv_compress'
     961      if (prt_level >= 9) PRINT *, 'cva_driver -> cv_compress'
    947962      CALL cv_compress(len, nloc, ncum, nd, &
    948                        iflag1, nk1, icb1, &
     963                       iflag1, compress, nk1, icb1, &
    949964                       cbmf1, plcl1, tnk1, qnk1, gznk1, &
    950965                       t1, q1, qs1, u1, v1, gz1, &
     
    12551270        if (prt_level >= 9) &
    12561271             PRINT *, 'cva_driver -> cv3a_uncompress'
    1257       CALL cv3a_uncompress(nloc, len, ncum, nd, ntra, idcum, compress, &
     1272      CALL cv3a_uncompress(nloc, len, ncum, nd, ntra, idcum, is_convect, compress, &
    12581273                           iflag, icb, inb, &
    12591274                           precip, cbmf, plcl, plfc, wbeff, sig, w0, ptop2, &
     
    12971312        if (prt_level >= 9) &
    12981313             PRINT *, 'cva_driver -> cv_uncompress'
    1299       CALL cv_uncompress(nloc, len, ncum, nd, idcum, &
     1314      CALL cv_uncompress(nloc, len, ncum, nd, idcum, is_convect, compress, &
    13001315                           iflag, &
    13011316                           precip, cbmf, &
Note: See TracChangeset for help on using the changeset viewer.