numhask-range-0.0.2: see readme.md

Safe HaskellNone
LanguageHaskell2010

NumHask.Range

Description

A Range a is a tuple representing an interval of a number space. A Range can be thought of as consisting of a low and high value, though low<high isn't strictly enforced, allowing a negative space so to speak. The library uses the NumHask classes and thus most of the usual arithmetic operators can be used.

Synopsis

Documentation

newtype Range a Source #

a newtype wrapped (a, a) tuple

Constructors

Range 

Fields

Instances

Functor Range Source # 

Methods

fmap :: (a -> b) -> Range a -> Range b #

(<$) :: a -> Range b -> Range a #

Ord a => AdditiveHomomorphic a (Range a) Source #

natural interpretation of an a as a `Range a` is a singular Range

Methods

plushom :: a -> Range a #

Eq a => Eq (Range a) Source # 

Methods

(==) :: Range a -> Range a -> Bool #

(/=) :: Range a -> Range a -> Bool #

Ord a => Ord (Range a) Source # 

Methods

compare :: Range a -> Range a -> Ordering #

(<) :: Range a -> Range a -> Bool #

(<=) :: Range a -> Range a -> Bool #

(>) :: Range a -> Range a -> Bool #

(>=) :: Range a -> Range a -> Bool #

max :: Range a -> Range a -> Range a #

min :: Range a -> Range a -> Range a #

Show a => Show (Range a) Source # 

Methods

showsPrec :: Int -> Range a -> ShowS #

show :: Range a -> String #

showList :: [Range a] -> ShowS #

Ord a => Semigroup (Range a) Source # 

Methods

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

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

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

(AdditiveUnital (Range a), Semigroup (Range a)) => Monoid (Range a) Source # 

Methods

mempty :: Range a #

mappend :: Range a -> Range a -> Range a #

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

Arbitrary a => Arbitrary (Range a) Source # 

Methods

arbitrary :: Gen (Range a) #

shrink :: Range a -> [Range a] #

(BoundedField a, Ord a) => Signed (Range a) Source # 

Methods

sign :: Range a -> Range a #

abs :: Range a -> Range a #

BoundedField a => MultiplicativeMagma (Range a) Source #

times may well be some sort of affine projection lurking under the hood

Methods

times :: Range a -> Range a -> Range a #

BoundedField a => MultiplicativeUnital (Range a) Source #

The unital object derives from:

view range one = one view mid zero = zero ie (-0.5,0.5)

Methods

one :: Range a #

BoundedField a => MultiplicativeAssociative (Range a) Source # 
(Ord a, BoundedField a) => MultiplicativeInvertible (Range a) Source # 

Methods

recip :: Range a -> Range a #

(Ord a, BoundedField a) => MultiplicativeLeftCancellative (Range a) Source # 

Methods

(~/) :: Range a -> Range a -> Range a #

(Ord a, BoundedField a) => MultiplicativeRightCancellative (Range a) Source # 

Methods

(/~) :: Range a -> Range a -> Range a #

Ord a => AdditiveMagma (Range a) Source #

choosing the convex hull as plus seems like a natural choice, given the cute zero definition.

Methods

plus :: Range a -> Range a -> Range a #

(Ord a, BoundedField a) => AdditiveUnital (Range a) Source # 

Methods

zero :: Range a #

Ord a => AdditiveAssociative (Range a) Source # 
Ord a => AdditiveCommutative (Range a) Source # 
Ord a => AdditiveInvertible (Range a) Source # 

Methods

negate :: Range a -> Range a #

(Ord a, BoundedField a) => Additive (Range a) Source # 

Methods

(+) :: Range a -> Range a -> Range a #

(BoundedField a, Ord a) => AdditiveGroup (Range a) Source # 

Methods

(-) :: Range a -> Range a -> Range a #

AdditiveGroup a => Normed (Range a) a Source # 

Methods

size :: Range a -> a #

(Ord a, AdditiveGroup a) => Metric (Range a) a Source # 

Methods

distance :: Range a -> Range a -> a #

BoundedField a => AdditiveHomomorphic (Range a) a Source #

natural interpretation of a `Range a` as an a is the mid-point

Methods

plushom :: Range a -> a #

(...) :: Ord a => a -> a -> Range a Source #

alternative constructor

low :: Lens' (Range a) a Source #

lens for the fst of the tuple

high :: Lens' (Range a) a Source #

lens for the snd of the tuple

mid :: BoundedField a => Lens' (Range a) a Source #

mid-value lens

width :: BoundedField a => Lens' (Range a) a Source #

range width lens

element :: Ord a => a -> Range a -> Bool Source #

determine whether a point is within the range

singular :: Eq a => Range a -> Bool Source #

is the range a singleton point

intersection :: Ord a => Range a -> Range a -> Range a Source #

contains :: Ord a => Range a -> Range a -> Bool Source #

range :: (Foldable f, Ord a, BoundedField a) => f a -> Range a Source #

range of a foldable

project :: Field b => Range b -> Range b -> b -> b Source #

project a data point from an old range to a new range project o n (view low o) == view low n project o n (view high o) == view high n project a a == id

data LinearPos Source #

overns where data points go on the range

Instances

linearSpace :: (Field a, FromInteger a) => LinearPos -> Range a -> Int -> [a] Source #

turn a range into a list of n equally-spaced as

linearSpaceSensible :: (Fractional a, Ord a, FromInteger a, QuotientField a, ExpField a) => LinearPos -> Range a -> Int -> [a] Source #

turn a range into n as pleasing to human sense and sensibility the as may well lie outside the original range as a result

fromLinearSpace :: [a] -> [Range a] Source #

take a list of (ascending) as and make some (ascending) ranges based on OuterPos fromLinearSpace . linearSpace OuterPos == id linearSpace OuterPos . fromLinearSpace == id