goal-geometry-0.20: The basic geometric type system of Goal
Safe HaskellNone
LanguageHaskell2010

Goal.Geometry.Manifold

Description

The core mathematical definitions used by the rest of Goal. The central object is a Point on a Manifold. A Manifold is an object with a Dimension, and a Point represents an element of the Manifold in a particular coordinate system, represented by a chart.

Synopsis

Manifolds

class KnownNat (Dimension x) => Manifold x Source #

A geometric object with a certain Dimension.

Associated Types

type Dimension x :: Nat Source #

Instances

Instances details
Manifold x => Manifold [x] Source # 
Instance details

Defined in Goal.Geometry.Manifold

Associated Types

type Dimension [x] :: Nat Source #

KnownNat k => Manifold (Euclidean k) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Associated Types

type Dimension (Euclidean k) :: Nat Source #

(Manifold x, Manifold y) => Manifold (x, y) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Associated Types

type Dimension (x, y) :: Nat Source #

(KnownNat k, Manifold x) => Manifold (Replicated k x) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Associated Types

type Dimension (Replicated k x) :: Nat Source #

(Manifold x, Manifold y) => Manifold (Tensor y x) Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

Associated Types

type Dimension (Tensor y x) :: Nat Source #

(Manifold z, Manifold (f y x)) => Manifold (Affine f y z x) Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

Associated Types

type Dimension (Affine f y z x) :: Nat Source #

(Manifold (Affine f z z y), Manifold (NeuralNetwork gys g y x)) => Manifold (NeuralNetwork ('(g, y) ': gys) f z x) Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

Associated Types

type Dimension (NeuralNetwork ('(g, y) ': gys) f z x) :: Nat Source #

Manifold (Affine f z z x) => Manifold (NeuralNetwork ('[] :: [(Type -> Type -> Type, Type)]) f z x) Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

Associated Types

type Dimension (NeuralNetwork '[] f z x) :: Nat Source #

(1 <= (r * c), Manifold x, Manifold y, KnownNat r, KnownNat c, KnownNat rd, KnownNat (Div (Dimension x) (r * c)), KnownNat (Div (Dimension y) (r * c))) => Manifold (Convolutional rd r c y x) Source # 
Instance details

Defined in Goal.Geometry.Map.Linear.Convolutional

Associated Types

type Dimension (Convolutional rd r c y x) :: Nat Source #

dimension :: Manifold x => Proxy x -> Int Source #

The Dimension of the given Manifold.

Combinators

data Replicated (k :: Nat) m Source #

A Sum type for repetitions of the same Manifold.

Instances

Instances details
(KnownNat k, Manifold x, Transition c d x) => Transition c d (Replicated k x) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Methods

transition :: (c # Replicated k x) -> d # Replicated k x Source #

(KnownNat k, Manifold x) => Manifold (Replicated k x) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Associated Types

type Dimension (Replicated k x) :: Nat Source #

(DuallyFlat x, KnownNat k) => DuallyFlat (Replicated k x) Source # 
Instance details

Defined in Goal.Geometry.Differential

(Legendre x, KnownNat k) => Legendre (Replicated k x) Source # 
Instance details

Defined in Goal.Geometry.Differential

type Dimension (Replicated k x) Source # 
Instance details

Defined in Goal.Geometry.Manifold

type Dimension (Replicated k x) = k * Dimension x
type PotentialCoordinates (Replicated k x) Source # 
Instance details

Defined in Goal.Geometry.Differential

type R k x = Replicated k x Source #

An abbreviation for Replicated.

Points

newtype Point c x Source #

A Point on a Manifold. The phantom type m represents the Manifold, and the phantom type c represents the coordinate system, or chart, in which the Point is represented.

Constructors

Point 

Fields

Instances

Instances details
Eq (Point c x) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Methods

(==) :: Point c x -> Point c x -> Bool #

(/=) :: Point c x -> Point c x -> Bool #

(Manifold x, KnownNat (Dimension x)) => Floating (Point c x) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Methods

pi :: Point c x #

exp :: Point c x -> Point c x #

log :: Point c x -> Point c x #

sqrt :: Point c x -> Point c x #

(**) :: Point c x -> Point c x -> Point c x #

logBase :: Point c x -> Point c x -> Point c x #

sin :: Point c x -> Point c x #

cos :: Point c x -> Point c x #

tan :: Point c x -> Point c x #

asin :: Point c x -> Point c x #

acos :: Point c x -> Point c x #

atan :: Point c x -> Point c x #

sinh :: Point c x -> Point c x #

cosh :: Point c x -> Point c x #

tanh :: Point c x -> Point c x #

asinh :: Point c x -> Point c x #

acosh :: Point c x -> Point c x #

atanh :: Point c x -> Point c x #

log1p :: Point c x -> Point c x #

expm1 :: Point c x -> Point c x #

log1pexp :: Point c x -> Point c x #

log1mexp :: Point c x -> Point c x #

(Manifold x, KnownNat (Dimension x)) => Fractional (Point c x) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Methods

(/) :: Point c x -> Point c x -> Point c x #

recip :: Point c x -> Point c x #

fromRational :: Rational -> Point c x #

(Manifold x, KnownNat (Dimension x)) => Num (c # x) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Methods

(+) :: (c # x) -> (c # x) -> c # x #

(-) :: (c # x) -> (c # x) -> c # x #

(*) :: (c # x) -> (c # x) -> c # x #

negate :: (c # x) -> c # x #

abs :: (c # x) -> c # x #

signum :: (c # x) -> c # x #

fromInteger :: Integer -> c # x #

Ord (Point c x) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Methods

compare :: Point c x -> Point c x -> Ordering #

(<) :: Point c x -> Point c x -> Bool #

(<=) :: Point c x -> Point c x -> Bool #

(>) :: Point c x -> Point c x -> Bool #

(>=) :: Point c x -> Point c x -> Bool #

max :: Point c x -> Point c x -> Point c x #

min :: Point c x -> Point c x -> Point c x #

Show (Point c x) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Methods

showsPrec :: Int -> Point c x -> ShowS #

show :: Point c x -> String #

showList :: [Point c x] -> ShowS #

KnownNat (Dimension x) => Storable (Point c x) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Methods

sizeOf :: Point c x -> Int #

alignment :: Point c x -> Int #

peekElemOff :: Ptr (Point c x) -> Int -> IO (Point c x) #

pokeElemOff :: Ptr (Point c x) -> Int -> Point c x -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Point c x) #

pokeByteOff :: Ptr b -> Int -> Point c x -> IO () #

peek :: Ptr (Point c x) -> IO (Point c x) #

poke :: Ptr (Point c x) -> Point c x -> IO () #

NFData (Point c x) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Methods

rnf :: Point c x -> () #

type (#) c x = Point c x infix 3 Source #

An infix version of Point, where x is assumed to be of type Double.

breakPoint :: Dimension x ~ Dimension y => (c # x) -> Point d y Source #

Throws away the type-level information about the chart and manifold of the given Point.

listCoordinates :: (c # x) -> [Double] Source #

Returns the coordinates of the point in list form.

boxCoordinates :: (c # x) -> Vector (Dimension x) Double Source #

Returns the coordinates of the point as a boxed vector.

Constructors

singleton :: Dimension x ~ 1 => Double -> c # x Source #

Constructs a Point with Dimension 1.

fromTuple :: (IndexedListLiterals ds (Dimension x) Double, KnownNat (Dimension x)) => ds -> c # x Source #

Constructs a Point from a tuple.

fromBoxed :: Vector (Dimension x) Double -> c # x Source #

Constructs a point with coordinates given by a boxed vector.

class (Manifold (First z), Manifold (Second z), Manifold z, Dimension z ~ (Dimension (First z) + Dimension (Second z))) => Product z where Source #

A Product Manifold is one that is produced out of the sumproductconcatenation of two source Manifolds.

Associated Types

type First z :: Type Source #

type Second z :: Type Source #

The 'Second Manifold.

Methods

join :: (c # First z) -> (c # Second z) -> c # z Source #

Combine Points from the First and Second Manifold into a Point on the Product Manifold.

split :: (c # z) -> (c # First z, c # Second z) Source #

Split a Point on the Product Manifold into Points from the First and Second Manifold.

Instances

Instances details
(Manifold x, Manifold y) => Product (x, y) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Associated Types

type First (x, y) Source #

type Second (x, y) Source #

Methods

join :: (c # First (x, y)) -> (c # Second (x, y)) -> c # (x, y) Source #

split :: (c # (x, y)) -> (c # First (x, y), c # Second (x, y)) Source #

(Manifold z, Manifold (f y x)) => Product (Affine f y z x) Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

Associated Types

type First (Affine f y z x) Source #

type Second (Affine f y z x) Source #

Methods

join :: (c # First (Affine f y z x)) -> (c # Second (Affine f y z x)) -> c # Affine f y z x Source #

split :: (c # Affine f y z x) -> (c # First (Affine f y z x), c # Second (Affine f y z x)) Source #

(Manifold (Affine f z z y), Manifold (NeuralNetwork gys g y x)) => Product (NeuralNetwork ('(g, y) ': gys) f z x) Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

Associated Types

type First (NeuralNetwork ('(g, y) ': gys) f z x) Source #

type Second (NeuralNetwork ('(g, y) ': gys) f z x) Source #

Methods

join :: (c # First (NeuralNetwork ('(g, y) ': gys) f z x)) -> (c # Second (NeuralNetwork ('(g, y) ': gys) f z x)) -> c # NeuralNetwork ('(g, y) ': gys) f z x Source #

split :: (c # NeuralNetwork ('(g, y) ': gys) f z x) -> (c # First (NeuralNetwork ('(g, y) ': gys) f z x), c # Second (NeuralNetwork ('(g, y) ': gys) f z x)) Source #

Reshaping Points

splitReplicated :: (KnownNat k, Manifold x) => (c # Replicated k x) -> Vector k (c # x) Source #

Splits a Point on a Replicated Manifold into a Vector of of Points.

joinReplicated :: (KnownNat k, Manifold x) => Vector k (c # x) -> c # Replicated k x Source #

Joins a Vector of of Points into a Point on a Replicated Manifold.

joinBoxedReplicated :: (KnownNat k, Manifold x) => Vector k (c # x) -> c # Replicated k x Source #

Joins a Vector of of Points into a Point on a Replicated Manifold.

mapReplicated :: (Storable a, KnownNat k, Manifold x) => ((c # x) -> a) -> (c # Replicated k x) -> Vector k a Source #

A combination of splitReplicated and fmap.

mapReplicatedPoint :: (KnownNat k, Manifold x, Manifold y) => ((c # x) -> Point d y) -> (c # Replicated k x) -> Point d (Replicated k y) Source #

A combination of splitReplicated and fmap, where the value of the mapped function is also a point.

joinReplicatedProduct :: (KnownNat k, Product x) => (c # Replicated k (First x)) -> (c # Replicated k (Second x)) -> c # Replicated k x Source #

joins a Replicated Product Manifold out of a pair of Replicated Manifolds.

Euclidean Manifolds

data Euclidean (n :: Nat) Source #

n-dimensional Euclidean space.

Instances

Instances details
Transition Polar Cartesian (Euclidean 2) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Transition Cartesian Polar (Euclidean 2) Source # 
Instance details

Defined in Goal.Geometry.Manifold

KnownNat k => Riemannian Cartesian (Euclidean k) Source # 
Instance details

Defined in Goal.Geometry.Differential

KnownNat k => Manifold (Euclidean k) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Associated Types

type Dimension (Euclidean k) :: Nat Source #

type Dimension (Euclidean k) Source # 
Instance details

Defined in Goal.Geometry.Manifold

type Dimension (Euclidean k) = k

Charts

data Polar Source #

Polar coordinates on Euclidean space.

Instances

Instances details
Transition Polar Cartesian (Euclidean 2) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Transition Cartesian Polar (Euclidean 2) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Transition

class Transition c d x where Source #

A transition involves taking a point represented by the chart c, and re-representing in terms of the chart d.

Methods

transition :: (c # x) -> d # x Source #

Instances

Instances details
Transition Polar Cartesian (Euclidean 2) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Transition Cartesian Polar (Euclidean 2) Source # 
Instance details

Defined in Goal.Geometry.Manifold

(KnownNat k, Manifold x, Transition c d x) => Transition c d (Replicated k x) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Methods

transition :: (c # Replicated k x) -> d # Replicated k x Source #

(Manifold x, Manifold y, Transition c d x, Transition c d y) => Transition c d (x, y) Source # 
Instance details

Defined in Goal.Geometry.Manifold

Methods

transition :: (c # (x, y)) -> d # (x, y) Source #

transition2 :: (Transition cx dx x, Transition cy dy y) => ((dx # x) -> (dy # y) -> a) -> (cx # x) -> (cy # y) -> a Source #

Generalizes a function of two points in given coordinate systems to a function on arbitrary coordinate systems.