Skip to content

Commit

Permalink
Update design_matrix
Browse files Browse the repository at this point in the history
  • Loading branch information
jchristopherson committed Apr 15, 2024
1 parent abd84a7 commit bcfb284
Show file tree
Hide file tree
Showing 4 changed files with 20 additions and 18 deletions.
2 changes: 1 addition & 1 deletion src/fstats.f90
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ module fstats
public :: digamma
public :: incomplete_gamma_upper
public :: incomplete_gamma_lower
public :: coefficient_matrix
public :: design_matrix
public :: covariance_matrix
public :: linear_least_squares
public :: regression_statistics
Expand Down
20 changes: 11 additions & 9 deletions src/fstats_regression.f90
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ module fstats_regression
public :: r_squared
public :: adjusted_r_squared
public :: correlation
public :: coefficient_matrix
public :: design_matrix
public :: covariance_matrix
public :: linear_least_squares
public :: calculate_regression_statistics
Expand Down Expand Up @@ -293,16 +293,18 @@ pure function correlation(x, y) result(rst)
end function

! ------------------------------------------------------------------------------
subroutine coefficient_matrix(order, intercept, x, c, err)
!! Computes the coefficient matrix \( X \) to the linear
subroutine design_matrix(order, intercept, x, c, err)
!! Computes the design matrix \( X \) for the linear
!! least-squares regression problem of \( X \beta = y \), where
!! \( X \) is the coefficient matrix computed here, \( \beta \) is
!! \( X \) is the matrix computed here, \( \beta \) is
!! the vector of coefficients to be determined, and \( y \) is the
!! vector of measured dependent variables.
!!
!! See Also
!!
!! - [Wikipedia](https://en.wikipedia.org/wiki/Linear_regression)
!! - [Wikipedia](https://en.wikipedia.org/wiki/Vandermonde_matrix)
!! - [Wikipedia](https://en.wikipedia.org/wiki/Design_matrix)
integer(int32), intent(in) :: order
!! The order of the equation to fit. This value must be
!! at least one (linear equation), but can be higher as desired.
Expand Down Expand Up @@ -343,12 +345,12 @@ subroutine coefficient_matrix(order, intercept, x, c, err)

! Input Check
if (order < 1) then
call errmgr%report_error("coefficient_matrix", &
call errmgr%report_error("design_matrix", &
"The model order must be at least one.", FS_INVALID_INPUT_ERROR)
return
end if
if (size(c, 1) /= npts .or. size(c, 2) /= ncols) then
call report_matrix_size_error(errmgr, "coefficient_matrix", &
call report_matrix_size_error(errmgr, "design_matrix", &
"c", npts, ncols, size(c, 1), size(c, 2))
return
end if
Expand All @@ -372,15 +374,15 @@ subroutine coefficient_matrix(order, intercept, x, c, err)
subroutine covariance_matrix(x, c, err)
!! Computes the covariance matrix \( C \) where
!! \( C = \left( X^{T} X \right)^{-1} \) and \( X \) is computed
!! by coefficient_matrix.
!! by design_matrix.
!!
!! See Also
!!
!! - [Wikipedia](https://en.wikipedia.org/wiki/Covariance_matrix)
!! - [Wikipedia - Regression](https://en.wikipedia.org/wiki/Linear_regression)
real(real64), intent(in) :: x(:,:)
!! An M-by-N matrix containing the formatted independent data
!! matrix \( X \) as computed by coefficient_matrix.
!! matrix \( X \) as computed by design_matrix.
real(real64), intent(out) :: c(:,:)
!! The N-by-N covariance matrix.
class(errors), intent(inout), optional, target :: err
Expand Down Expand Up @@ -551,7 +553,7 @@ subroutine linear_least_squares(order, intercept, x, y, coeffs, &
end if

! Compute the coefficient matrix
call coefficient_matrix(order, intercept, x, a, errmgr)
call design_matrix(order, intercept, x, a, errmgr)
if (errmgr%has_error_occurred()) return

! Compute the covariance matrix
Expand Down
14 changes: 7 additions & 7 deletions tests/fstats_regression_tests.f90
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ module fstats_regression_tests
implicit none
contains
! ------------------------------------------------------------------------------
function coefficient_matrix_test_1() result(rst)
function design_matrix_test_1() result(rst)
! Arguments
logical :: rst

Expand Down Expand Up @@ -37,24 +37,24 @@ function coefficient_matrix_test_1() result(rst)
ans3(:,5) = x**4

! Test 1 - linear w/ intercept
call coefficient_matrix(order1, .true., x, c1)
call design_matrix(order1, .true., x, c1)
if (.not.is_equal(c1, ans1)) then
rst = .false.
print '(A)', "TEST FAILED: Coefficient Matrix Test 1 - 1"
print '(A)', "TEST FAILED: Design Matrix Test 1 - 1"
end if

! Test 2 - linear w/o intercept
call coefficient_matrix(order1, .false., x, c2)
call design_matrix(order1, .false., x, c2)
if (.not.is_equal(c2, ans2)) then
rst = .false.
print '(A)', "TEST FAILED: Coefficient Matrix Test 1 - 2"
print '(A)', "TEST FAILED: Design Matrix Test 1 - 2"
end if

! Test 3 - 4th order w/ intercept
call coefficient_matrix(order2, .true., x, c3)
call design_matrix(order2, .true., x, c3)
if (.not.is_equal(c3, ans3)) then
rst = .false.
print '(A)', "TEST FAILED: Coefficient Matrix Test 1 - 3"
print '(A)', "TEST FAILED: Design Matrix Test 1 - 3"
end if
end function

Expand Down
2 changes: 1 addition & 1 deletion tests/fstats_tests.f90
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,7 @@ program tests
local = incomplete_gamma_test_1()
if (.not.local) overall = .false.

local = coefficient_matrix_test_1()
local = design_matrix_test_1()
if (.not.local) overall = .false.

local = regression_test_1()
Expand Down

0 comments on commit bcfb284

Please sign in to comment.