regression-simple-0.1.1: Simple linear and quadratic regression
Safe HaskellNone
LanguageHaskell2010

Math.Regression.Simple

Synopsis

Regressions

linear :: (Foldable' xs x, IsDoublePair x) => xs -> V2 Source #

Linear regression.

The type is

linear :: [(Double, Double)] -> V2

but overloaded to work with boxed and unboxed Vectors.

>>> let input1 = [(0, 1), (1, 3), (2, 5)]
>>> PP $ linear input1
V2 2.0000 1.00000
>>> let input2 = [(0.1, 1.2), (1.3, 3.1), (1.9, 4.9), (3.0, 7.1), (4.1, 9.0)]
>>> PP $ linear input2
V2 2.0063 0.88685

linearWithErrors :: (Foldable' xs x, IsDoublePair x) => xs -> (V2, V2) Source #

Like linear but also return parameters' standard errors.

To get confidence intervals you should multiply the errors by quantile (studentT (n - 2)) ci' from statistics package or similar. For big n using value 1 gives 68% interval and using value 2 gives 95% confidence interval. See https://en.wikipedia.org/wiki/Student%27s_t-distribution#Table_of_selected_values (quantile calculates one-sided values, you need two-sided, thus adjust ci value).

The first input is perfect fit:

>>> PP $ linearWithErrors input1
(V2 2.0000 1.00000, V2 0.00000 0.00000)

The second input is quite good:

>>> PP $ linearWithErrors input2
(V2 2.0063 0.88685, V2 0.09550 0.23826)

But the third input isn't so much, standard error of a slope argument is 20%.

>>> let input3 = [(0, 2), (1, 3), (2, 6), (3, 11)]
>>> PP $ linearWithErrors input3
(V2 3.0000 1.00000, V2 0.63246 1.1832)

Since: 0.1.1

quadratic :: (Foldable' xs x, IsDoublePair x) => xs -> V3 Source #

Quadratic regression.

The type is

quadratic :: [(Double, Double)] -> V3

but overloaded to work with boxed and unboxed Vectors.

>>> let input1 = [(0, 1), (1, 3), (2, 5)]
>>> quadratic input1
V3 0.0 2.0 1.0
>>> let input2 = [(0.1, 1.2), (1.3, 3.1), (1.9, 4.9), (3.0, 7.1), (4.1, 9.0)]
>>> PP $ quadratic input2
V3 (-0.00589) 2.0313 0.87155
>>> let input3 = [(0, 2), (1, 3), (2, 6), (3, 11)]
>>> PP $ quadratic input3
V3 1.00000 0.00000 2.0000

quadraticWithErrors :: (Foldable' xs x, IsDoublePair x) => xs -> (V3, V3) Source #

Like quadratic but also return parameters' standard errors.

>>> PP $ quadraticWithErrors input2
(V3 (-0.00589) 2.0313 0.87155, V3 0.09281 0.41070 0.37841)
>>> PP $ quadraticWithErrors input3
(V3 1.00000 0.00000 2.0000, V3 0.00000 0.00000 0.00000)

Since: 0.1.1

quadraticAndLinear :: (Foldable' xs x, IsDoublePair x) => xs -> (V3, V2) Source #

Do both linear and quadratic regression in one data scan.

>>> PP $ quadraticAndLinear input2
(V3 (-0.00589) 2.0313 0.87155, V2 2.0063 0.88685)

quadraticAndLinearWithErrors :: (Foldable' xs x, IsDoublePair x) => xs -> ((V3, V2), (V3, V2)) Source #

Like quadraticAndLinear but also return parameters' standard errors

>>> PP $ quadraticAndLinearWithErrors input2
((V3 (-0.00589) 2.0313 0.87155, V2 2.0063 0.88685), (V3 0.09281 0.41070 0.37841, V2 0.09550 0.23826))

Since: 0.1.1

Operations

class Add a where Source #

Addition

Methods

zero :: a Source #

add :: a -> a -> a infixl 6 Source #

Instances

Instances details
Add Double Source # 
Instance details

Defined in Math.Regression.Simple

Add M33 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

zero :: M33 Source #

add :: M33 -> M33 -> M33 Source #

Add V3 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

zero :: V3 Source #

add :: V3 -> V3 -> V3 Source #

Add M22 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

zero :: M22 Source #

add :: M22 -> M22 -> M22 Source #

Add V2 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

zero :: V2 Source #

add :: V2 -> V2 -> V2 Source #

class Eye a where Source #

Identity

Methods

eye :: a Source #

Instances

Instances details
Eye Double Source # 
Instance details

Defined in Math.Regression.Simple

Methods

eye :: Double Source #

Eye M33 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

eye :: M33 Source #

Eye M22 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

eye :: M22 Source #

class Eye a => Mult a b c | a b -> c where Source #

Multiplication of different things.

Methods

mult :: a -> b -> c infixl 7 Source #

Instances

Instances details
Mult Double M33 M33 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: Double -> M33 -> M33 Source #

Mult Double V3 V3 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: Double -> V3 -> V3 Source #

Mult Double M22 M22 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: Double -> M22 -> M22 Source #

Mult Double V2 V2 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: Double -> V2 -> V2 Source #

Mult M33 V3 V3 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: M33 -> V3 -> V3 Source #

Mult M22 M22 M22 Source #
>>> M22 1 2 3 4 `mult` eye @M22
M22 1.0 2.0 3.0 4.0
Instance details

Defined in Math.Regression.Simple

Methods

mult :: M22 -> M22 -> M22 Source #

Mult M22 V2 V2 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: M22 -> V2 -> V2 Source #

class Eye a => Det a where Source #

Determinant

Methods

det :: a -> Double Source #

Instances

Instances details
Det Double Source # 
Instance details

Defined in Math.Regression.Simple

Methods

det :: Double -> Double Source #

Det M33 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

det :: M33 -> Double Source #

Det M22 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

det :: M22 -> Double Source #

class Det a => Inv a where Source #

Inverse

Methods

inv :: a -> a Source #

Instances

Instances details
Inv Double Source # 
Instance details

Defined in Math.Regression.Simple

Methods

inv :: Double -> Double Source #

Inv M33 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

inv :: M33 -> M33 Source #

Inv M22 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

inv :: M22 -> M22 Source #

Zeros

zerosLin :: V2 -> Double Source #

Solve linear equation.

>>> zerosLin (V2 1 2)
-2.0

zerosQuad :: V3 -> Either (Complex Double, Complex Double) (Double, Double) Source #

Solve quadratic equation.

>>> zerosQuad (V3 2 0 (-1))
Right (-0.7071067811865476,0.7071067811865476)
>>> zerosQuad (V3 2 0 1)
Left ((-0.0) :+ (-0.7071067811865476),(-0.0) :+ 0.7071067811865476)

Double root is not treated separately:

>>> zerosQuad (V3 1 0 0)
Right (-0.0,0.0)
>>> zerosQuad (V3 1 (-2) 1)
Right (1.0,1.0)

optimaQuad :: V3 -> Double Source #

Find an optima point.

>>> optimaQuad (V3 1 (-2) 0)
1.0

compare to

>>> zerosQuad (V3 1 (-2) 0)
Right (0.0,2.0)

Two dimensions

data V2 Source #

2d vector. Strict pair of Doubles.

Also used to represent linear polynomial: V2 a b \(= a x + b\).

Constructors

V2 !Double !Double 

Instances

Instances details
Eq V2 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

(==) :: V2 -> V2 -> Bool #

(/=) :: V2 -> V2 -> Bool #

Show V2 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

showsPrec :: Int -> V2 -> ShowS #

show :: V2 -> String #

showList :: [V2] -> ShowS #

IsDoublePair V2 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

withDP :: V2 -> (Double -> Double -> r) -> r Source #

makeDP :: Double -> Double -> V2 Source #

Add V2 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

zero :: V2 Source #

add :: V2 -> V2 -> V2 Source #

Mult Double V2 V2 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: Double -> V2 -> V2 Source #

Mult M22 V2 V2 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: M22 -> V2 -> V2 Source #

data M22 Source #

2×2 matrix.

Constructors

M22 !Double !Double !Double !Double 

Instances

Instances details
Eq M22 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

(==) :: M22 -> M22 -> Bool #

(/=) :: M22 -> M22 -> Bool #

Show M22 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

showsPrec :: Int -> M22 -> ShowS #

show :: M22 -> String #

showList :: [M22] -> ShowS #

Inv M22 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

inv :: M22 -> M22 Source #

Det M22 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

det :: M22 -> Double Source #

Eye M22 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

eye :: M22 Source #

Add M22 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

zero :: M22 Source #

add :: M22 -> M22 -> M22 Source #

Mult Double M22 M22 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: Double -> M22 -> M22 Source #

Mult M22 M22 M22 Source #
>>> M22 1 2 3 4 `mult` eye @M22
M22 1.0 2.0 3.0 4.0
Instance details

Defined in Math.Regression.Simple

Methods

mult :: M22 -> M22 -> M22 Source #

Mult M22 V2 V2 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: M22 -> V2 -> V2 Source #

Three dimensions

data V3 Source #

3d vector. Strict triple of Doubles.

Also used to represent quadratic polynomial: V3 a b c \(= a x^2 + b x + c\).

Constructors

V3 !Double !Double !Double 

Instances

Instances details
Eq V3 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

(==) :: V3 -> V3 -> Bool #

(/=) :: V3 -> V3 -> Bool #

Show V3 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

showsPrec :: Int -> V3 -> ShowS #

show :: V3 -> String #

showList :: [V3] -> ShowS #

Add V3 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

zero :: V3 Source #

add :: V3 -> V3 -> V3 Source #

Mult Double V3 V3 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: Double -> V3 -> V3 Source #

Mult M33 V3 V3 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: M33 -> V3 -> V3 Source #

data M33 Source #

3×3 matrix.

Instances

Instances details
Eq M33 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

(==) :: M33 -> M33 -> Bool #

(/=) :: M33 -> M33 -> Bool #

Show M33 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

showsPrec :: Int -> M33 -> ShowS #

show :: M33 -> String #

showList :: [M33] -> ShowS #

Inv M33 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

inv :: M33 -> M33 Source #

Det M33 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

det :: M33 -> Double Source #

Eye M33 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

eye :: M33 Source #

Add M33 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

zero :: M33 Source #

add :: M33 -> M33 -> M33 Source #

Mult Double M33 M33 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: Double -> M33 -> M33 Source #

Mult M33 V3 V3 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

mult :: M33 -> V3 -> V3 Source #

Auxiliary classes

class Foldable' xs x | xs -> x where Source #

Like Foldable but with element in the class definition.

Methods

foldl' :: (b -> x -> b) -> b -> xs -> b Source #

Instances

Instances details
Foldable' [a] a Source # 
Instance details

Defined in Math.Regression.Simple

Methods

foldl' :: (b -> a -> b) -> b -> [a] -> b Source #

Unbox a => Foldable' (Vector a) a Source # 
Instance details

Defined in Math.Regression.Simple

Methods

foldl' :: (b -> a -> b) -> b -> Vector a -> b Source #

Foldable' (Vector a) a Source # 
Instance details

Defined in Math.Regression.Simple

Methods

foldl' :: (b -> a -> b) -> b -> Vector a -> b Source #

class IsDoublePair dp where Source #

Class witnessing that dp has a pair of Doubles.

Methods

withDP :: dp -> (Double -> Double -> r) -> r Source #

makeDP :: Double -> Double -> dp Source #

Instances

Instances details
IsDoublePair V2 Source # 
Instance details

Defined in Math.Regression.Simple

Methods

withDP :: V2 -> (Double -> Double -> r) -> r Source #

makeDP :: Double -> Double -> V2 Source #

(a ~ Double, b ~ Double) => IsDoublePair (a, b) Source # 
Instance details

Defined in Math.Regression.Simple

Methods

withDP :: (a, b) -> (Double -> Double -> r) -> r Source #

makeDP :: Double -> Double -> (a, b) Source #