fftpack Module



Contents


Interfaces

interface

  • public pure subroutine dcosqb(n, x, wsave)

    Unnormalized inverse of dcosqf. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    real(kind=rk), intent(inout) :: x(*)
    real(kind=rk), intent(in) :: wsave(*)

interface

  • public pure subroutine dcosqf(n, x, wsave)

    Forward transform of quarter wave data. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    real(kind=rk), intent(inout) :: x(*)
    real(kind=rk), intent(in) :: wsave(*)

interface

  • public pure subroutine dcosqi(n, wsave)

    Initialize dcosqf and dcosqb. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    real(kind=rk), intent(out) :: wsave(*)

interface

  • public pure subroutine dcost(n, x, wsave)

    Discrete fourier cosine transform of an even sequence. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    real(kind=rk), intent(inout) :: x(*)
    real(kind=rk), intent(in) :: wsave(*)

interface

  • public pure subroutine dcosti(n, wsave)

    Initialize dcost. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    real(kind=rk), intent(out) :: wsave(*)

public interface dct

Dsicrete cosine transforms. (Specification)

  • private pure module function dct_rk(x, n, type) result(result)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=rk), intent(in) :: x(:)
    integer, intent(in), optional :: n
    integer, intent(in), optional :: type

    Return Value real(kind=rk), allocatable, (:)

public interface dct_t1

Perform DCT type-1 (Specification)

  • public interface dcost()

    Arguments

    None

public interface dct_t1i

Initialize DCT type-1 (Specification)

  • public interface dcosti()

    Arguments

    None

public interface dct_t2

Perform DCT type-2 (Specification)

  • public interface dcosqb()

    Arguments

    None

public interface dct_t23i

Initialize DCT types 2, 3 (Specification)

  • public interface dcosqi()

    Arguments

    None

public interface dct_t3

Perform DCT type-3 (Specification)

  • public interface dcosqf()

    Arguments

    None

interface

  • public pure subroutine dfftb(n, r, wsave)

    Unnormalized inverse of dfftf. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    real(kind=rk), intent(inout) :: r(*)
    real(kind=rk), intent(in) :: wsave(*)

interface

  • public pure subroutine dfftf(n, r, wsave)

    Forward transform of a real periodic sequence. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    real(kind=rk), intent(inout) :: r(*)
    real(kind=rk), intent(in) :: wsave(*)

interface

  • public pure subroutine dffti(n, wsave)

    Initialize dfftf and dfftb. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    real(kind=rk), intent(out) :: wsave(*)

interface

  • public pure subroutine dzfftb(n, r, azero, a, b, wsave)

    Unnormalized inverse of dzfftf. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    real(kind=rk), intent(out) :: r(*)
    real(kind=rk), intent(in) :: azero
    real(kind=rk), intent(in) :: a(*)
    real(kind=rk), intent(in) :: b(*)
    real(kind=rk), intent(in) :: wsave(*)

interface

  • public pure subroutine dzfftf(n, r, azero, a, b, wsave)

    Simplified forward transform of a real periodic sequence. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    real(kind=rk), intent(in) :: r(*)
    real(kind=rk), intent(out) :: azero
    real(kind=rk), intent(out) :: a(*)
    real(kind=rk), intent(out) :: b(*)
    real(kind=rk), intent(in) :: wsave(*)

interface

  • public pure subroutine dzffti(n, wsave)

    Initialize dzfftf and dzfftb. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    real(kind=rk), intent(out) :: wsave(*)

public interface fft

Forward transform of a complex periodic sequence. (Specifiction)

  • private pure module function fft_rk(x, n) result(result)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=rk), intent(in) :: x(:)
    integer, intent(in), optional :: n

    Return Value complex(kind=rk), allocatable, (:)

interface

  • public pure module function fftfreq(n) result(out)

    Integer frequency values involved in complex FFT. (Specifiction)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n

    Return Value integer, dimension(n)

public interface fftshift

Shifts zero-frequency component to center of spectrum. (Specifiction)

  • private pure module function fftshift_crk(x) result(result)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=rk), intent(in) :: x(:)

    Return Value complex(kind=rk), dimension(size(x))

  • private pure module function fftshift_rrk(x) result(result)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=rk), intent(in) :: x(:)

    Return Value real(kind=rk), dimension(size(x))

public interface idct

Inverse discrete cosine transforms. (Specification)

  • private pure module function idct_rk(x, n, type) result(result)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=rk), intent(in) :: x(:)
    integer, intent(in), optional :: n
    integer, intent(in), optional :: type

    Return Value real(kind=rk), allocatable, (:)

public interface ifft

Backward transform of a complex periodic sequence. (Specifiction)

  • private pure module function ifft_rk(x, n) result(result)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=rk), intent(in) :: x(:)
    integer, intent(in), optional :: n

    Return Value complex(kind=rk), allocatable, (:)

public interface ifftshift

Shifts zero-frequency component to beginning of spectrum. (Specifiction)

  • private pure module function ifftshift_crk(x) result(result)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=rk), intent(in) :: x(:)

    Return Value complex(kind=rk), dimension(size(x))

  • private pure module function ifftshift_rrk(x) result(result)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=rk), intent(in) :: x(:)

    Return Value real(kind=rk), dimension(size(x))

public interface irfft

Backward transform of a real periodic sequence. (Specifiction)

  • private pure module function irfft_rk(x, n) result(result)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=rk), intent(in) :: x(:)
    integer, intent(in), optional :: n

    Return Value real(kind=rk), allocatable, (:)

public interface rfft

Forward transform of a real periodic sequence. (Specifiction)

  • private pure module function rfft_rk(x, n) result(result)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=rk), intent(in) :: x(:)
    integer, intent(in), optional :: n

    Return Value real(kind=rk), allocatable, (:)

interface

  • public pure module function rfftfreq(n) result(out)

    Integer frequency values involved in real FFT. (Specifiction)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n

    Return Value integer, dimension(n)

interface

  • public pure subroutine zfftb(n, c, wsave)

    Unnormalized inverse of zfftf. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    complex(kind=rk), intent(inout) :: c(*)
    real(kind=rk), intent(in) :: wsave(*)

interface

  • public pure subroutine zfftf(n, c, wsave)

    Forward transform of a complex periodic sequence. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    complex(kind=rk), intent(inout) :: c(*)
    real(kind=rk), intent(in) :: wsave(*)

interface

  • public pure subroutine zffti(n, wsave)

    Initialize zfftf and zfftb. (Specification)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    real(kind=rk), intent(out) :: wsave(*)