FU_Statistics Module

Statistics tools for Fortran programs.


Uses


Contents


Interfaces

public interface mean

Calculates the mean value of a set of values given in a vector of any size with one dimension applying the following equation:

Where:

  • is a vector with real numbers.
  • is how many numbers are included in .

Syntax

y = mean(x)

Where:

  • x = vector of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • y = real number of the same kind as x with the mean value of x.

Example

The following program calculates the mean value of a vector:

 PROGRAM meanExample
    USE FU_Statistics, ONLY: mean
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    WRITE(*,*) mean(x)
 END PROGRAM meanExample
  • private pure function mean_sp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the mean value. It can have any size and it must have one dimension.

    Return Value real(kind=sp)

    Real number with the average of x.

  • private pure function mean_dp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the mean value. It can have any size and it must have one dimension.

    Return Value real(kind=dp)

    Real number with the average of x.

  • private pure function mean_qp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the mean value. It can have any size and it must have one dimension.

    Return Value real(kind=qp)

    Real number with the average of x.

public interface gmean

Calculates the geometric mean of a set of values given in a vector of any size with one dimension applying the following equation:

Where:

  • is a vector with real numbers.
  • is how many numbers are included in .

Syntax

y = gmean(x)

Where:

  • x = vector of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • y = real number of the same kind as x with the geometric mean of x.

Example

The following program calculates the geometric mean value of a vector:

 PROGRAM gmeanExample
    USE FU_Statistics, ONLY: gmean
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    WRITE(*,*) gmean(x)
 END PROGRAM gmeanExample
  • private pure function gmean_sp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the geometric mean. It can have any size and it must have one dimension.

    Return Value real(kind=sp)

    Real number with the geometric mean of the x.

  • private pure function gmean_dp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the geometric mean. It can have any size and it must have one dimension.

    Return Value real(kind=dp)

    Real number with the geometric mean of the x.

  • private pure function gmean_qp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the geometric mean. It can have any size and it must have one dimension.

    Return Value real(kind=qp)

    Real number with the geometric mean of the x.

public interface variance

Calculates the sample variance of a set of values given in a vector of any size with one dimension applying the following equation:

Where:

  • is a vector with real numbers.
  • is how many numbers are included in .

Syntax

y = variance(x)

Where:

  • x = vector of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • y = real number of the same kind as x with the sample variance of x.

Example

The following program calculates the variance of a vector:

 PROGRAM varianceExample
    USE FU_Statistics, ONLY: variance
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    WRITE(*,*) variance(x)
 END PROGRAM varianceExample
  • private pure function variance_sp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the sample variance. It can have any size and it must have one dimension.

    Return Value real(kind=sp)

    Real number with the sample variance of x.

  • private pure function variance_dp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the sample variance. It can have any size and it must have one dimension.

    Return Value real(kind=dp)

    Real number with the sample variance of x.

  • private pure function variance_qp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the sample variance. It can have any size and it must have one dimension.

    Return Value real(kind=qp)

    Real number with the sample variance of x.

public interface stdev

Calculates the sample standard deviation of a set of values given in a vector of any size with one dimension applying the following equation:

Where:

  • is a vector with real numbers.
  • is how many numbers are included in .

Syntax

y = stdev(x)

Where:

  • x = vector of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • y = real number of the same kind as x with the sample standard deviation of x.

Example

The following program calculates the sample standard deviation of a vector:

 PROGRAM stdevExample
    USE FU_Statistics, ONLY: stdev
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    WRITE(*,*) stdev(x)
 END PROGRAM stdevExample
  • private pure function stdev_sp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the sample standard deviation. It can have any size and it must have one dimension.

    Return Value real(kind=sp)

    Real number with the sample standard deviation of x.

  • private pure function stdev_dp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the sample standard deviation. It can have any size and it must have one dimension.

    Return Value real(kind=dp)

    Real number with the sample standard deviation of x.

  • private pure function stdev_qp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the sample standard deviation. It can have any size and it must have one dimension.

    Return Value real(kind=qp)

    Real number with the sample standard deviation of x.

public interface pvariance

Calculates the population variance of a set of values given in a vector of any size with one dimension applying the following equation:

Where:

  • is a vector with real numbers.
  • is how many numbers are included in .

Syntax

y = pvariance(x)

Where:

  • x = vector of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • y = real number of the same kind as x with the population variance of x.

Example

The following program calculates the population variance of a vector:

 PROGRAM pvarianceExample
    USE FU_Statistics, ONLY: pvariance
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    WRITE(*,*) pvariance(x)
 END PROGRAM pvarianceExample
  • private pure function pvariance_sp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the population variance. It can have any size and it must have one dimension.

    Return Value real(kind=sp)

    Real number with the variance of x.

  • private pure function pvariance_dp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the population variance. It can have any size and it must have one dimension.

    Return Value real(kind=dp)

    Real number with the variance of x.

  • private pure function pvariance_qp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the population variance. It can have any size and it must have one dimension.

    Return Value real(kind=qp)

    Real number with the variance of x.

public interface pstdev

Calculates the population standard deviation of a set of values given in a vector of any size with one dimension applying the following equation:

Where:

  • is a vector with real numbers.
  • is how many numbers are included in .

Syntax

y = pstdev(x)

Where:

  • x = vector of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • y = real number of the same kind as x with the population standard deviation of x.

Example

The following program calculates the population standard deviation of a vector:

 PROGRAM pstdevExample
    USE FU_Statistics, ONLY: pstdev
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    WRITE(*,*) pstdev(x)
 END PROGRAM pstdevExample
  • private pure function pstdev_sp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the population standard deviation. It can have any size and it must have one dimension.

    Return Value real(kind=sp)

    Real number with the population standard deviation of x.

  • private pure function pstdev_dp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the population standard deviation. It can have any size and it must have one dimension.

    Return Value real(kind=dp)

    Real number with the population standard deviation of x.

  • private pure function pstdev_qp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the population standard deviation. It can have any size and it must have one dimension.

    Return Value real(kind=qp)

    Real number with the population standard deviation of x.

public interface covariance

Calculates the sample covariance between two variables given in two vectors of any size with one dimension applying the following equation:

Where:

  • and are vectors with real numbers.
  • is how many numbers are included in and .

Syntax

z = covariance(x,y)

Where:

  • x and y = vectors of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • z = real number of the same kind as x and y with the sample covariance of x and y.

Example

The following program calculates the covariance between two variables:

 PROGRAM covarianceExample
    USE FU_Statistics, ONLY: covariance
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    REAL, DIMENSION(5) :: y = [6., 7., 8., 9., 10.]
    WRITE(*,*) covariance(x, y)
 END PROGRAM covarianceExample
  • private pure function covariance_sp(x, y) result(res)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=sp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    Return Value real(kind=sp)

    Real number with the sample covariance between both variables.

  • private pure function covariance_dp(x, y) result(res)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=dp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    Return Value real(kind=dp)

    Real number with the sample covariance between both variables.

  • private pure function covariance_qp(x, y) result(res)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=qp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    Return Value real(kind=qp)

    Real number with the sample covariance between both variables.

public interface pcovariance

Calculates the population covariance between two variables given in two vectors of any size with one dimension applying the following equation:

Where:

  • and are vectors with real numbers.
  • is how many numbers are included in and .

Syntax

z = pcovariance(x,y)

Where:

  • x and y = vectors of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • z = real number of the same kind as x and y with the population covariance of x and y.

Example

The following program calculates the population covariance between two variables:

 PROGRAM pcovarianceExample
    USE FU_Statistics, ONLY: pcovariance
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    REAL, DIMENSION(5) :: y = [6., 7., 8., 9., 10.]
    WRITE(*,*) pcovariance(x, y)
 END PROGRAM pcovarianceExample
  • private pure function pcovariance_sp(x, y) result(res)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=sp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    Return Value real(kind=sp)

    Real number with the population covariance between both variables.

  • private pure function pcovariance_dp(x, y) result(res)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=dp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    Return Value real(kind=dp)

    Real number with the population covariance between both variables.

  • private pure function pcovariance_qp(x, y) result(res)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=qp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    Return Value real(kind=qp)

    Real number with the population covariance between both variables.

public interface correlation

Calculates the correlation coefficient between two variables given in two vectors of any size with one dimension applying the following equation:

Where:

  • and are vectors with real numbers.
  • is how many numbers are included in and .

Syntax

z = correlation(x,y)

Where:

  • x and y = vectors of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • z = real number of the same kind as x and y with the correlation coefficient of x and y.

Example

The following program calculates the correlation coefficient between two variables:

 PROGRAM correlationExample
    USE FU_Statistics, ONLY: correlation
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    REAL, DIMENSION(5) :: y = [6., 7., 8., 9., 10.]
    WRITE(*,*) correlation(x, y)
 END PROGRAM correlationExample
  • private pure function correlation_sp(x, y) result(res)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=sp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    Return Value real(kind=sp)

    Real number with the population covariance between both variables.

  • private pure function correlation_dp(x, y) result(res)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=dp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    Return Value real(kind=dp)

    Real number with the population covariance between both variables.

  • private pure function correlation_qp(x, y) result(res)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=qp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    Return Value real(kind=qp)

    Real number with the population covariance between both variables.

public interface lin_error_propagation

Performs linear error (or uncertainties) propagation given the sensitivity coefficients and a covariance matrix. The following formula is applied:

Where:

  • is the response whose uncertainty is to be calculated.
  • is a set of input parameters to propagate their uncertainty to .
  • is the vector of sensitivity coefficients of with respect to the different parameters in .
  • is the covariance matrix of the parameters in .

Syntax

y = lin_error_propagation(s,m)

Where:

  • s = vector of rank 1 with real numbers containing the sensitivity coefficients.
  • m = array of rank 2 containing the covariance matrix.
  • y = real number of the same kind as s and m with the error or uncertainty propagated to this new variable.

Example

The following program calculates the linearly propagated error:

 PROGRAM lin_error_propagationExample
    USE FU_Statistics, ONLY: lin_error_propagation
    IMPLICIT NONE
    REAL, DIMENSION(3) :: s = [1., 2., 3.]
    REAL, DIMENSION(3,3) :: m = &
       RESHAPE((/0.5, 2., 3., 2., 5.4, 6., 3., 6., 3.3/),SHAPE(m))
    WRITE(*,*) lin_error_propagation(s, m)
 END PROGRAM lin_error_propagationExample
  • private pure function lin_error_propagation_sp(sensitivities, matcovar) result(res)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in), DIMENSION(:) :: sensitivities

    Vector of sensitivity coefficients of the new variable with the respect the prior variable. It can have any size and it must have one dimension.

    real(kind=sp), intent(in), DIMENSION(:,:) :: matcovar

    Covariance matrix with the error or uncertainty of the prior variable. Dimensions of sensitivities and matcovar must be in agreement.

    Return Value real(kind=sp)

    Real number with the error or uncertainty (variance) propagated to the new variable.

  • private pure function lin_error_propagation_dp(sensitivities, matcovar) result(res)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in), DIMENSION(:) :: sensitivities

    Vector of sensitivity coefficients of the new variable with the respect the prior variable. It can have any size and it must have one dimension.

    real(kind=dp), intent(in), DIMENSION(:,:) :: matcovar

    Covariance matrix with the error or uncertainty of the prior variable. Dimensions of sensitivities and matcovar must be in agreement.

    Return Value real(kind=dp)

    Real number with the error or uncertainty (variance) propagated to the new variable.

  • private pure function lin_error_propagation_qp(sensitivities, matcovar) result(res)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=qp), intent(in), DIMENSION(:) :: sensitivities

    Vector of sensitivity coefficients of the new variable with the respect the prior variable. It can have any size and it must have one dimension.

    real(kind=qp), intent(in), DIMENSION(:,:) :: matcovar

    Covariance matrix with the error or uncertainty of the prior variable. Dimensions of sensitivities and matcovar must be in agreement.

    Return Value real(kind=qp)

    Real number with the error or uncertainty (variance) propagated to the new variable.

public interface median

Calculates the median value. This function does not work with quadruple precision numbers because of the ordering subroutine written in C++.

Syntax

y = median(x)

Where:

  • x = vector of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • y = real number of the same kind as x with the median of x.

Example

The following program calculates the median of a vector:

 PROGRAM medianExample
    USE FU_Statistics, ONLY: median
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    WRITE(*,*) median(x)
 END PROGRAM medianExample
  • private function median_sp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the median. It can have any size and it must have one dimension.

    Return Value real(kind=sp)

    Real number with the median

  • private function median_dp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the median. It can have any size and it must have one dimension.

    Return Value real(kind=dp)

    Real number with the median

public interface skewness

Calculates the sample skewness of a set of values given in a vector of any size with one dimension applying the following equation:

Where:

  • is a vector with real numbers.
  • is how many numbers are included in .

Syntax

y = skewness(x)

Where:

  • x = vector of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • y = real number of the same kind as x with the sample skewness of x.

Example

The following program calculates the sample skewness of a vector:

 PROGRAM skewnessExample
    USE FU_Statistics, ONLY: skewness
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    WRITE(*,*) skewness(x)
 END PROGRAM skewnessExample
  • private pure function skewness_sp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the sample skewness. It can have any size and it must have one dimension.

    Return Value real(kind=sp)

    Real number with the sample skewness of the x.

  • private pure function skewness_dp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the sample skewness. It can have any size and it must have one dimension.

    Return Value real(kind=dp)

    Real number with the sample skewness of the x.

  • private pure function skewness_qp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the sample skewness. It can have any size and it must have one dimension.

    Return Value real(kind=qp)

    Real number with the sample skewness of the x.

public interface pskewness

Calculates the population skewness of a set of values given in a vector of any size with one dimension applying the following equation:

Where:

  • is a vector with real numbers.
  • is how many numbers are included in .

Syntax

y = pskewness(x)

Where:

  • x = vector of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • y = real number of the same kind as x with the population skewness of x.

Example

The following program calculates the population skewness of a vector:

 PROGRAM pskewnessExample
    USE FU_Statistics, ONLY: pskewness
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    WRITE(*,*) pskewness(x)
 END PROGRAM pskewnessExample
  • private pure function pskewness_sp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the population skewness. It can have any size and it must have one dimension.

    Return Value real(kind=sp)

    Real number with the population skewness of the x.

  • private pure function pskewness_dp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the population skewness. It can have any size and it must have one dimension.

    Return Value real(kind=dp)

    Real number with the population skewness of the x.

  • private pure function pskewness_qp(x) result(res)

    Arguments

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

    Vector of real numbers to calculate the population skewness. It can have any size and it must have one dimension.

    Return Value real(kind=qp)

    Real number with the population skewness of the x.

public interface linreg

Performs linear regression between two sets of values, obtaining parameters and of the following equation.

Where:

  • and are vectors with real numbers.
  • and are the regression coefficients.

Parameter is also calculated to measure the goodness of fit.

Syntax

CALL linreg(x,y,a,b,R2)

Where:

  • x and y = vectors of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • a, b = regression coefficients calculated by the subroutine.
  • R2 = the determination coefficient to measure the goodness of fit, calculated by the subroutine.

Example

The following program performs a linear regression of two variables:

 PROGRAM linregExample
    USE FU_Statistics, ONLY: linreg
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    REAL, DIMENSION(5) :: y = [3., 4., 5., 6., 7.]
    REAL :: a, b, R2
    CALL linreg(x, y, a, b, R2)
    WRITE(*,*) a, b, R2
 END PROGRAM linregExample
  • private pure subroutine linreg_sp(x, y, a, b, R2)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=sp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    real(kind=sp), intent(out) :: a

    Regression coefficient.

    real(kind=sp), intent(out) :: b

    Regression coefficient.

    real(kind=sp), intent(out) :: R2

    Determination coefficient.

  • private pure subroutine linreg_dp(x, y, a, b, R2)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=dp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    real(kind=dp), intent(out) :: a

    Regression coefficient.

    real(kind=dp), intent(out) :: b

    Regression coefficient.

    real(kind=dp), intent(out) :: R2

    Determination coefficient.

  • private pure subroutine linreg_qp(x, y, a, b, R2)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=qp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    real(kind=qp), intent(out) :: a

    Regression coefficient.

    real(kind=qp), intent(out) :: b

    Regression coefficient.

    real(kind=qp), intent(out) :: R2

    Determination coefficient.

public interface logreg

Performs logarithmic regression between two sets of values, obtaining parameters and of the following equation.

Where:

  • and are vectors with real numbers.
  • and are the regression coefficients.

Parameter is also calculated to determine the goodness of fit.

Syntax

CALL logreg(x,y,a,b,R2)

Where:

  • x and y = vectors of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • a, b = regression coefficients calculated by the subroutine.
  • R2 = the determination coefficient to measure the goodness of fit, calculated by the subroutine.

Example

The following program performs a logarithmic regression of two variables:

 PROGRAM logregExample
    USE FU_Statistics, ONLY: logreg
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    REAL, DIMENSION(5) :: y = [3., 4., 5., 6., 7.]
    REAL :: a, b, R2
    CALL logreg(x, y, a, b, R2)
    WRITE(*,*) a, b, R2
 END PROGRAM logregExample
  • private pure subroutine logreg_sp(x, y, a, b, R2)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=sp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    real(kind=sp), intent(out) :: a

    Regression coefficient.

    real(kind=sp), intent(out) :: b

    Regression coefficient.

    real(kind=sp), intent(out) :: R2

    Determination coefficient.

  • private pure subroutine logreg_dp(x, y, a, b, R2)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=dp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    real(kind=dp), intent(out) :: a

    Regression coefficient.

    real(kind=dp), intent(out) :: b

    Regression coefficient.

    real(kind=dp), intent(out) :: R2

    Determination coefficient.

  • private pure subroutine logreg_qp(x, y, a, b, R2)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=qp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    real(kind=qp), intent(out) :: a

    Regression coefficient.

    real(kind=qp), intent(out) :: b

    Regression coefficient.

    real(kind=qp), intent(out) :: R2

    Determination coefficient.

public interface expreg

Performs exponential regression between two sets of values, obtaining parameters and of the following equation.

Where:

  • and are vectors with real numbers.
  • and are the regression coefficients.

Parameter is also calculated to determine the goodness of fit.

Syntax

CALL expreg(x,y,a,b,R2)

Where:

  • x and y = vectors of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • a, b = regression coefficients calculated by the subroutine.
  • R2 = the determination coefficient to measure the goodness of fit, calculated by the subroutine.

Example

The following program performs a exponential regression of two variables:

 PROGRAM expregExample
    USE FU_Statistics, ONLY: expreg
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    REAL, DIMENSION(5) :: y = [3., 4., 5., 6., 7.]
    REAL :: a, b, R2
    CALL expreg(x, y, a, b, R2)
    WRITE(*,*) a, b, R2
 END PROGRAM expregExample
  • private pure subroutine expreg_sp(x, y, a, b, R2)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=sp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    real(kind=sp), intent(out) :: a

    Regression coefficient.

    real(kind=sp), intent(out) :: b

    Regression coefficient.

    real(kind=sp), intent(out) :: R2

    Determination coefficient.

  • private pure subroutine expreg_dp(x, y, a, b, R2)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=dp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    real(kind=dp), intent(out) :: a

    Regression coefficient.

    real(kind=dp), intent(out) :: b

    Regression coefficient.

    real(kind=dp), intent(out) :: R2

    Determination coefficient.

  • private pure subroutine expreg_qp(x, y, a, b, R2)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=qp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    real(kind=qp), intent(out) :: a

    Regression coefficient.

    real(kind=qp), intent(out) :: b

    Regression coefficient.

    real(kind=qp), intent(out) :: R2

    Determination coefficient.

public interface potreg

Performs potential regression between two sets of values, obtaining parameters and of the following equation.

Where:

  • and are vectors with real numbers.
  • and are the regression coefficients.

Parameter is also calculated to determine the goodness of fit.

Syntax

CALL potreg(x,y,a,b,R2)

Where:

  • x and y = vectors of rank 1 with real numbers. See this example to use an array of rank larger than 1.
  • a, b = regression coefficients calculated by the subroutine.
  • R2 = the determination coefficient to measure the goodness of fit, calculated by the subroutine.

Example

The following program performs a potential regression of two variables:

 PROGRAM potregExample
    USE FU_Statistics, ONLY: potreg
    IMPLICIT NONE
    REAL, DIMENSION(5) :: x = [1., 2., 3., 4., 5.]
    REAL, DIMENSION(5) :: y = [3., 4., 5., 6., 7.]
    REAL :: a, b, R2
    CALL potreg(x, y, a, b, R2)
    WRITE(*,*) a, b, R2
 END PROGRAM potregExample
  • private pure subroutine potreg_sp(x, y, a, b, R2)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=sp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    real(kind=sp), intent(out) :: a

    Regression coefficient.

    real(kind=sp), intent(out) :: b

    Regression coefficient.

    real(kind=sp), intent(out) :: R2

    Determination coefficient.

  • private pure subroutine potreg_dp(x, y, a, b, R2)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=dp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    real(kind=dp), intent(out) :: a

    Regression coefficient.

    real(kind=dp), intent(out) :: b

    Regression coefficient.

    real(kind=dp), intent(out) :: R2

    Determination coefficient.

  • private pure subroutine potreg_qp(x, y, a, b, R2)

    Arguments

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

    Vector of real numbers with the values of the first variable. It can have any size and it must have one dimension.

    real(kind=qp), intent(in), DIMENSION(:) :: y

    Vector of real numbers with the values of the second variable. It can have any size and it must have one dimension.

    real(kind=qp), intent(out) :: a

    Regression coefficient.

    real(kind=qp), intent(out) :: b

    Regression coefficient.

    real(kind=qp), intent(out) :: R2

    Determination coefficient.