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.Types

Contents

Description

Several low-dimensional manifolds, represented in some simple way as Haskell data types. All these are in the PseudoAffine class.

Synopsis

Documentation

data S⁰ Source #

The zero-dimensional sphere is actually just two points. Implementation might therefore change to ℝ⁰ + ℝ⁰: the disjoint sum of two single-point spaces.

Instances
Eq S⁰ Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Methods

(==) :: S⁰ -> S⁰ -> Bool #

(/=) :: S⁰ -> S⁰ -> Bool #

Show S⁰ Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Methods

showsPrec :: Int -> S⁰ -> ShowS #

show :: S⁰ -> String #

showList :: [S⁰] -> ShowS #

Generic S⁰ Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Associated Types

type Rep S⁰ :: Type -> Type #

Methods

from :: S⁰ -> Rep S⁰ x #

to :: Rep S⁰ x -> S⁰ #

PseudoAffine S⁰ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Semimanifold S⁰ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle S⁰ :: Type Source #

type Interior S⁰ :: Type Source #

type Rep S⁰ Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

type Rep S⁰ = D1 (MetaData "S\8304" "Math.Manifold.Core.Types.Internal" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" False) (C1 (MetaCons "PositiveHalfSphere" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NegativeHalfSphere" PrefixI False) (U1 :: Type -> Type))
type Needle S⁰ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Interior S⁰ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

newtype Source #

The unit circle.

Constructors

S¹Polar 

Fields

Instances
Eq Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Methods

(==) :: -> -> Bool #

(/=) :: -> -> Bool #

Show Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Methods

showsPrec :: Int -> -> ShowS #

show :: -> String #

showList :: [] -> ShowS #

Generic Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Associated Types

type Rep :: Type -> Type #

Methods

from :: -> Rep x #

to :: Rep x -> #

PseudoAffine Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Semimanifold Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle :: Type Source #

type Interior :: Type Source #

type Rep Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

type Rep = D1 (MetaData "S\185" "Math.Manifold.Core.Types.Internal" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" True) (C1 (MetaCons "S\185Polar" PrefixI True) (S1 (MetaSel (Just "\966ParamS\185") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))
type Needle Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Needle =
type Interior Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

pattern :: Double -> Source #

Deprecated: Use Math.Manifold.Core.Types.S¹Polar

data Source #

The ordinary unit sphere.

Constructors

S²Polar 

Fields

Instances
Eq Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Methods

(==) :: -> -> Bool #

(/=) :: -> -> Bool #

Show Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Methods

showsPrec :: Int -> -> ShowS #

show :: -> String #

showList :: [] -> ShowS #

Generic Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Associated Types

type Rep :: Type -> Type #

Methods

from :: -> Rep x #

to :: Rep x -> #

type Rep Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

type Rep = D1 (MetaData "S\178" "Math.Manifold.Core.Types.Internal" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" False) (C1 (MetaCons "S\178Polar" PrefixI True) (S1 (MetaSel (Just "\977ParamS\178") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "\966ParamS\178") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)))

pattern :: Double -> Double -> Source #

Deprecated: Use Math.Manifold.Core.Types.S²Polar

newtype Source #

The “one-dimensional disk” – really just the line segment between the two points -1 and 1 of S⁰, i.e. this is simply a closed interval.

Constructors

 

Fields

Instances
Show Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Methods

showsPrec :: Int -> -> ShowS #

show :: -> String #

showList :: [] -> ShowS #

Generic Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Associated Types

type Rep :: Type -> Type #

Methods

from :: -> Rep x #

to :: Rep x -> #

PseudoAffine Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Semimanifold Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle :: Type Source #

type Interior :: Type Source #

type Rep Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

type Rep = D1 (MetaData "D\185" "Math.Manifold.Core.Types.Internal" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" True) (C1 (MetaCons "D\185" PrefixI True) (S1 (MetaSel (Just "xParamD\185") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))
type Needle Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Needle =
type Interior Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

data Source #

The standard, closed unit disk. Homeomorphic to the cone over , but not in the the obvious, “flat” way. (In is not homeomorphic, despite the almost identical ADT definition, to the projective space ℝP²!)

Constructors

D²Polar 

Fields

Instances
Show Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Methods

showsPrec :: Int -> -> ShowS #

show :: -> String #

showList :: [] -> ShowS #

Generic Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Associated Types

type Rep :: Type -> Type #

Methods

from :: -> Rep x #

to :: Rep x -> #

type Rep Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

type Rep = D1 (MetaData "D\178" "Math.Manifold.Core.Types.Internal" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" False) (C1 (MetaCons "D\178Polar" PrefixI True) (S1 (MetaSel (Just "rParamD\178") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "\966ParamD\178") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)))

pattern :: Double -> Double -> Source #

Deprecated: Use Math.Manifold.Core.Types.D²Polar

data ℝP⁰ Source #

Constructors

ℝPZero 
Instances
Eq ℝP⁰ Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Methods

(==) :: ℝP⁰ -> ℝP⁰ -> Bool #

(/=) :: ℝP⁰ -> ℝP⁰ -> Bool #

Show ℝP⁰ Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Generic ℝP⁰ Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Associated Types

type Rep ℝP⁰ :: Type -> Type #

Methods

from :: ℝP⁰ -> Rep ℝP⁰ x #

to :: Rep ℝP⁰ x -> ℝP⁰ #

PseudoAffine ℝP⁰ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Semimanifold ℝP⁰ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle ℝP⁰ :: Type Source #

type Interior ℝP⁰ :: Type Source #

type Rep ℝP⁰ Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

type Rep ℝP⁰ = D1 (MetaData "\8477P\8304" "Math.Manifold.Core.Types.Internal" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" False) (C1 (MetaCons "\8477PZero" PrefixI False) (U1 :: Type -> Type))
type Needle ℝP⁰ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Interior ℝP⁰ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

newtype ℝP¹ Source #

Constructors

HemisphereℝP¹Polar 

Fields

Instances
Show ℝP¹ Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Generic ℝP¹ Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Associated Types

type Rep ℝP¹ :: Type -> Type #

Methods

from :: ℝP¹ -> Rep ℝP¹ x #

to :: Rep ℝP¹ x -> ℝP¹ #

PseudoAffine ℝP¹ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Semimanifold ℝP¹ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle ℝP¹ :: Type Source #

type Interior ℝP¹ :: Type Source #

type Rep ℝP¹ Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

type Rep ℝP¹ = D1 (MetaData "\8477P\185" "Math.Manifold.Core.Types.Internal" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" True) (C1 (MetaCons "Hemisphere\8477P\185Polar" PrefixI True) (S1 (MetaSel (Just "\966Param\8477P\185") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))
type Needle ℝP¹ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

type Interior ℝP¹ Source # 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

pattern ℝP¹ :: Double -> ℝP¹ Source #

Deprecated: Use Math.Manifold.Core.Types.HemisphereℝP¹Polar (notice: different range)

data ℝP² Source #

The two-dimensional real projective space, implemented as a disk with opposing points on the rim glued together. Image this disk as the northern hemisphere of a unit sphere; ℝP² is the space of all straight lines passing through the origin of ℝ³, and each of these lines is represented by the point at which it passes through the hemisphere.

Constructors

HemisphereℝP²Polar 

Fields

Instances
Show ℝP² Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Generic ℝP² Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Associated Types

type Rep ℝP² :: Type -> Type #

Methods

from :: ℝP² -> Rep ℝP² x #

to :: Rep ℝP² x -> ℝP² #

type Rep ℝP² Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

type Rep ℝP² = D1 (MetaData "\8477P\178" "Math.Manifold.Core.Types.Internal" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" False) (C1 (MetaCons "Hemisphere\8477P\178Polar" PrefixI True) (S1 (MetaSel (Just "\977Param\8477P\178") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "\966Param\8477P\178") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)))

pattern ℝP² :: Double -> Double -> ℝP² Source #

Deprecated: Use Math.Manifold.Core.Types.HemisphereℝP²Polar (notice: different range)

data Cℝay x Source #

An open cone is homeomorphic to a closed cone without the “lid”, i.e. without the “last copy” of x, at the far end of the height interval. Since that means the height does not include its supremum, it is actually more natural to express it as the entire real ray, hence the name.

Constructors

Cℝay 

Fields

Instances
Show x => Show (Cℝay x) Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Methods

showsPrec :: Int -> Cℝay x -> ShowS #

show :: Cℝay x -> String #

showList :: [Cℝay x] -> ShowS #

Generic (Cℝay x) Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Associated Types

type Rep (Cℝay x) :: Type -> Type #

Methods

from :: Cℝay x -> Rep (Cℝay x) x0 #

to :: Rep (Cℝay x) x0 -> Cℝay x #

type Rep (Cℝay x) Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

type Rep (Cℝay x) = D1 (MetaData "C\8477ay" "Math.Manifold.Core.Types.Internal" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" False) (C1 (MetaCons "C\8477ay" PrefixI True) (S1 (MetaSel (Just "hParamC\8477ay") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "pParamC\8477ay") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 x)))

data CD¹ x Source #

A (closed) cone over a space x is the product of x with the closed interval of “heights”, except on its “tip”: here, x is smashed to a single point.

This construct becomes (homeomorphic-to-) an actual geometric cone (and to ) in the special case x = .

Constructors

CD¹ 

Fields

Instances
Show x => Show (CD¹ x) Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Methods

showsPrec :: Int -> CD¹ x -> ShowS #

show :: CD¹ x -> String #

showList :: [CD¹ x] -> ShowS #

Generic (CD¹ x) Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

Associated Types

type Rep (CD¹ x) :: Type -> Type #

Methods

from :: CD¹ x -> Rep (CD¹ x) x0 #

to :: Rep (CD¹ x) x0 -> CD¹ x #

type Rep (CD¹ x) Source # 
Instance details

Defined in Math.Manifold.Core.Types.Internal

type Rep (CD¹ x) = D1 (MetaData "CD\185" "Math.Manifold.Core.Types.Internal" "manifolds-core-0.5.0.4-B8Kp6L8TW711kRSgoVKNgU" False) (C1 (MetaCons "CD\185" PrefixI True) (S1 (MetaSel (Just "hParamCD\185") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "pParamCD\185") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 x)))

Orphan instances

HasBasis () Source # 
Instance details

Associated Types

type Basis () :: Type #

Methods

basisValue :: Basis () -> () #

decompose :: () -> [(Basis (), Scalar ())] #

decompose' :: () -> Basis () -> Scalar () #

VectorSpace () Source # 
Instance details

Associated Types

type Scalar () :: Type #

Methods

(*^) :: Scalar () -> () -> () #

InnerSpace () Source # 
Instance details

Methods

(<.>) :: () -> () -> Scalar () #