interval-patterns-0.8.1: Intervals, and monoids thereof
Safe HaskellNone
LanguageGHC2021

Data.Interval.Layers

Synopsis

Documentation

newtype Layers x y Source #

Constructors

Layers (Map (Interval x) y) 

Instances

Instances details
Foldable (Layers x) Source # 
Instance details

Defined in Data.Interval.Layers

Methods

fold :: Monoid m => Layers x m -> m #

foldMap :: Monoid m => (a -> m) -> Layers x a -> m #

foldMap' :: Monoid m => (a -> m) -> Layers x a -> m #

foldr :: (a -> b -> b) -> b -> Layers x a -> b #

foldr' :: (a -> b -> b) -> b -> Layers x a -> b #

foldl :: (b -> a -> b) -> b -> Layers x a -> b #

foldl' :: (b -> a -> b) -> b -> Layers x a -> b #

foldr1 :: (a -> a -> a) -> Layers x a -> a #

foldl1 :: (a -> a -> a) -> Layers x a -> a #

toList :: Layers x a -> [a] #

null :: Layers x a -> Bool #

length :: Layers x a -> Int #

elem :: Eq a => a -> Layers x a -> Bool #

maximum :: Ord a => Layers x a -> a #

minimum :: Ord a => Layers x a -> a #

sum :: Num a => Layers x a -> a #

product :: Num a => Layers x a -> a #

Traversable (Layers x) Source # 
Instance details

Defined in Data.Interval.Layers

Methods

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

sequenceA :: Applicative f => Layers x (f a) -> f (Layers x a) #

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

sequence :: Monad m => Layers x (m a) -> m (Layers x a) #

Functor (Layers x) Source # 
Instance details

Defined in Data.Interval.Layers

Methods

fmap :: (a -> b) -> Layers x a -> Layers x b #

(<$) :: a -> Layers x b -> Layers x a #

FoldableWithIndex (Interval x) (Layers x) Source # 
Instance details

Defined in Data.Interval.Layers

Methods

ifoldMap :: Monoid m => (Interval x -> a -> m) -> Layers x a -> m #

ifoldMap' :: Monoid m => (Interval x -> a -> m) -> Layers x a -> m #

ifoldr :: (Interval x -> a -> b -> b) -> b -> Layers x a -> b #

ifoldl :: (Interval x -> b -> a -> b) -> b -> Layers x a -> b #

ifoldr' :: (Interval x -> a -> b -> b) -> b -> Layers x a -> b #

ifoldl' :: (Interval x -> b -> a -> b) -> b -> Layers x a -> b #

FunctorWithIndex (Interval x) (Layers x) Source # 
Instance details

Defined in Data.Interval.Layers

Methods

imap :: (Interval x -> a -> b) -> Layers x a -> Layers x b #

TraversableWithIndex (Interval x) (Layers x) Source # 
Instance details

Defined in Data.Interval.Layers

Methods

itraverse :: Applicative f => (Interval x -> a -> f b) -> Layers x a -> f (Layers x b) #

(Data x, Data y, Ord x) => Data (Layers x y) Source # 
Instance details

Defined in Data.Interval.Layers

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Layers x y -> c (Layers x y) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Layers x y) #

toConstr :: Layers x y -> Constr #

dataTypeOf :: Layers x y -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Layers x y)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Layers x y)) #

gmapT :: (forall b. Data b => b -> b) -> Layers x y -> Layers x y #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Layers x y -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Layers x y -> r #

gmapQ :: (forall d. Data d => d -> u) -> Layers x y -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Layers x y -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Layers x y -> m (Layers x y) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Layers x y -> m (Layers x y) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Layers x y -> m (Layers x y) #

(Ord x, Ord y, Semigroup y) => Monoid (Layers x y) Source # 
Instance details

Defined in Data.Interval.Layers

Methods

mempty :: Layers x y #

mappend :: Layers x y -> Layers x y -> Layers x y #

mconcat :: [Layers x y] -> Layers x y #

(Ord x, Ord y, Semigroup y) => Semigroup (Layers x y) Source # 
Instance details

Defined in Data.Interval.Layers

Methods

(<>) :: Layers x y -> Layers x y -> Layers x y #

sconcat :: NonEmpty (Layers x y) -> Layers x y #

stimes :: Integral b => b -> Layers x y -> Layers x y #

Generic (Layers x y) Source # 
Instance details

Defined in Data.Interval.Layers

Associated Types

type Rep (Layers x y) 
Instance details

Defined in Data.Interval.Layers

type Rep (Layers x y) = D1 ('MetaData "Layers" "Data.Interval.Layers" "interval-patterns-0.8.1-8WeIEXvn2zcJ6U5H28TxFh" 'True) (C1 ('MetaCons "Layers" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (Interval x) y))))

Methods

from :: Layers x y -> Rep (Layers x y) x0 #

to :: Rep (Layers x y) x0 -> Layers x y #

(Ord x, Show x, Show y) => Show (Layers x y) Source # 
Instance details

Defined in Data.Interval.Layers

Methods

showsPrec :: Int -> Layers x y -> ShowS #

show :: Layers x y -> String #

showList :: [Layers x y] -> ShowS #

(Ord x, Eq y) => Eq (Layers x y) Source # 
Instance details

Defined in Data.Interval.Layers

Methods

(==) :: Layers x y -> Layers x y -> Bool #

(/=) :: Layers x y -> Layers x y -> Bool #

(Ord x, Ord y) => Ord (Layers x y) Source # 
Instance details

Defined in Data.Interval.Layers

Methods

compare :: Layers x y -> Layers x y -> Ordering #

(<) :: Layers x y -> Layers x y -> Bool #

(<=) :: Layers x y -> Layers x y -> Bool #

(>) :: Layers x y -> Layers x y -> Bool #

(>=) :: Layers x y -> Layers x y -> Bool #

max :: Layers x y -> Layers x y -> Layers x y #

min :: Layers x y -> Layers x y -> Layers x y #

(Ord x, Ord y, Group y) => Group (Layers x y) Source # 
Instance details

Defined in Data.Interval.Layers

Methods

invert :: Layers x y -> Layers x y #

(~~) :: Layers x y -> Layers x y -> Layers x y #

pow :: Integral x0 => Layers x y -> x0 -> Layers x y #

type Rep (Layers x y) Source # 
Instance details

Defined in Data.Interval.Layers

type Rep (Layers x y) = D1 ('MetaData "Layers" "Data.Interval.Layers" "interval-patterns-0.8.1-8WeIEXvn2zcJ6U5H28TxFh" 'True) (C1 ('MetaCons "Layers" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (Interval x) y))))

fromList :: (Ord x, Ord y, Semigroup y) => [(Interval x, y)] -> Layers x y Source #

Draw the Layers of specified bases and thicknesses.

toList :: Ord x => Layers x y -> [(Interval x, y)] Source #

Get all of the bases and thicknesses in the Layers.

empty :: Layers x y Source #

A blank canvas.

singleton :: Ord x => Interval x -> y -> Layers x y Source #

singleton ix y is the rectangle with base ix of thickness y.

insert :: (Ord x, Ord y, Semigroup y) => Interval x -> y -> Layers x y -> Layers x y Source #

insert ix y l draws over l a rectangle with base ix of thickness y.

pile :: (Ord x, Ord y, Semigroup y) => y -> Interval x -> Layers x y -> Layers x y Source #

Flipped synonym for insert. Mnemonic: "pile" this much onto the existing Layers over the given Interval.

squash :: Ord x => Layers x y -> Borel x Source #

Ignore the Layers and focus only on whether points are within any contained Interval or not.

squashing :: Ord x => (y -> Bool) -> Layers x y -> Borel x Source #

squash together the intervals satisfying a predicate.

isquashing :: Ord x => (Interval x -> y -> Bool) -> Layers x y -> Borel x Source #

Perform squashing with a test that accepts the Interval as an argument.

land :: (Ord x, Monoid y, Ord y) => Layers x y -> Borel x Source #

Treating mempty as sea level, consider the Borel set of a provided Layers that is "land".

An improvement over squash in that it will not return Whole if baseline or some involved interval calculations have been used.

landAbove :: (Ord x, Ord y) => y -> Layers x y -> Borel x Source #

Given a "sea level", consider the Borel set of a provided Layers that is "land".

An improvement over squash in that it will not return Whole if baseline or some involved interval calculations have been used.

thickness :: (Ord x, Semigroup y) => Levitated x -> Layers x y -> Maybe y Source #

Get the thickness of the Layers at a point.

thickest :: (Ord x, Ord y) => Layers x y -> Maybe (Interval x, y) Source #

Where and how thick is the thickest Interval?

dig :: (Ord x, Ord y, Group y) => y -> Interval x -> Layers x y -> Layers x y Source #

Take away a thickness over a given base from the Layers.

remove :: (Ord x, Ord y, Semigroup y) => Interval x -> Layers x y -> Layers x y Source #

Completely remove an Interval from the Layers.

(\-) :: (Ord x, Ord y, Semigroup y) => Layers x y -> Interval x -> Layers x y Source #

Fliped infix version of remove.

baseline :: (Ord x, Ord y, Semigroup y) => y -> Layers x y -> Layers x y Source #

Add the given thickness to every point.

difference :: (Ord x, Ord y, Group y) => Layers x y -> Layers x y -> Layers x y Source #

Excavate the second argument from the first.

truncate :: (Ord x, Ord y, Semigroup y) => Interval x -> Layers x y -> Layers x y Source #

Restrict the range of the Layers to the given Interval.

(\=) :: (Ord x, Ord y, Semigroup y) => Layers x y -> Interval x -> Layers x y Source #

Flipped infix version of truncate.

toStepFunction :: (Ord x, Ord y, Monoid y) => Layers x y -> [(Levitated x, y)] Source #

Convert the Layers into a list of beginning-points and heights, that define a step function piecewise.

integrate :: (Ord x, Ord y, Semigroup y, Num z) => (x -> x -> z) -> (y -> z) -> Interval x -> Layers x y -> Maybe z Source #

integrate diff hgt ix l calculates the area under the Interval ix using the measure diff of the interval multiplied by the height hgt of the layers over each sub-interval in the layers.

Helper functions

nestings :: (Ord x, Ord y, Semigroup y) => [(Interval x, y)] -> [(Interval x, y)] Source #