home *** CD-ROM | disk | FTP | other *** search
-
- (*:Version: Mathematica 2.0 *)
-
- (*:Name: Statistics`HypothesisTests *)
-
- (*:Title: Hypothesis Tests Related to the Normal Distribution *)
-
- (*:Author:
- David Withoff (Wolfram Research), February, 1990
- *)
-
- (*:Legal:
- Copyright (c) 1990, Wolfram Research, Inc.
- *)
-
- (*:Reference: Usage messages only. *)
-
- (*:Summary:
- Hypothesis tests based on elementary distributions derived
- from the normal distribution. Distributions represented are
- NormalDistribution, StudentTDistribution, ChiSquareDistribution,
- and FRatioDistribution.
- *)
-
- (*:Keywords: hypothesis test, significance level *)
-
- (*:Requirements: No special system requirements. *)
-
- (*:Warning: None. *)
-
- (*:Sources: Basic statistics texts. *)
-
- BeginPackage["Statistics`HypothesisTests`",
- "Statistics`Common`DistributionsCommon`",
- "Statistics`NormalDistribution`",
- "Statistics`DescriptiveStatistics`",
- "Statistics`Common`HypothesisCommon`"]
-
- ResultOfTest::usage =
- "ResultOfTest[pvalue, options] is a utility used by the hypothesis testing
- functions to determine the conclusion of the test using the probability
- estimate pvalue for the test described by the options."
-
- (* Note: The option list for ResultOfTest must appear in this package *)
- (* before the other test function option lists, since it is used in *)
- (* assigning default values for those lists. *)
- Options[ResultOfTest] = {SignificanceLevel -> None, TwoSided -> False}
-
- MeanTest::usage =
- "MeanTest[list, mu0, options] returns a probability estimate (p-value)
- for the relationship between the hypothesized population mean mu0 and
- the mean of the entries in list."
-
- Options[MeanTest] = {KnownStandardDeviation -> None,FullReport -> False,
- KnownVariance -> None} ~Join~ Options[ResultOfTest]
-
- MeanDifferenceTest::usage =
- "MeanDifferenceTest[list1, list2, diff0, options] returns probability
- estimates (p-values) and other hypothesis test information for the
- relationship between the hypothesized population mean difference diff0
- and Mean[list1] - Mean[list2]."
-
- Options[MeanDifferenceTest] = {KnownStandardDeviation -> None,
- FullReport->False, KnownVariance -> None,
- EqualVariances -> False} ~Join~ Options[ResultOfTest]
-
- VarianceTest::usage =
- "VarianceTest[list, var0, options] returns probability
- estimates (p-values) and other hypothesis test information for
- the relationship between var0 and Variance[list]."
-
- Options[VarianceTest] = {FullReport->False} ~Join~ Options[ResultOfTest]
-
- VarianceRatioTest::usage =
- "VarianceRatioTest[numlist, denlist, ratio0, options] returns
- probability estimates (p-values) and other hypothesis test information
- for the relationship between ratio0 and the ratio
- Variance[numlist]/Variance[denlist]."
-
- Options[VarianceRatioTest] = {FullReport->False} ~Join~ Options[ResultOfTest]
-
- NormalPValue::usage =
- "NormalPValue[teststat] returns the cumulative density beyond teststat
- for NormalDistribution[]."
-
- Options[NormalPValue] = Options[ResultOfTest]
-
- StudentTPValue::usage =
- "StudentTPValue[teststat, dof] returns the cumulative density beyond
- teststat for the StudentTDistribution, with dof degrees of freedom."
-
- Options[StudentTPValue] = Options[ResultOfTest]
-
- ChiSquarePValue::usage =
- "ChiSquarePValue[teststat, dof] returns the cumulative density beyond
- teststat for the ChiSquareDistribution with dof degrees of freedom."
-
- Options[ChiSquarePValue] = Options[ResultOfTest]
-
- FRatioPValue::usage =
- "FRatioPValue[teststat, numdof, dendof] returns the cumulative
- density beyond teststat for the FRatioDistribution with numdof numerator
- degrees of freedom and dendof denominator degrees of freedom."
-
- Options[FRatioPValue] = Options[ResultOfTest]
-
- (* Output names *)
-
- OneSidedPValue::usage =
- "OneSidedPValue is used in the output of statistical hypothesis tests
- to identify the probability for sample parameters to be further from
- the corresponding population parameter than is the current sample parameter,
- and on the same side of the sampling distribution."
-
- TwoSidedPValue::usage =
- "TwoSidedPValue is used in the output of statistical hypothesis tests
- to identify the probability for sample parameters to be further from
- the corresponding population parameter than the current sample parameter,
- on either side of the sampling distribution."
-
- (* Options *)
-
- SignificanceLevel::usage =
- "SignificanceLevel is an option to statistical hypothesis tests and is
- used to specify the significance level of the test."
-
- TwoSided::usage =
- "TwoSided is an option to statistical hypothesis tests and is used
- to request a two-sided test."
-
- FullReport::usage =
- "FullReport is an option to statistical hypothesis tests and is used
- to indicate whether the estimator, test statistic, and number of
- degrees of freedom are included in the output."
-
-
- Begin["`Private`"]
-
- VariancePair[{var0_}] := {var0, var0}
-
- VariancePair[var0_List] := {var0[[1]], var0[[2]]} /; Length[var0] >= 2
-
- VariancePair[var0_] := {var0, var0} /; Head[var0] =!= List
-
- (* ==== Hypothesis tests for one mean ================================= *)
-
- MeanTest[args___] :=
- Block[{answer = iMeanTest[OptionExtract[{args}, MeanTest]]},
- answer /; answer =!= Fail
- ]
-
- iMeanTest[{list_List?(Length[#] > 0 &), mu0_, optionlist_}] :=
- Block[{diff, n, var0, sd0, test, subopts, out, rep},
- diff = Mean[list] - mu0;
- n = Length[list];
- {var0, sd0, rep} = ReplaceAll[{KnownVariance, KnownStandardDeviation,
- FullReport}, optionlist] /. Options[MeanTest];
- If[sd0 =!= None,
- If[var0 =!= None, Message[MeanTest::varsd]];
- var0 = sd0^2
- ];
- If[var0 =!= None,
- test = diff Sqrt[n/var0];
- subopts = OptionSelect[optionlist, NormalPValue];
- out = NormalPValue[test, subopts];
- If[TrueQ[rep],
- rep = FullReport ->TableForm[{{Mean[list],N[test]}},
- TableHeadings->{None,{"Mean","TestStat"}}];
- out =Flatten[{rep,"NormalDistribution",out}]];
- out,
- (* else, estimate the variance from the sample. *)
- var0 = VarianceOfSampleMean[list];
- If[Head[var0] === VarianceOfSampleMean,
- Message[MeanTest::novar]; Return[Fail]
- ];
- If[var0 == 0, Message[MeanTest::zerovar]];
- test = diff/Sqrt[var0];
- subopts = OptionSelect[optionlist, StudentTPValue];
- out = StudentTPValue[test, n-1, subopts];
- If[TrueQ[rep],
- rep = FullReport ->TableForm[{{Mean[list],N[test],n-1}},
- TableHeadings->{None,{"Mean","TestStat","DF"}}];
- out =Flatten[{rep,"StudentTDistribution",out}]];
- out ]]
-
-
- iMeanTest[badargs_] :=
- (If[badargs =!= Fail, Message[MeanTest::badargs]]; Fail)
-
- MeanTest::badargs = "Incorrect number or type of arguments."
-
- MeanTest::varsd = "Warning: KnownStandardDeviation and KnownVariance
- have both been specified. KnownVariance will be ignored."
-
- MeanTest::novar = "Unable to estimate variance from the sample."
-
- MeanTest::zerovar = "Warning: Estimated variance is zero; subsequent
- results may be misleading."
-
- (* ==== Hypothesis test for a difference of means ===================== *)
-
- MeanDifferenceTest[args___] :=
- Block[{result = vMeanDifferenceTest[
- OptionExtract[{args}, MeanDifferenceTest]]},
- result /; result =!= Fail]
-
- vMeanDifferenceTest[{list1_List, list2_List, diff1minus2_, optionlist_}] :=
- Block[{diff, var0, sd0, pval},
- diff = Mean[list1] - Mean[list2] - diff1minus2;
- {var0, sd0} = ReplaceAll[{KnownVariance, KnownStandardDeviation},
- optionlist] /. Options[MeanDifferenceTest];
- If[sd0 =!= None,
- If[var0 =!= None, Message[MeanDifferenceTest::varsd]];
- var0 = sd0^2
- ];
- iMeanDifferenceTest[list1, list2, diff, var0, optionlist]
-
- ]
-
- vMeanDifferenceTest[badargs_] :=
- (If[badargs =!= Fail, Message[MeanDifferenceTest::badargs]]; Fail)
-
- MeanDifferenceTest::badargs = "Incorrect number or type of arguments."
-
- MeanDifferenceTest::varsd = "Warning: KnownStandardDeviation and
- KnownVariance have both been specified. KnownVariance will be ignored."
-
- iMeanDifferenceTest[list1_, list2_, diff_, None, optionlist_] :=
- Block[
- {var1, var2, n1, n2, dof, pooledvar, test, equalvar, subopts,rep,out},
- {equalvar,rep} = {EqualVariances,FullReport} /. optionlist;
- var1 = Variance[list1];
- var2 = Variance[list2];
- n1 = Length[list1];
- n2 = Length[list2];
- If[TrueQ[equalvar],
- dof = n1 + n2 - 2;
- pooledvar = ((n1-1) var1 + (n2-1) var2) / dof;
- test = diff/Sqrt[pooledvar (1/n1 + 1/n2)],
- (* else *)
- pooledvar = var1/n1 + var2/n2;
- dof = pooledvar^2 /
- ((var1/n1)^2/(n1-1) + (var2/n2)^2/(n2-1));
- test = diff/Sqrt[pooledvar]
- ];
- subopts = OptionSelect[optionlist, StudentTPValue];
- out = StudentTPValue[test, dof, subopts];
- If[TrueQ[rep],
- rep = FullReport ->TableForm[{{N[Mean[list1]-Mean[list2]],N[test],dof
- }} ,TableHeadings->{None,{"MeanDiff","TestStat","DF"}}];
- out =Flatten[{rep,"StudentTDistribution",out}]];
- out
- ]
-
- iMeanDifferenceTest[list1_, list2_, diff_, var0_, options___] :=
- Block[{var1, var2, n1, n2, dof, pooledvar, test, subopts,out,rep},
- {var1, var2} = VariancePair[var0];
- rep = FullReport /. options;
- n1 = Length[list1];
- n2 = Length[list2];
- pooledvar = var1/n1 + var2/n2;
- test = diff/Sqrt[pooledvar];
- subopts = OptionSelect[{options}, NormalPValue];
- out = NormalPValue[test, subopts];
- If[TrueQ[rep],
- rep = FullReport ->TableForm[{{N[Mean[list1]-Mean[list2]],N[test]}}
- ,TableHeadings->{None,{"MeanDiff","TestStat"}}];
- out =Flatten[{rep,"NormalDistribution",out}]];
- out
- ] /; var0 =!= None
-
- (* ==== Hypothesis test for a single variance ========================= *)
-
- VarianceTest[args___] :=
- Block[{result = iVarianceTest[
- OptionExtract[{args}, VarianceTest]]},
- result /; result =!= Fail]
-
- iVarianceTest[{list_List, var0_, optionlist_}] :=
- Block[{dof, ssq, test, subopts, rep, out},
- rep = FullReport /. optionlist /. Options[VarianceTest];
- dof = Length[list]-1;
- ssq = (dof+1) Variance[list];
- test = ssq/var0;
- subopts = OptionSelect[optionlist, ChiSquarePValue];
- out = ChiSquarePValue[test, dof, subopts];
- If[TrueQ[rep],
- rep = FullReport ->TableForm[{{Variance[list],N[test],dof}},
- TableHeadings->{None,{"Variance","TestStat","DF"}}];
- out =Flatten[{rep,"ChiSquare Distribution",out}]]; out
- ]
-
- iVarianceTest[badargs_] :=
- (If[badargs =!= Fail, Message[VarianceTest::badargs]]; Fail)
-
- VarianceTest::badargs = "Incorrect number or type of arguments."
-
- (* ==== Hypothesis test for a variance ratio ========================== *)
-
- VarianceRatioTest[args___] :=
- Block[{result = iVarianceRatioTest[
- OptionExtract[{args}, VarianceRatioTest]]},
- result /; result =!= Fail]
-
- iVarianceRatioTest[
- {numlist_List, denlist_List, ratio0_, optionlist_}] :=
- Block[{numdof, dendof, test, pval, subopts, rep, out},
- rep = FullReport /.optionlist /. Options[VarianceRatioTest];
- test = (Variance[numlist]/Variance[denlist])/ratio0;
- numdof = Length[numlist] - 1;
- dendof = Length[denlist] - 1;
- subopts = OptionSelect[optionlist, FRatioPValue];
- out = FRatioPValue[test, numdof, dendof, subopts];
- If[TrueQ[rep],
- rep=FullReport->TableForm[{{N[test ratio0],N[test],numdof,dendof}}
- ,TableHeadings->{None,{"Ratio","TestStat","NumDF","DenDF"}}];
- out =Flatten[{rep,"FRatio Distribution",out}]]; out
- ]
-
- iVarianceRatioTest[badargs_] :=
- CompoundExpression[
- If[badargs =!= Fail,
- Message[VarianceRatioTest::badargs, badargs]];
- Fail
- ]
-
- VarianceRatioTest::badargs = "Incorrect arguments `1`."
-
- (* ==== Basic hypothesis test functions ========================== *)
-
- NormalPValue[test_, options___] :=
- Block[{pval},
- pval = N[CDF[NormalDistribution[], test]];
- ResultOfTest[pval, options]
- ]
-
- StudentTPValue[test_, dof_, options___] :=
- Block[{pval},
- pval = N[CDF[StudentTDistribution[dof], test]];
- ResultOfTest[pval, options]
- ]
-
- ChiSquarePValue[test_, dof_, options___] :=
- Block[{pval},
- pval = N[CDF[ChiSquareDistribution[dof], test]];
- ResultOfTest[pval, options]
- ]
-
- FRatioPValue[test_, numdof_, dendof_, options___] :=
- Block[{pval},
- pval = N[CDF[FRatioDistribution[numdof, dendof], test]];
- ResultOfTest[pval, options]
- ]
-
- (* Hypothesis test utilities *)
-
- ResultOfTest[pval_, options___] :=
- Block[{properpval, sig, twosided, report},
- {sig, twosided} = {SignificanceLevel, TwoSided} /.
- Options[{options}] /. Options[ResultOfTest];
- properpval = ProperPValue[pval];
- If[TrueQ[twosided],
- properpval = 2 properpval;
- report = TwoSidedPValue -> properpval,
- (* else *)
- report = OneSidedPValue -> properpval
- ];
- If[sig =!= None,
- report = {report, SignificanceMessage[properpval, sig]}
- ];
- report
- ]
-
- ProperPValue[pval_] :=
- If[pval > .5,
- 1 - pval,
- (* else *)
- pval,
- (* undetermined *)
- Message[ResultOfTest::nonum, pval];
- pval
- ]
-
- ResultOfTest::nonum = "Warning: P-value `1` is non-numerical.
- The symbolic answer may be ambiguous."
-
- SignificanceMessage[pval_, level_] :=
- If[N[pval > level],
- "Accept null hypothesis at significance level" -> level,
- (* else *)
- "Reject null hypothesis at significance level" -> level,
- (* undetermined *)
- If[pval > level,
- "Accept null hypothesis at significance level" -> level]
- ]
-
- OptionExtract[input_List, f_] :=
- Module[{n, opts, answer, known},
- For[n = Length[input], n > 0, n--,
- If[!OptionQ[input[[n]]], Break[]]
- ];
- answer = Take[input, n];
- opts = Options[input];
- known = Map[First, Options[f]];
- opts = Select[opts,
- If[MemberQ[known,First[#]], True,
- Message[f::optx, #, f]; False] &];
- AppendTo[answer, opts]
- ]
-
- OptionSelect[opts_List, sel_] :=
- With[{known = First /@ Options[sel]},
- Select[Flatten[opts], MemberQ[known, First[#]] &]
- ]
-
- End[]
- SetAttributes[ ResultOfTest ,ReadProtected];
- SetAttributes[ MeanTest ,ReadProtected];
- SetAttributes[ MeanDifferenceTest ,ReadProtected];
- SetAttributes[ VarianceTest ,ReadProtected];
- SetAttributes[ VarianceRatioTest ,ReadProtected];
- SetAttributes[ NormalPValue ,ReadProtected];
- SetAttributes[ StudentTPValue ,ReadProtected];
- SetAttributes[ ChiSquarePValue, ReadProtected];
- SetAttributes[ FRatioPValue, ReadProtected];
- SetAttributes[ OneSidedPValue, ReadProtected];
- SetAttributes[ TwoSidedPValue, ReadProtected];
- SetAttributes[ SignificanceLevel, ReadProtected];
- SetAttributes[ TwoSided, ReadProtected];
- SetAttributes[ SignTest, ReadProtected];
-
- Protect[ResultOfTest,MeanTest,MeanDifferenceTest,VarianceTest,
- VarianceRatioTest, NormalPValue,StudentTPValue, ChiSquarePValue,
- FRatioPValue,OneSidedPValue, TwoSidedPValue,SignificanceLevel,
- TwoSided, SignTest];
-
-
- EndPackage[]
-