-- |
-- Module      :  ELynx.Tools.Equality
-- Copyright   :  2021 Dominik Schrempf
-- License     :  GPL-3.0-or-later
--
-- Maintainer  :  dominik.schrempf@gmail.com
-- Stability   :  unstable
-- Portability :  portable
--
-- Creation date: Thu Feb 14 13:27:05 2019.
--
-- Equality tests.
module ELynx.Tools.Equality
  ( -- * Equality
    allEqual,
    allNearlyEqualWith,
    allNearlyEqual,
    nearlyEqWith,
    eps,
    nearlyEq,
    (=~=),
    nearlyEqListWith,
    nearlyEqList,
    nearlyEqVecWith,
    nearlyEqVec,
    nearlyEqMatWith,
    nearlyEqMat,
  )
where

import ELynx.Tools.Definitions
import Numeric.LinearAlgebra

-- | Test if all elements of a list are equal; returns True for empty list.
allEqual :: Eq a => [a] -> Bool
-- Well, maybe it should be False, but then, it is True that all elements are
-- equal :).
allEqual :: forall a. Eq a => [a] -> Bool
allEqual [] = Bool
True
allEqual [a]
xs = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (forall a. Eq a => a -> a -> Bool
== forall a. [a] -> a
head [a]
xs) (forall a. [a] -> [a]
tail [a]
xs)

-- | Test if all elements of a list are nearly equal; returns True for empty list.
allNearlyEqualWith :: Double -> [Double] -> Bool
allNearlyEqualWith :: Double -> [Double] -> Bool
allNearlyEqualWith Double
_ [] = Bool
True
allNearlyEqualWith Double
tol [Double]
xs = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Double -> Double -> Double -> Bool
nearlyEqWith Double
tol forall a b. (a -> b) -> a -> b
$ forall a. [a] -> a
head [Double]
xs) (forall a. [a] -> [a]
tail [Double]
xs)

-- | Test if all elements of a list are nearly equal; returns True for empty list.
allNearlyEqual :: [Double] -> Bool
allNearlyEqual :: [Double] -> Bool
allNearlyEqual = Double -> [Double] -> Bool
allNearlyEqualWith Double
eps

-- | Test for equality with given tolerance (needed because of machine precision).
nearlyEqWith :: Double -> Double -> Double -> Bool
nearlyEqWith :: Double -> Double -> Double -> Bool
nearlyEqWith Double
tol Double
a Double
b = Double
tol forall a. Ord a => a -> a -> Bool
> forall a. Num a => a -> a
abs (Double
a forall a. Num a => a -> a -> a
- Double
b)

-- | Test for equality with predefined tolerance 'eps' (needed because of
-- machine precision).
nearlyEq :: Double -> Double -> Bool
nearlyEq :: Double -> Double -> Bool
nearlyEq = Double -> Double -> Double -> Bool
nearlyEqWith Double
eps

-- | Infix synonym for 'nearlyEq'.
(=~=) :: Double -> Double -> Bool
=~= :: Double -> Double -> Bool
(=~=) = Double -> Double -> Bool
nearlyEq

-- Test if the given number is nearly equal to all elements of a list.
nearlyEqValListWith :: Double -> Double -> [Double] -> Bool
nearlyEqValListWith :: Double -> Double -> [Double] -> Bool
nearlyEqValListWith Double
tol Double
a = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Double -> Double -> Double -> Bool
nearlyEqWith Double
tol Double
a)

-- | Test if two lists are nearly equal.
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 (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (-) [Double]
xs [Double]
ys)

-- | Test if two lists are nearly equal; use tolerance 'eps'.
nearlyEqList :: [Double] -> [Double] -> Bool
nearlyEqList :: [Double] -> [Double] -> Bool
nearlyEqList = Double -> [Double] -> [Double] -> Bool
nearlyEqListWith Double
eps

-- | Test if two vectors are nearly equal.
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 (forall a. Storable a => Vector a -> [a]
toList forall a b. (a -> b) -> a -> b
$ Vector Double
a forall a. Num a => a -> a -> a
- Vector Double
b)

-- | Test if two vectors are nearly equal; use tolerance 'eps'.
nearlyEqVec :: Vector R -> Vector R -> Bool
nearlyEqVec :: Vector Double -> Vector Double -> Bool
nearlyEqVec = Double -> Vector Double -> Vector Double -> Bool
nearlyEqVecWith Double
eps

-- | Test if two vectors are nearly equal.
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 (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Element t => Matrix t -> [[t]]
toLists forall a b. (a -> b) -> a -> b
$ Matrix Double
a forall a. Num a => a -> a -> a
- Matrix Double
b)

-- | Test if two vectors are nearly equal; use tolerance 'eps'.
nearlyEqMat :: Matrix R -> Matrix R -> Bool
nearlyEqMat :: Matrix Double -> Matrix Double -> Bool
nearlyEqMat = Double -> Matrix Double -> Matrix Double -> Bool
nearlyEqMatWith Double
eps