Safe Haskell | None |
---|---|
Language | Haskell2010 |
Metric classes
Synopsis
- class (Additive a, Multiplicative a) => Signed a where
- class (Additive a, Multiplicative b, Additive b) => Norm a b | a -> b where
- distance :: (Norm a b, Subtractive a) => a -> a -> b
- class (Additive coord, Multiplicative coord, Additive dir, Multiplicative dir) => Direction coord dir | coord -> dir where
- data Polar mag dir = Polar {}
- polar :: (Norm coord mag, Direction coord dir) => coord -> Polar mag dir
- coord :: (MultiplicativeAction coord mag, Direction coord dir) => Polar mag dir -> coord
- class (Eq a, Additive a, Subtractive a, MeetSemiLattice a) => Epsilon a where
- epsilon :: a
- nearZero :: a -> Bool
- aboutEqual :: a -> a -> Bool
- (~=) :: Epsilon a => a -> a -> Bool
Documentation
class (Additive a, Multiplicative a) => Signed a where Source #
signum
from base is not an operator name in numhask and is replaced by sign
. Compare with Norm
where there is a change in codomain.
abs a * sign a == a
abs zero == zero, so any value for sign zero is ok. We choose lawful neutral:
sign zero == zero
Instances
Signed Double Source # | |
Signed Float Source # | |
Signed Int Source # | |
Signed Int8 Source # | |
Signed Int16 Source # | |
Signed Int32 Source # | |
Signed Int64 Source # | |
Signed Integer Source # | |
Signed Natural Source # | |
Signed Word Source # | |
Signed Word8 Source # | |
Signed Word16 Source # | |
Signed Word32 Source # | |
Signed Word64 Source # | |
(Ord a, Signed a, Integral a, Ring a) => Signed (Ratio a) Source # | |
class (Additive a, Multiplicative b, Additive b) => Norm a b | a -> b where Source #
Norm is a slight generalisation of Signed. The class has the same shape but allows the codomain to be different to the domain.
norm a >= zero norm zero == zero a == norm a .* basis a norm (basis a) == one
Instances
Norm Double Double Source # | |
Norm Float Float Source # | |
Norm Int Int Source # | |
Norm Int8 Int8 Source # | |
Norm Int16 Int16 Source # | |
Norm Int32 Int32 Source # | |
Norm Int64 Int64 Source # | |
Norm Integer Integer Source # | |
Norm Natural Natural Source # | |
Norm Word Word Source # | |
Norm Word8 Word8 Source # | |
Norm Word16 Word16 Source # | |
Norm Word32 Word32 Source # | |
Norm Word64 Word64 Source # | |
ExpField a => Norm (Complex a) a Source # | A euclidean-style norm is strong convention for Complex. |
(Ord a, Signed a, Integral a, Ring a) => Norm (Ratio a) (Ratio a) Source # | |
distance :: (Norm a b, Subtractive a) => a -> a -> b Source #
Distance, which combines the Subtractive notion of difference, with Norm.
distance a b >= zero distance a a == zero distance a b .* basis (a - b) == a - b
class (Additive coord, Multiplicative coord, Additive dir, Multiplicative dir) => Direction coord dir | coord -> dir where Source #
Convert between a "co-ordinated" or "higher-kinded" number and representations of an angle. Typically thought of as polar co-ordinate conversion.
ray . angle == basis norm (ray x) == one
Something that has a magnitude and a direction.
Instances
(Eq mag, Eq dir) => Eq (Polar mag dir) Source # | |
(Show mag, Show dir) => Show (Polar mag dir) Source # | |
Generic (Polar mag dir) Source # | |
type Rep (Polar mag dir) Source # | |
Defined in NumHask.Algebra.Metric type Rep (Polar mag dir) = D1 ('MetaData "Polar" "NumHask.Algebra.Metric" "numhask-0.8.1.0-6vtGETGPv6z5KBqA0pprnK" 'False) (C1 ('MetaCons "Polar" 'PrefixI 'True) (S1 ('MetaSel ('Just "magnitude") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 mag) :*: S1 ('MetaSel ('Just "direction") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 dir))) |
polar :: (Norm coord mag, Direction coord dir) => coord -> Polar mag dir Source #
Convert from a number to a Polar.
coord :: (MultiplicativeAction coord mag, Direction coord dir) => Polar mag dir -> coord Source #
Convert from a Polar to a (coordinated aka higher-kinded) number.
class (Eq a, Additive a, Subtractive a, MeetSemiLattice a) => Epsilon a where Source #
A small number, especially useful for approximate equality.
Nothing
Instances
Epsilon Double Source # | 1e-14 |
Epsilon Float Source # | 1e-6 |
Epsilon Int Source # | 0 |
Epsilon Int8 Source # | |
Epsilon Int16 Source # | |
Epsilon Int32 Source # | |
Epsilon Int64 Source # | |
Epsilon Integer Source # | |
Epsilon Word Source # | |
Epsilon Word8 Source # | |
Epsilon Word16 Source # | |
Epsilon Word32 Source # | |
Epsilon Word64 Source # | |
(Ord a, Signed a, Subtractive a, Epsilon a) => Epsilon (Complex a) Source # | |
(Ord a, Signed a, Integral a, Ring a, MeetSemiLattice a) => Epsilon (Ratio a) Source # | |