numhask-range-0.1.0: Numbers that are range representations

Safe HaskellNone
LanguageHaskell2010

NumHask.Range

Description

'Range -0.5 0.5 :: Range Double' is a 1-dimensional instance of a 'Space Double' from -0.5 to 0.5 on the Double number line.

The instances chosen for Range are conducive to Charting. Specifically:

  • a Range is polymorphic, with the main constraint being 'Ord a'
  • Additive and Multiplicative instances define numeric manipulation rather than relying on the Num class in base.
  • '(+)' and '(<>)' are defined as the convex hull of two ranges (compare the interval package approach for + of `fmap (+)`). zero and mempty are defined as `Range infinity neginfinity`. This arrangement targets a neat definition for conversion of a foldable into a range via a very neat `foldMap singleton`. An additional benefit is that Ranges are additively idempotent (a + a = a).
  • The starting point for understanding Range multiplication is the diagrams unitSquare. Restricting consideration to one-dimension, a natural one Range is `Range -0.5 0.5`, which uniquely satisfies the equations:

`mid one == zero` `width one == one`

where the right zero and one refer to the underlying type.

Synopsis

Documentation

newtype Range a Source #

Range is a newtype wrapped (a,a) tuple

Constructors

Range' (a, a) 

Instances

Monad Range Source # 

Methods

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

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

return :: a -> Range a #

fail :: String -> Range a #

Functor Range Source #

and here we recover the desired property of fmap'ing over both elements in contrast to the (a,) functor.

Methods

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

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

Applicative Range Source # 

Methods

pure :: a -> Range a #

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

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

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

Foldable Range Source # 

Methods

fold :: Monoid m => Range m -> m #

foldMap :: Monoid m => (a -> m) -> Range a -> m #

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

foldr' :: (a -> b -> b) -> b -> Range a -> b #

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

foldl' :: (b -> a -> b) -> b -> Range a -> b #

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

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

toList :: Range a -> [a] #

null :: Range a -> Bool #

length :: Range a -> Int #

elem :: Eq a => a -> Range a -> Bool #

maximum :: Ord a => Range a -> a #

minimum :: Ord a => Range a -> a #

sum :: Num a => Range a -> a #

product :: Num a => Range a -> a #

Traversable Range Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Range a -> f (Range b) #

sequenceA :: Applicative f => Range (f a) -> f (Range a) #

mapM :: Monad m => (a -> m b) -> Range a -> m (Range b) #

sequence :: Monad m => Range (m a) -> m (Range a) #

Distributive Range Source # 

Methods

distribute :: Functor f => f (Range a) -> Range (f a) #

collect :: Functor f => (a -> Range b) -> f a -> Range (f b) #

distributeM :: Monad m => m (Range a) -> Range (m a) #

collectM :: Monad m => (a -> Range b) -> m a -> Range (m b) #

Representable Range Source # 

Associated Types

type Rep (Range :: * -> *) :: * #

Methods

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

index :: Range a -> Rep Range -> a #

Eq1 Range Source # 

Methods

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

Show1 Range Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Range a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Range a] -> ShowS #

Traversable1 Range Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Range a -> f (Range b) #

sequence1 :: Apply f => Range (f b) -> f (Range b) #

Apply Range Source # 

Methods

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

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

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

Foldable1 Range Source # 

Methods

fold1 :: Semigroup m => Range m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Range a -> m #

toNonEmpty :: Range a -> NonEmpty a #

Eq a => Eq (Range a) Source # 

Methods

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

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

Show a => Show (Range a) Source #

recovering the synonym name

Methods

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

show :: Range a -> String #

showList :: [Range a] -> ShowS #

Generic (Range a) Source # 

Associated Types

type Rep (Range a) :: * -> * #

Methods

from :: Range a -> Rep (Range a) x #

to :: Rep (Range a) x -> Range a #

(Ord a, BoundedField a, FromInteger 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] #

NFData a => NFData (Range a) Source # 

Methods

rnf :: Range a -> () #

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

Methods

sign :: Range a -> Range a #

abs :: Range a -> Range a #

(Ord a, BoundedField a, FromInteger 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 #

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

The unital object derives from:

width one = one

mid zero = zero

ie (-0.5,0.5)

Methods

one :: Range a #

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

Methods

recip :: Range a -> Range a #

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

Methods

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

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

Methods

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

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

Associated Types

type Element (Range a) :: * Source #

type Grid (Range a) :: * Source #

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 #

type Rep Range Source # 
type Rep Range = Bool
type Rep (Range a) Source # 
type Rep (Range a) = D1 (MetaData "Range" "NumHask.Range" "numhask-range-0.1.0-I1DWEepfHM8IinfnHaT18f" True) (C1 (MetaCons "Range'" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (a, a))))
type Element (Range a) Source # 
type Element (Range a) = a
type Grid (Range a) Source # 
type Grid (Range a) = Int

pattern Range :: forall a. a -> a -> Range a Source #

A tuple is the preferred concrete implementation of a Range, due to many libraries having substantial optimizations for tuples already (eg Vector). 'Pattern Synonyms' allow us to recover a constructor without the need for tuple syntax. >>> Range 0 1 Range 0 1

gridSensible :: (Fractional a, Ord a, FromInteger a, QuotientField a, ExpField a) => Pos -> 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