interval-patterns-0.2.0.1
Safe HaskellNone
LanguageHaskell2010

Data.Interval.Borel

Synopsis

Documentation

data Borel x Source #

The Borel sets on a type are the sets generated by its open intervals. It forms a Heyting algebra with union as join and intersection as meet, and a Ring with symmetricDifference as addition and intersection as multiplication (and complement as negation). In fact the algebra is Boolean as the operation x ==> y = complement x \/ y.

It is a monoid that is convenient for agglomerating groups of intervals, such as for calculating the overall timespan of a group of events. However, it is agnostic of how many times each given point has been covered. To keep track of this data, use Layers.

Instances

Instances details
Ord x => Eq (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

Methods

(==) :: Borel x -> Borel x -> Bool #

(/=) :: Borel x -> Borel x -> Bool #

Ord x => Ord (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

Methods

compare :: Borel x -> Borel x -> Ordering #

(<) :: Borel x -> Borel x -> Bool #

(<=) :: Borel x -> Borel x -> Bool #

(>) :: Borel x -> Borel x -> Bool #

(>=) :: Borel x -> Borel x -> Bool #

max :: Borel x -> Borel x -> Borel x #

min :: Borel x -> Borel x -> Borel x #

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

Defined in Data.Interval.Borel

Methods

showsPrec :: Int -> Borel x -> ShowS #

show :: Borel x -> String #

showList :: [Borel x] -> ShowS #

Generic (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

Associated Types

type Rep (Borel x) :: Type -> Type #

Methods

from :: Borel x -> Rep (Borel x) x0 #

to :: Rep (Borel x) x0 -> Borel x #

Ord x => Semigroup (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

Methods

(<>) :: Borel x -> Borel x -> Borel x #

sconcat :: NonEmpty (Borel x) -> Borel x #

stimes :: Integral b => b -> Borel x -> Borel x #

Ord x => Monoid (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

Methods

mempty :: Borel x #

mappend :: Borel x -> Borel x -> Borel x #

mconcat :: [Borel x] -> Borel x #

(Ord x, Lattice x) => Heyting (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

Methods

(==>) :: Borel x -> Borel x -> Borel x #

neg :: Borel x -> Borel x #

(<=>) :: Borel x -> Borel x -> Borel x #

(Ord x, Lattice x) => Lattice (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

Methods

(\/) :: Borel x -> Borel x -> Borel x #

(/\) :: Borel x -> Borel x -> Borel x #

(Ord x, Lattice x) => BoundedJoinSemiLattice (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

Methods

bottom :: Borel x #

(Ord x, Lattice x) => BoundedMeetSemiLattice (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

Methods

top :: Borel x #

Ord x => One (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

Associated Types

type OneItem (Borel x) #

Methods

one :: OneItem (Borel x) -> Borel x #

(Ord x, Lattice x) => Semiring (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

Methods

plus :: Borel x -> Borel x -> Borel x #

zero :: Borel x #

times :: Borel x -> Borel x -> Borel x #

one :: Borel x #

fromNatural :: Natural -> Borel x #

(Ord x, Lattice x) => Ring (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

Methods

negate :: Borel x -> Borel x #

type Rep (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

type Rep (Borel x) = D1 ('MetaData "Borel" "Data.Interval.Borel" "interval-patterns-0.2.0.1-5IEJQVZOhrW5Vnz72Ma3YD" 'True) (C1 ('MetaCons "Borel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set (Interval x)))))
type OneItem (Borel x) Source # 
Instance details

Defined in Data.Interval.Borel

type OneItem (Borel x) = Interval x

borel :: Ord x => [Interval x] -> Borel x Source #

Consider the Borel set identified by a list of Intervals.

intervalSet :: Ord x => Borel x -> Set (Interval x) Source #

Turn a Borel set into a Set of Intervals.

empty :: Ord x => Borel x Source #

The empty Borel set.

singleton :: Ord x => Interval x -> Borel x Source #

The Borel set consisting of a single Interval.

null :: Borel x -> Bool Source #

Is this Borel set empty?

insert :: Ord x => Interval x -> Borel x -> Borel x Source #

Insert an Interval into a Borel set, agglomerating along the way.

whole :: Ord x => Borel x Source #

The maximal Borel set, that covers the entire range.

cutout :: Ord x => Interval x -> Borel x -> Borel x Source #

Completely remove an Interval from a Borel set.

clip :: Ord x => Interval x -> Borel x -> Borel x Source #

Given an Interval i, clip i will trim a Borel set so that its hull is contained in i.

member :: Ord x => x -> Borel x -> Bool Source #

Is this point within any connected component of the Borel set?

notMember :: Ord x => x -> Borel x -> Bool Source #

Is this point not within any connected component of the Borel set?

union :: Ord x => Borel x -> Borel x -> Borel x Source #

A synonym for (<>).

unions :: Ord x => [Borel x] -> Borel x Source #

A synonym for fold.

difference :: Ord x => Borel x -> Borel x -> Borel x Source #

Remove all intervals of the second set from the first.

symmetricDifference :: Ord x => Borel x -> Borel x -> Borel x Source #

Take the symmetric difference of two Borel sets.

complement :: Ord x => Borel x -> Borel x Source #

Take the Borel set consisting of each point not in the given one.

intersection :: Ord x => Borel x -> Borel x -> Borel x Source #

Take the intersection of two Borel sets.

intersections :: Ord x => [Borel x] -> Borel x Source #

Take the intersection of a list of Borel sets.

hull :: Ord x => Borel x -> Maybe (Interval x) Source #

Take the smallest spanning Interval of a Borel set, provided that it is not the empty set.