Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Interval a where
- IntervArbitrary :: Int -> Int -> Interval Arbitrary
- IntervInfiniteArbitrary :: Interval Arbitrary
- IntervHoled :: Int64 -> Int64 -> Bool -> Interval Standard
- IntervInfinite :: Interval Standard
- data Bound
- approxVec :: forall n. Vec n (Interval Arbitrary) -> Approximation (Vec n (Interval Standard))
- data Offsets
- = Offsets (Set Int64)
- | SetOfIntegers
- type UnionNF n a = NonEmpty (Vec n a)
- vecLength :: UnionNF n a -> Natural n
- unfCompare :: forall a b n. (Container a, Container b, MemberTyp a ~ Int64, MemberTyp b ~ Int64, CompTyp a ~ SInt64, CompTyp b ~ SInt64) => UnionNF n a -> UnionNF n b -> Ordering
- optimise :: UnionNF n (Interval Standard) -> UnionNF n (Interval Standard)
- maximas :: [Vec n (Interval Standard)] -> [Vec n (Interval Standard)]
- data Approximation a
- lowerBound :: Approximation a -> a
- upperBound :: Approximation a -> a
- fromExact :: Approximation a -> a
- data Multiplicity a
- class Peelable a where
- type CoreTyp a
Documentation
data Interval a where Source #
Interval data structure assumes the following: 1. The first num. param. is less than the second; 2. For holed intervals, first num. param. <= 0 <= second num. param.;
IntervArbitrary :: Int -> Int -> Interval Arbitrary | |
IntervInfiniteArbitrary :: Interval Arbitrary | |
IntervHoled :: Int64 -> Int64 -> Bool -> Interval Standard | |
IntervInfinite :: Interval Standard |
approxVec :: forall n. Vec n (Interval Arbitrary) -> Approximation (Vec n (Interval Standard)) Source #
unfCompare :: forall a b n. (Container a, Container b, MemberTyp a ~ Int64, MemberTyp b ~ Int64, CompTyp a ~ SInt64, CompTyp b ~ SInt64) => UnionNF n a -> UnionNF n b -> Ordering Source #
data Approximation a Source #
Functor Approximation Source # | |
Foldable Approximation Source # | |
Traversable Approximation Source # | |
Eq a => Eq (Approximation a) Source # | |
Data a => Data (Approximation a) Source # | |
Show (Multiplicity (Approximation Spatial)) # | |
Show a => Show (Approximation a) Source # | |
Show (Approximation Spatial) # | |
SynToAst (Multiplicity (Approximation Region)) (Multiplicity (Approximation Spatial)) Source # | |
SynToAst (Approximation Region) (Approximation Spatial) Source # | |
lowerBound :: Approximation a -> a Source #
upperBound :: Approximation a -> a Source #
fromExact :: Approximation a -> a Source #
data Multiplicity a Source #
Functor Multiplicity Source # | |
Foldable Multiplicity Source # | |
Traversable Multiplicity Source # | |
Eq a => Eq (Multiplicity a) Source # | |
Data a => Data (Multiplicity a) Source # | |
Show a => Show (Multiplicity a) Source # | |
Show (Multiplicity (Approximation Spatial)) # | |
Peelable (Multiplicity a) Source # | |
SynToAst (Multiplicity (Approximation Region)) (Multiplicity (Approximation Spatial)) Source # | |
type CoreTyp (Multiplicity a) Source # | |
Orphan instances
JoinSemiLattice (UnionNF n a) Source # | |
BoundedLattice a => MeetSemiLattice (UnionNF n a) Source # | |
BoundedLattice a => Lattice (UnionNF n a) Source # | |
PartialOrd a => PartialOrd (Vec n a) Source # | |