manifolds-core-0.5.0.4: The basic classes for the manifolds hierarchy.

Copyright(c) Justus Sagemüller 2016
LicenseGPL v3
Maintainer(@) jsag $ hvl.no
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Math.Manifold.Core.PseudoAffine

Description

 
Synopsis

Documentation

data SemimanifoldWitness x where Source #

This is the reified form of the property that the interior of a semimanifold is a manifold. These constraints would ideally be expressed directly as superclass constraints, but that would require the UndecidableSuperclasses extension, which is not reliable yet.

Also, if all those equality constraints are in scope, GHC tends to infer needlessly complicated types like Interior (Interior (Needle (Interior x))), which is the same as just Needle x.

class AdditiveGroup (Needle x) => Semimanifold x where Source #

Minimal complete definition

((.+~^) | fromInterior), toInterior, translateP

Associated Types

type Needle x :: * Source #

The space of “natural” ways starting from some reference point and going to some particular target point. Hence, the name: like a compass needle, but also with an actual length. For affine spaces, Needle is simply the space of line segments (aka vectors) between two points, i.e. the same as Diff. The AffineManifold constraint makes that requirement explicit.

This space should be isomorphic to the tangent space (and is in fact used somewhat synonymously).

type Interior x :: * Source #

Manifolds with boundary are a bit tricky. We support such manifolds, but carry out most calculations only in “the fleshy part” – the interior, which is an “infinite space”, so you can arbitrarily scale paths.

The default implementation is Interior x = x, which corresponds to a manifold that has no boundary to begin with.

Methods

(.+~^) :: Interior x -> Needle x -> x infixl 6 Source #

Generalised translation operation. Note that the result will always also be in the interior; scaling up the needle can only get you ever closer to a boundary.

fromInterior :: Interior x -> x Source #

id sans boundary.

toInterior :: x -> Maybe (Interior x) Source #

toInterior :: (Generic x, Semimanifold (VRep x), Interior x ~ GenericInterior x) => x -> Maybe (Interior x) Source #

translateP :: Tagged x (Interior x -> Needle x -> Interior x) Source #

The signature of .+~^ should really be Interior x -> Needle x -> Interior x, only, this is not possible because it only consists of non-injective type families. The solution is this tagged signature, which is of course rather unwieldy. That's why .+~^ has the stronger, but easier usable signature. Without boundary, these functions should be equivalent, i.e. translateP = Tagged (.+~^).

translateP :: (Generic x, Semimanifold (VRep x), Interior x ~ GenericInterior x, Needle x ~ GenericNeedle x) => Tagged x (Interior x -> Needle x -> Interior x) Source #

The signature of .+~^ should really be Interior x -> Needle x -> Interior x, only, this is not possible because it only consists of non-injective type families. The solution is this tagged signature, which is of course rather unwieldy. That's why .+~^ has the stronger, but easier usable signature. Without boundary, these functions should be equivalent, i.e. translateP = Tagged (.+~^).

(.-~^) :: Interior x -> Needle x -> x infixl 6 Source #

Shorthand for \p v -> p .+~^ negateV v, which should obey the asymptotic law

p .-~^ v .+~^ v ≅ p

Meaning: if v is scaled down with sufficiently small factors η, then the difference (p.-~^v.+~^v) .-~. p should scale down even faster: as O (η²). For large vectors, it will however behave differently, except in flat spaces (where all this should be equivalent to the AffineSpace instance).

semimanifoldWitness :: SemimanifoldWitness x Source #

semimanifoldWitness :: (Semimanifold (Interior x), Semimanifold (Needle x), Interior (Interior x) ~ Interior x, Needle (Interior x) ~ Needle x, Needle (Needle x) ~ Needle x, Interior (Needle x) ~ Needle x) => SemimanifoldWitness x Source #

Instances
Semimanifold Double Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle Double :: Type Source #

type Interior Double :: Type Source #

Semimanifold Rational Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle Rational :: Type Source #

type Interior Rational :: Type Source #

Semimanifold Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle :: Type Source #

type Interior :: Type Source #

Semimanifold ℝP¹ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle ℝP¹ :: Type Source #

type Interior ℝP¹ :: Type Source #

Semimanifold Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle :: Type Source #

type Interior :: Type Source #

Semimanifold ℝP⁰ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle ℝP⁰ :: Type Source #

type Interior ℝP⁰ :: Type Source #

Semimanifold S⁰ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle S⁰ :: Type Source #

type Interior S⁰ :: Type Source #

Semimanifold (ZeroDim k) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (ZeroDim k) :: Type Source #

type Interior (ZeroDim k) :: Type Source #

Semimanifold (VRep x) => Semimanifold (GenericInterior x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (GenericInterior x) :: Type Source #

type Interior (GenericInterior x) :: Type Source #

AdditiveGroup (Needle (VRep x)) => Semimanifold (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (GenericNeedle x) :: Type Source #

type Interior (GenericNeedle x) :: Type Source #

(Semimanifold a, Semimanifold b) => Semimanifold (a, b) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (a, b) :: Type Source #

type Interior (a, b) :: Type Source #

Methods

(.+~^) :: Interior (a, b) -> Needle (a, b) -> (a, b) Source #

fromInterior :: Interior (a, b) -> (a, b) Source #

toInterior :: (a, b) -> Maybe (Interior (a, b)) Source #

translateP :: Tagged (a, b) (Interior (a, b) -> Needle (a, b) -> Interior (a, b)) Source #

(.-~^) :: Interior (a, b) -> Needle (a, b) -> (a, b) Source #

semimanifoldWitness :: SemimanifoldWitness (a, b) Source #

Semimanifold a => Semimanifold (Rec0 a s) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (Rec0 a s) :: Type Source #

type Interior (Rec0 a s) :: Type Source #

Methods

(.+~^) :: Interior (Rec0 a s) -> Needle (Rec0 a s) -> Rec0 a s Source #

fromInterior :: Interior (Rec0 a s) -> Rec0 a s Source #

toInterior :: Rec0 a s -> Maybe (Interior (Rec0 a s)) Source #

translateP :: Tagged (Rec0 a s) (Interior (Rec0 a s) -> Needle (Rec0 a s) -> Interior (Rec0 a s)) Source #

(.-~^) :: Interior (Rec0 a s) -> Needle (Rec0 a s) -> Rec0 a s Source #

semimanifoldWitness :: SemimanifoldWitness (Rec0 a s) Source #

(Semimanifold a, Semimanifold b, Semimanifold c) => Semimanifold (a, b, c) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (a, b, c) :: Type Source #

type Interior (a, b, c) :: Type Source #

Methods

(.+~^) :: Interior (a, b, c) -> Needle (a, b, c) -> (a, b, c) Source #

fromInterior :: Interior (a, b, c) -> (a, b, c) Source #

toInterior :: (a, b, c) -> Maybe (Interior (a, b, c)) Source #

translateP :: Tagged (a, b, c) (Interior (a, b, c) -> Needle (a, b, c) -> Interior (a, b, c)) Source #

(.-~^) :: Interior (a, b, c) -> Needle (a, b, c) -> (a, b, c) Source #

semimanifoldWitness :: SemimanifoldWitness (a, b, c) Source #

(Semimanifold (f p), Semimanifold (g p)) => Semimanifold (InteriorProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (InteriorProductSpace f g p) :: Type Source #

type Interior (InteriorProductSpace f g p) :: Type Source #

(Semimanifold (f p), Semimanifold (g p)) => Semimanifold (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (NeedleProductSpace f g p) :: Type Source #

type Interior (NeedleProductSpace f g p) :: Type Source #

(Semimanifold (f p), Semimanifold (g p)) => Semimanifold ((f :*: g) p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle ((f :*: g) p) :: Type Source #

type Interior ((f :*: g) p) :: Type Source #

Methods

(.+~^) :: Interior ((f :*: g) p) -> Needle ((f :*: g) p) -> (f :*: g) p Source #

fromInterior :: Interior ((f :*: g) p) -> (f :*: g) p Source #

toInterior :: (f :*: g) p -> Maybe (Interior ((f :*: g) p)) Source #

translateP :: Tagged ((f :*: g) p) (Interior ((f :*: g) p) -> Needle ((f :*: g) p) -> Interior ((f :*: g) p)) Source #

(.-~^) :: Interior ((f :*: g) p) -> Needle ((f :*: g) p) -> (f :*: g) p Source #

semimanifoldWitness :: SemimanifoldWitness ((f :*: g) p) Source #

Semimanifold (f p) => Semimanifold (M1 i c f p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (M1 i c f p) :: Type Source #

type Interior (M1 i c f p) :: Type Source #

Methods

(.+~^) :: Interior (M1 i c f p) -> Needle (M1 i c f p) -> M1 i c f p Source #

fromInterior :: Interior (M1 i c f p) -> M1 i c f p Source #

toInterior :: M1 i c f p -> Maybe (Interior (M1 i c f p)) Source #

translateP :: Tagged (M1 i c f p) (Interior (M1 i c f p) -> Needle (M1 i c f p) -> Interior (M1 i c f p)) Source #

(.-~^) :: Interior (M1 i c f p) -> Needle (M1 i c f p) -> M1 i c f p Source #

semimanifoldWitness :: SemimanifoldWitness (M1 i c f p) Source #

class Semimanifold x => PseudoAffine x where Source #

This is the class underlying manifolds. (Manifold only precludes boundaries and adds an extra constraint that would be circular if it was in a single class. You can always just use Manifold as a constraint in your signatures, but you must define only PseudoAffine for manifold types – the Manifold instance follows universally from this, if 'Interior x ~ x.)

The interface is (boundaries aside) almost identical to the better-known AffineSpace class, but we don't require associativity of .+~^ with ^+^ – except in an asymptotic sense for small vectors.

That innocent-looking change makes the class applicable to vastly more general types: while an affine space is basically nothing but a vector space without particularly designated origin, a pseudo-affine space can have nontrivial topology on the global scale, and yet be used in practically the same way as an affine space. At least the usual spheres and tori make good instances, perhaps the class is in fact equivalent to manifolds in their usual maths definition (with an atlas of charts: a family of overlapping regions of the topological space, each homeomorphic to the Needle vector space or some simply-connected subset thereof).

Minimal complete definition

(.-~.) | (.-~!)

Methods

(.-~.) :: x -> x -> Maybe (Needle x) infix 6 Source #

The path reaching from one point to another. Should only yield Nothing if

  • The points are on disjoint segments of a non–path-connected space.
  • Either of the points is on the boundary. Use |-~. to deal with this.

On manifolds, the identity

p .+~^ (q.-~.p) ≡ q

should hold, at least save for floating-point precision limits etc..

.-~. and .+~^ only really work in manifolds without boundary. If you consider the path between two points, one of which lies on the boundary, it can't really be possible to scale this path any longer – it would have to reach “out of the manifold”. To adress this problem, these functions basically consider only the interior of the space.

(.-~!) :: HasCallStack => x -> x -> Needle x infix 6 Source #

Unsafe version of .-~.. If the two points lie in disjoint regions, the behaviour is undefined.

pseudoAffineWitness :: PseudoAffineWitness x Source #

pseudoAffineWitness :: (PseudoAffine (Interior x), PseudoAffine (Needle x)) => PseudoAffineWitness x Source #

Instances
PseudoAffine Double Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine Rational Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine ℝP¹ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine ℝP⁰ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine S⁰ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine (ZeroDim k) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine (VRep x) => PseudoAffine (GenericInterior x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

AdditiveGroup (Needle (VRep x)) => PseudoAffine (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

(PseudoAffine a, PseudoAffine b) => PseudoAffine (a, b) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Methods

(.-~.) :: (a, b) -> (a, b) -> Maybe (Needle (a, b)) Source #

(.-~!) :: (a, b) -> (a, b) -> Needle (a, b) Source #

pseudoAffineWitness :: PseudoAffineWitness (a, b) Source #

PseudoAffine a => PseudoAffine (Rec0 a s) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Methods

(.-~.) :: Rec0 a s -> Rec0 a s -> Maybe (Needle (Rec0 a s)) Source #

(.-~!) :: Rec0 a s -> Rec0 a s -> Needle (Rec0 a s) Source #

pseudoAffineWitness :: PseudoAffineWitness (Rec0 a s) Source #

(PseudoAffine a, PseudoAffine b, PseudoAffine c) => PseudoAffine (a, b, c) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Methods

(.-~.) :: (a, b, c) -> (a, b, c) -> Maybe (Needle (a, b, c)) Source #

(.-~!) :: (a, b, c) -> (a, b, c) -> Needle (a, b, c) Source #

pseudoAffineWitness :: PseudoAffineWitness (a, b, c) Source #

(PseudoAffine (f p), PseudoAffine (g p)) => PseudoAffine (InteriorProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

(PseudoAffine (f p), PseudoAffine (g p)) => PseudoAffine (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

(PseudoAffine (f p), PseudoAffine (g p)) => PseudoAffine ((f :*: g) p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Methods

(.-~.) :: (f :*: g) p -> (f :*: g) p -> Maybe (Needle ((f :*: g) p)) Source #

(.-~!) :: (f :*: g) p -> (f :*: g) p -> Needle ((f :*: g) p) Source #

pseudoAffineWitness :: PseudoAffineWitness ((f :*: g) p) Source #

PseudoAffine (f p) => PseudoAffine (M1 i c f p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Methods

(.-~.) :: M1 i c f p -> M1 i c f p -> Maybe (Needle (M1 i c f p)) Source #

(.-~!) :: M1 i c f p -> M1 i c f p -> Needle (M1 i c f p) Source #

pseudoAffineWitness :: PseudoAffineWitness (M1 i c f p) Source #

data FibreBundle b f Source #

A fibre bundle combines points in the base space b with points in the fibre f. The type FibreBundle b f is thus isomorphic to the tuple space (b,f), but it can have a different topology, the prime example being TangentBundle, where nearby points may have differently-oriented tangent spaces.

Constructors

FibreBundle 

Fields

Instances
(Show b, Show f) => Show (FibreBundle b f) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Methods

showsPrec :: Int -> FibreBundle b f -> ShowS #

show :: FibreBundle b f -> String #

showList :: [FibreBundle b f] -> ShowS #

Generic (FibreBundle b f) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Rep (FibreBundle b f) :: Type -> Type #

Methods

from :: FibreBundle b f -> Rep (FibreBundle b f) x #

to :: Rep (FibreBundle b f) x -> FibreBundle b f #

type Rep (FibreBundle b f) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Rep (FibreBundle b f) = D1 (MetaData "FibreBundle" "Math.Manifold.Core.PseudoAffine" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" False) (C1 (MetaCons "FibreBundle" PrefixI True) (S1 (MetaSel (Just "baseSpace") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b) :*: S1 (MetaSel (Just "fibreSpace") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 f)))

type TangentBundle m = FibreBundle m (Needle m) Source #

Points on a manifold, combined with vectors in the respective tangent space.

palerp :: forall x. (PseudoAffine x, VectorSpace (Needle x)) => x -> x -> Maybe (Scalar (Needle x) -> x) Source #

Interpolate between points, approximately linearly. For points that aren't close neighbours (i.e. lie in an almost flat region), the pathway is basically undefined – save for its end points.

A proper, really well-defined (on global scales) interpolation only makes sense on a Riemannian manifold, as Geodesic.

palerpB :: forall x. (PseudoAffine x, VectorSpace (Needle x), Scalar (Needle x) ~ ) => x -> x -> Maybe ( -> x) Source #

Like palerp, but actually restricted to the interval between the points, with a signature like geodesicBetween rather than alerp.

alerpB :: forall x. (AffineSpace x, VectorSpace (Diff x), Scalar (Diff x) ~ ) => x -> x -> -> x Source #

Like alerp, but actually restricted to the interval between the points.

data NeedleProductSpace f g p Source #

Constructors

NeedleProductSpace !(Needle (f p)) !(Needle (g p)) 
Instances
Generic (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Rep (NeedleProductSpace f g p) :: Type -> Type #

Methods

from :: NeedleProductSpace f g p -> Rep (NeedleProductSpace f g p) x #

to :: Rep (NeedleProductSpace f g p) x -> NeedleProductSpace f g p #

(Semimanifold (f p), Semimanifold (g p)) => AffineSpace (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Diff (NeedleProductSpace f g p) :: Type #

(Semimanifold (f p), Semimanifold (g p), HasBasis (Needle (f p)), HasBasis (Needle (g p)), Scalar (Needle (f p)) ~ Scalar (Needle (g p))) => HasBasis (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Basis (NeedleProductSpace f g p) :: Type #

(Semimanifold (f p), Semimanifold (g p), VectorSpace (Needle (f p)), VectorSpace (Needle (g p)), Scalar (Needle (f p)) ~ Scalar (Needle (g p))) => VectorSpace (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Scalar (NeedleProductSpace f g p) :: Type #

(Semimanifold (f p), Semimanifold (g p), InnerSpace (Needle (f p)), InnerSpace (Needle (g p)), Scalar (Needle (f p)) ~ Scalar (Needle (g p)), Num (Scalar (Needle (f p)))) => InnerSpace (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

(Semimanifold (f p), Semimanifold (g p)) => AdditiveGroup (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

(PseudoAffine (f p), PseudoAffine (g p)) => PseudoAffine (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

(Semimanifold (f p), Semimanifold (g p)) => Semimanifold (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (NeedleProductSpace f g p) :: Type Source #

type Interior (NeedleProductSpace f g p) :: Type Source #

type Rep (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Rep (NeedleProductSpace f g p) = D1 (MetaData "NeedleProductSpace" "Math.Manifold.Core.PseudoAffine" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" False) (C1 (MetaCons "NeedleProductSpace" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Needle (f p))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Needle (g p)))))
type Diff (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Basis (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Basis (NeedleProductSpace f g p) = Either (Basis (Needle (f p))) (Basis (Needle (g p)))
type Scalar (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Scalar (NeedleProductSpace f g p) = Scalar (VRep (NeedleProductSpace f g p))
type Needle (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Interior (NeedleProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

data InteriorProductSpace f g p Source #

Constructors

InteriorProductSpace !(Interior (f p)) !(Interior (g p)) 
Instances
Generic (InteriorProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Rep (InteriorProductSpace f g p) :: Type -> Type #

(PseudoAffine (f p), PseudoAffine (g p)) => PseudoAffine (InteriorProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

(Semimanifold (f p), Semimanifold (g p)) => Semimanifold (InteriorProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (InteriorProductSpace f g p) :: Type Source #

type Interior (InteriorProductSpace f g p) :: Type Source #

type Rep (InteriorProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Rep (InteriorProductSpace f g p) = D1 (MetaData "InteriorProductSpace" "Math.Manifold.Core.PseudoAffine" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" False) (C1 (MetaCons "InteriorProductSpace" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Interior (f p))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Interior (g p)))))
type Needle (InteriorProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Interior (InteriorProductSpace f g p) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

newtype GenericNeedle x Source #

Constructors

GenericNeedle 
Instances
Generic (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Rep (GenericNeedle x) :: Type -> Type #

Methods

from :: GenericNeedle x -> Rep (GenericNeedle x) x0 #

to :: Rep (GenericNeedle x) x0 -> GenericNeedle x #

AdditiveGroup (Needle (VRep x)) => AffineSpace (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Diff (GenericNeedle x) :: Type #

VectorSpace (Needle (VRep x)) => VectorSpace (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Scalar (GenericNeedle x) :: Type #

InnerSpace (Needle (VRep x)) => InnerSpace (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

AdditiveGroup (Needle (VRep x)) => AdditiveGroup (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

AdditiveGroup (Needle (VRep x)) => PseudoAffine (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

AdditiveGroup (Needle (VRep x)) => Semimanifold (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (GenericNeedle x) :: Type Source #

type Interior (GenericNeedle x) :: Type Source #

type Rep (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Rep (GenericNeedle x) = D1 (MetaData "GenericNeedle" "Math.Manifold.Core.PseudoAffine" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" True) (C1 (MetaCons "GenericNeedle" PrefixI True) (S1 (MetaSel (Just "getGenericNeedle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Needle (VRep x)))))
type Diff (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Scalar (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Needle (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Interior (GenericNeedle x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

newtype GenericInterior x Source #

Constructors

GenericInterior 
Instances
Generic (GenericInterior x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Rep (GenericInterior x) :: Type -> Type #

PseudoAffine (VRep x) => PseudoAffine (GenericInterior x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Semimanifold (VRep x) => Semimanifold (GenericInterior x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (GenericInterior x) :: Type Source #

type Interior (GenericInterior x) :: Type Source #

type Rep (GenericInterior x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Rep (GenericInterior x) = D1 (MetaData "GenericInterior" "Math.Manifold.Core.PseudoAffine" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" True) (C1 (MetaCons "GenericInterior" PrefixI True) (S1 (MetaSel (Just "getGenericInterior") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Interior (VRep x)))))
type Needle (GenericInterior x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Interior (GenericInterior x) Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type VRep x = Rep x Void Source #