Ignore:
Timestamp:
Jul 15, 2020, 10:14:37 PM (5 years ago)
Author:
adurocher
Message:

Use cvl_comp_threshold to control whether to use compression or not

cvl_comp_threshold now defaults to 0 (never compress)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Optimisation_LMDZ/libf/phylmd/cv3a_driver.f90

    r3764 r3765  
    141141  SUBROUTINE cv3a_driver(len, nd, ndp1, ntra, nloc, k_upper, &
    142142                         iflag_con, iflag_mix, iflag_ice_thermo, iflag_clos, ok_conserv_q, &
    143                          delt, &
     143                         delt, comp_threshold, &
    144144                         t1, q1, qs1, t1_wake, q1_wake, qs1_wake, s1_wake, &
    145145                         u1, v1, &
     
    181181    REAL, INTENT(IN)                                  :: coefw_cld_cv ! coefficient for updraft velocity in convection
    182182    REAL, INTENT(IN)                                  :: delt ! time step
     183    REAL, INTENT (IN)                                 :: comp_threshold
    183184    REAL, DIMENSION(len, nd), INTENT(IN)             :: t1 ! temperature (sat draught envt)
    184185    REAL, DIMENSION(len, nd), INTENT(IN)             :: q1 ! specific hum (sat draught envt)
     
    406407! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
    407408
    408     compress = .false.
     409    ! Compression has 3 possible modes:
     410    ! 1) Compress = true :
     411    compress_mode = COMPRESS_MODE_COMPRESS ! 1.1) Copy convective cells in contiguous array
     412    !compress_mode = COMPRESS_MODE_COPY ! 1.2) Copy all cells and also compute on non-convective cells
     413    ! 2) Compress = false : Don't copy and use original arrays, compute on non-convective cells
     414    ! Never compress when comp_threshold = 0, always compress when comp_threshold = 1
     415    ! comp_threshold = 0 (default) offers best performance when using many CPUs
     416    compress = (comp_threshold == 1) .or. ( get_compress_size(len, (iflag1(:) == 0)) < len*comp_threshold )
     417
    409418    if (compress) then
    410       compress_mode = COMPRESS_MODE_COMPRESS
    411       !compress_mode = COMPRESS_MODE_COPY
    412 
    413419      nloc = get_compress_size(len, (iflag1(:) == 0))
    414420
Note: See TracChangeset for help on using the changeset viewer.