s_tst_ttest_1s_core Subroutine

private pure subroutine s_tst_ttest_1s_core(x, mu0, t, df, p, h1)

The 1-sample t-test.

Arguments

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

x vector (samples)

real(kind=wp), intent(in) :: mu0

population mean (null hypothesis expected value)

real(kind=wp), intent(out) :: t

test statistic

real(kind=wp), intent(out) :: df

degrees of freedom

real(kind=wp), intent(out) :: p

p-value

character(len=*), intent(in) :: h1

option: two (default), le, ge


Calls

proc~~s_tst_ttest_1s_core~~CallsGraph proc~s_tst_ttest_1s_core s_tst_ttest_1s_core proc~f_dst_t_cdf_core f_dst_t_cdf_core proc~s_tst_ttest_1s_core->proc~f_dst_t_cdf_core proc~f_sts_mean_core f_sts_mean_core proc~s_tst_ttest_1s_core->proc~f_sts_mean_core proc~f_dst_betai_core f_dst_betai_core proc~f_dst_t_cdf_core->proc~f_dst_betai_core

Called by

proc~~s_tst_ttest_1s_core~~CalledByGraph proc~s_tst_ttest_1s_core s_tst_ttest_1s_core proc~s_tst_ttest_1s s_tst_ttest_1s proc~s_tst_ttest_1s->proc~s_tst_ttest_1s_core proc~s_tst_ttest_paired_core s_tst_ttest_paired_core proc~s_tst_ttest_paired_core->proc~s_tst_ttest_1s_core interface~fsml_ttest_1sample fsml_ttest_1sample interface~fsml_ttest_1sample->proc~s_tst_ttest_1s proc~s_tst_ttest_paired s_tst_ttest_paired proc~s_tst_ttest_paired->proc~s_tst_ttest_paired_core interface~fsml_ttest_paired fsml_ttest_paired interface~fsml_ttest_paired->proc~s_tst_ttest_paired

Source Code

pure subroutine s_tst_ttest_1s_core(x, mu0, t, df, p, h1)

! ==== Description
!! The 1-sample t-test.

! ==== Declarations
  real(wp)         , intent(in)  :: x(:) !! x vector (samples)
  real(wp)         , intent(in)  :: mu0  !! population mean (null hypothesis expected value)
  character(len=*) , intent(in)  :: h1   !! \( H_{1} \) option: two (default), le, ge
  real(wp)         , intent(out) :: t    !! test statistic
  real(wp)         , intent(out) :: df   !! degrees of freedom
  real(wp)         , intent(out) :: p    !! p-value
  real(wp)                       :: xbar !! sample mean
  real(wp)                       :: s    !! sample standard deviation
  integer(i4)                    :: n    !! sample size

! ==== Instructions

  ! get mean, sample size, and sample standard deviation (using n-1)
  xbar = f_sts_mean_core(x)
  n = size(x)
  s = sqrt( dot_product( (x - xbar), (x - xbar) ) / real( (n-1), kind=wp ) )

  ! get test statistic
  t = f_tst_ttest_1s_t(xbar, s, n, mu0)

  ! get degrees of freedom
  df = real(n, kind=wp) - 1.0_wp

  ! get p-value
  select case(h1)
     ! less than
     case("lt")
        p = f_dst_t_cdf_core(t, df, mu=0.0_wp, sigma=1.0_wp, tail="left")
     ! greater than
     case("gt")
        p = f_dst_t_cdf_core(t, df, mu=0.0_wp, sigma=1.0_wp, tail="right")
     ! two-sided
     case("two")
        p = f_dst_t_cdf_core(t, df, mu=0.0_wp, sigma=1.0_wp, tail="two")
  end select

  contains

  ! --------------------------------------------------------------- !
  pure function f_tst_ttest_1s_t(xbar, s, n, mu0) result(t)

     ! ==== Description
     !! Calculates the test statstic \( t \) for 1 sample t-test.
     ! TODO: Think about making elemental and public for batch processing

     ! ==== Declarations
     real(wp)   , intent(in) :: xbar !! sample mean
     real(wp)   , intent(in) :: s    !! sample standard deviation
     integer(i4), intent(in) :: n    !! sample size
     real(wp)   , intent(in) :: mu0  !! population mean
     real(wp)                :: t    !! test statistic

     ! ==== Instructions
     t = (xbar - mu0) / ( s / sqrt( real(n, kind=wp) ) )

  end function f_tst_ttest_1s_t

end subroutine s_tst_ttest_1s_core