numhask-range-0.2.2.0: Numbers that are range representations

Safe HaskellNone
LanguageHaskell2010

NumHask.Space

Description

A Space represents an abstract continuous range class for a type. The interval package is an alternative approach.

Synopsis

Documentation

class (Eq (Element s), Ord (Element s), Field (Element s)) => Space s where Source #

space laws

a `union` nul == a
a `union` a == a
project o n (lower o) == lower n
project o n (upper o) == upper n
project a a == id

Minimal complete definition

lower, upper, singleton, union, nul, grid, gridSpace

Associated Types

type Element s :: * Source #

type Grid s :: * Source #

Methods

lower :: s -> Element s Source #

lower boundary of space

upper :: s -> Element s Source #

upper boundary of space

mid :: s -> Element s Source #

mid-point of the space

width :: s -> Element s Source #

distance between boundaries

singleton :: Element s -> s Source #

singleton space

singular :: s -> Bool Source #

zero-width test

element :: Element s -> s -> Bool Source #

determine whether an a is in the space

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

is a space contained within another?

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

do two spaces intersect?

intersects :: s -> s -> Bool Source #

do two spaces intersect?

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

convex hull

nul :: s Source #

null space, which can be interpreted as mempty

space :: Foldable f => f (Element s) -> s Source #

the containing space of a Foldable

project :: s -> s -> Element s -> Element s Source #

project a data point from an old range to a new range

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

create equally-spaced as from a space

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

create equally-spaced `Space a`s from a space

Instances

(FromInteger a, Ord a, BoundedField a) => Space (Range a) Source # 

Associated Types

type Element (Range a) :: * Source #

type Grid (Range a) :: * Source #

(FromInteger a, Signed a, Ord a, BoundedField a) => Space (Rect a) Source # 

Associated Types

type Element (Rect a) :: * Source #

type Grid (Rect a) :: * Source #

Methods

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

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

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

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

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

singular :: Rect a -> Bool Source #

element :: Element (Rect a) -> Rect a -> Bool Source #

contains :: Rect a -> Rect a -> Bool Source #

disjoint :: Rect a -> Rect a -> Bool Source #

intersects :: Rect a -> Rect a -> Bool Source #

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

nul :: Rect a Source #

space :: Foldable f => f (Element (Rect a)) -> Rect a Source #

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

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

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

data Pos Source #

Pos suggests where data points are placed on a grid across a range. Pos can also be thought about as whether the lower and upper points on the range are open or closed (plus the mid-point as an extra option).

Instances

Eq Pos Source # 

Methods

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

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

Show Pos Source # 

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Generic Pos Source # 

Associated Types

type Rep Pos :: * -> * #

Methods

from :: Pos -> Rep Pos x #

to :: Rep Pos x -> Pos #

type Rep Pos Source # 
type Rep Pos = D1 * (MetaData "Pos" "NumHask.Space" "numhask-range-0.2.2.0-LlG1lNRQve2DexLLd4G6s8" False) ((:+:) * ((:+:) * (C1 * (MetaCons "OuterPos" PrefixI False) (U1 *)) (C1 * (MetaCons "InnerPos" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LowerPos" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "UpperPos" PrefixI False) (U1 *)) (C1 * (MetaCons "MidPos" PrefixI False) (U1 *)))))