{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -Wall #-} #if ( __GLASGOW_HASKELL__ < 820 ) {-# OPTIONS_GHC -fno-warn-incomplete-patterns #-} {-# OPTIONS_GHC -fno-warn-unrecognised-pragmas #-} #endif -- | A 'Space' represents an abstract continuous range class for a type. The package is an alternative approach. module NumHask.Space ( Space(..) , Pos(..) ) where import NumHask.Prelude hiding (singleton) -- | 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 class (Eq (Element s), Ord (Element s), Field (Element s)) => Space s where type Element s :: * -- | lower boundary of space lower :: s -> Element s -- | upper boundary of space upper :: s -> Element s -- | mid-point of the space mid :: s -> Element s mid s = (lower s + upper s)/(one+one) -- | distance between boundaries width :: s -> Element s width s = upper s - lower s -- | singleton space singleton :: Element s -> s -- | zero-width test singular :: s -> Bool singular s = lower s == upper s -- | determine whether an a is in the space element :: Element s -> s -> Bool element a s = a >= lower s && a <= upper s -- | is a space contained within another? contains :: s -> s -> Bool contains s0 s1 = lower s0 <= lower s1 && upper s0 >= upper s1 -- | convex hull union :: s -> s -> s -- | null space, which can be interpreted as mempty nul :: s -- | the containing space of a Foldable space :: (Foldable f) => f (Element s) -> s space = foldr (\a x -> x `union` singleton a) nul -- | project a data point from an old range to a new range project :: s -> s -> Element s -> Element s project s0 s1 p = ((p-lower s0)/(upper s0-lower s0)) * (upper s1-lower s1) + lower s1 type Grid s :: * -- | create equally-spaced `a`s from a space grid :: Pos -> s -> Grid s -> [Element s] -- | create equally-spaced `Space a`s from a space gridSpace :: s -> Grid s -> [s] -- | 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). data Pos = OuterPos | InnerPos | LowerPos | UpperPos | MidPos deriving (Eq)