| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
Chart.Data
Contents
Description
Synopsis
- newtype Rect a = Rect' (Compose Point Range a)
- pattern Rect :: a -> a -> a -> a -> Rect a
- mid :: (Space s, Field (Element s)) => s -> Element s
- foldRect :: Ord a => [Rect a] -> Maybe (Rect a)
- addPoint :: Additive a => Point a -> Rect a -> Rect a
- projectOnP :: Rect Double -> Rect Double -> Point Double -> Point Double
- projectOnR :: Rect Double -> Rect Double -> Rect Double -> Rect Double
- space1 :: (Space s, Traversable f) => f (Element s) -> Maybe s
- padRect :: Subtractive a => a -> Rect a -> Rect a
- padSingletons :: Rect Double -> Rect Double
- isSingleton :: Rect Double -> Bool
- data Point a = Point {}
- addp :: Point Double -> Point Double -> Point Double
- data Range a = Range a a
- class Multiplicative a where
- one :: a
- class Additive a where
- zero :: a
- abs :: Absolute a => a -> a
- class (Distributive coord, Distributive (Dir coord)) => Direction coord where
- class Distributive (Mag a) => Basis a where
Data Primitives
a rectangular space often representing a finite 2-dimensional or XY plane.
>>>one :: Rect DoubleRect (-0.5) 0.5 (-0.5) 0.5
>>>zero :: Rect DoubleRect 0.0 0.0 0.0 0.0
>>>one + one :: Rect DoubleRect (-1.0) 1.0 (-1.0) 1.0
>>>let a = Rect (-1.0) 1.0 (-2.0) 4.0>>>aRect (-1.0) 1.0 (-2.0) 4.0
>>>a * oneRect (-1.0) 1.0 (-2.0) 4.0
>>>let (Ranges x y) = a>>>xRange -1.0 1.0>>>yRange -2.0 4.0>>>fmap (+1) (Rect 1 2 3 4)Rect 2 3 4 5
as a Space instance with Points as Elements
>>>project (Rect 0.0 1.0 (-1.0) 0.0) (Rect 1.0 4.0 10.0 0.0) (Point 0.5 1.0)Point 2.5 (-10.0)>>>gridSpace (Rect 0.0 10.0 0.0 1.0) (Point (2::Int) (2::Int))[Rect 0.0 5.0 0.0 0.5,Rect 0.0 5.0 0.5 1.0,Rect 5.0 10.0 0.0 0.5,Rect 5.0 10.0 0.5 1.0]>>>grid MidPos (Rect 0.0 10.0 0.0 1.0) (Point (2::Int) (2::Int))[Point 2.5 0.25,Point 2.5 0.75,Point 7.5 0.25,Point 7.5 0.75]
Instances
| Representable Rect | |
| Foldable Rect | |
Defined in NumHask.Space.Rect Methods fold :: Monoid m => Rect m -> m # foldMap :: Monoid m => (a -> m) -> Rect a -> m # foldMap' :: Monoid m => (a -> m) -> Rect a -> m # foldr :: (a -> b -> b) -> b -> Rect a -> b # foldr' :: (a -> b -> b) -> b -> Rect a -> b # foldl :: (b -> a -> b) -> b -> Rect a -> b # foldl' :: (b -> a -> b) -> b -> Rect a -> b # foldr1 :: (a -> a -> a) -> Rect a -> a # foldl1 :: (a -> a -> a) -> Rect a -> a # elem :: Eq a => a -> Rect a -> Bool # maximum :: Ord a => Rect a -> a # | |
| Traversable Rect | |
| Applicative Rect | |
| Functor Rect | |
| Distributive Rect | |
| Ord a => Semigroup (Rect a) | |
| Generic (Rect a) | |
| (Ord a, Additive a, Show a) => Show (Rect a) | |
| Eq a => Eq (Rect a) | |
| Additive a => Additive (Rect a) | Numeric algebra based on interval arithmetic for addition and unitRect and projection for multiplication >>> one + one :: Rect Double Rect (-1.0) 1.0 (-1.0) 1.0 |
| Subtractive a => Subtractive (Rect a) | |
| (Ord a, Field a) => Basis (Rect a) | |
| (Ord a, Field a) => Divisive (Rect a) | |
| (Ord a, Field a) => Multiplicative (Rect a) | |
| (FromIntegral a Int, Field a, Ord a) => FieldSpace (Rect a) | |
| Ord a => Space (Rect a) | |
Defined in NumHask.Space.Rect Methods lower :: Rect a -> Element (Rect a) # upper :: Rect a -> Element (Rect a) # singleton :: Element (Rect a) -> Rect a # intersection :: Rect a -> Rect a -> Rect a # union :: Rect a -> Rect a -> Rect a # normalise :: Rect a -> Rect a # (...) :: Element (Rect a) -> Element (Rect a) -> Rect a # (>.<) :: Element (Rect a) -> Element (Rect a) -> Rect a # (|.|) :: Element (Rect a) -> Rect a -> Bool # | |
| type Rep Rect | |
Defined in NumHask.Space.Rect | |
| type Rep (Rect a) | |
Defined in NumHask.Space.Rect | |
| type Base (Rect a) | |
Defined in NumHask.Space.Rect | |
| type Mag (Rect a) | |
Defined in NumHask.Space.Rect | |
| type Element (Rect a) | |
Defined in NumHask.Space.Rect | |
| type Grid (Rect a) | |
Defined in NumHask.Space.Rect | |
foldRect :: Ord a => [Rect a] -> Maybe (Rect a) #
convex hull union of Rect's
>>>foldRect [Rect 0 1 0 1, one]Just Rect (-0.5) 1.0 (-0.5) 1.0
addPoint :: Additive a => Point a -> Rect a -> Rect a #
add a Point to a Rect
>>>addPoint (Point 0 1) oneRect (-0.5) 0.5 0.5 1.5
projectOnP :: Rect Double -> Rect Double -> Point Double -> Point Double #
project a Point from one Rect to another, preserving relative position, with guards for singleton Rects.
>>>projectOnP one (Rect 0 1 0 1) zeroPoint (-0.5) (-0.5)
projectOnR :: Rect Double -> Rect Double -> Rect Double -> Rect Double #
project a Rect from one Rect to another, preserving relative position, with guards for singleton Rects.
>>>projectOnR one (Rect 0 1 0 1) (Rect 0 0.5 0 0.5)Rect (-0.5) 0.0 (-0.5) 0.0
space1 :: (Space s, Traversable f) => f (Element s) -> Maybe s #
Maybe containing space of a traversable.
padRect :: Subtractive a => a -> Rect a -> Rect a Source #
Additive pad (or frame or buffer) a Rect.
>>>padRect 1 oneRect (-1.5) 1.5 (-1.5) 1.5
padSingletons :: Rect Double -> Rect Double Source #
Pad a Rect to remove singleton dimensions.
Attempting to scale a singleton dimension of a Rect is a common bug.
Due to the use of scaling, and thus zero dividing, this is a common exception to guard against.
>>>project (Rect 0 0 0 1) one (Point 0 0)Point NaN (-0.5)
>>>project (padSingletons (Rect 0 0 0 1)) one (Point 0 0)Point 0.0 (-0.5)
A 2-dimensional Point of a's
In contrast with a tuple, a Point is functorial over both arguments.
>>>let p = Point 1 1>>>p + pPoint 2 2>>>(2*) <$> pPoint 2 2
A major reason for this bespoke treatment (compared to just using linear, say) is that Points do not have maximums and minimums but they do form a lattice, and this is useful for folding sets of points to find out the (rectangular) Space they occupy.
>>>Point 0 1 /\ Point 1 0Point 0 0>>>Point 0 1 \/ Point 1 0Point 1 1
This is used extensively in chart-svg to ergonomically obtain chart areas.
unsafeSpace1 [Point 1 0, Point 0 1] :: Rect Double
Rect 0.0 1.0 0.0 1.0
Instances
addp :: Point Double -> Point Double -> Point Double Source #
add Points, dimension-wise
>>>Point 1 1 `addp` Point 0 2Point 1.0 3.0
A continuous range over type a
>>>let a = Range (-1) 1>>>aRange -1 1
>>>a + aRange -2 2
>>>a * aRange -2.0 2.0
>>>(+1) <$> (Range 1 2)Range 2 3
Ranges are very useful in shifting a bunch of numbers from one Range to another. eg project 0.5 from the range 0 to 1 to the range 1 to 4
>>>project (Range 0 1) (Range 1 4) 0.52.5
Create an equally spaced grid including outer bounds over a Range
>>>grid OuterPos (Range 0.0 10.0) 5[0.0,2.0,4.0,6.0,8.0,10.0]
divide up a Range into equal-sized sections
>>>gridSpace (Range 0.0 1.0) 4[Range 0.0 0.25,Range 0.25 0.5,Range 0.5 0.75,Range 0.75 1.0]
Constructors
| Range a a |
Instances
NumHask Exports
class Multiplicative a where #
For practical reasons, we begin the class tree with Additive and Multiplicative. Starting with Associative and Unital, or using Semigroup and Monoid from base tends to confuse the interface once you start having to disinguish between (say) monoidal addition and monoidal multiplication.
\a -> one * a == a
\a -> a * one == a
\a b c -> (a * b) * c == a * (b * c)
By convention, (*) is regarded as not necessarily commutative, but this is not universal, and the introduction of another symbol which means commutative multiplication seems a bit dogmatic.
>>>one * 22
>>>2 * 36
Instances
| Multiplicative Int16 | |
| Multiplicative Int32 | |
| Multiplicative Int64 | |
| Multiplicative Int8 | |
| Multiplicative Word16 | |
| Multiplicative Word32 | |
| Multiplicative Word64 | |
| Multiplicative Word8 | |
| Multiplicative Integer | |
| Multiplicative Natural | |
| Multiplicative Bool | |
| Multiplicative Double | |
| Multiplicative Float | |
| Multiplicative Int | |
| Multiplicative Word | |
| Multiplicative a => Multiplicative (EuclideanPair a) | |
Defined in NumHask.Algebra.Metric | |
| (Subtractive a, Multiplicative a) => Multiplicative (Complex a) | |
| (Ord a, EndoBased a, Integral a, Ring a) => Multiplicative (Ratio a) | |
| Multiplicative a => Multiplicative (Point a) | |
| (Field a, Ord a) => Multiplicative (Range a) | |
| (Ord a, Field a) => Multiplicative (Rect a) | |
| Multiplicative b => Multiplicative (a -> b) | |
Defined in NumHask.Algebra.Multiplicative | |
or Addition
For practical reasons, we begin the class tree with Additive. Starting with Associative and Unital, or using Semigroup and Monoid from base tends to confuse the interface once you start having to disinguish between (say) monoidal addition and monoidal multiplication.
\a -> zero + a == a
\a -> a + zero == a
\a b c -> (a + b) + c == a + (b + c)
\a b -> a + b == b + a
By convention, (+) is regarded as commutative, but this is not universal, and the introduction of another symbol which means non-commutative addition seems a bit dogmatic.
>>>zero + 11
>>>1 + 12
Instances
| Additive Int16 | |
| Additive Int32 | |
| Additive Int64 | |
| Additive Int8 | |
| Additive Word16 | |
| Additive Word32 | |
| Additive Word64 | |
| Additive Word8 | |
| Additive Integer | |
| Additive Natural | |
| Additive Bool | |
| Additive Double | |
| Additive Float | |
| Additive Int | |
| Additive Word | |
| Additive a => Additive (Sum a) | |
| Additive a => Additive (EuclideanPair a) | |
Defined in NumHask.Algebra.Metric | |
| Additive a => Additive (Complex a) | |
| (Ord a, EndoBased a, Integral a, Ring a) => Additive (Ratio a) | |
| Additive a => Additive (Point a) | |
| (Additive a, Ord a) => Additive (Range a) | |
| Additive a => Additive (Rect a) | Numeric algebra based on interval arithmetic for addition and unitRect and projection for multiplication >>> one + one :: Rect Double Rect (-1.0) 1.0 (-1.0) 1.0 |
| Additive b => Additive (a -> b) | |
Defined in NumHask.Algebra.Additive | |
The absolute value of a number.
\a -> abs a * signum a ~= a
>>>abs (-1)1
class (Distributive coord, Distributive (Dir coord)) => Direction coord where #
Convert between a "co-ordinated" or "higher-kinded" number and a direction.
ray . angle == basis magnitude (ray x) == one
Since: numhask-0.7
Instances
| TrigField a => Direction (EuclideanPair a) | |
Defined in NumHask.Algebra.Metric Associated Types type Dir (EuclideanPair a) # Methods angle :: EuclideanPair a -> Dir (EuclideanPair a) # ray :: Dir (EuclideanPair a) -> EuclideanPair a # | |
| TrigField a => Direction (Complex a) | |
| TrigField a => Direction (Point a) | angle formed by a vector from the origin to a Point and the x-axis (Point 1 0). Note that an angle between two points p1 & p2 is thus angle p2 - angle p1 |
class Distributive (Mag a) => Basis a where #
Basis encapsulates the notion of magnitude (intuitively the quotienting of a higher-kinded number to a scalar one) and the basis on which the magnitude quotienting was performed. An instance needs to satisfy these laws:
\a -> magnitude a >= zero \a -> magnitude zero == zero \a -> a == magnitude a *| basis a \a -> magnitude (basis a) == one
The names chosen are meant to represent the spiritual idea of a basis rather than a specific mathematics. See https://en.wikipedia.org/wiki/Basis_(linear_algebra) & https://en.wikipedia.org/wiki/Norm_(mathematics) for some mathematical motivations.
>>>magnitude (-0.5 :: Double)0.5
>>>basis (-0.5 :: Double)-1.0
Since: numhask-0.11
Instances
| Basis Int16 | |
| Basis Int32 | |
| Basis Int64 | |
| Basis Int8 | |
| Basis Word16 | |
| Basis Word32 | |
| Basis Word64 | |
| Basis Word8 | |
| Basis Integer | |
| Basis Natural | |
| Basis Double | |
| Basis Float | |
| Basis Int | |
| Basis Word | |
| (ExpField a, Eq a) => Basis (EuclideanPair a) | |
Defined in NumHask.Algebra.Metric Methods magnitude :: EuclideanPair a -> Mag (EuclideanPair a) # basis :: EuclideanPair a -> Base (EuclideanPair a) # | |
| (Additive a, Multiplicative a) => Basis (Polar a) | |
| (ExpField a, Eq a) => Basis (Complex a) | |
| (Ord a, EndoBased a, Integral a, Ring a) => Basis (Ratio a) | |
| (ExpField a, Eq a) => Basis (Point a) | |
| (Field a, Ord a) => Basis (Range a) | |
| (Ord a, Field a) => Basis (Rect a) | |