Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Spaceable (Element s) => Space s where
- type Spaceable a = (Eq a, JoinSemiLattice a, MeetSemiLattice a)
- newtype Union a = Union {
- getUnion :: a
- newtype Intersection a = Intersection {
- getIntersection :: a
- class (Space s, Subtractive (Element s), Field (Element s)) => FieldSpace s where
- mid :: (Space s, Field (Element s)) => s -> Element s
- project :: (Space s, Field (Element s), Subtractive (Element s)) => s -> s -> Element s -> Element s
- data Pos
- space1 :: (Space s, Traversable f) => f (Element s) -> s
- (|.|) :: Space s => Element s -> s -> Bool
- memberOf :: Space s => Element s -> s -> Bool
- contains :: Space s => s -> s -> Bool
- disjoint :: Space s => s -> s -> Bool
- (|>|) :: Space s => s -> s -> Bool
- (|<|) :: Space s => s -> s -> Bool
- width :: (Space s, Subtractive (Element s)) => s -> Element s
- (+/-) :: (Space s, Subtractive (Element s)) => Element s -> Element s -> s
- monotone :: (Space a, Space b) => (Element a -> Element b) -> a -> b
- whole :: (Space s, BoundedJoinSemiLattice (Element s), BoundedMeetSemiLattice (Element s)) => s
- negWhole :: (Space s, BoundedJoinSemiLattice (Element s), BoundedMeetSemiLattice (Element s)) => s
- eps :: (Space s, Epsilon (Element s), Multiplicative (Element s)) => Element s -> Element s -> s
- widen :: (Space s, Subtractive (Element s)) => Element s -> s -> s
- widenEps :: (Space s, Epsilon (Element s), Multiplicative (Element s)) => Element s -> s -> s
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
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
the union of two spaces
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 # | |
Defined in NumHask.Data.Range lower :: Range a -> Element (Range a) Source # upper :: Range a -> Element (Range a) Source # singleton :: Element (Range a) -> Range a Source # intersection :: Range a -> Range a -> Range a Source # union :: Range a -> Range a -> Range a Source # norm :: Range a -> Range a Source # (...) :: Element (Range a) -> Element (Range a) -> Range a Source # (>.<) :: Element (Range a) -> Element (Range a) -> Range a Source # | |
Lattice a => Space (Rect a) Source # | |
Defined in NumHask.Data.Rect 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 # |
type Spaceable a = (Eq a, JoinSemiLattice a, MeetSemiLattice a) Source #
newtype Intersection a Source #
Instances
Space a => Semigroup (Intersection a) Source # | |
Defined in NumHask.Analysis.Space (<>) :: Intersection a -> Intersection a -> Intersection a # sconcat :: NonEmpty (Intersection a) -> Intersection a # stimes :: Integral b => b -> Intersection a -> Intersection a # | |
(BoundedMeetSemiLattice a, Space a) => Monoid (Intersection a) Source # | |
Defined in NumHask.Analysis.Space mempty :: Intersection a # mappend :: Intersection a -> Intersection a -> Intersection a # mconcat :: [Intersection a] -> Intersection a # |
class (Space s, Subtractive (Element s), Field (Element s)) => FieldSpace s where Source #
a space that can be divided neatly
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 # | |
(Lattice a, Field a, Subtractive a, FromInteger a) => FieldSpace (Rect a) Source # | |
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
Pos suggests where points should be placed in forming a grid across a field space.
space1 :: (Space s, Traversable f) => f (Element s) -> s Source #
the containing space of a non-empty Foldable
(+/-) :: (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
whole :: (Space s, BoundedJoinSemiLattice (Element s), BoundedMeetSemiLattice (Element s)) => s Source #
a big, big space
negWhole :: (Space s, BoundedJoinSemiLattice (Element s), BoundedMeetSemiLattice (Element s)) => s Source #
a negative space