Nodes of different colours represent the following:
Solid arrows point from a parent (sub)module to the submodule which is descended from it. Dashed arrows point from a module being used to the module or program unit using it. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer | :: | CurveNum | ||||
character(len=MaxNameLength) | :: | TableType | ||||
character(len=MaxNameLength) | :: | CurveName | ||||
real(kind=R64), | DIMENSION(:) | :: | RawDataX | |||
real(kind=R64), | DIMENSION(:) | :: | RawDataY | |||
real(kind=R64), | optional | DIMENSION(:) | :: | RawDataX2 |
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
SUBROUTINE SolveRegression(CurveNum, TableType, CurveName, RawDataX, RawDataY, RawDataX2)
! SUBROUTINE INFORMATION:
! AUTHOR Richard Raustad, FSEC
! DATE WRITTEN June 2010
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS FUNCTION:
! Given the curve index and the values of 1 or 2 independent variables,
! calls the curve or table routine to return the value of an equipment performance curve or table.
! The solution requires use of linear algebra and forms a matrix of sums of the data set.
! For a linear equation of the form Z = a + bX + cX^2, the general solution is as follows.
!
! Phi = SUM1ToN[Zi - f(Xi)]^2 = SUM1ToN[Zi - (a+bX+cX^2)]^2 = minimum
!
! substitue Y = X^2 in the equations above.
! then set up the partials of Phi with respect to a, the partial of Phi with respect to b, etc.
!
! PartialPhiRespectToa = 2 * SUM1ToN[1*(Zi-(a+bXi+cYi))] = 0
! PartialPhiRespectTob = 2 * SUM1ToN[Xi(Zi-(a+bXi+cYi))] = 0
! PartialPhiRespectTob = 2 * SUM1ToN[Yi(Zi-(a+bXi+cYi))] = 0
!
! then set up the square matrix by solving the above partials.
!
! SUM1ToN(Zi) = a * SUM1ToN(1) + b * SUM1ToN(Xi) + c * SUM1ToN(Yi)
! SUM1ToN(ZiXi) = a * SUM1ToN(Xi) + b * SUM1ToN(Xi)^2 + c * SUM1ToN(XiYi)
! SUM1ToN(ZiYi) = a * SUM1ToN(Yi) + b * SUM1ToN(XiYi) + c * SUM1ToN(Yi)^2
!
! the matirx (A) is then the 3x3 matrix on the right, with a solution of the 1x3 matrix on the left
! Note symmetry about the diagonal.
! (i.e., A(1,2)=A(2,1), A(1,3)=A(3,1), A(3,2)=A(2,3), and diagonal are all squared terms)
! _ _ _ _
! | SUM1ToN(1) SUM1ToN(Xi) SUM1ToN(Yi) | | SUM1ToN(Zi) |
! A = | SUM1ToN(Xi) SUM1ToN(Xi)^2 SUM1ToN(XiYi) | Results = | SUM1ToN(ZiXi) |
! |_ SUM1ToN(Yi) SUM1ToN(XiYi) SUM1ToN(Yi)^2 _| |_ SUM1ToN(ZiYi)_|
!
! The linear algebra equation is then solved using foward elimination and reverse substitution
! This solution (Results) provides the coefficients of the associated performance curve (a,b,and c in the eq. above).
!
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE General, ONLY: RoundSigDigits, TrimSigDigits
USE DataGlobals, ONLY: DisplayAdvancedReportVariables, OutputFileInits
USE DataInterfaces, ONLY: ShowContinueError, ShowSevereError
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER :: CurveNum ! index to performance curve
Character(len=MaxNameLength) :: TableType ! tabular data object type
Character(len=MaxNameLength) :: CurveName ! performance curve name
Real(R64), DIMENSION(:) :: RawDataX ! table data X values (1st independent variable)
Real(R64), DIMENSION(:) :: RawDataY ! table data Y values (dependent variables)
Real(R64), OPTIONAL, DIMENSION(:) :: RawDataX2 ! table data X2 values (2nd independent variable)
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
Real(r64) :: X, X2, Y, V, U, T, Z ! linear algebra equation coefficients
INTEGER :: MatrixSize ! square matrix array size (MatrixSize,MatrixSize)
INTEGER :: LoopCount ! loop counter
INTEGER :: N, i, j, k ! loop variables
Real(r64) :: C ! intermediate calculation of a constant in matrix solution
Real(r64) :: sX ! sum of the X
Real(r64) :: sX2 ! sum of the X^2
Real(r64) :: sX3 ! sum of the X^3
Real(r64) :: sY ! sum of the Y
Real(r64) :: sY2 ! sum of the Y^2
Real(r64) :: sV ! sum of the V
Real(r64) :: sV2 ! sum of the V^2
Real(r64) :: sU ! sum of the U
Real(r64) :: sU2 ! sum of the U^2
Real(r64) :: sT ! sum of the T
Real(r64) :: sT2 ! sum of the T^2
Real(r64) :: sXY ! sum of the XY
Real(r64) :: sXV ! sum of the XV
Real(r64) :: sXU ! sum of the XU
Real(r64) :: sXT ! sum of the XT
Real(r64) :: sYV ! sum of the TV
Real(r64) :: sYU ! sum of the YU
Real(r64) :: sYT ! sum of the YT
Real(r64) :: sVU ! sum of the VU
Real(r64) :: sVT ! sum of the VT
Real(r64) :: sUT ! sum of the UT
Real(r64) :: Results1 ! regression coefficient #1
Real(r64) :: Results2 ! regression coefficient #2
Real(r64) :: Results3 ! regression coefficient #3
Real(r64) :: Results4 ! regression coefficient #4
Real(r64) :: Results5 ! regression coefficient #5
Real(r64) :: Results6 ! regression coefficient #6
Real(r64) :: MinX, MaxX, MinX2, MaxX2, MinY, MaxY ! equation variable min/max statistics
Real(r64) :: Mean, RSquared, StandardError, Est ! statistical parameters
Real(r64),ALLOCATABLE,DIMENSION(:) :: Results ! performance curve coefficients
Real(r64),ALLOCATABLE,DIMENSION(:,:) :: A ! linear algebra matrix
Character(len=MaxNameLength) :: StrCurve ! string representation of curve type
LOGICAL, SAVE :: WriteHeaderOnce = .TRUE.
LOGICAL :: EchoTableDataToEio ! logical set equal to global and used to report to eio file
EchoTableDataToEio = DisplayAdvancedReportVariables
SELECT CASE(PerfCurve(CurveNum)%CurveType)
CASE(LINEAR)
MatrixSize = 2
StrCurve = 'Linear'
CASE(QUADRATIC)
MatrixSize = 3
StrCurve = 'Quadratic'
CASE(CUBIC)
MatrixSize = 4
StrCurve = 'Cubic'
CASE(QUARTIC)
MatrixSize = 5
StrCurve = 'Quartic'
CASE(BIQUADRATIC)
MatrixSize = 6
StrCurve = 'BiQuadratic'
CASE(QUADRATICLINEAR)
MatrixSize = 6
StrCurve = 'QuadraticLinear'
CASE DEFAULT
RETURN
END SELECT
IF(SIZE(RawDataX) .LT. (MatrixSize))THEN
SELECT CASE(PerfCurve(CurveNum)%ObjectType)
CASE(CurveType_TableOneIV)
CALL ShowSevereError('TABLE:ONEINDEPENDENTVARIABLE: "'//TRIM(PerfCurve(CurveNum)%Name)//'"')
CASE(CurveType_TableTwoIV)
CALL ShowSevereError('TABLE:TWOINDEPENDENTVARIABLES: "'//TRIM(PerfCurve(CurveNum)%Name)//'"')
CASE(CurveType_TableMultiIV)
CALL ShowSevereError('TABLE:MULTIVARIABLELOOKUP: "'//TRIM(PerfCurve(CurveNum)%Name)//'"')
CASE DEFAULT
CALL ShowSevereError('SOLVEREGRESSION: Incorrect object type with name = '//TRIM(PerfCurve(CurveNum)%Name)//'"')
END SELECT
CALL ShowContinueError('Insufficient data to calculate regression coefficients.')
CALL ShowContinueError('Required data pairs = '//trim(RoundSigDigits(MatrixSize)))
CALL ShowContinueError('Entered data pairs = '//trim(RoundSigDigits(SIZE(RawDataX))))
CALL ShowContinueError('Setting interpolation type equal to LinearInterpolationOfTable and simulation continues.')
PerfCurve(CurveNum)%InterpolationType = LinearInterpolationOfTable
RETURN
END IF
ALLOCATE(Results(MatrixSize))
Results = 0.0D0
ALLOCATE(A(MatrixSize,MatrixSize))
! ' Sum data
N = 0
sX = 0.0d0
SX2 = 0.0d0
SY = 0.0d0
SY2 = 0.0d0
SV = 0.0d0
SV2 = 0.0d0
SU = 0.0d0
SU2 = 0.0d0
ST = 0.0d0
ST2 = 0.0d0
SXY = 0.0d0
SXV = 0.0d0
SXU = 0.0d0
SXT = 0.0d0
SYV = 0.0d0
SYU = 0.0d0
SYT = 0.0d0
SVU = 0.0d0
SVT = 0.0d0
SUT = 0.0d0
Results = 0.0d0
Results1 = 0.0d0
Results2 = 0.0d0
Results3 = 0.0d0
Results4 = 0.0d0
Results5 = 0.0d0
Results6 = 0.0d0
X2 = 0.0D0
Y = 0.0D0
V = 0.0D0
U = 0.0D0
T = 0.0D0
DO LoopCount = 1, SIZE(RawDataX)
X = RawDataX(LoopCount)
IF(Present(RawDataX2))X2 = RawDataX2(LoopCount)
SELECT CASE(PerfCurve(CurveNum)%CurveType)
CASE(LINEAR,QUADRATIC,CUBIC,QUARTIC)
Y=X*X
V=X*Y
U=X*V
CASE(BIQUADRATIC)
Y=X*X
V=X2
U=V*V
T=X*X2
CASE(QUADRATICLINEAR)
Y=X*X
V=X2
U=X*V
T=Y*X2
CASE DEFAULT
END SELECT
Z = RawDataY(LoopCount)
N = N + 1 ! Count
sX = sX + X ! Sum X
SX2 = SX2 + X * X ! Sum X*X
SY = SY + Y ! Sum Y
SY2 = SY2 + Y * Y ! Sum Y*Y
SV = SV + V ! Sum V
SV2 = SV2 + V * V ! Sum V*V
SU = SU + U ! Sum U
SU2 = SU2 + U * U ! Sum U*U
ST = ST + T ! Sum T
ST2 = ST2 + T * T ! Sum T*T
SXY = SXY + X * Y ! Sum XY
SXV = SXV + X * V ! Sum XV
SXU = SXU + X * U ! Sum XU
SXT = SXT + X * T ! Sum XT
SYV = SYV + Y * V ! Sum YV
SYU = SYU + Y * U ! Sum YU
SYT = SYT + Y * T ! Sum YT
SVU = SVU + V * U ! Sum VU
SVT = SVT + V * T ! Sum VT
SUT = SUT + U * T ! Sum UT
Results1 = Results1 + Z ! Sum Z
Results2 = Results2 + Z * X ! Sum ZX
Results3 = Results3 + Z * Y ! Sum ZY
Results4 = Results4 + Z * V ! Sum ZV
Results5 = Results5 + Z * U ! Sum ZU
Results6 = Results6 + Z * T ! Sum ZT
END DO
Results(1) = Results1
Results(2) = Results2
SELECT CASE(PerfCurve(CurveNum)%CurveType)
CASE(LINEAR)
CASE(QUADRATIC)
Results(3) = Results3
CASE(CUBIC)
Results(3) = Results3
Results(4) = Results4
CASE(QUARTIC)
Results(3) = Results3
Results(4) = Results4
Results(5) = Results5
CASE(BIQUADRATIC,QUADRATICLINEAR)
Results(3) = Results3
Results(4) = Results4
Results(5) = Results5
Results(6) = Results6
END SELECT
Mean = Results(1) / N
! ' Form "A" Matrix
A(1, 1) = Real(N,r64)
A(1, 2) = sX
A(2, 2) = SX2
SELECT CASE(PerfCurve(CurveNum)%CurveType)
CASE(LINEAR)
CASE(QUADRATIC)
A(1, 3) = SY
A(2, 3) = SXY
A(3, 3) = SY2
CASE(CUBIC)
A(1, 3) = SY
A(1, 4) = SV
A(2, 3) = SXY
A(2, 4) = SXV
A(3, 3) = SY2
A(3, 4) = SYV
A(4, 4) = SV2
CASE(QUARTIC)
A(1, 3) = SY
A(1, 4) = SV
A(1, 5) = SU
A(2, 3) = SXY
A(2, 4) = SXV
A(2, 5) = SXU
A(3, 3) = SY2
A(3, 4) = SYV
A(3, 5) = SYU
A(4, 4) = SV2
A(4, 5) = SVU
A(5, 5) = SU2
CASE(BIQUADRATIC,QUADRATICLINEAR)
A(1, 3) = SY
A(1, 4) = SV
A(1, 5) = SU
A(1, 6) = ST
A(2, 3) = SXY
A(2, 4) = SXV
A(2, 5) = SXU
A(2, 6) = SXT
A(3, 3) = SY2
A(3, 4) = SYV
A(3, 5) = SYU
A(3, 6) = SYT
A(4, 4) = SV2
A(4, 5) = SVU
A(4, 6) = SVT
A(5, 5) = SU2
A(5, 6) = SUT
A(6, 6) = ST2
CASE DEFAULT
END SELECT
! copy elements to bottom half of symmetrical square matrix
DO i = 1, MatrixSize - 1
DO j = i + 1, MatrixSize
A(j, i) = A(i, j)
END DO
END DO
! Forward Eliminiation
DO i = 1, MatrixSize - 1
If (A(i, i) .EQ. 0.0D0) Then
CALL ShowSevereError('SolveRegression: Zero value on the diagonal.')
CALL ShowContinueError('Setting interpolation type equal to LinearInterpolationOfTable and simulation continues.')
PerfCurve(CurveNum)%InterpolationType = LinearInterpolationOfTable
RETURN
End If
DO j = i + 1, MatrixSize
! find the ratio of the element to the one above it
C = A(j, i) / A(i, i)
! replace the element by reducing it by the ratio multiplied by the element above it
! this makes the bottom half of symmetrical square matix 0's
DO k = i, MatrixSize
A(j, k) = A(j, k) - C * A(i, k)
END DO
Results(j) = Results(j) - C * Results(i)
END DO
END DO
! ' Back Substitution
If (A(MatrixSize, MatrixSize) .EQ. 0.0D0) Then
CALL ShowSevereError('SolveRegression: Zero value on the diagonal end point.')
CALL ShowContinueError('Setting interpolation type equal to LinearInterpolationOfTable and simulation continues.')
PerfCurve(CurveNum)%InterpolationType = LinearInterpolationOfTable
RETURN
End If
! now starting at the lower right corner of the matrix solve for the last coefficient
Results(MatrixSize) = Results(MatrixSize) / A(MatrixSize, MatrixSize)
! substitute that coefficient back into the equation above it and solve for the 2nd to last coefficient
! proceed until all coefficients are found
DO i = MatrixSize - 1, 1, -1
C = Results(i)
DO j = 1, MatrixSize - i
C = C - A(i, i + j) * Results(i + j)
END DO
Results(i) = C / A(i, i)
END DO
! calculate the regression statistics
sX = 0.0D0
sX2 = 0.0D0
sX3 = 0.0D0
MinX = 9999999.0D0
MaxX = -9999999.0D0
MinX2 = 9999999.0D0
MaxX2 = -9999999.0D0
MinY = 9999999.0D0
MaxY = -9999999.0D0
DO LoopCount = 1, N
X = RawDataX(LoopCount)
IF(Present(RawDataX2))X2 = RawDataX2(LoopCount)
SELECT CASE(PerfCurve(CurveNum)%CurveType)
CASE(LINEAR,QUADRATIC,CUBIC,QUARTIC)
Y=X*X
V=X*Y
U=X*V
CASE(BIQUADRATIC)
Y=X*X
V=X2
U=V*V
T=X*X2
CASE(QUADRATICLINEAR)
Y=X*X
V=X2
U=X*V
T=Y*X2
CASE DEFAULT
END SELECT
Z = RawDataY(LoopCount)
IF(MinX .GT. X)MinX = X
IF(MaxX .LT. X)MaxX = X
IF(MinX2 .GT. X2)MinX2 = X2
IF(MaxX2 .LT. X2)MaxX2 = X2
IF(MinY .GT. Z)MinY = Z
IF(MaxY .LT. Z)MaxY = Z
SELECT CASE(PerfCurve(CurveNum)%CurveType)
CASE(LINEAR)
Est = Results(1) + X*Results(2)
CASE(QUADRATIC)
Est = Results(1) + X*Results(2) + Y*Results(3)
CASE(CUBIC)
Est = Results(1) + X*Results(2) + Y*Results(3) + V*Results(4)
CASE(QUARTIC)
Est = Results(1) + X*Results(2) + Y*Results(3) + V*Results(4) + U*Results(5)
CASE(BIQUADRATIC,QUADRATICLINEAR)
Est = Results(1) + X*Results(2) + Y*Results(3) + V*Results(4) + U*Results(5) + T*Results(6)
CASE DEFAULT
END SELECT
sX = sX + (Est - Mean) * (Est - Mean)
sX2 = sX2 + (Z-Mean) * (Z-Mean)
sX3 = sX3 + (Z-Est) * (Z-Est)
END DO
IF(sX2 .NE. 0.0D0)THEN
RSquared = sX / sX2
ELSE
RSquared = 0.0D0
END IF
IF(N .GT. MatrixSize)THEN
StandardError = SQRT(sX3/(N-MatrixSize))
ELSE
StandardError = 0.0D0
END IF
SELECT CASE(PerfCurve(CurveNum)%InterpolationType)
CASE(LinearInterpolationOfTable)
CASE(EvaluateCurveToLimits)
MinX = MIN(MinX,PerfCurve(CurveNum)%Var1Min)
MaxX = MAX(MaxX,PerfCurve(CurveNum)%Var1Max)
MinX2 = MIN(MinX2,PerfCurve(CurveNum)%Var2Min)
MaxX2 = MAX(MaxX2,PerfCurve(CurveNum)%Var2Max)
MinY = MIN(MinY,PerfCurve(CurveNum)%CurveMin)
MaxY = MAX(MaxY,PerfCurve(CurveNum)%CurveMax)
CASE DEFAULT
END SELECT
! echo new curve object to eio file
110 FORMAT('! <CREATING NEW CURVE OBJECT>')
130 FORMAT('CREATING NEW CURVE OBJECT')
IF(EchoTableDataToEio)THEN
IF(WriteHeaderOnce)THEN
WRITE(OutputFileInits,110)
WriteHeaderOnce = .FALSE.
END IF
140 FORMAT('! Input as ',A,' "',A,'"')
150 FORMAT('! RSquared = ',A)
160 FORMAT('! Standard Error = ',A)
170 FORMAT('! Sample Size = ',A)
180 FORMAT('Curve:',A,',')
190 FORMAT('FromTable_',A,', !- Name')
200 FORMAT(' ',A,', !- Coefficient1 Constant')
210 FORMAT(' ',A,', !- Coefficient2 x')
300 FORMAT(' ',A,', !- Minimum Value of x')
310 FORMAT(' ',A,', !- Maximum Value of x')
340 FORMAT(' ',A,', !- Minimum Curve Output')
350 FORMAT(' ',A,'; !- Maximum Curve Output')
360 FORMAT('END CREATING NEW CURVE OBJECT')
WRITE(OutputFileInits,130)
WRITE(OutputFileInits,140)TRIM(TableType),TRIM(CurveName)
WRITE(OutputFileInits,150)TRIM(RoundSigDigits(RSquared,10))
WRITE(OutputFileInits,160)TRIM(RoundSigDigits(StandardError,10))
WRITE(OutputFileInits,170)TRIM(TrimSigDigits(N))
WRITE(OutputFileInits,180)TRIM(StrCurve)
WRITE(OutputFileInits,190)TRIM(CurveName)
WRITE(OutputFileInits,200)TRIM(RoundSigDigits(Results(1),10))
SELECT CASE(PerfCurve(CurveNum)%CurveType)
CASE(LINEAR,QUADRATIC,CUBIC,QUARTIC,BIQUADRATIC,QUADRATICLINEAR)
WRITE(OutputFileInits,210)TRIM(RoundSigDigits(Results(2),10))
CASE DEFAULT
END SELECT
SELECT CASE(PerfCurve(CurveNum)%CurveType)
CASE(QUADRATIC,CUBIC,QUARTIC,BIQUADRATIC,QUADRATICLINEAR)
220 FORMAT(' ',A,', !- Coefficient3 x**2')
WRITE(OutputFileInits,220)TRIM(RoundSigDigits(Results(3),10))
CASE DEFAULT
END SELECT
SELECT CASE(PerfCurve(CurveNum)%CurveType)
CASE(CUBIC,QUARTIC)
230 FORMAT(' ',A,', !- !- Coefficient4 x**3')
WRITE(OutputFileInits,230)TRIM(RoundSigDigits(Results(4),10))
CASE(BIQUADRATIC,QUADRATICLINEAR)
240 FORMAT(' ',A,', !- Coefficient4 y')
WRITE(OutputFileInits,240)TRIM(RoundSigDigits(Results(4),10))
CASE DEFAULT
END SELECT
SELECT CASE(PerfCurve(CurveNum)%CurveType)
CASE(QUARTIC)
250 FORMAT(' ',A,', !- !- Coefficient5 x**4')
WRITE(OutputFileInits,250)TRIM(RoundSigDigits(Results(5),10))
CASE(BIQUADRATIC)
260 FORMAT(' ',A,', !- Coefficient5 y**2')
WRITE(OutputFileInits,260)TRIM(RoundSigDigits(Results(5),10))
CASE(QUADRATICLINEAR)
270 FORMAT(' ',A,', !- Coefficient5 xy')
WRITE(OutputFileInits,270)TRIM(RoundSigDigits(Results(5),10))
CASE DEFAULT
END SELECT
SELECT CASE(PerfCurve(CurveNum)%CurveType)
CASE(BIQUADRATIC)
280 FORMAT(' ',A,', !- Coefficient6 x*y')
WRITE(OutputFileInits,280)TRIM(RoundSigDigits(Results(6),10))
CASE(QUADRATICLINEAR)
290 FORMAT(' ',A,', !- Coefficient6 x**2y')
WRITE(OutputFileInits,290)TRIM(RoundSigDigits(Results(6),10))
CASE DEFAULT
END SELECT
WRITE(OutputFileInits,300)TRIM(RoundSigDigits(MinX,10))
WRITE(OutputFileInits,310)TRIM(RoundSigDigits(MaxX,10))
SELECT CASE(PerfCurve(CurveNum)%CurveType)
CASE(QUARTIC)
CASE(BIQUADRATIC,QUADRATICLINEAR)
320 FORMAT(' ',A,', !- Minimum Value of y')
330 FORMAT(' ',A,', !- Maximum Value of y')
WRITE(OutputFileInits,320)TRIM(RoundSigDigits(MinX2,10))
WRITE(OutputFileInits,330)TRIM(RoundSigDigits(MaxX2,10))
CASE DEFAULT
END SELECT
WRITE(OutputFileInits,340)TRIM(RoundSigDigits(MinY,10))
WRITE(OutputFileInits,350)TRIM(RoundSigDigits(MaxY,10))
WRITE(OutputFileInits,360)
END IF
! save results in performance curve structure
SELECT CASE(PerfCurve(CurveNum)%CurveType)
CASE(LINEAR)
PerfCurve(CurveNum)%Coeff1 = Results(1)
PerfCurve(CurveNum)%Coeff2 = Results(2)
CASE(QUADRATIC)
PerfCurve(CurveNum)%Coeff1 = Results(1)
PerfCurve(CurveNum)%Coeff2 = Results(2)
PerfCurve(CurveNum)%Coeff3 = Results(3)
CASE(CUBIC)
PerfCurve(CurveNum)%Coeff1 = Results(1)
PerfCurve(CurveNum)%Coeff2 = Results(2)
PerfCurve(CurveNum)%Coeff3 = Results(3)
PerfCurve(CurveNum)%Coeff4 = Results(4)
CASE(QUARTIC)
PerfCurve(CurveNum)%Coeff1 = Results(1)
PerfCurve(CurveNum)%Coeff2 = Results(2)
PerfCurve(CurveNum)%Coeff3 = Results(3)
PerfCurve(CurveNum)%Coeff4 = Results(4)
PerfCurve(CurveNum)%Coeff5 = Results(5)
CASE(BIQUADRATIC,QUADRATICLINEAR)
PerfCurve(CurveNum)%Coeff1 = Results(1)
PerfCurve(CurveNum)%Coeff2 = Results(2)
PerfCurve(CurveNum)%Coeff3 = Results(3)
PerfCurve(CurveNum)%Coeff4 = Results(4)
PerfCurve(CurveNum)%Coeff5 = Results(5)
PerfCurve(CurveNum)%Coeff6 = Results(6)
CASE DEFAULT
END SELECT
PerfCurve(CurveNum)%Var1Min = MinX
PerfCurve(CurveNum)%Var1Max = MaxX
PerfCurve(CurveNum)%Var2Min = MinX2
PerfCurve(CurveNum)%Var2Max = MaxX2
PerfCurve(CurveNum)%CurveMin = MinY
PerfCurve(CurveNum)%CurveMax = MaxY
PerfCurve(CurveNum)%CurveMinPresent = .TRUE.
PerfCurve(CurveNum)%CurveMaxPresent = .TRUE.
DEALLOCATE(A)
DEALLOCATE(Results)
END SUBROUTINE SolveRegression