numhask-space-0.1.1: numerical spaces

Safe HaskellNone
LanguageHaskell2010

NumHask.Analysis.Space

Synopsis

Documentation

class Spaceable (Element s) => Space s where Source #

a continuous set of numbers mathematics does not define a space, so library devs are free to experiment.

a `contains` union a b && b `contains` union a b
lower a \/ upper a == lower a
lower a /\ upper a == upper a

Minimal complete definition

lower, upper, (>.<)

Associated Types

type Element s :: * Source #

the underlying element in the space

Methods

lower :: s -> Element s Source #

lower boundary

upper :: s -> Element s Source #

upper boundary

singleton :: Element s -> s Source #

space containing a single element

intersection :: s -> s -> s Source #

the intersection of two spaces

union :: s -> s -> s Source #

the union of two spaces

norm :: s -> s Source #

Normalise a space so that > lower a / upper a == lower a > lower a / upper a == upper a

(...) :: Element s -> Element s -> s infix 3 Source #

create a normalised space from two elements

(>.<) :: Element s -> Element s -> s infix 3 Source #

create a space from two elements witjout normalising

Instances
Lattice a => Space (Range a) Source # 
Instance details

Defined in NumHask.Data.Range

Associated Types

type Element (Range a) :: Type Source #

Lattice a => Space (Rect a) Source # 
Instance details

Defined in NumHask.Data.Rect

Associated Types

type Element (Rect a) :: Type Source #

Methods

lower :: Rect a -> Element (Rect a) Source #

upper :: Rect a -> Element (Rect a) Source #

singleton :: Element (Rect a) -> Rect a Source #

intersection :: Rect a -> Rect a -> Rect a Source #

union :: Rect a -> Rect a -> Rect a Source #

norm :: Rect a -> Rect a Source #

(...) :: Element (Rect a) -> Element (Rect a) -> Rect a Source #

(>.<) :: Element (Rect a) -> Element (Rect a) -> Rect a Source #

newtype Union a Source #

Constructors

Union 

Fields

Instances
Space a => Semigroup (Union a) Source # 
Instance details

Defined in NumHask.Analysis.Space

Methods

(<>) :: Union a -> Union a -> Union a #

sconcat :: NonEmpty (Union a) -> Union a #

stimes :: Integral b => b -> Union a -> Union a #

(BoundedJoinSemiLattice a, Space a) => Monoid (Union a) Source # 
Instance details

Defined in NumHask.Analysis.Space

Methods

mempty :: Union a #

mappend :: Union a -> Union a -> Union a #

mconcat :: [Union a] -> Union a #

class (Space s, Subtractive (Element s), Field (Element s)) => FieldSpace s where Source #

a space that can be divided neatly

Associated Types

type Grid s :: * Source #

Methods

grid :: Pos -> s -> Grid s -> [Element s] Source #

create equally-spaced elements across a space

gridSpace :: s -> Grid s -> [s] Source #

create equally-spaced spaces from a space

Instances
(Lattice a, Field a, Subtractive a, FromInteger a) => FieldSpace (Range a) Source # 
Instance details

Defined in NumHask.Data.Range

Associated Types

type Grid (Range a) :: Type Source #

Methods

grid :: Pos -> Range a -> Grid (Range a) -> [Element (Range a)] Source #

gridSpace :: Range a -> Grid (Range a) -> [Range a] Source #

(Lattice a, Field a, Subtractive a, FromInteger a) => FieldSpace (Rect a) Source # 
Instance details

Defined in NumHask.Data.Rect

Associated Types

type Grid (Rect a) :: Type Source #

Methods

grid :: Pos -> Rect a -> Grid (Rect a) -> [Element (Rect a)] Source #

gridSpace :: Rect a -> Grid (Rect a) -> [Rect a] Source #

mid :: (Space s, Field (Element s)) => s -> Element s Source #

mid-point of the space

project :: (Space s, Field (Element s), Subtractive (Element s)) => s -> s -> Element s -> Element s Source #

project a data point from one space to another, preserving relative position

project o n (lower o) = lower n
project o n (upper o) = upper n
project a a x = x

data Pos Source #

Pos suggests where points should be placed in forming a grid across a field space.

Instances
Eq Pos Source # 
Instance details

Defined in NumHask.Analysis.Space

Methods

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

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

Show Pos Source # 
Instance details

Defined in NumHask.Analysis.Space

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

space1 :: (Space s, Traversable f) => f (Element s) -> s Source #

the containing space of a non-empty Foldable

(|.|) :: Space s => Element s -> s -> Bool infixl 7 Source #

is an element in the space

memberOf :: Space s => Element s -> s -> Bool Source #

contains :: Space s => s -> s -> Bool Source #

is a space contained within another?

disjoint :: Space s => s -> s -> Bool Source #

are two spaces disjoint?

(|>|) :: Space s => s -> s -> Bool infixl 7 Source #

is one space completely above the other

(|<|) :: Space s => s -> s -> Bool infixl 7 Source #

is one space completely below the other

width :: (Space s, Subtractive (Element s)) => s -> Element s Source #

distance between boundaries

(+/-) :: (Space s, Subtractive (Element s)) => Element s -> Element s -> s infixl 6 Source #

create a space centered on a plus or minus b

monotone :: (Space a, Space b) => (Element a -> Element b) -> a -> b Source #

lift a monotone function (increasing or decreasing) over a given space

eps :: (Space s, Epsilon (Element s), Multiplicative (Element s)) => Element s -> Element s -> s Source #

a small space

widen :: (Space s, Subtractive (Element s)) => Element s -> s -> s Source #

widen a space

widenEps :: (Space s, Epsilon (Element s), Multiplicative (Element s)) => Element s -> s -> s Source #

widen by a small amount