dcosqi Subroutine

subroutine dcosqi(n, Wsave)

Arguments

Type IntentOptional Attributes Name
integer :: n
real(kind=rk) :: Wsave

Contents

Source Code


Variables

Type Visibility Attributes Name Initial
real(kind=rk), public :: dt
real(kind=rk), public :: fk
integer, public :: k
real(kind=rk), public, parameter :: pih = acos(-1.0_rk)/2.0_rk

Source Code

      subroutine dcosqi(n,Wsave)
      use fftpack_kind
      implicit none
      real(rk) :: dt , fk , Wsave
      integer :: k , n
      dimension Wsave(*)
      real(rk),parameter :: pih = acos(-1.0_rk) / 2.0_rk ! pi / 2
      dt = pih/real(n, rk)
      fk = 0.0_rk
      do k = 1 , n
         fk = fk + 1.0_rk
         Wsave(k) = cos(fk*dt)
      enddo
      call dffti(n,Wsave(n+1))
      end subroutine dcosqi