DhbIterativeProcess subclass: #DhbLeastSquareFit instanceVariableNames: 'dataHolder errorMatrix chiSquare equations constants degreeOfFreedom ' classVariableNames: '' poolDictionaries: ''! DhbLeastSquareFit subclass: #DhbMaximumLikekihoodHistogramFit instanceVariableNames: 'count countVariance ' classVariableNames: '' poolDictionaries: ''! Object subclass: #DhbLinearRegression instanceVariableNames: 'sum1 sumX sumY sumXX sumYY sumXY slope intercept correlationCoefficient ' classVariableNames: '' poolDictionaries: ''! DhbPolynomial subclass: #DhbEstimatedPolynomial instanceVariableNames: 'errorMatrix ' classVariableNames: '' poolDictionaries: ''! Object subclass: #DhbPolynomialLeastSquareFit instanceVariableNames: 'pointCollection degreePlusOne ' classVariableNames: '' poolDictionaries: ''! Object subclass: #DhbWeightedPoint instanceVariableNames: 'xValue yValue weight error ' classVariableNames: '' poolDictionaries: ''! PointSeries subclass: #DhbPointSeriesWithError instanceVariableNames: '' classVariableNames: '' poolDictionaries: ''! SubApplication subclass: #DhbEstimation instanceVariableNames: '' classVariableNames: '' poolDictionaries: ''! !DhbEstimatedPolynomial publicMethods ! error: aNumber "Compute the error on the value of the receiver for argument aNumber. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " | errorVector term nextTerm | nextTerm := 1. errorVector := ( coefficients collect: [ :each | term := nextTerm. nextTerm := aNumber * nextTerm. term]) asVector. ^( errorVector * errorMatrix * errorVector) sqrt ! errorMatrix "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 21/5/99 " ^errorMatrix! errorMatrix: aMatrix "Defines the error matrix of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " errorMatrix := aMatrix.! valueAndError: aNumber "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 20/5/99 " ^Array with: ( self value: aNumber) with: ( self error: aNumber)! ! !DhbFastStatisticalMoments publicMethods ! unnormalizedVariance "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 1/22/00 " ^(moments at: 3) - ((moments at: 2) squared * self count)! ! !DhbHistogram publicMethods ! tConfidenceLevel: aStatisticalMomentsOrHistogram "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 1/22/00 " ^moments tConfidenceLevel: aStatisticalMomentsOrHistogram! unnormalizedVariance "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 1/22/00 " ^moments unnormalizedVariance! ! !DhbLeastSquareFit class publicMethods ! histogram: aHistogram distributionClass: aProbabilityDensityFunctionClass "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/3/99 " ^self points: aHistogram function: (DhbScaledProbabilityDensityFunction histogram: aHistogram distributionClass: aProbabilityDensityFunctionClass)! points: aDataHolder function: aParametricFunction "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/3/99 " ^aParametricFunction ifNotNil: [ :dp | super new initialize: aDataHolder data: dp]! ! !DhbLeastSquareFit publicMethods ! chiSquare "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 15/4/99 " chiSquare isNil ifTrue: [ self computeChiSquare]. ^chiSquare! confidenceLevel "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/6/00 " ^( DhbChiSquareDistribution degreeOfFreedom: self degreeOfFreedom) confidenceLevel: self chiSquare! degreeOfFreedom "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 15/4/99 " degreeOfFreedom isNil ifTrue: [ self computeChiSquare]. ^degreeOfFreedom! errorMatrix "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 14/4/99 " ^DhbSymmetricMatrix rows: errorMatrix inverseMatrixComponents! evaluateIteration "Dummy method (must be implemented by subclass). (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 6/1/99 " | changes maxChange| self computeEquationSystem. changes := self computeChanges. result changeParametersBy: changes. maxChange := 0. result parameters with: changes do: [ :r :d | maxChange := ( d / r) abs max: maxChange]. ^maxChange! finalizeIterations "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 9/3/99 " equations := nil. constants := nil. degreeOfFreedom := nil. chiSquare := nil! fitType "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 15/4/99 " ^'Least square fit'! initializeIterations "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 6/1/99 " | n | n := self numberOfParameters. constants := (DhbVector new: n) atAllPut: 0; yourself. equations := (1 to: n) collect: [:k | (DhbVector new: n) atAllPut: 0; yourself]! value: aNumber "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/8/00 " ^result value: aNumber! valueAndError: aNumber "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/8/00 " | valueGradient | valueGradient := result valueAndGradient: aNumber. ^Array with: valueGradient first with: ( valueGradient last * ( self errorMatrix * valueGradient last)) sqrt! ! !DhbLeastSquareFit privateMethods ! accumulate: aWeightedPoint "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/3/99 " | f g | f := result valueAndGradient: aWeightedPoint xValue. g := f last. f := f first. constants accumulate: g * ( ( aWeightedPoint yValue - f) * aWeightedPoint weight). 1 to: g size do: [ :k | ( equations at: k) accumulate: g * ( ( g at: k) * aWeightedPoint weight). ].! accumulateEquationSystem "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/3/99 " dataHolder pointsAndErrorsDo: [ :each | self accumulate: each].! computeChanges "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/3/99 " errorMatrix := DhbLUPDecomposition direct: equations. ^errorMatrix solve: constants! computeChiSquare "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 15/4/99 " chiSquare := 0. degreeOfFreedom := self numberOfFreeParameters negated. dataHolder pointsAndErrorsDo: [ :each | chiSquare := ( each chi2Contribution: result) + chiSquare. degreeOfFreedom := degreeOfFreedom + 1. ].! computeEquationSystem "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/3/99 " constants atAllPut: 0. equations do: [ :each | each atAllPut: 0]. self accumulateEquationSystem.! initialize: aDataHolder data: aParametricFunction "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/3/99 " dataHolder := aDataHolder. result := aParametricFunction. ^self! numberOfFreeParameters "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 15/4/99 " ^self numberOfParameters! numberOfParameters "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/3/99 " ^result parameters size! ! !DhbLinearRegression class publicMethods ! new "Create a new instance of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " ^( super new) reset; yourself! ! !DhbLinearRegression publicMethods ! add: aPoint "Accumulate aPoint into of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " self add: aPoint weight: 1.! add: aPoint weight: aNumber "Accumulate aPoint into of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " sum1 := sum1 + aNumber. sumX := sumX + (aPoint x * aNumber). sumY := sumY + (aPoint y * aNumber). sumXX := sumXX + (aPoint x squared * aNumber). sumYY := sumYY + (aPoint y squared * aNumber). sumXY := sumXY + (aPoint x * aPoint y * aNumber). self resetResults! asEstimatedPolynomial "Answer the resulting linear dependence found by the receiver in the form of a polynomial with embedded error matrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " ^( DhbEstimatedPolynomial coefficients: self coefficients) errorMatrix: self errorMatrix; yourself! asPolynomial "Answer the resulting linear dependence found by the receiver in the form of a polynomial. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " ^DhbPolynomial coefficients: self coefficients! correlationCoefficient "Answers the correlation coefficient of the receiver (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " correlationCoefficient isNil ifTrue: [ self computeResults]. ^correlationCoefficient! errorMatrix "Answer the resulting linear dependence found by the receiver in the form of a polynomial with embedded error matrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " | c1 cx cxx | c1 := 1.0 / (sumXX * sum1 - sumX squared). cx := sumX negated * c1. cxx := sumXX * c1. c1 := sum1 * c1. ^DhbSymmetricMatrix rows: (Array with: (Array with: cxx with: cx) with: (Array with: cx with: c1))! errorOnIntercept "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 21/5/99 " ^(sumXX / (sumXX * sum1 - sumX squared)) sqrt! errorOnSlope "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 21/5/99 " ^(sum1 / (sumXX * sum1 - sumX squared)) sqrt! intercept "Answers the intercept of the receiver (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " intercept isNil ifTrue: [ self computeResults]. ^intercept! remove: aPoint "Remove aPoint which was accumulated into of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " sum1 := sum1 - 1. sumX := sumX - aPoint x. sumY := sumY - aPoint y. sumXX := sumXX - aPoint x squared. sumYY := sumYY - aPoint y squared. sumXY := sumXY - (aPoint x * aPoint y). self resetResults! reset "Set all accumulators of the receiver to zero and reset its results. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " sum1 := 0. sumX := 0. sumY := 0. sumXX := 0. sumYY := 0. sumXY := 0. self resetResults! slope "Answers the slope of the receiver (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " slope isNil ifTrue: [ self computeResults]. ^slope! value: aNumber "Answer the value interpolated at aNumber by the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " ^aNumber * self slope + self intercept! ! !DhbLinearRegression privateMethods ! coefficients "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " ^Array with: self intercept with: self slope! computeResults "Private - Compute the results of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " | xNorm xyNorm | xNorm := sumXX * sum1 - (sumX * sumX). xyNorm := sumXY * sum1 - (sumX * sumY). slope := xyNorm / xNorm. intercept := (sumXX * sumY - (sumXY * sumX)) / xNorm. correlationCoefficient := xyNorm / (xNorm * (sumYY * sum1 - (sumY * sumY))) sqrt! resetResults "Private - Reset the results of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " slope := nil. intercept := nil. correlationCoefficient := nil.! ! !DhbMaximumLikekihoodHistogramFit publicMethods ! finalizeIterations "Compute the normalization factor. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 9/3/99 " self computeNormalization. result setCount: count. super finalizeIterations! fitType "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 15/4/99 " ^'Maximum likelihood fit'! initializeIterations "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/3/99 " result setCount: 1. count := dataHolder totalCount. super initializeIterations! normalization "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/12/00 " ^count! normalizationError "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/12/00 " ^countVariance sqrt! valueAndError: aNumber "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/8/00 " | valueGradient gradient gVar | valueGradient := result valueAndGradient: aNumber. gradient := valueGradient last copyFrom: 1 to: valueGradient last size - 1. gVar := gradient * (self errorMatrix * gradient) / count. ^Array with: valueGradient first with: ((valueGradient first / count) squared * countVariance + gVar) sqrt! ! !DhbMaximumLikekihoodHistogramFit privateMethods ! accumulate: aWeightedPoint "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/3/99 " | f g temp inverseProbability| f := result valueAndGradient: aWeightedPoint xValue. g := f last copyFrom: 1 to: ( f last size - 1). f := f first. f = 0 ifTrue: [ ^nil]. inverseProbability := 1 / f. temp := aWeightedPoint yValue * inverseProbability. constants accumulate: g * temp. temp := temp * inverseProbability. 1 to: g size do: [ :k | ( equations at: k) accumulate: g * ( ( g at: k) * temp). ].! computeChanges "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/3/99 " ^super computeChanges copyWith: 0! computeNormalization "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/3/99 " | numerator denominator temp | numerator := 0. denominator := 0. dataHolder pointsAndErrorsDo: [:each | temp := result value: each xValue. temp = 0 ifFalse: [numerator := numerator + (each yValue squared / temp). denominator := denominator + temp]]. count := ( numerator / denominator) sqrt. countVariance := numerator / ( 4 * count).! numberOfFreeParameters "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 15/4/99 " ^super numberOfParameters! numberOfParameters "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/3/99 " ^super numberOfParameters - 1! ! !DhbPointSeriesWithError publicMethods ! at: anInteger "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " | pt | pt := points at: anInteger. ^( pt at: 1) @ ( pt at: 2)! collectPoints: aBlock "Collect aBlock for all points of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " ^points collect: [ :each | aBlock value: ( ( each at: 1) @ ( each at: 2))]! pointsAndErrorsDo: aBlock "Evaluate aBlock for all point and errors of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " points do: [ :each | aBlock value: ( DhbWeightedPoint point: (each at: 1) @ (each at: 2) error: (each at: 3))].! pointsDo: aBlock "Evaluate aBlock for all points of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " points do: [ :each | aBlock value: ( ( each at: 1) @ ( each at: 2))].! ! !DhbPointSeriesWithError privateMethods ! sortBlock "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 27/5/99 " ^[ :a :b | a first < b first]! ! !DhbPolynomialLeastSquareFit class publicMethods ! new: anInteger "Create a new instance of the receiver with given degree. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " ^super new initialize: anInteger! new: anInteger on: aCollectionOfPoints "Create a new instance of the receiver with given degree and points. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " ^super new initialize: anInteger on: aCollectionOfPoints! ! !DhbPolynomialLeastSquareFit publicMethods ! add: aWeightedPoint "Add a point to the collection of points. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " ^pointCollection add: aWeightedPoint! evaluate "Perform the least square fit and answers the fitted polynomial. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " | system errorMatrix | system := self computeEquations. errorMatrix := ( system at: 1) inverse. ^( DhbEstimatedPolynomial coefficients: errorMatrix * (system at: 2)) errorMatrix: errorMatrix; yourself! ! !DhbPolynomialLeastSquareFit privateMethods ! accumulate: aWeightedPoint into: aVectorOfVectors and: aVector "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " | t p powers | p := 1.0. powers := aVector collect: [ :each | t := p. p := p * aWeightedPoint xValue. t]. aVector accumulate: powers * ( aWeightedPoint yValue * aWeightedPoint weight). 1 to: aVector size do: [ :k | ( aVectorOfVectors at: k) accumulate: powers * ( ( powers at: k) * aWeightedPoint weight). ].! computeEquations "Private - Answer a pair Matrix/Vector defining the system of equations to solve the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " | rows vector | vector := ( DhbVector new: degreePlusOne) atAllPut: 0 ; yourself. rows := ( 1 to: degreePlusOne) collect: [ :k | ( DhbVector new: degreePlusOne) atAllPut: 0 ; yourself]. pointCollection do: [ :each | self accumulate: each into: rows and: vector]. ^Array with: ( DhbSymmetricMatrix rows: rows) with: vector! initialize: anInteger "Private - Create an empty point collection for the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " ^self initialize: anInteger on: OrderedCollection new! initialize: anInteger on: aCollectionOfPoints "Private - Defines the collection of points for the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 18/3/99 " pointCollection := aCollectionOfPoints. degreePlusOne := anInteger + 1. ^self! ! !DhbStatisticalMoments publicMethods ! tConfidenceLevel: aStatisticalMomentsOrHistogram "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 1/22/00 " | sbar dof | dof := self count + aStatisticalMomentsOrHistogram count - 2. sbar := ( ( self unnormalizedVariance + aStatisticalMomentsOrHistogram unnormalizedVariance) / dof) sqrt. ^( DhbStudentDistribution degreeOfFreedom: dof) confidenceLevel: ( self average - (aStatisticalMomentsOrHistogram average)) / ( ( 1 / self count + ( 1 / aStatisticalMomentsOrHistogram count)) sqrt * sbar)! ! !DhbWeightedPoint class publicMethods ! point: aPoint "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/5/00 " ^self new initialize: aPoint weight: 1! point: aNumber count: anInteger "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/5/00 " ^self point: aNumber @ anInteger weight: ( anInteger > 0 ifTrue: [ 1 / anInteger] ifFalse:[ 1])! point: aPoint error: aNumber "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/5/00 " ^self new initialize: aPoint error: aNumber! point: aPoint weight: aNumber "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/5/00 " ^self new initialize: aPoint weight: aNumber! ! !DhbWeightedPoint publicMethods ! chi2ComparisonContribution: aWeightedPoint "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/5/00 " ^(aWeightedPoint yValue - yValue) squared / ( 1 / aWeightedPoint weight + ( 1 / weight))! chi2Contribution: aFunction "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/5/00 " ^(yValue - ( aFunction value: xValue)) squared * weight! error "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/5/00 " error isNil ifTrue: [ error := 1 / weight sqrt]. ^error! point "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/5/00 " ^xValue @ yValue! weight ^weight! xValue ^xValue! yValue ^yValue! ! !DhbWeightedPoint privateMethods ! initialize: aPoint error: aNumber "Private - (c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/5/00 " error := aNumber. ^self initialize: aPoint weight: 1 / aNumber squared! initialize: aPoint weight: aNumber "Private - (c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/5/00 " xValue := aPoint x. yValue := aPoint y. weight := aNumber. ^self! ! DhbLeastSquareFit initializeAfterLoad! DhbMaximumLikekihoodHistogramFit initializeAfterLoad! DhbLinearRegression initializeAfterLoad! DhbEstimatedPolynomial initializeAfterLoad! DhbPolynomialLeastSquareFit initializeAfterLoad! DhbWeightedPoint initializeAfterLoad! DhbPointSeriesWithError initializeAfterLoad! DhbEstimation initializeAfterLoad!