goal-geometry-0.1: Scientific computing on geometric objects

Safe HaskellNone
LanguageHaskell2010

Goal.Geometry.Manifold

Contents

Description

This module provides the core mathematical definitions used by the rest of Goal. In Goal, all mathematical structures are Manifolds, even when they are not especially complicated ones; Manifolds may indicate highly articulated structures, but may also indicate simpler concepts such as (vector) spaces.

Manifolds are sets of points which can be described locally as Euclidean spaces. In geometry, a point is typically a member of the actual Manifold. However, arbitrary types of points will often be difficult to represent directly, and so points in Goal are always represented in terms of their Coordinates in terms of a given chart.

Charts are in turn represented by phantom types. Mathematically, charts are maps between the Manifold and the relevant Cartesian coordinate system. However, since we do not represent the points of a Manifold explicility, we also cannot represent Charts explicitly. As such, Atlases merely index a point so as to indicate how to interpret its particular Coordinates.

Synopsis

Manifolds

class Eq m => Manifold m where Source

A geometric object with a certain dimension. We assume that a Manifold somehow represents all the geometric, coordinate independent structure under consideration. Manifolds should satisfy

dimension m = length $ coordinates (Point m cs)

Methods

dimension :: m -> Int Source

class Transition c d m where Source

A transition involves taking a point represented by the chart c, and re-representing in terms of the chart d. This will usually require recomputation of the Coordinates. Transitions should satisfy the law

transition $ transition p = p

Methods

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

Sets

data Embedded m c Source

Constructors

Embedded 

Fields

disembed :: m
 

Instances

Eq m => Eq (Embedded m c) Source 
Read m => Read (Embedded m c) Source 
Show m => Show (Embedded m c) Source 
Manifold m => Set (Embedded m c) Source 
type Element (Embedded m c) = (:#:) c m Source 

Points

type Coordinates = Vector Double Source

Elements of Euclidean spaces are referred to as Coordinates.

data c :#: m infixr 1 Source

A point is an element of a Manifold m in terms of a particular chart c.

Instances

Eq m => Eq ((:#:) c m) Source 
Read m => Read ((:#:) c m) Source 
Show m => Show ((:#:) c m) Source 

coordinate :: Int -> (c :#: m) -> Double Source

chart :: Manifold m => c -> (c :#: m) -> c :#: m Source

chart allows one to specify the Atlas of a new point. This is often necessary when typeclass methods are used to generate points under a variety of coordinate systems.

breakChart :: Manifold m => (c :#: m) -> d :#: m Source

alterChart :: Manifold m => d -> (c :#: m) -> d :#: m Source

Combines breakChart and chart.

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

Returns the Coordinates of the point in list form.

alterCoordinates :: Manifold m => (Double -> Double) -> (c :#: m) -> c :#: m Source

alterCoordinates allows one to map a function over the coordinates of a point without changing the chart.

toPair :: (c :#: m) -> (Double, Double) Source

Charts

Constructors

fromList :: Manifold m => m -> [Double] -> c :#: m Source

fromList builds points without the need to work with vectors.

euclideanPoint :: [Double] -> Cartesian :#: Euclidean Source

A convenience function for building Euclidean vectors.

realNumber :: Double -> Cartesian :#: Continuum Source

A convenience function for building elements of a Continuum.

Direct Sums

Replicated

mapReplicated :: Manifold m => ((c :#: m) -> x) -> (c :#: Replicated m) -> [x] Source

A function to map functions over a point on a Replicated Manifold.

joinReplicated :: Manifold m => [c :#: m] -> c :#: Replicated m Source

Joins a list of distributions into a Replicated Manifold. Be advised that this function assumes that the families of the individual distributions are equal.

DirectSum

joinPair :: (Manifold m, Manifold n) => (c :#: m) -> (d :#: n) -> (c, d) :#: (m, n) Source

Joins a pair of Points into a Point on the the direct sum of the underlying Charts and Manifolds.

splitPair :: (Manifold m, Manifold n) => ((c, d) :#: (m, n)) -> (c :#: m, d :#: n) Source

Splits a direct sum pair.

joinPair' :: (Manifold m, Manifold n) => (c :#: m) -> (c :#: n) -> c :#: (m, n) Source

Alternative version where we assume that the Charts are shared.

splitPair' :: (Manifold m, Manifold n) => (c :#: (m, n)) -> (c :#: m, c :#: n) Source

Alternative version where we assume that the Charts are shared.

joinTriple :: (Manifold m, Manifold n, Manifold o) => (c :#: m) -> (d :#: n) -> (e :#: o) -> (c, d, e) :#: (m, n, o) Source

Joins a triple of Points into a Point on the the direct sum of the underlying Charts and Manifolds.

splitTriple :: (Manifold m, Manifold n, Manifold o) => ((c, d, e) :#: (m, n, o)) -> (c :#: m, d :#: n, e :#: o) Source

Splits a direct sum triple.

joinTriple' :: (Manifold m, Manifold n, Manifold o) => (c :#: m) -> (c :#: n) -> (c :#: o) -> c :#: (m, n, o) Source

Alternative version where we assume that the Charts are shared.

splitTriple' :: (Manifold m, Manifold n, Manifold o) => (c :#: (m, n, o)) -> (c :#: m, c :#: n, c :#: o) Source

Alternative version where we assume that the Charts are shared.