home *** CD-ROM | disk | FTP | other *** search
-
- (*:Version: Mathematica 2.0 *)
-
- (*:Name: Statistics`DescriptiveStatistics` *)
-
- (*:Title: Basic Descriptive Statistics *)
-
- (*:Author:
- Original version by Stephen Wolfram (Wolfram Research), April, 1989.
- Revised by David Withoff (Wolfram Research), February, 1990.
- *)
-
- (*:Legal: Copyright (c) 1990, Wolfram Research Inc. *)
-
- (*:Reference: usage messages only. *)
-
- (*:Summary:
- Descriptive statistics (location and shape statistics) for
- samples represented by lists.
- *)
-
- (*:Keywords: maximum likelihood estimate, unbiased estimate *)
-
- (*:Requirements: no special system requirements. *)
-
- (*:Warning: none. *)
-
- (*:Sources: basic statistics texts. *)
-
- BeginPackage["Statistics`DescriptiveStatistics`"]
-
- (* Location statistics *)
-
- LocationReport::usage =
- "LocationReport[list] gives location statistics for list."
-
- Mean::usage =
- "Mean[list] gives the mean of the entries in list."
-
- GeometricMean::usage =
- "GeometricMean[list] gives the geometric mean of the entries in list."
-
- HarmonicMean::usage =
- "HarmonicMean[list] gives the harmonic mean of the entries in list."
-
- RootMeanSquare::usage =
- "RootMeanSquare[list] gives the root mean square of values in list."
-
- TrimmedMean::usage =
- "TrimmedMean[list, f] gives the mean of the entries in list, with a
- fraction f of entries at each end dropped. TrimmedMean[list, {f1, f2}]
- finds the mean with fractions f1 and f2 trimmed off."
-
- Quantile::usage =
- "Quantile[list, q] gives the q-th quantile of the entries in list."
-
- InterpolatedQuantile::usage =
- "InterpolatedQuantile[list, q] gives the q-th quantile of the
- probability distribution inferred by linear interpolation of the
- entries in list."
-
- Median::usage =
- "Median[list] gives the median of the entries in list."
-
- If[StringPosition[Mode::usage, "Mode[list] gives the mode"] === {},
- Mode::usage = Mode::usage <> " " <>
- "Mode[list] gives the mode of the entries in list. A list of modes
- is returned if the data is bimodal, trimodal, or multimodal."
- ]
-
- Quartiles::usage =
- "Quartiles[list] gives a list of the quartiles of the entries in list."
-
- (* Dispersion statistics *)
-
- DispersionReport::usage =
- "DispersionReport[list] gives dispersion statistics for list."
-
- SampleRange::usage =
- "SampleRange[list] gives the range of values in list."
-
- Variance::usage =
- "Variance[list] gives the variance of the entries in list.
- Division by n-1 (rather than n) is used, giving an unbiased
- estimate of the population variance (use VarianceMLE[list]
- for a maximum likelihood estimate)."
-
- VarianceMLE::usage =
- "VaranceMLE[list] gives the variance of the entries in list.
- Division by n (rather than n-1) is used, giving a maximum
- likelihood estimate of the population variance (use Variance[list]
- for an unbiased estimate)."
-
- VarianceOfSampleMean::usage =
- "VarianceOfSampleMean[list] returns an unbiased estimate of the variance
- of the sample mean, using the entries in list as a sample from the
- population."
-
- StandardDeviation::usage =
- "StandardDeviation[list] gives the standard deviation of the entries
- in list. Division by n-1 is used."
-
- StandardDeviationMLE::usage =
- "StandardDeviationMLE[list] returns the standard deviation of the entries
- in list. Division by n is used, giving a miximum likelihood estimate of
- the population standard deviation."
-
- StandardErrorOfSampleMean::usage =
- "StandardErrorOfSampleMean[list] returns an unbiased estimate of the
- standard error (standard deviation) of the sample mean, using the entries
- in list as a sample from the population."
-
- MeanDeviation::usage =
- "MeanDeviation[list] gives the mean absolute deviation about the
- mean of the entries in list."
-
- MedianDeviation::usage =
- "MedianDeviation[list] gives the median absolute deviation about
- the median of the entries in list."
-
- InterquartileRange::usage =
- "InterquartileRange[list] gives the difference between the upper
- and lower quartiles for the entries in list."
-
- QuartileDeviation::usage =
- "QuartileDeviation[list] gives the quartile deviation, or
- semi-interquartile range of the entries in list."
-
- (* Shape statistics *)
-
- ShapeReport::usage =
- "ShapeReport[list] gives shape statistics for list."
-
- CentralMoment::usage =
- "CentralMoment[list, n] gives the n-th central moment of
- the entries in list with respect to their mean."
-
- Skewness::usage =
- "Skewness[list] gives the coefficient of skewness of the
- entries in list."
-
- PearsonSkewness1::usage =
- "PearsonSkewness1[list] gives Pearson's first coefficient of
- skewness of the entries in list."
-
- PearsonSkewness2::usage =
- "PearsonSkewness2[list] gives Pearson's second coefficient of
- skewness of the entries in list."
-
- QuartileSkewness::usage =
- "QuartileSkewness[list] gives the quartile coefficient of
- skewness of the entries in list."
-
- Kurtosis::usage =
- "Kurtosis[list] gives the kurtosis coefficient for the entries
- in list."
-
- KurtosisExcess::usage =
- "KurtosisExcess[list] gives the kurtosis excess for the entries
- in list."
-
-
- Begin["`private`"]
-
- Mean[list_] := Apply[Plus, list] / Length[list] /;
- VectorQ[list] && Length[list] > 0
-
- GeometricMean[list_] := Apply[Times, list^(1/Length[list])] /;
- VectorQ[list] && Length[list] > 0
-
- HarmonicMean[list_] := Length[list] / Apply[Plus, 1/list] /;
- VectorQ[list] && Length[list] > 0
-
- RootMeanSquare[list_] := Sqrt[Mean[list^2]]
-
- TrimmedMean[list_, f_] := TrimmedMean[list, {f, f}] /; 2 f < 1
-
- TrimmedMean[list_, {f1_, f2_}] :=
- Block[{s, n},
- s = Sort[list] ;
- n = Length[list] ;
- s = Take[s, { 1 + Floor[f1 n],
- n - Floor[f2 n] } ] ;
- Mean[s]
- ] /; VectorQ[list] && Length[list] > 2 && (f1 + f2) < 1
-
- Quantile[list_, q_] := Part[ Sort[list], -Floor[-q Length[list]] ] /;
- VectorQ[list] && 0 < q < 1 && Length[list] > 2
-
- InterpolatedQuantile[list_, q_] :=
- Block[{s, n},
- s = Sort[list] ;
- n = Length[list] ;
- Which[
- q < 1/(2n), First[s],
- q > 1-1/(2n), Last[s],
- True,
- Block[{f, i, u},
- u = n q + 1/2 ;
- i = Floor[u] ;
- f = u - i ;
- (1 - f) s[[i]] + f s[[i+1]]
- ]
- ]
- ] /; VectorQ[list] && 0 < q < 1 && Length[list] > 2
-
- Median[list_] := Sort[list][[(Length[list]+1)/2]] /;
- VectorQ[list] && OddQ[Length[list]]
-
- Median[list_] :=
- Block[{s, n},
- s = Sort[list] ;
- n = Length[list] ;
- (s[[n/2]] + s[[n/2 + 1]]) / 2
- ] /; VectorQ[list] && EvenQ[Length[list]]
-
- Unprotect[Mode]
- Mode[list_]:=Module[{u,c,ms},
- u = Union[list];
- c = Map[Count[list,#]&,u];
- ms = Cases[Transpose[{u,c}],{val_,Max[c]}->val];
- If[Max[c] > 1,
- If[Length[ms] == 1,ms[[1]],ms],
- {}]
- ] /;VectorQ[list]&&Length[list]>0
-
- LocationReport[list_] :=
- {
- Mean -> Mean[list] ,
- HarmonicMean -> HarmonicMean[list] ,
- Median -> Median[list]
- } /; VectorQ[list]
-
-
- Quartiles[list_] := {InterpolatedQuantile[list, 1/4],
- InterpolatedQuantile[list, 1/2],
- InterpolatedQuantile[list, 3/4]} /; VectorQ[list]
-
- VarianceMLE[list_] := Mean[ (list - Mean[list])^2 ] /;
- VectorQ[list] && Length[list] > 0
-
- Variance[list_] :=
- Apply[Plus, (list - Mean[list])^2]/(Length[list] - 1) /;
- VectorQ[list] && Length[list] > 1
-
- VarianceOfSampleMean[args___] :=
- Block[{answer = iVarianceOfSampleMean[args]},
- answer /; answer =!= Fail
- ]
-
- iVarianceOfSampleMean[list_?VectorQ] :=
- 1/Length[list] Variance[list] /; Length[list] > 1
-
- iVarianceOfSampleMean[bad___] :=
- Block[{arglist = {bad}},
- Which[
- Length[arglist] =!= 1,
- Message[VarianceOfSampleMean::argct],
- arglist[[1,0]] =!= List,
- Message[VarianceOfSampleMean::notlist],
- Length[arglist[[1]]] <= 1,
- Message[VarianceOfSampleMean::short],
- True,
- Message[VarianceOfSampleMean::err]
- ];
- Fail
- ]
-
- VarianceOfSampleMean::argct = "Incorrect number of arguments;
- one argument is expected."
-
- VarianceOfSampleMean::notlist = "Argument is not a list."
-
- VarianceOfSampleMean::short = "Argument list must have length greater
- than one."
-
- VarianceOfSampleMean::err = "Parameters did not match required form."
-
-
- StandardDeviation[list_] := Sqrt[Variance[list]]
-
- StandardDeviationMLE[list_]:= Sqrt[VarianceMLE[list]]
-
- StandardErrorOfSampleMean[list_List] := Sqrt[VarianceOfSampleMean[list]]
-
- SampleRange[list_] := Max[list] - Min[list] /;
- VectorQ[list] && Length[list] > 0
-
- MeanDeviation[list_] := Mean[ Abs[list - Mean[list]] ] /;
- VectorQ[list] && Length[list] > 0
-
- MedianDeviation[list_] := Median[ Abs[list - Median[list]] ] /;
- VectorQ[list] && Length[list] > 0
-
- InterquartileRange[list_] :=
- InterpolatedQuantile[list, 3/4] - InterpolatedQuantile[list, 1/4] /;
- VectorQ[list]
-
- QuartileDeviation[list_] :=
- InterquartileRange[list] / 2
-
- DispersionReport[list_] :=
- {
- Variance -> Variance[list] ,
- StandardDeviation -> StandardDeviation[list] ,
- SampleRange -> SampleRange[list] ,
- MeanDeviation -> MeanDeviation[list] ,
- MedianDeviation -> MedianDeviation[list] ,
- QuartileDeviation -> QuartileDeviation[list]
- } /; VectorQ[list]
-
-
- CentralMoment[list_, n_] := Mean[ (list - Mean[list])^n ] /; VectorQ[list]
-
- Skewness[list_] := CentralMoment[list, 3] / StandardDeviation[list]^3
-
- PearsonSkewness1[list_] :=
- 3 (Mean[list] - Mode[list]) / StandardDeviation[list]
-
- PearsonSkewness2[list_] :=
- 3 (Mean[list] - Median[list]) / StandardDeviation[list]
-
- QuartileSkewness[list_] :=
- Block[{q1,q2,q3},
- {q1,q2, q3} = Quartiles[list] ;
- (q3 - 2 q2 + q1) / (q3 - q1)
- ] /; VectorQ[list] && Length[list] > 0
-
- Kurtosis[list_] :=
- CentralMoment[list, 4] / Variance[list]^2
-
- KurtosisExcess[list_] := Kurtosis[list] - 3
-
-
- ShapeReport[list_] :=
- {
- Skewness -> Skewness[list] ,
- QuartileSkewness -> QuartileSkewness[list] ,
- KurtosisExcess -> KurtosisExcess[list]
- }
-
- End[ ]
-
- SetAttributes[LocationReport , ReadProtected];
- SetAttributes[ GeometricMean, ReadProtected];
- SetAttributes[ HarmonicMean, ReadProtected];
- SetAttributes[ RootMeanSquare, ReadProtected];
- SetAttributes[ TrimmedMean, ReadProtected];
- SetAttributes[ InterpolatedQuantile, ReadProtected];
- SetAttributes[ Mean, ReadProtected];
- SetAttributes[ Median, ReadProtected];
- SetAttributes[ Mode, ReadProtected];
- SetAttributes[ Quartiles, ReadProtected];
- SetAttributes[ DispersionReport, ReadProtected];
- SetAttributes[ SampleRange, ReadProtected];
- SetAttributes[ MeanDeviation, ReadProtected];
- SetAttributes[ MedianDeviation, ReadProtected];
- SetAttributes[ InterquartileRange, ReadProtected];
- SetAttributes[ Variance, ReadProtected];
- SetAttributes[ VarianceOfSampleMean, ReadProtected];
- SetAttributes[ StandardErrorOfSampleMean, ReadProtected];
- SetAttributes[ StandardDeviation, ReadProtected];
- SetAttributes[ Quantile, ReadProtected];
- SetAttributes[ QuartileDeviation, ReadProtected];
- SetAttributes[ ShapeReport, ReadProtected];
- SetAttributes[ CentralMoment, ReadProtected];
- SetAttributes[ Skewness, ReadProtected];
- SetAttributes[ PearsonSkewness1 , ReadProtected];
- SetAttributes[ PearsonSkewness2, ReadProtected];
- SetAttributes[ QuartileSkewness, ReadProtected];
- SetAttributes[ Kurtosis, ReadProtected];
- SetAttributes[ KurtosisExcess, ReadProtected];
-
- Protect[LocationReport, GeometricMean, HarmonicMean,RootMeanSquare,
- TrimmedMean, InterpolatedQuantile,Mean, Median,Mode,Quartiles,
- DispersionReport,SampleRange,MeanDeviation, MedianDeviation,
- InterquartileRange, Variance, Quantile,StandardErrorOfSampleMean,
- VarianceOfSampleMean,
- QuartileDeviation, ShapeReport, CentralMoment,
- Skewness, PearsonSkewness1, PearsonSkewness2,
- QuartileSkewness, Kurtosis, KurtosisExcess];
-
- EndPackage[ ]
-
-
-