[Fortran] shiftl and shiftr

Hi,

I was recently implementing some functions that needed to use the Fortran intrinsics shiftl and shiftr but found out with nvfortran 23 that they are not available under the standard name, so in order to be cross-compiler compatible I had to add a pre-processing hack of the sorts:

utilities module
module utilities
    use, intrinsic :: iso_fortran_env, only: sp=>int32, dp=>int64
    implicit none
    private

#ifdef __NVCOMPILER
    interface shiftl
      module procedure shiftl_sp
      module procedure shiftl_dp
    end interface
    interface shiftr
      module procedure shiftr_sp
      module procedure shiftr_dp
    end interface
    public :: shiftl, shiftr
#endif
    
contains
 
#ifdef __NVCOMPILER
elemental integer(sp) function shiftr_sp( I , shift )
  integer(sp), intent(in) :: I 
  integer, intent(in) :: shift
  shiftr_sp = rshift( I, shift )
end function

elemental integer(dp) function shiftr_dp( I , shift )
  integer(dp), intent(in) :: I 
  integer, intent(in) :: shift
  shiftr_dp = rshift( I, shift )
end function

elemental integer(sp) function shiftl_sp( I , shift )
  integer(sp), intent(in) :: I 
  integer, intent(in) :: shift
  shiftl_sp = lshift( I, shift )
end function

elemental integer(dp) function shiftl_dp( I , shift )
  integer(dp), intent(in) :: I 
  integer, intent(in) :: shift
  shiftl_dp = lshift( I, shift )
end function
#endif
end module utilities

Just wanted to signal it, and second ask if there would be any plans on including them with the standard naming?

Thanks

Coincidently, we just had another request for this two days so we opened RFE (TPR #34649) to add the F2008 shiftr and shiftl intrinsics. Engineering is evaluating, but having two separate requests typically help bump the priority of add these types of feature requests. I’ll add your request to the RFE.

-Mat

1 Like

Thanks for the quick update!!

To complement this thread, I’m using the shiftr/shiftl among others, to work in these fast log functions:

Summary
!
! SPDX-FileCopyrightText: 2016-2022 Federico Perini <perini@wisc.edu>
!
! SPDX-License-Identifier: MIT
!
!   ***********************************************************************************************
!> @brief A module to compute FAST logarithm functions, based on Perini and Reitz, "Fast         **
!>        approximations of exponential and logarithm functions combined with efficient          **
!>        storage/retrieval for combustion kinetics calculations" Comb Flame 194(2018), 37-51.   **
!   ***********************************************************************************************
module fast_log
    use, intrinsic :: iso_fortran_env, only: dp=>real64
    use utilities
    implicit none
    private
    
    public :: flog_p3, flog_p5

    interface flog_p3
        module procedure flog_p3_dp
    end interface
    interface flog_p5
        module procedure flog_p5_dp
    end interface
    
contains

    elemental function flog_p3_dp(x) result(y)
        integer, parameter :: wp = dp
        real(wp), intent(in) :: x
        real(wp) :: y
        !-- Internal Variables
        real(wp) :: xi,xf
        integer(wp) :: iwp
        integer(wp), parameter :: mantissa_left  = 2_wp**52
        integer(wp), parameter :: mantissa       = -9218868437227405313_wp ! not(shiftl(2047_wp,52))
        integer(wp), parameter :: bias           = 1023_wp
        integer(wp), parameter :: ishift         = mantissa_left*bias

        real(wp), parameter :: log2         = log(2._wp)
        real(wp), parameter :: rlog2        = 1._wp/log2
        real(wp), parameter :: sqrt2        = sqrt(2._wp)
        real(wp), parameter :: s(3)= [rlog2,3.0_wp-2.5_wp*rlog2,1.5_wp*rlog2-2.0_wp]
        !-------------------------------------------------
        iwp = transfer(x,iwp)
        xi = shiftr(iwp,52)-bias

        ! Take mantissa part only
        xf = transfer(iand(iwp,mantissa)+ishift,xf)-1._wp

        ! Apply cubic polynomial
        xf = xf*(s(1)+xf*(s(2)+xf*s(3)))

        ! Compute log and Change of basis: log_2(x) -> log_e(x) = log2*log_2(x)
        y = (xf+xi)*log2

    end function flog_p3_dp

    elemental function flog_p5_dp(x) result(y)
        integer, parameter :: wp = dp
        real(wp), intent(in) :: x
        real(wp) :: y
        !-- Internal Variables
        real(wp) :: xi,xf
        integer(wp) :: iwp
        integer(wp), parameter :: mantissa_left  = 2_wp**52
        integer(wp), parameter :: mantissa       = -9218868437227405313_wp ! not(shiftl(2047_wp,52))
        integer(wp), parameter :: bias           = 1023_wp
        integer(wp), parameter :: ishift         = mantissa_left*bias

        real(wp), parameter :: log2         = log(2._wp)
        real(wp), parameter :: rlog2        = 1._wp/log2
        real(wp), parameter :: sqrt2        = sqrt(2._wp)
        real(wp), parameter :: s(5)= [ 1.44269504088896e+0_wp,&
                                      -7.21347520444482e-1_wp,&
                                       4.42145354110618e-1_wp,&
                                      -2.12375830888126e-1_wp,&
                                       4.88829563330264e-2_wp]
        !-------------------------------------------------
        iwp = transfer(x,iwp)
        xi = shiftr(iwp,52)-bias

        ! Take mantissa part only
        xf = transfer(iand(iwp,mantissa)+ishift,xf)-1._wp

        ! Apply quintic polynomial
        xf = xf*(s(1)+xf*(s(2)+xf*(s(3)+xf*(s(4)+xf*s(5)))))

        ! Compute log and Change of basis: log_2(x) -> log_e(x) = log2*log_2(x)
        y = (xf+xi)*log2

    end function flog_p5_dp
    
end module fast_log

Here

integer(wp), parameter :: mantissa       = not(shiftl(2047_wp,52))

I get the error

NVFORTRAN-S-0155-Intrinsic not supported in initialization: not (././src/fast_log.f90: 36)
  0 inform,   0 warnings,   1 severes, 0 fatal for flog_p3_dp
NVFORTRAN-S-0155-Intrinsic not supported in initialization: not (././src/fast_log.f90: 67)
  0 inform,   0 warnings,   1 severes, 0 fatal for flog_p5_dp

So I had to define the constant -9218868437227405313_wp but enabling evaluation of intrinsic functions for declaring a parameter value is something standard with other compilers.