Statistics tools for Fortran programs.
Calculates the mean value of a set of values given in a vector of any size with one dimension applying the following equation:
Where:
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
.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
Type | Intent | Optional | 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. |
Real number with the average of x.
Type | Intent | Optional | 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. |
Real number with the average of x.
Type | Intent | Optional | 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. |
Real number with the average of x.
Calculates the geometric mean of a set of values given in a vector of any size with one dimension applying the following equation:
Where:
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
.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
Type | Intent | Optional | 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. |
Real number with the geometric mean of the x.
Type | Intent | Optional | 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. |
Real number with the geometric mean of the x.
Type | Intent | Optional | 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. |
Real number with the geometric mean of the x.
Calculates the sample variance of a set of values given in a vector of any size with one dimension applying the following equation:
Where:
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
.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
Type | Intent | Optional | 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. |
Real number with the sample variance of x.
Type | Intent | Optional | 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. |
Real number with the sample variance of x.
Type | Intent | Optional | 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. |
Real number with the sample variance of x.
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:
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
.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
Type | Intent | Optional | 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. |
Real number with the sample standard deviation of x.
Type | Intent | Optional | 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. |
Real number with the sample standard deviation of x.
Type | Intent | Optional | 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. |
Real number with the sample standard deviation of x.
Calculates the population variance of a set of values given in a vector of any size with one dimension applying the following equation:
Where:
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
.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
Type | Intent | Optional | 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. |
Real number with the variance of x.
Type | Intent | Optional | 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. |
Real number with the variance of x.
Type | Intent | Optional | 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. |
Real number with the variance of x.
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:
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
.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
Type | Intent | Optional | 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. |
Real number with the population standard deviation of x.
Type | Intent | Optional | 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. |
Real number with the population standard deviation of x.
Type | Intent | Optional | 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. |
Real number with the population standard deviation of x.
Calculates the sample covariance between two variables given in two vectors of any size with one dimension applying the following equation:
Where:
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
.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
Type | Intent | Optional | 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 number with the sample covariance between both variables.
Type | Intent | Optional | 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 number with the sample covariance between both variables.
Type | Intent | Optional | 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 number with the sample covariance between both variables.
Calculates the population covariance between two variables given in two vectors of any size with one dimension applying the following equation:
Where:
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
.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
Type | Intent | Optional | 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 number with the population covariance between both variables.
Type | Intent | Optional | 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 number with the population covariance between both variables.
Type | Intent | Optional | 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 number with the population covariance between both variables.
Calculates the correlation coefficient between two variables given in two vectors of any size with one dimension applying the following equation:
Where:
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
.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
Type | Intent | Optional | 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 number with the population covariance between both variables.
Type | Intent | Optional | 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 number with the population covariance between both variables.
Type | Intent | Optional | 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 number with the population covariance between both variables.
Performs linear error (or uncertainties) propagation given the sensitivity coefficients and a covariance matrix. The following formula is applied:
Where:
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.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
Type | Intent | Optional | 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. |
Real number with the error or uncertainty (variance) propagated to the new variable.
Type | Intent | Optional | 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. |
Real number with the error or uncertainty (variance) propagated to the new variable.
Type | Intent | Optional | 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. |
Real number with the error or uncertainty (variance) propagated to the new variable.
Calculates the median value. This function does not work with quadruple precision numbers because of the ordering subroutine written in C++.
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
.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
Type | Intent | Optional | 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. |
Real number with the median
Type | Intent | Optional | 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. |
Real number with the median
Calculates the sample skewness of a set of values given in a vector of any size with one dimension applying the following equation:
Where:
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
.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
Type | Intent | Optional | 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. |
Real number with the sample skewness of the x.
Type | Intent | Optional | 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. |
Real number with the sample skewness of the x.
Type | Intent | Optional | 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. |
Real number with the sample skewness of the x.
Calculates the population skewness of a set of values given in a vector of any size with one dimension applying the following equation:
Where:
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
.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
Type | Intent | Optional | 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. |
Real number with the population skewness of the x.
Type | Intent | Optional | 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. |
Real number with the population skewness of the x.
Type | Intent | Optional | 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. |
Real number with the population skewness of the x.
Performs linear regression between two sets of values, obtaining parameters and of the following equation.
Where:
Parameter is also calculated to measure the goodness of fit.
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.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
Type | Intent | Optional | 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. |
Type | Intent | Optional | 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. |
Type | Intent | Optional | 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. |
Performs logarithmic regression between two sets of values, obtaining parameters and of the following equation.
Where:
Parameter is also calculated to determine the goodness of fit.
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.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
Type | Intent | Optional | 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. |
Type | Intent | Optional | 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. |
Type | Intent | Optional | 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. |
Performs exponential regression between two sets of values, obtaining parameters and of the following equation.
Where:
Parameter is also calculated to determine the goodness of fit.
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.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
Type | Intent | Optional | 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. |
Type | Intent | Optional | 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. |
Type | Intent | Optional | 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. |
Performs potential regression between two sets of values, obtaining parameters and of the following equation.
Where:
Parameter is also calculated to determine the goodness of fit.
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.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
Type | Intent | Optional | 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. |
Type | Intent | Optional | 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. |
Type | Intent | Optional | 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. |