module ELynx.Tools.Equality
(
allEqual,
allNearlyEqualWith,
allNearlyEqual,
nearlyEqWith,
eps,
nearlyEq,
(=~=),
nearlyEqListWith,
nearlyEqList,
nearlyEqVecWith,
nearlyEqVec,
nearlyEqMatWith,
nearlyEqMat,
)
where
import ELynx.Tools.Definitions
import Numeric.LinearAlgebra
allEqual :: Eq a => [a] -> Bool
allEqual :: [a] -> Bool
allEqual [] = Bool
True
allEqual [a]
xs = (a -> Bool) -> [a] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== [a] -> a
forall a. [a] -> a
head [a]
xs) ([a] -> [a]
forall a. [a] -> [a]
tail [a]
xs)
allNearlyEqualWith :: Double -> [Double] -> Bool
allNearlyEqualWith :: Double -> [Double] -> Bool
allNearlyEqualWith Double
_ [] = Bool
True
allNearlyEqualWith Double
tol [Double]
xs = (Double -> Bool) -> [Double] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Double -> Double -> Double -> Bool
nearlyEqWith Double
tol (Double -> Double -> Bool) -> Double -> Double -> Bool
forall a b. (a -> b) -> a -> b
$ [Double] -> Double
forall a. [a] -> a
head [Double]
xs) ([Double] -> [Double]
forall a. [a] -> [a]
tail [Double]
xs)
allNearlyEqual :: [Double] -> Bool
allNearlyEqual :: [Double] -> Bool
allNearlyEqual = Double -> [Double] -> Bool
allNearlyEqualWith Double
eps
nearlyEqWith :: Double -> Double -> Double -> Bool
nearlyEqWith :: Double -> Double -> Double -> Bool
nearlyEqWith Double
tol Double
a Double
b = Double
tol Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double -> Double
forall a. Num a => a -> a
abs (Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
b)
nearlyEq :: Double -> Double -> Bool
nearlyEq :: Double -> Double -> Bool
nearlyEq = Double -> Double -> Double -> Bool
nearlyEqWith Double
eps
(=~=) :: Double -> Double -> Bool
=~= :: Double -> Double -> Bool
(=~=) = Double -> Double -> Bool
nearlyEq
nearlyEqValListWith :: Double -> Double -> [Double] -> Bool
nearlyEqValListWith :: Double -> Double -> [Double] -> Bool
nearlyEqValListWith Double
tol Double
a = (Double -> Bool) -> [Double] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Double -> Double -> Double -> Bool
nearlyEqWith Double
tol Double
a)
nearlyEqListWith :: Double -> [Double] -> [Double] -> Bool
nearlyEqListWith :: Double -> [Double] -> [Double] -> Bool
nearlyEqListWith Double
tol [Double]
xs [Double]
ys = Double -> Double -> [Double] -> Bool
nearlyEqValListWith Double
tol Double
0 ((Double -> Double -> Double) -> [Double] -> [Double] -> [Double]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (-) [Double]
xs [Double]
ys)
nearlyEqList :: [Double] -> [Double] -> Bool
nearlyEqList :: [Double] -> [Double] -> Bool
nearlyEqList = Double -> [Double] -> [Double] -> Bool
nearlyEqListWith Double
eps
nearlyEqVecWith :: Double -> Vector R -> Vector R -> Bool
nearlyEqVecWith :: Double -> Vector Double -> Vector Double -> Bool
nearlyEqVecWith Double
tol Vector Double
a Vector Double
b = Double -> Double -> [Double] -> Bool
nearlyEqValListWith Double
tol Double
0 (Vector Double -> [Double]
forall a. Storable a => Vector a -> [a]
toList (Vector Double -> [Double]) -> Vector Double -> [Double]
forall a b. (a -> b) -> a -> b
$ Vector Double
a Vector Double -> Vector Double -> Vector Double
forall a. Num a => a -> a -> a
- Vector Double
b)
nearlyEqVec :: Vector R -> Vector R -> Bool
nearlyEqVec :: Vector Double -> Vector Double -> Bool
nearlyEqVec = Double -> Vector Double -> Vector Double -> Bool
nearlyEqVecWith Double
eps
nearlyEqMatWith :: Double -> Matrix R -> Matrix R -> Bool
nearlyEqMatWith :: Double -> Matrix Double -> Matrix Double -> Bool
nearlyEqMatWith Double
tol Matrix Double
a Matrix Double
b = Double -> Double -> [Double] -> Bool
nearlyEqValListWith Double
tol Double
0 ([[Double]] -> [Double]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Double]] -> [Double])
-> (Matrix Double -> [[Double]]) -> Matrix Double -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix Double -> [[Double]]
forall t. Element t => Matrix t -> [[t]]
toLists (Matrix Double -> [Double]) -> Matrix Double -> [Double]
forall a b. (a -> b) -> a -> b
$ Matrix Double
a Matrix Double -> Matrix Double -> Matrix Double
forall a. Num a => a -> a -> a
- Matrix Double
b)
nearlyEqMat :: Matrix R -> Matrix R -> Bool
nearlyEqMat :: Matrix Double -> Matrix Double -> Bool
nearlyEqMat = Double -> Matrix Double -> Matrix Double -> Bool
nearlyEqMatWith Double
eps