-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A numeric prelude -- -- A numeric prelude, providing a clean structure for numbers and -- operations that combine them. @package numhask @version 0.1.2 -- | numbers with a shape module NumHask.Shape -- | Not everything that has a shape is representable. -- -- todo: Structure is a useful alternative concept/naming convention class HasShape f where type Shape f where { type family Shape f; } shape :: HasShape f => f a -> Shape f -- | A Functor f is Representable if tabulate -- and index witness an isomorphism to (->) x. -- -- Every Distributive Functor is actually -- Representable. -- -- Every Representable Functor from Hask to Hask is a right -- adjoint. -- --
--   tabulate . index  ≡ id
--   index . tabulate  ≡ id
--   tabulate . returnreturn
--   
class Distributive f => Representable (f :: * -> *) where type Rep (f :: * -> *) :: * where { type family Rep (f :: * -> *) :: *; } -- |
--   fmap f . tabulatetabulate . fmap f
--   
tabulate :: Representable f => (Rep f -> a) -> f a index :: Representable f => f a -> Rep f -> a -- | This class could also be called replicate. Looking forward, however, -- it may be useful to consider a Representable such as -- --
--   VectorThing a = Vector a | Single a | Zero
--   
-- -- and then -- --
--   singleton a = Single a
--   singleton zero = Zero
--   
-- -- short-circuiting an expensive computation. As the class action then -- doesn't actually involve replication, it would be mis-named. class Singleton f singleton :: Singleton f => a -> f a instance Data.Functor.Rep.Representable f => NumHask.Shape.Singleton f -- | Bootstrapping the number system. -- -- This heirarchy is repeated for the Additive and Multiplicative -- structures, in order to achieve class separation, so these classes are -- not used in the main numerical classes. module NumHask.Algebra.Magma -- | A Magma is a tuple (T,⊕) consisting of -- -- -- -- The mathematical laws for a magma are: -- -- -- -- or, more tersly, -- --
--   ∀ a, b ∈ T: a ⊕ b ∈ T
--   
-- -- These laws are true by construction in haskell: the type signature of -- magma and the above mathematical laws are synonyms. class Magma a (⊕) :: Magma a => a -> a -> a -- | A Unital Magma -- --
--   unit ⊕ a = a
--   a ⊕ unit = a
--   
class Magma a => Unital a unit :: Unital a => a -- | An Associative Magma -- --
--   (a ⊕ b) ⊕ c = a ⊕ (b ⊕ c)
--   
class Magma a => Associative a -- | A Commutative Magma -- --
--   a ⊕ b = b ⊕ a
--   
class Magma a => Commutative a -- | An Invertible Magma -- --
--   ∀ a ∈ T: inv a ∈ T
--   
-- -- law is true by construction in Haskell class Magma a => Invertible a inv :: Invertible a => a -> a -- | An Idempotent Magma -- --
--   a ⊕ a = a
--   
class Magma a => Idempotent a -- | A Monoidal Magma is associative and unital. class (Associative a, Unital a) => Monoidal a -- | A CMonoidal Magma is commutative, associative and unital. class (Commutative a, Associative a, Unital a) => CMonoidal a -- | A Loop is unital and invertible class (Unital a, Invertible a) => Loop a -- | A Group is associative, unital and invertible class (Associative a, Unital a, Invertible a) => Group a -- | see http://chris-taylor.github.io/blog/2013/02/25/xor-trick/ groupSwap :: (Group a) => (a, a) -> (a, a) -- | An Abelian Group is associative, unital, invertible and commutative class (Associative a, Unital a, Invertible a, Commutative a) => Abelian a -- | A magma heirarchy for addition. The basic magma structure is repeated -- and prefixed with 'Additive-'. module NumHask.Algebra.Additive -- | plus is used as the operator for the additive magma to -- distinguish from + which, by convention, implies commutativity -- --
--   ∀ a,b ∈ A: a `plus` b ∈ A
--   
-- -- law is true by construction in Haskell class AdditiveMagma a plus :: AdditiveMagma a => a -> a -> a -- | Unital magma for addition. -- --
--   zero `plus` a == a
--   a `plus` zero == a
--   
class AdditiveMagma a => AdditiveUnital a zero :: AdditiveUnital a => a -- | Associative magma for addition. -- --
--   (a `plus` b) `plus` c == a `plus` (b `plus` c)
--   
class AdditiveMagma a => AdditiveAssociative a -- | Commutative magma for addition. -- --
--   a `plus` b == b `plus` a
--   
class AdditiveMagma a => AdditiveCommutative a -- | Invertible magma for addition. -- --
--   ∀ a ∈ A: negate a ∈ A
--   
-- -- law is true by construction in Haskell class AdditiveMagma a => AdditiveInvertible a negate :: AdditiveInvertible a => a -> a -- | Idempotent magma for addition. -- --
--   a `plus` a == a
--   
class AdditiveMagma a => AdditiveIdempotent a -- | sum definition avoiding a clash with the Sum monoid in base sum :: (Additive a, Foldable f) => f a -> a -- | Additive is commutative, unital and associative under addition -- --
--   zero + a == a
--   a + zero == a
--   (a + b) + c == a + (b + c)
--   a + b == b + a
--   
class (AdditiveCommutative a, AdditiveUnital a, AdditiveAssociative a) => Additive a where a + b = plus a b (+) :: Additive a => a -> a -> a -- | Non-commutative right minus -- --
--   a `plus` negate a = zero
--   
class (AdditiveUnital a, AdditiveAssociative a, AdditiveInvertible a) => AdditiveRightCancellative a where (-~) a b = a `plus` negate b (-~) :: AdditiveRightCancellative a => a -> a -> a -- | Non-commutative left minus -- --
--   negate a `plus` a = zero
--   
class (AdditiveUnital a, AdditiveAssociative a, AdditiveInvertible a) => AdditiveLeftCancellative a where (~-) a b = negate b `plus` a (~-) :: AdditiveLeftCancellative a => a -> a -> a -- | Minus (-) is reserved for where both the left and right -- cancellative laws hold. This then implies that the AdditiveGroup is -- also Abelian. -- -- Syntactic unary negation - substituting "negate a" for "-a" in code - -- is hard-coded in the language to assume a Num instance. So, for -- example, using ''-a = zero - a' for the second rule below doesn't -- work. -- --
--   a - a = zero
--   negate a = zero - a
--   negate a + a = zero
--   a + negate a = zero
--   
class (Additive a, AdditiveInvertible a) => AdditiveGroup a where (-) a b = a `plus` negate b (-) :: AdditiveGroup a => a -> a -> a instance NumHask.Algebra.Additive.AdditiveMagma GHC.Types.Double instance NumHask.Algebra.Additive.AdditiveMagma GHC.Types.Float instance NumHask.Algebra.Additive.AdditiveMagma GHC.Types.Int instance NumHask.Algebra.Additive.AdditiveMagma GHC.Integer.Type.Integer instance NumHask.Algebra.Additive.AdditiveMagma GHC.Types.Bool instance NumHask.Algebra.Additive.AdditiveMagma a => NumHask.Algebra.Additive.AdditiveMagma (Data.Complex.Complex a) instance NumHask.Algebra.Additive.AdditiveUnital GHC.Types.Double instance NumHask.Algebra.Additive.AdditiveUnital GHC.Types.Float instance NumHask.Algebra.Additive.AdditiveUnital GHC.Types.Int instance NumHask.Algebra.Additive.AdditiveUnital GHC.Integer.Type.Integer instance NumHask.Algebra.Additive.AdditiveUnital GHC.Types.Bool instance NumHask.Algebra.Additive.AdditiveUnital a => NumHask.Algebra.Additive.AdditiveUnital (Data.Complex.Complex a) instance NumHask.Algebra.Additive.AdditiveAssociative GHC.Types.Double instance NumHask.Algebra.Additive.AdditiveAssociative GHC.Types.Float instance NumHask.Algebra.Additive.AdditiveAssociative GHC.Types.Int instance NumHask.Algebra.Additive.AdditiveAssociative GHC.Integer.Type.Integer instance NumHask.Algebra.Additive.AdditiveAssociative GHC.Types.Bool instance NumHask.Algebra.Additive.AdditiveAssociative a => NumHask.Algebra.Additive.AdditiveAssociative (Data.Complex.Complex a) instance NumHask.Algebra.Additive.AdditiveCommutative GHC.Types.Double instance NumHask.Algebra.Additive.AdditiveCommutative GHC.Types.Float instance NumHask.Algebra.Additive.AdditiveCommutative GHC.Types.Int instance NumHask.Algebra.Additive.AdditiveCommutative GHC.Integer.Type.Integer instance NumHask.Algebra.Additive.AdditiveCommutative GHC.Types.Bool instance NumHask.Algebra.Additive.AdditiveCommutative a => NumHask.Algebra.Additive.AdditiveCommutative (Data.Complex.Complex a) instance NumHask.Algebra.Additive.AdditiveInvertible GHC.Types.Double instance NumHask.Algebra.Additive.AdditiveInvertible GHC.Types.Float instance NumHask.Algebra.Additive.AdditiveInvertible GHC.Types.Int instance NumHask.Algebra.Additive.AdditiveInvertible GHC.Integer.Type.Integer instance NumHask.Algebra.Additive.AdditiveInvertible GHC.Types.Bool instance NumHask.Algebra.Additive.AdditiveInvertible a => NumHask.Algebra.Additive.AdditiveInvertible (Data.Complex.Complex a) instance NumHask.Algebra.Additive.AdditiveIdempotent GHC.Types.Bool instance NumHask.Algebra.Additive.Additive GHC.Types.Double instance NumHask.Algebra.Additive.Additive GHC.Types.Float instance NumHask.Algebra.Additive.Additive GHC.Types.Int instance NumHask.Algebra.Additive.Additive GHC.Integer.Type.Integer instance NumHask.Algebra.Additive.Additive GHC.Types.Bool instance NumHask.Algebra.Additive.Additive a => NumHask.Algebra.Additive.Additive (Data.Complex.Complex a) instance NumHask.Algebra.Additive.AdditiveGroup GHC.Types.Double instance NumHask.Algebra.Additive.AdditiveGroup GHC.Types.Float instance NumHask.Algebra.Additive.AdditiveGroup GHC.Types.Int instance NumHask.Algebra.Additive.AdditiveGroup GHC.Integer.Type.Integer instance NumHask.Algebra.Additive.AdditiveGroup a => NumHask.Algebra.Additive.AdditiveGroup (Data.Complex.Complex a) -- | A magma heirarchy for multiplication. The basic magma structure is -- repeated and prefixed with 'Multiplicative-'. module NumHask.Algebra.Multiplicative -- | times is used as the operator for the multiplicative magam to -- distinguish from * which, by convention, implies commutativity -- --
--   ∀ a,b ∈ A: a `times` b ∈ A
--   
-- -- law is true by construction in Haskell class MultiplicativeMagma a times :: MultiplicativeMagma a => a -> a -> a -- | Unital magma for multiplication. -- --
--   one `times` a == a
--   a `times` one == a
--   
class MultiplicativeMagma a => MultiplicativeUnital a one :: MultiplicativeUnital a => a -- | Associative magma for multiplication. -- --
--   (a `times` b) `times` c == a `times` (b `times` c)
--   
class MultiplicativeMagma a => MultiplicativeAssociative a -- | Commutative magma for multiplication. -- --
--   a `times` b == b `times` a
--   
class MultiplicativeMagma a => MultiplicativeCommutative a -- | Invertible magma for multiplication. -- --
--   ∀ a ∈ A: recip a ∈ A
--   
-- -- law is true by construction in Haskell class MultiplicativeMagma a => MultiplicativeInvertible a recip :: MultiplicativeInvertible a => a -> a -- | product definition avoiding a clash with the Product monoid in base product :: (Multiplicative a, Foldable f) => f a -> a -- | Multiplicative is commutative, associative and unital under -- multiplication -- --
--   one * a == a
--   a * one == a
--   (a * b) * c == a * (b * c)
--   a * b == b * a
--   
class (MultiplicativeCommutative a, MultiplicativeUnital a, MultiplicativeAssociative a) => Multiplicative a where a * b = times a b (*) :: Multiplicative a => a -> a -> a -- | Non-commutative right divide -- --
--   a `times` recip a = one
--   
class (MultiplicativeUnital a, MultiplicativeAssociative a, MultiplicativeInvertible a) => MultiplicativeRightCancellative a where a /~ b = a `times` recip b (/~) :: MultiplicativeRightCancellative a => a -> a -> a -- | Non-commutative left divide -- --
--   recip a `times` a = one
--   
class (MultiplicativeUnital a, MultiplicativeAssociative a, MultiplicativeInvertible a) => MultiplicativeLeftCancellative a where a ~/ b = recip b `times` a (~/) :: MultiplicativeLeftCancellative a => a -> a -> a -- | Divide (/) is reserved for where both the left and right -- cancellative laws hold. This then implies that the MultiplicativeGroup -- is also Abelian. -- --
--   a / a = one
--   recip a = one / a
--   recip a * a = one
--   a * recip a = one
--   
class (Multiplicative a, MultiplicativeInvertible a) => MultiplicativeGroup a where (/) a b = a `times` recip b (/) :: MultiplicativeGroup a => a -> a -> a instance NumHask.Algebra.Multiplicative.MultiplicativeMagma GHC.Types.Double instance NumHask.Algebra.Multiplicative.MultiplicativeMagma GHC.Types.Float instance NumHask.Algebra.Multiplicative.MultiplicativeMagma GHC.Types.Int instance NumHask.Algebra.Multiplicative.MultiplicativeMagma GHC.Integer.Type.Integer instance NumHask.Algebra.Multiplicative.MultiplicativeMagma GHC.Types.Bool instance (NumHask.Algebra.Multiplicative.MultiplicativeMagma a, NumHask.Algebra.Additive.AdditiveGroup a) => NumHask.Algebra.Multiplicative.MultiplicativeMagma (Data.Complex.Complex a) instance NumHask.Algebra.Multiplicative.MultiplicativeUnital GHC.Types.Double instance NumHask.Algebra.Multiplicative.MultiplicativeUnital GHC.Types.Float instance NumHask.Algebra.Multiplicative.MultiplicativeUnital GHC.Types.Int instance NumHask.Algebra.Multiplicative.MultiplicativeUnital GHC.Integer.Type.Integer instance NumHask.Algebra.Multiplicative.MultiplicativeUnital GHC.Types.Bool instance (NumHask.Algebra.Additive.AdditiveUnital a, NumHask.Algebra.Additive.AdditiveGroup a, NumHask.Algebra.Multiplicative.MultiplicativeUnital a) => NumHask.Algebra.Multiplicative.MultiplicativeUnital (Data.Complex.Complex a) instance NumHask.Algebra.Multiplicative.MultiplicativeAssociative GHC.Types.Double instance NumHask.Algebra.Multiplicative.MultiplicativeAssociative GHC.Types.Float instance NumHask.Algebra.Multiplicative.MultiplicativeAssociative GHC.Types.Int instance NumHask.Algebra.Multiplicative.MultiplicativeAssociative GHC.Integer.Type.Integer instance NumHask.Algebra.Multiplicative.MultiplicativeAssociative GHC.Types.Bool instance (NumHask.Algebra.Additive.AdditiveGroup a, NumHask.Algebra.Multiplicative.MultiplicativeAssociative a) => NumHask.Algebra.Multiplicative.MultiplicativeAssociative (Data.Complex.Complex a) instance NumHask.Algebra.Multiplicative.MultiplicativeCommutative GHC.Types.Double instance NumHask.Algebra.Multiplicative.MultiplicativeCommutative GHC.Types.Float instance NumHask.Algebra.Multiplicative.MultiplicativeCommutative GHC.Types.Int instance NumHask.Algebra.Multiplicative.MultiplicativeCommutative GHC.Integer.Type.Integer instance NumHask.Algebra.Multiplicative.MultiplicativeCommutative GHC.Types.Bool instance (NumHask.Algebra.Additive.AdditiveGroup a, NumHask.Algebra.Multiplicative.MultiplicativeCommutative a) => NumHask.Algebra.Multiplicative.MultiplicativeCommutative (Data.Complex.Complex a) instance NumHask.Algebra.Multiplicative.MultiplicativeInvertible GHC.Types.Double instance NumHask.Algebra.Multiplicative.MultiplicativeInvertible GHC.Types.Float instance (NumHask.Algebra.Additive.AdditiveGroup a, NumHask.Algebra.Multiplicative.MultiplicativeInvertible a) => NumHask.Algebra.Multiplicative.MultiplicativeInvertible (Data.Complex.Complex a) instance NumHask.Algebra.Multiplicative.MultiplicativeIdempotent GHC.Types.Bool instance NumHask.Algebra.Multiplicative.Multiplicative GHC.Types.Double instance NumHask.Algebra.Multiplicative.Multiplicative GHC.Types.Float instance NumHask.Algebra.Multiplicative.Multiplicative GHC.Types.Int instance NumHask.Algebra.Multiplicative.Multiplicative GHC.Integer.Type.Integer instance NumHask.Algebra.Multiplicative.Multiplicative GHC.Types.Bool instance (NumHask.Algebra.Additive.AdditiveGroup a, NumHask.Algebra.Multiplicative.Multiplicative a) => NumHask.Algebra.Multiplicative.Multiplicative (Data.Complex.Complex a) instance NumHask.Algebra.Multiplicative.MultiplicativeGroup GHC.Types.Double instance NumHask.Algebra.Multiplicative.MultiplicativeGroup GHC.Types.Float instance (NumHask.Algebra.Additive.AdditiveGroup a, NumHask.Algebra.Multiplicative.MultiplicativeGroup a) => NumHask.Algebra.Multiplicative.MultiplicativeGroup (Data.Complex.Complex a) -- | Element-by-element operation for Representables module NumHask.Algebra.Basis -- | element by element addition -- --
--   (a .+. b) .+. c == a .+. (b .+. c)
--   zero .+. a = a
--   a .+. zero = a
--   a .+. b == b .+. a
--   
class (Representable m, Additive a) => AdditiveBasis m a where (.+.) = liftR2 (+) (.+.) :: AdditiveBasis m a => m a -> m a -> m a -- | element by element subtraction -- --
--   a .-. a = singleton zero
--   
class (Representable m, AdditiveGroup a) => AdditiveGroupBasis m a where (.-.) = liftR2 (-) (.-.) :: AdditiveGroupBasis m a => m a -> m a -> m a -- | element by element multiplication -- --
--   (a .*. b) .*. c == a .*. (b .*. c)
--   singleton one .*. a = a
--   a .*. singelton one = a
--   a .*. b == b .*. a
--   
class (Representable m, Multiplicative a) => MultiplicativeBasis m a where (.*.) = liftR2 (*) (.*.) :: MultiplicativeBasis m a => m a -> m a -> m a -- | element by element division -- --
--   a ./. a == singleton one
--   
class (Representable m, MultiplicativeGroup a) => MultiplicativeGroupBasis m a where (./.) = liftR2 (/) (./.) :: MultiplicativeGroupBasis m a => m a -> m a -> m a instance (Data.Functor.Rep.Representable r, NumHask.Algebra.Additive.Additive a) => NumHask.Algebra.Basis.AdditiveBasis r a instance (Data.Functor.Rep.Representable r, NumHask.Algebra.Additive.AdditiveGroup a) => NumHask.Algebra.Basis.AdditiveGroupBasis r a instance (Data.Functor.Rep.Representable r, NumHask.Algebra.Multiplicative.Multiplicative a) => NumHask.Algebra.Basis.MultiplicativeBasis r a instance (Data.Functor.Rep.Representable r, NumHask.Algebra.Multiplicative.MultiplicativeGroup a) => NumHask.Algebra.Basis.MultiplicativeGroupBasis r a -- | Distribution avoids a name clash with Distributive module NumHask.Algebra.Distribution -- | Distribution (and annihilation) laws -- --
--   a * (b + c) == a * b + a * c
--   (a + b) * c == a * c + b * c
--   a * zero == zero
--   zero * a == zero
--   
class (Additive a, MultiplicativeMagma a) => Distribution a instance NumHask.Algebra.Distribution.Distribution GHC.Types.Double instance NumHask.Algebra.Distribution.Distribution GHC.Types.Float instance NumHask.Algebra.Distribution.Distribution GHC.Types.Int instance NumHask.Algebra.Distribution.Distribution GHC.Integer.Type.Integer instance NumHask.Algebra.Distribution.Distribution GHC.Types.Bool instance (NumHask.Algebra.Additive.AdditiveGroup a, NumHask.Algebra.Distribution.Distribution a) => NumHask.Algebra.Distribution.Distribution (Data.Complex.Complex a) -- | Ring classes. A distinguishment is made between Rings and Commutative -- Rings. module NumHask.Algebra.Ring -- | Semiring class (MultiplicativeAssociative a, MultiplicativeUnital a, Distribution a) => Semiring a -- | Ring a summary of the laws inherited from the ring super-classes -- --
--   zero + a == a
--   a + zero == a
--   (a + b) + c == a + (b + c)
--   a + b == b + a
--   a - a = zero
--   negate a = zero - a
--   negate a + a = zero
--   a + negate a = zero
--   one `times` a == a
--   a `times` one == a
--   (a `times` b) `times` c == a `times` (b `times` c)
--   a `times` (b + c) == a `times` b + a `times` c
--   (a + b) `times` c == a `times` c + b `times` c
--   a `times` zero == zero
--   zero `times` a == zero
--   
class (AdditiveGroup a, MultiplicativeAssociative a, MultiplicativeUnital a, Distribution a) => Ring a -- | CRing is a Ring with Multiplicative Commutation. It arises often due -- to * being defined as a multiplicative commutative operation. class (Multiplicative a, Ring a) => CRing a instance NumHask.Algebra.Ring.Semiring GHC.Types.Double instance NumHask.Algebra.Ring.Semiring GHC.Types.Float instance NumHask.Algebra.Ring.Semiring GHC.Types.Int instance NumHask.Algebra.Ring.Semiring GHC.Integer.Type.Integer instance NumHask.Algebra.Ring.Semiring GHC.Types.Bool instance (NumHask.Algebra.Additive.AdditiveGroup a, NumHask.Algebra.Ring.Semiring a) => NumHask.Algebra.Ring.Semiring (Data.Complex.Complex a) instance NumHask.Algebra.Ring.Ring GHC.Types.Double instance NumHask.Algebra.Ring.Ring GHC.Types.Float instance NumHask.Algebra.Ring.Ring GHC.Types.Int instance NumHask.Algebra.Ring.Ring GHC.Integer.Type.Integer instance NumHask.Algebra.Ring.Ring a => NumHask.Algebra.Ring.Ring (Data.Complex.Complex a) instance NumHask.Algebra.Ring.CRing GHC.Types.Double instance NumHask.Algebra.Ring.CRing GHC.Types.Float instance NumHask.Algebra.Ring.CRing GHC.Types.Int instance NumHask.Algebra.Ring.CRing GHC.Integer.Type.Integer instance NumHask.Algebra.Ring.CRing a => NumHask.Algebra.Ring.CRing (Data.Complex.Complex a) -- | Field classes module NumHask.Algebra.Field -- | A Semifield is a Field without Commutative Multiplication. class (MultiplicativeInvertible a, Ring a) => Semifield a -- | A Field is a Ring plus additive invertible and multiplicative -- invertible operations. -- -- A summary of the rules inherited from super-classes of Field -- --
--   zero + a == a
--   a + zero == a
--   (a + b) + c == a + (b + c)
--   a + b == b + a
--   a - a = zero
--   negate a = zero - a
--   negate a + a = zero
--   a + negate a = zero
--   one * a == a
--   a * one == a
--   (a * b) * c == a * (b * c)
--   a * (b + c) == a * b + a * c
--   (a + b) * c == a * c + b * c
--   a * zero == zero
--   zero * a == zero
--   a * b == b * a
--   a / a = one
--   recip a = one / a
--   recip a * a = one
--   a * recip a = one
--   
class (AdditiveGroup a, MultiplicativeGroup a, Ring a) => Field a -- | A hyperbolic field class -- --
--   sqrt . (**2) == identity
--   log . exp == identity
--   for +ive b, a != 0,1: a ** logBase a b ≈ b
--   
class (Field a) => ExpField a where logBase a b = log b / log a (**) a b = exp (log a * b) sqrt a = a ** (one / (one + one)) exp :: ExpField a => a -> a log :: ExpField a => a -> a logBase :: ExpField a => a -> a -> a (**) :: ExpField a => a -> a -> a sqrt :: ExpField a => a -> a -- | quotient fields explode constraints if they allow for polymorphic -- integral types -- --
--   a - one < floor a <= a <= ceiling a < a + one
--   round a == floor (a + one/(one+one))
--   
class (Field a) => QuotientField a round :: QuotientField a => a -> Integer ceiling :: QuotientField a => a -> Integer floor :: QuotientField a => a -> Integer (^^) :: QuotientField a => a -> Integer -> a -- | A bounded field includes the concepts of infinity and NaN, thus moving -- away from error throwing. -- --
--   one / zero + infinity == infinity
--   infinity + a == infinity
--   isNaN (infinity - infinity)
--   isNaN (infinity / infinity)
--   isNaN (nan + a)
--   zero / zero != nan
--   
-- -- Note the tricky law that, although nan is assigned to zero/zero, they -- are never-the-less not equal. A committee decided this. class (Field a) => BoundedField a where maxBound = one / zero minBound = negate (one / zero) nan = zero / zero maxBound :: BoundedField a => a minBound :: BoundedField a => a nan :: BoundedField a => a isNaN :: BoundedField a => a -> Bool -- | prints as Infinity infinity :: BoundedField a => a -- | prints as `-Infinity` neginfinity :: BoundedField a => a -- | Trigonometric Field class (Ord a, Field a) => TrigField a where tan x = sin x / cos x tanh x = sinh x / cosh x atan2 y x | x > zero = atan (y / x) | x == zero && y > zero = pi / (one + one) | x < one && y > one = pi + atan (y / x) | (x <= zero && y < zero) || (x < zero) = negate (atan2 (negate y) x) | y == zero = pi | x == zero && y == zero = y | otherwise = x + y pi :: TrigField a => a sin :: TrigField a => a -> a cos :: TrigField a => a -> a tan :: TrigField a => a -> a asin :: TrigField a => a -> a acos :: TrigField a => a -> a atan :: TrigField a => a -> a sinh :: TrigField a => a -> a cosh :: TrigField a => a -> a tanh :: TrigField a => a -> a asinh :: TrigField a => a -> a acosh :: TrigField a => a -> a atanh :: TrigField a => a -> a atan2 :: TrigField a => a -> a -> a instance NumHask.Algebra.Field.Semifield GHC.Types.Double instance NumHask.Algebra.Field.Semifield GHC.Types.Float instance NumHask.Algebra.Field.Semifield a => NumHask.Algebra.Field.Semifield (Data.Complex.Complex a) instance NumHask.Algebra.Field.Field GHC.Types.Double instance NumHask.Algebra.Field.Field GHC.Types.Float instance NumHask.Algebra.Field.Field a => NumHask.Algebra.Field.Field (Data.Complex.Complex a) instance NumHask.Algebra.Field.ExpField GHC.Types.Double instance NumHask.Algebra.Field.ExpField GHC.Types.Float instance (NumHask.Algebra.Field.TrigField a, NumHask.Algebra.Field.ExpField a) => NumHask.Algebra.Field.ExpField (Data.Complex.Complex a) instance NumHask.Algebra.Field.QuotientField GHC.Types.Float instance NumHask.Algebra.Field.QuotientField GHC.Types.Double instance NumHask.Algebra.Field.BoundedField GHC.Types.Float instance NumHask.Algebra.Field.BoundedField GHC.Types.Double instance NumHask.Algebra.Field.BoundedField a => NumHask.Algebra.Field.BoundedField (Data.Complex.Complex a) instance NumHask.Algebra.Field.TrigField GHC.Types.Double instance NumHask.Algebra.Field.TrigField GHC.Types.Float -- | Metric classes module NumHask.Algebra.Metric -- | signum from base is not an operator replicated in numhask, -- being such a very silly name, and preferred is the much more obvious -- sign. Compare with Norm and Banach where -- there is a change in codomain -- --
--   abs a * sign a == a
--   
-- -- Generalising this class tends towards size and direction (abs is the -- size on the one-dim number line of a vector with its tail at zero, and -- sign is the direction, right?). class (MultiplicativeUnital a) => Signed a sign :: Signed a => a -> a abs :: Signed a => a -> a -- | Like Signed, except the codomain can be different to the domain. class Normed a b size :: Normed a b => a -> b -- | distance between numbers -- --
--   distance a b >= zero
--   distance a a == zero
--   \a b c -> distance a c + distance b c - distance a b >= zero &&
--             distance a b + distance b c - distance a c >= zero &&
--             distance a b + distance a c - distance b c >= zero &&
--   
class Metric a b distance :: Metric a b => a -> a -> b -- | todo: This should probably be split off into some sort of alternative -- Equality logic, but to what end? class (AdditiveGroup a) => Epsilon a where positive a = a == abs a veryPositive a = not (nearZero a) && positive a veryNegative a = not (nearZero a || positive a) nearZero :: Epsilon a => a -> Bool aboutEqual :: Epsilon a => a -> a -> Bool positive :: (Epsilon a, Eq a, Signed a) => a -> Bool veryPositive :: (Epsilon a, Eq a, Signed a) => a -> Bool veryNegative :: (Epsilon a, Eq a, Signed a) => a -> Bool -- | todo: is utf perfectly acceptable these days? (≈) :: (Epsilon a) => a -> a -> Bool infixl 4 ≈ instance NumHask.Algebra.Metric.Signed GHC.Types.Double instance NumHask.Algebra.Metric.Signed GHC.Types.Float instance NumHask.Algebra.Metric.Signed GHC.Types.Int instance NumHask.Algebra.Metric.Signed GHC.Integer.Type.Integer instance NumHask.Algebra.Metric.Normed GHC.Types.Double GHC.Types.Double instance NumHask.Algebra.Metric.Normed GHC.Types.Float GHC.Types.Float instance NumHask.Algebra.Metric.Normed GHC.Types.Int GHC.Types.Int instance NumHask.Algebra.Metric.Normed GHC.Integer.Type.Integer GHC.Integer.Type.Integer instance (NumHask.Algebra.Multiplicative.Multiplicative a, NumHask.Algebra.Field.ExpField a, NumHask.Algebra.Metric.Normed a a) => NumHask.Algebra.Metric.Normed (Data.Complex.Complex a) a instance NumHask.Algebra.Metric.Metric GHC.Types.Double GHC.Types.Double instance NumHask.Algebra.Metric.Metric GHC.Types.Float GHC.Types.Float instance NumHask.Algebra.Metric.Metric GHC.Types.Int GHC.Types.Int instance NumHask.Algebra.Metric.Metric GHC.Integer.Type.Integer GHC.Integer.Type.Integer instance (NumHask.Algebra.Multiplicative.Multiplicative a, NumHask.Algebra.Field.ExpField a, NumHask.Algebra.Metric.Normed a a) => NumHask.Algebra.Metric.Metric (Data.Complex.Complex a) a instance NumHask.Algebra.Metric.Epsilon GHC.Types.Double instance NumHask.Algebra.Metric.Epsilon GHC.Types.Float instance NumHask.Algebra.Metric.Epsilon GHC.Types.Int instance NumHask.Algebra.Metric.Epsilon GHC.Integer.Type.Integer instance NumHask.Algebra.Metric.Epsilon a => NumHask.Algebra.Metric.Epsilon (Data.Complex.Complex a) -- | Integral classes module NumHask.Algebra.Integral -- | Integral laws -- --
--   b == zero || b * (a `div` b) + (a `mod` b) == a
--   
class (Ring a) => Integral a where div a1 a2 = fst (divMod a1 a2) mod a1 a2 = snd (divMod a1 a2) div :: Integral a => a -> a -> a mod :: Integral a => a -> a -> a divMod :: Integral a => a -> a -> (a, a) -- | toInteger is kept separate from Integral to help with compatability -- issues. class ToInteger a toInteger :: ToInteger a => a -> Integer -- | fromInteger is the most problematic of the Num class -- operators. Particularly heinous, it is assumed that any number type -- can be constructed from an Integer, so that the broad classes of -- objects that are composed of multiple elements is avoided in haskell. class FromInteger a fromInteger :: FromInteger a => Integer -> a -- | coercion of Integrals -- --
--   fromIntegral a == a
--   
fromIntegral :: (ToInteger a, FromInteger b) => a -> b instance NumHask.Algebra.Integral.Integral GHC.Types.Int instance NumHask.Algebra.Integral.Integral GHC.Integer.Type.Integer instance NumHask.Algebra.Integral.FromInteger GHC.Types.Double instance NumHask.Algebra.Integral.FromInteger GHC.Types.Float instance NumHask.Algebra.Integral.FromInteger GHC.Types.Int instance NumHask.Algebra.Integral.FromInteger GHC.Integer.Type.Integer instance NumHask.Algebra.Integral.ToInteger GHC.Types.Int instance NumHask.Algebra.Integral.ToInteger GHC.Integer.Type.Integer -- | Algebra for Representable numbers module NumHask.Algebra.Module -- | Additive Module Laws -- --
--   (a + b) .+ c == a + (b .+ c)
--   (a + b) .+ c == (a .+ c) + b
--   a .+ zero == a
--   a .+ b == b +. a
--   
class (Representable r, Additive a) => AdditiveModule r a where r .+ a = fmap (a +) r a +. r = fmap (a +) r (.+) :: AdditiveModule r a => r a -> a -> r a (+.) :: AdditiveModule r a => a -> r a -> r a -- | Subtraction Module Laws -- --
--   (a + b) .- c == a + (b .- c)
--   (a + b) .- c == (a .- c) + b
--   a .- zero == a
--   a .- b == negate b +. a
--   
class (Representable r, AdditiveGroup a) => AdditiveGroupModule r a where r .- a = fmap (\ x -> x - a) r a -. r = fmap (\ x -> a - x) r (.-) :: AdditiveGroupModule r a => r a -> a -> r a (-.) :: AdditiveGroupModule r a => a -> r a -> r a -- | Multiplicative Module Laws -- --
--   a .* one == a
--   (a + b) .* c == (a .* c) + (b .* c)
--   c *. (a + b) == (c *. a) + (c *. b)
--   a .* zero == zero
--   a .* b == b *. a
--   
class (Representable r, Multiplicative a) => MultiplicativeModule r a where r .* a = fmap (a *) r a *. r = fmap (a *) r (.*) :: MultiplicativeModule r a => r a -> a -> r a (*.) :: MultiplicativeModule r a => a -> r a -> r a -- | Division Module Laws -- --
--   nearZero a || a ./ one == a
--   b == zero || a ./ b == recip b *. a
--   
class (Representable r, MultiplicativeGroup a) => MultiplicativeGroupModule r a where r ./ a = fmap (/ a) r a /. r = fmap (\ x -> a / x) r (./) :: MultiplicativeGroupModule r a => r a -> a -> r a (/.) :: MultiplicativeGroupModule r a => a -> r a -> r a -- | Banach (with Norm) laws form rules around size and direction of a -- number, with a potential crossing into another codomain. -- --
--   a == singleton zero || normalize a *. size a == a
--   
class (Representable r, ExpField a, Normed (r a) a) => Banach r a where normalize a = a ./ size a normalize :: Banach r a => r a -> r a -- | the inner product of a representable over a semiring -- --
--   a <.> b == b <.> a
--   a <.> (b +c) == a <.> b + a <.> c
--   a <.> (s *. b + c) == s * (a <.> b) + a <.> c
--   
-- -- (s0 *. a) . (s1 *. b) == s0 * s1 * (a . b) class (Semiring a, Foldable r, Representable r) => Hilbert r a where (<.>) a b = sum $ liftR2 times a b (<.>) :: Hilbert r a => r a -> r a -> a -- | synonym for (.) inner :: (Hilbert r a) => r a -> r a -> a -- | tensorial type -- | generalised outer product -- --
--   a><b + c><b == (a+c) >< b
--   a><b + a><c == a >< (b+c)
--   
-- -- todo: work out why these laws down't apply > a *. (b>== -- (a<b) .* c > (a>.* c == a *. (b<c) class TensorProduct a where outer = (><) (><) :: TensorProduct a => a -> a -> (a >< a) outer :: TensorProduct a => a -> a -> (a >< a) timesleft :: TensorProduct a => a -> (a >< a) -> a timesright :: TensorProduct a => (a >< a) -> a -> a instance (Data.Functor.Rep.Representable r, NumHask.Algebra.Additive.Additive a) => NumHask.Algebra.Module.AdditiveModule r a instance (Data.Functor.Rep.Representable r, NumHask.Algebra.Additive.AdditiveGroup a) => NumHask.Algebra.Module.AdditiveGroupModule r a instance (Data.Functor.Rep.Representable r, NumHask.Algebra.Multiplicative.Multiplicative a) => NumHask.Algebra.Module.MultiplicativeModule r a instance (Data.Functor.Rep.Representable r, NumHask.Algebra.Multiplicative.MultiplicativeGroup a) => NumHask.Algebra.Module.MultiplicativeGroupModule r a instance (NumHask.Algebra.Metric.Normed (r a) a, NumHask.Algebra.Field.ExpField a, Data.Functor.Rep.Representable r) => NumHask.Algebra.Module.Banach r a instance (NumHask.Algebra.Module.Hilbert r a, NumHask.Algebra.Multiplicative.Multiplicative a) => NumHask.Algebra.Module.TensorProduct (r a) -- | Algebraic structure module NumHask.Algebra -- | Two classes are supplied: -- -- module NumHask.Vector -- | A one-dimensional array where shape is specified at the type level The -- main purpose of this, beyond safe-typing, is to supply the -- Representable instance with an initial object. A boxed Vector -- is used under the hood. newtype Vector (n :: Nat) a Vector :: Vector a -> Vector a [toVec] :: Vector a -> Vector a -- | a one-dimensional array where shape is specified at the value level data SomeVector a SomeVector :: Int -> (Vector a) -> SomeVector a -- | convert from a Vector to a SomeVector someVector :: (KnownNat r) => Vector (r :: Nat) a -> SomeVector a -- | convert from a SomeVector to a Vector with no shape -- check unsafeToVector :: SomeVector a -> Vector (r :: Nat) a -- | convert from a SomeVector to a Vector, checking shape toVector :: forall a r. (KnownNat r) => SomeVector a -> Maybe (Vector (r :: Nat) a) -- | ShapeV is used to generate sensible lengths for arbitrary instances of -- SomeVector and SomeMatrix newtype ShapeV ShapeV :: Int -> ShapeV [unshapeV] :: ShapeV -> Int instance GHC.Classes.Ord a => GHC.Classes.Ord (NumHask.Vector.SomeVector a) instance Data.Foldable.Foldable NumHask.Vector.SomeVector instance GHC.Classes.Eq a => GHC.Classes.Eq (NumHask.Vector.SomeVector a) instance GHC.Base.Functor NumHask.Vector.SomeVector instance Data.Traversable.Traversable (NumHask.Vector.Vector n) instance Data.Foldable.Foldable (NumHask.Vector.Vector n) instance GHC.Base.Functor (NumHask.Vector.Vector n) instance GHC.Classes.Eq a => GHC.Classes.Eq (NumHask.Vector.Vector n a) instance Data.Functor.Classes.Eq1 (NumHask.Vector.Vector n) instance (GHC.Show.Show a, GHC.TypeLits.KnownNat n) => GHC.Show.Show (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveUnital a) => GHC.Exts.IsList (NumHask.Vector.Vector n a) instance GHC.TypeLits.KnownNat n => NumHask.Shape.HasShape (NumHask.Vector.Vector n) instance GHC.TypeLits.KnownNat n => Data.Distributive.Distributive (NumHask.Vector.Vector n) instance GHC.TypeLits.KnownNat n => Data.Functor.Rep.Representable (NumHask.Vector.Vector n) instance GHC.TypeLits.KnownNat n => GHC.Base.Applicative (NumHask.Vector.Vector n) instance (GHC.TypeLits.KnownNat n, Test.QuickCheck.Arbitrary.Arbitrary a, NumHask.Algebra.Additive.AdditiveUnital a) => Test.QuickCheck.Arbitrary.Arbitrary (NumHask.Vector.Vector n a) instance NumHask.Shape.HasShape NumHask.Vector.SomeVector instance GHC.Show.Show a => GHC.Show.Show (NumHask.Vector.SomeVector a) instance GHC.Exts.IsList (NumHask.Vector.SomeVector a) instance Test.QuickCheck.Arbitrary.Arbitrary NumHask.Vector.ShapeV instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (NumHask.Vector.SomeVector a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveMagma a) => NumHask.Algebra.Additive.AdditiveMagma (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveUnital a) => NumHask.Algebra.Additive.AdditiveUnital (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveAssociative a) => NumHask.Algebra.Additive.AdditiveAssociative (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveCommutative a) => NumHask.Algebra.Additive.AdditiveCommutative (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveInvertible a) => NumHask.Algebra.Additive.AdditiveInvertible (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.Additive a) => NumHask.Algebra.Additive.Additive (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveGroup a) => NumHask.Algebra.Additive.AdditiveGroup (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Multiplicative.MultiplicativeMagma a) => NumHask.Algebra.Multiplicative.MultiplicativeMagma (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Multiplicative.MultiplicativeUnital a) => NumHask.Algebra.Multiplicative.MultiplicativeUnital (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Multiplicative.MultiplicativeAssociative a) => NumHask.Algebra.Multiplicative.MultiplicativeAssociative (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Multiplicative.MultiplicativeCommutative a) => NumHask.Algebra.Multiplicative.MultiplicativeCommutative (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Multiplicative.MultiplicativeInvertible a) => NumHask.Algebra.Multiplicative.MultiplicativeInvertible (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Multiplicative.Multiplicative a) => NumHask.Algebra.Multiplicative.Multiplicative (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Multiplicative.MultiplicativeGroup a) => NumHask.Algebra.Multiplicative.MultiplicativeGroup (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Multiplicative.MultiplicativeMagma a, NumHask.Algebra.Additive.Additive a) => NumHask.Algebra.Distribution.Distribution (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Ring.Semiring a) => NumHask.Algebra.Ring.Semiring (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Ring.Ring a) => NumHask.Algebra.Ring.Ring (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Ring.CRing a) => NumHask.Algebra.Ring.CRing (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Field.Field a) => NumHask.Algebra.Field.Field (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Field.ExpField a) => NumHask.Algebra.Field.ExpField (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Field.BoundedField a) => NumHask.Algebra.Field.BoundedField (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Metric.Signed a) => NumHask.Algebra.Metric.Signed (NumHask.Vector.Vector n a) instance NumHask.Algebra.Field.ExpField a => NumHask.Algebra.Metric.Normed (NumHask.Vector.Vector n a) a instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Metric.Epsilon a) => NumHask.Algebra.Metric.Epsilon (NumHask.Vector.Vector n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Field.ExpField a) => NumHask.Algebra.Metric.Metric (NumHask.Vector.Vector n a) a instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Integral.Integral a) => NumHask.Algebra.Integral.Integral (NumHask.Vector.Vector n a) instance (NumHask.Algebra.Ring.Semiring a, GHC.TypeLits.KnownNat n) => NumHask.Algebra.Module.Hilbert (NumHask.Vector.Vector n) a -- | Two-dimensional arrays. Two classes are supplied -- -- -- -- In both cases, the underlying data is contained as a flat vector for -- efficiency purposes. module NumHask.Matrix -- | A two-dimensional array where shape is specified at the type level The -- main purpose of this, beyond safe typing, is to supply the -- Representable instance with an initial object. A single Boxed -- Vector is used underneath for efficient slicing, but this may -- change or become polymorphic in the future. -- -- todo: the natural type for a matrix, the output from a vector outer -- product for example, is a Vector (Vector a). We should -- be able to unify to a different representation such as this, using -- type families. newtype Matrix m n a Matrix :: Vector a -> Matrix m n a [flattenMatrix] :: Matrix m n a -> Vector a -- | a two-dimensional array where shape is specified at the value level as -- a '(Int,Int)' Use this to avoid type-level hasochism by demoting a -- Matrix with someMatrix data SomeMatrix a SomeMatrix :: (Int, Int) -> (Vector a) -> SomeMatrix a -- | convert from a Matrix to a SomeMatrix someMatrix :: (KnownNat m, KnownNat n) => Matrix (m :: Nat) (n :: Nat) a -> SomeMatrix a -- | convert from a SomeMatrix to a Matrix with no shape -- check unsafeToMatrix :: SomeMatrix a -> Matrix (m :: Nat) (n :: Nat) a -- | convert from a SomeMatrix to a Matrix, checking shape toMatrix :: forall a m n. (KnownNat m, KnownNat n) => SomeMatrix a -> Maybe (Matrix (m :: Nat) (n :: Nat) a) -- | conversion from a double Vector representation unsafeFromVV :: forall a m n. Vector m (Vector n a) -> Matrix m n a -- | conversion to a double Vector representation toVV :: forall a m n. (KnownNat m, KnownNat n) => Matrix m n a -> Vector m (Vector n a) -- | convert a Vector to a column Matrix toCol :: forall a n. Vector n a -> Matrix 1 n a -- | convert a Vector to a row Matrix toRow :: forall a m. Vector m a -> Matrix m 1 a -- | convert a row Matrix to a Vector fromCol :: forall a n. Matrix 1 n a -> Vector n a -- | convert a column Matrix to a Vector fromRow :: forall a m. Matrix m 1 a -> Vector m a -- | extract a column from a Matrix as a Vector col :: forall a m n. (KnownNat m, KnownNat n) => Matrix m n a -> Int -> Vector m a -- | extract a row from a Matrix as a Vector row :: forall a m n. (KnownNat m, KnownNat n) => Matrix m n a -> Int -> Vector n a -- | join column-wise joinc :: forall m n0 n1 a. (KnownNat m, KnownNat n0, KnownNat n1, Representable (Matrix m (n0 :+ n1))) => Matrix m n0 a -> Matrix m n1 a -> Matrix m (n0 :+ n1) a -- | join row-wise joinr :: forall m0 m1 n a. (KnownNat m0, KnownNat m1, KnownNat n, Representable (Matrix (m0 :+ m1) n)) => Matrix m0 n a -> Matrix m1 n a -> Matrix (m0 :+ m1) n a -- | resize matrix, appending with zero if needed resize :: forall m0 m1 n0 n1 a. (KnownNat m0, KnownNat m1, KnownNat n0, KnownNat n1, AdditiveUnital a) => Matrix m0 n0 a -> Matrix m1 n1 a -- | reshape matrix, appending with zero if needed reshape :: forall m0 m1 n0 n1 a. (KnownNat m0, KnownNat m1, KnownNat n0, KnownNat n1, AdditiveUnital a) => Matrix m0 n0 a -> Matrix m1 n1 a -- | matrix multiplication mmult :: forall m n k a. (Hilbert (Vector k) a, KnownNat m, KnownNat n, KnownNat k) => Matrix m k a -> Matrix k n a -> Matrix m n a -- | matrix transposition -- -- trans . trans == identity trans :: forall m n a. (KnownNat m, KnownNat n) => Matrix m n a -> Matrix n m a -- | extract the matrix diagonal as a vector -- --
--   getDiag one == one
--   
getDiag :: forall n a. (KnownNat n) => Matrix n n a -> Vector n a -- | create a matrix using a vector as the diagonal -- --
--   diagonal one = one
--   getDiag . diagonal == identity
--   
diagonal :: forall n a. (KnownNat n, AdditiveUnital a) => Vector n a -> Matrix n n a -- | map a homomorphic vector function, column-wise mapc :: forall m n a. (KnownNat m, KnownNat n) => (Vector m a -> Vector m a) -> Matrix m n a -> Matrix m n a -- | map a homomorphic vector function, row-wise mapr :: forall m n a. (KnownNat m, KnownNat n) => (Vector n a -> Vector n a) -> Matrix m n a -> Matrix m n a -- | used to get sensible arbitrary instances of SomeMatrix newtype ShapeM ShapeM :: (Int, Int) -> ShapeM [unshapeM] :: ShapeM -> (Int, Int) instance Data.Foldable.Foldable NumHask.Matrix.SomeMatrix instance GHC.Classes.Eq a => GHC.Classes.Eq (NumHask.Matrix.SomeMatrix a) instance GHC.Base.Functor NumHask.Matrix.SomeMatrix instance forall k (m :: k) k1 (n :: k1). Data.Traversable.Traversable (NumHask.Matrix.Matrix m n) instance forall k (m :: k) k1 (n :: k1). Data.Foldable.Foldable (NumHask.Matrix.Matrix m n) instance forall k (m :: k) k1 (n :: k1) a. GHC.Classes.Eq a => GHC.Classes.Eq (NumHask.Matrix.Matrix m n a) instance forall k (m :: k) k1 (n :: k1). GHC.Base.Functor (NumHask.Matrix.Matrix m n) instance (GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n) => NumHask.Shape.HasShape (NumHask.Matrix.Matrix m n) instance (GHC.Show.Show a, GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n) => GHC.Show.Show (NumHask.Matrix.Matrix m n a) instance (GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n, Test.QuickCheck.Arbitrary.Arbitrary a, NumHask.Algebra.Additive.AdditiveUnital a) => Test.QuickCheck.Arbitrary.Arbitrary (NumHask.Matrix.Matrix m n a) instance (GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n) => Data.Distributive.Distributive (NumHask.Matrix.Matrix m n) instance (GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n) => Data.Functor.Rep.Representable (NumHask.Matrix.Matrix m n) instance NumHask.Shape.HasShape NumHask.Matrix.SomeMatrix instance GHC.Show.Show a => GHC.Show.Show (NumHask.Matrix.SomeMatrix a) instance (GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveUnital a) => GHC.Exts.IsList (NumHask.Matrix.Matrix m n a) instance GHC.Exts.IsList (NumHask.Matrix.SomeMatrix a) instance Test.QuickCheck.Arbitrary.Arbitrary NumHask.Matrix.ShapeM instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (NumHask.Matrix.SomeMatrix a) instance (GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveMagma a) => NumHask.Algebra.Additive.AdditiveMagma (NumHask.Matrix.Matrix m n a) instance (GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveUnital a) => NumHask.Algebra.Additive.AdditiveUnital (NumHask.Matrix.Matrix m n a) instance (GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveAssociative a) => NumHask.Algebra.Additive.AdditiveAssociative (NumHask.Matrix.Matrix m n a) instance (GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveCommutative a) => NumHask.Algebra.Additive.AdditiveCommutative (NumHask.Matrix.Matrix m n a) instance (GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveInvertible a) => NumHask.Algebra.Additive.AdditiveInvertible (NumHask.Matrix.Matrix m n a) instance (GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.Additive a) => NumHask.Algebra.Additive.Additive (NumHask.Matrix.Matrix m n a) instance (GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveGroup a) => NumHask.Algebra.Additive.AdditiveGroup (NumHask.Matrix.Matrix m n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Ring.Semiring a) => NumHask.Algebra.Multiplicative.MultiplicativeMagma (NumHask.Matrix.Matrix n n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Ring.Semiring a) => NumHask.Algebra.Multiplicative.MultiplicativeUnital (NumHask.Matrix.Matrix n n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Ring.Semiring a) => NumHask.Algebra.Multiplicative.MultiplicativeAssociative (NumHask.Matrix.Matrix n n a) instance (GHC.TypeLits.KnownNat n, GHC.Real.Fractional a, GHC.Classes.Eq a, NumHask.Algebra.Field.BoundedField a, NumHask.Algebra.Ring.Semiring a) => NumHask.Algebra.Multiplicative.MultiplicativeInvertible (NumHask.Matrix.Matrix n n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Ring.Semiring a) => NumHask.Algebra.Distribution.Distribution (NumHask.Matrix.Matrix n n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Ring.Semiring a) => NumHask.Algebra.Ring.Semiring (NumHask.Matrix.Matrix n n a) instance (GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveGroup a, NumHask.Algebra.Ring.Semiring a) => NumHask.Algebra.Ring.Ring (NumHask.Matrix.Matrix n n a) instance (GHC.Classes.Eq a, GHC.Real.Fractional a, NumHask.Algebra.Field.BoundedField a, GHC.TypeLits.KnownNat n, NumHask.Algebra.Additive.AdditiveGroup a, NumHask.Algebra.Ring.Semiring a) => NumHask.Algebra.Field.Semifield (NumHask.Matrix.Matrix n n a) instance (GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n, NumHask.Algebra.Metric.Epsilon a) => NumHask.Algebra.Metric.Epsilon (NumHask.Matrix.Matrix m n a) instance (NumHask.Algebra.Ring.Semiring a, GHC.TypeLits.KnownNat m, GHC.TypeLits.KnownNat n) => NumHask.Algebra.Module.Hilbert (NumHask.Matrix.Matrix m n) a -- | A prelude for NumHask module NumHask.Prelude -- | NumHask usage examples module NumHask.Examples