SF_STAT Module


Uses

  • module~~sf_stat~~UsesGraph module~sf_stat SF_STAT module~sf_arrays SF_ARRAYS module~sf_stat->module~sf_arrays module~sf_integrate SF_INTEGRATE module~sf_stat->module~sf_integrate module~sf_iotools SF_IOTOOLS module~sf_stat->module~sf_iotools module~sf_linalg SF_LINALG module~sf_stat->module~sf_linalg module~gauss_quadrature GAUSS_QUADRATURE module~sf_integrate->module~gauss_quadrature module~iofile IOFILE module~sf_iotools->module~iofile module~ioplot IOPLOT module~sf_iotools->module~ioplot module~ioread IOREAD module~sf_iotools->module~ioread module~sf_blacs SF_BLACS module~sf_linalg->module~sf_blacs module~ioplot->module~iofile module~ioread->module~iofile

Used by

  • module~~sf_stat~~UsedByGraph module~sf_stat SF_STAT module~scifor SCIFOR module~scifor->module~sf_stat

Interfaces

public interface pdf_allocate

  • private subroutine pdf_allocate_1d(self, N)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
    integer :: N
  • private subroutine pdf_allocate_2d(self, Nvec)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel_2d) :: self
    integer :: Nvec(2)

public interface pdf_deallocate

  • private subroutine pdf_deallocate_1d(self)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
  • private subroutine pdf_deallocate_2d(self)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel_2d) :: self

public interface pdf_save

  • private subroutine pdf_save_1d(self, pfile)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
    character(len=*) :: pfile
  • private subroutine pdf_save_2d(self, pfile)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel_2d) :: self
    character(len=*) :: pfile

public interface pdf_read

  • private subroutine pdf_read_1d(self, pfile)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
    character(len=*) :: pfile
  • private subroutine pdf_read_2d(self, pfile)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel_2d) :: self
    character(len=*) :: pfile

public interface pdf_set_range

  • private subroutine pdf_set_range_1d(self, a, b)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
    real(kind=8) :: a
    real(kind=8) :: b
  • private subroutine pdf_set_range_2d(self, a, b)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel_2d) :: self
    real(kind=8) :: a(2)
    real(kind=8) :: b(2)

public interface pdf_push_sigma

  • private subroutine pdf_push_sigma_1d(self, sigma)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
    real(kind=8) :: sigma
  • private subroutine pdf_push_sigma_2d(self, sigma)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel_2d) :: self
    real(kind=8) :: sigma(2,2)

public interface pdf_sigma

  • private subroutine pdf_sigma_data_1d(self, data, h)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
    real(kind=8), dimension(:) :: data
    real(kind=8) :: h
  • private subroutine pdf_sigma_sdev_1d(self, sdev, N, h)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
    real(kind=8) :: sdev
    integer :: N
    real(kind=8) :: h
  • private subroutine pdf_sigma_data_2d(self, data, h)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel_2d) :: self
    real(kind=8), dimension(:,:) :: data
    real(kind=8) :: h(2,2)
  • private subroutine pdf_sigma_sdev_2d(self, sdev, Nvec, h)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel_2d) :: self
    real(kind=8) :: sdev(2)
    integer :: Nvec(2)
    real(kind=8) :: h(2,2)

public interface pdf_accumulate

  • private subroutine pdf_accumulate_s_1d(self, data, sigma)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
    real(kind=8) :: data
    real(kind=8), optional :: sigma
  • private subroutine pdf_accumulate_v_1d(self, data, sigma)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
    real(kind=8) :: data(:)
    real(kind=8), optional :: sigma
  • private subroutine pdf_accumulate_s_2d(self, data, sigma)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel_2d) :: self
    real(kind=8) :: data(2)
    real(kind=8), optional :: sigma(2,2)

public interface pdf_normalize

  • private subroutine pdf_normalize_1d(self)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
  • private subroutine pdf_normalize_2d(self)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel_2d) :: self

public interface pdf_print

  • private subroutine pdf_print_pfile_1d(self, pfile, normalize)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
    character(len=*) :: pfile
    logical, optional :: normalize
  • private subroutine pdf_print_pfile_2d(self, pfile, normalize)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel_2d) :: self
    character(len=*) :: pfile
    logical, optional :: normalize

public interface pdf_mean

  • private function pdf_mean_1d(self) result(mean)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self

    Return Value real(kind=8)

public interface pdf_var

  • private function pdf_var_1d(self) result(var)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self

    Return Value real(kind=8)

public interface pdf_sdev

  • private function pdf_sdev_1d(self) result(sdev)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self

    Return Value real(kind=8)

public interface pdf_moment

  • private function pdf_moment_1d(self, n, mu) result(mom)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
    integer :: n
    real(kind=8), optional :: mu

    Return Value real(kind=8)

public interface pdf_skew

  • private function pdf_skew_1d(self) result(skew)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self

    Return Value real(kind=8)

public interface pdf_curt

  • private function pdf_curt_1d(self) result(curt)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self

    Return Value real(kind=8)

public interface pdf_print_moments

  • private subroutine pdf_print_moments_pfile_1d(self, pfile)

    Arguments

    Type IntentOptional Attributes Name
    type(pdf_kernel) :: self
    character(len=*) :: pfile

Derived Types

type, public ::  histogram

Components

Type Visibility Attributes Name Initial
integer, public :: n = 0
real(kind=8), public, dimension(:), pointer :: range
real(kind=8), public, dimension(:), pointer :: bin

type, public ::  pdf_kernel

Components

Type Visibility Attributes Name Initial
integer, public :: N = 0
real(kind=8), public :: xmin
real(kind=8), public :: xmax
real(kind=8), public :: dx
integer, public :: Ndata = 0
real(kind=8), public, dimension(:), allocatable :: x
real(kind=8), public, dimension(:), allocatable :: pdf
real(kind=8), public :: sigma
logical, public :: status = .false.
logical, public :: variance = .false.
logical, public :: rescale = .false.

type, public ::  pdf_kernel_2d

Components

Type Visibility Attributes Name Initial
integer, public, dimension(2) :: N
real(kind=8), public, dimension(2) :: xmin
real(kind=8), public, dimension(2) :: xmax
real(kind=8), public, dimension(2) :: dx
integer, public :: Ndata = 0
real(kind=8), public, dimension(:), allocatable :: x
real(kind=8), public, dimension(:), allocatable :: y
real(kind=8), public, dimension(:,:), allocatable :: pdf
real(kind=8), public, dimension(2,2) :: Sigma
logical, public :: status = .false.
logical, public :: variance = .false.
logical, public :: rescale = .false.

Functions

public function get_mean(data) result(mean)

Arguments

Type IntentOptional Attributes Name
real(kind=8), intent(in), dimension(:) :: data

Return Value real(kind=8)

public function get_sd(data) result(sd)

Arguments

Type IntentOptional Attributes Name
real(kind=8), intent(in), dimension(:) :: data

Return Value real(kind=8)

public function get_var(data) result(var)

Arguments

Type IntentOptional Attributes Name
real(kind=8), intent(in), dimension(:) :: data

Return Value real(kind=8)

public function get_skew(data) result(skew)

Arguments

Type IntentOptional Attributes Name
real(kind=8), intent(in), dimension(:) :: data

Return Value real(kind=8)

public function get_curt(data) result(curt)

Arguments

Type IntentOptional Attributes Name
real(kind=8), intent(in), dimension(:) :: data

Return Value real(kind=8)

public function get_covariance(data, mean) result(covariance)

Arguments

Type IntentOptional Attributes Name
real(kind=8), intent(in), dimension(:,:) :: data
real(kind=8), intent(in), dimension(size(data,1)) :: mean

Return Value real(kind=8), dimension(size(data,1),size(data,1))

public function histogram_allocate(n) result(h)

Arguments

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

Return Value type(histogram)

public function histogram_get_value(h, index) result(value)

Arguments

Type IntentOptional Attributes Name
type(histogram), intent(in) :: h
integer, intent(in) :: index

Return Value real(kind=8)


Subroutines

public subroutine get_moments(data, ave, sdev, var, skew, curt)

Arguments

Type IntentOptional Attributes Name
real(kind=8), intent(in), dimension(:) :: data
real(kind=8), intent(out), optional :: ave
real(kind=8), intent(out), optional :: sdev
real(kind=8), intent(out), optional :: var
real(kind=8), intent(out), optional :: skew
real(kind=8), intent(out), optional :: curt

public subroutine histogram_deallocate(h)

Arguments

Type IntentOptional Attributes Name
type(histogram) :: h

public subroutine histogram_reset(h)

Arguments

Type IntentOptional Attributes Name
type(histogram) :: h

public subroutine histogram_set_range_uniform(h, xmin, xmax)

Arguments

Type IntentOptional Attributes Name
type(histogram), intent(inout) :: h
real(kind=8), intent(in) :: xmin
real(kind=8), intent(in) :: xmax

public subroutine histogram_accumulate(h, x, w)

Arguments

Type IntentOptional Attributes Name
type(histogram), intent(inout) :: h
real(kind=8), intent(in) :: x
real(kind=8), intent(in) :: w

public subroutine histogram_get_range(h, index, lower, upper)

Arguments

Type IntentOptional Attributes Name
type(histogram), intent(in) :: h
integer, intent(in) :: index
real(kind=8), intent(out) :: lower
real(kind=8), intent(out) :: upper

public subroutine histogram_print(h, unit)

Arguments

Type IntentOptional Attributes Name
type(histogram), intent(in) :: h
integer, intent(in) :: unit