aern2-fun-0.2.9.0: Generic operations for real functions
Copyright(c) Michal Konecny
LicenseBSD3
Maintainermikkonecny@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

AERN2.Interval

Description

Intervals for use as function domains

Documentation

data Interval l r Source #

Constructors

Interval l r 

Instances

Instances details
ConvertibleExactly Integer DyadicInterval Source # 
Instance details

Defined in AERN2.Interval

ConvertibleExactly Rational DyadicInterval Source # 
Instance details

Defined in AERN2.Interval

ConvertibleExactly MPBall DyadicInterval Source # 
Instance details

Defined in AERN2.Interval

ConvertibleExactly Dyadic DyadicInterval Source # 
Instance details

Defined in AERN2.Interval

ConvertibleExactly DyadicInterval MPBall Source # 
Instance details

Defined in AERN2.Interval

(Eq l, Eq r) => Eq (Interval l r) Source # 
Instance details

Defined in AERN2.Interval

Methods

(==) :: Interval l r -> Interval l r -> Bool #

(/=) :: Interval l r -> Interval l r -> Bool #

(Read l, Read r) => Read (Interval l r) Source # 
Instance details

Defined in AERN2.Interval

(Show l, Show r) => Show (Interval l r) Source # 
Instance details

Defined in AERN2.Interval

Methods

showsPrec :: Int -> Interval l r -> ShowS #

show :: Interval l r -> String #

showList :: [Interval l r] -> ShowS #

Generic (Interval l r) Source # 
Instance details

Defined in AERN2.Interval

Associated Types

type Rep (Interval l r) :: Type -> Type #

Methods

from :: Interval l r -> Rep (Interval l r) x #

to :: Rep (Interval l r) x -> Interval l r #

(Arbitrary l, Arbitrary r, HasOrderCertainlyAsymmetric l r) => Arbitrary (Interval l r) Source # 
Instance details

Defined in AERN2.Interval

Methods

arbitrary :: Gen (Interval l r) #

shrink :: Interval l r -> [Interval l r] #

IsInterval (Interval e e) Source # 
Instance details

Defined in AERN2.Interval

Associated Types

type IntervalEndpoint (Interval e e) #

(HasOrderAsymmetric l Integer, OrderCompareType l Integer ~ Bool, HasOrderAsymmetric Integer r, OrderCompareType Integer r ~ Bool) => CanTestContains (Interval l r) Integer Source # 
Instance details

Defined in AERN2.Interval

Methods

contains :: Interval l r -> Integer -> Bool #

(HasOrderAsymmetric l Int, OrderCompareType l Int ~ Bool, HasOrderAsymmetric Int r, OrderCompareType Int r ~ Bool) => CanTestContains (Interval l r) Int Source # 
Instance details

Defined in AERN2.Interval

Methods

contains :: Interval l r -> Int -> Bool #

(HasOrderAsymmetric l Rational, OrderCompareType l Rational ~ Bool, HasOrderAsymmetric Rational r, OrderCompareType Rational r ~ Bool) => CanTestContains (Interval l r) Rational Source # 
Instance details

Defined in AERN2.Interval

Methods

contains :: Interval l r -> Rational -> Bool #

(HasOrderAsymmetric l Dyadic, OrderCompareType l Dyadic ~ Bool, HasOrderAsymmetric Dyadic r, OrderCompareType Dyadic r ~ Bool) => CanTestContains (Interval l r) Dyadic Source # 
Instance details

Defined in AERN2.Interval

Methods

contains :: Interval l r -> Dyadic -> Bool #

(CanSubSameType e, CanAddSubMulBy t e, HasIntegerBounds t, CanSubThis t Integer, CanDivBy t Integer) => CanMapInside (Interval e e) t Source # 
Instance details

Defined in AERN2.Interval

Methods

mapInside :: Interval e e -> t -> t #

(CanBeCReal l, CanBeCReal r, HasOrderCertainly l r, Show l, Show r, Typeable l, Typeable r) => ConvertibleExactly (l, r) RealInterval Source # 
Instance details

Defined in AERN2.Interval

(CanBeDyadic l, CanBeDyadic r, HasOrderCertainly l r, Show l, Show r, Typeable l, Typeable r) => ConvertibleExactly (l, r) DyadicInterval Source # 
Instance details

Defined in AERN2.Interval

(HasOrderAsymmetric l l', OrderCompareType l l' ~ Bool, HasOrderAsymmetric r' r, OrderCompareType r' r ~ Bool) => CanTestContains (Interval l r) (Interval l' r') Source # 
Instance details

Defined in AERN2.Interval

Methods

contains :: Interval l r -> Interval l' r' -> Bool #

(CanMinMaxSameType l, CanMinMaxSameType r, HasOrderCertainly l r) => CanIntersectAsymmetric (Interval l r) (Interval l r) Source # 
Instance details

Defined in AERN2.Interval

Associated Types

type IntersectionType (Interval l r) (Interval l r) #

Methods

intersect :: Interval l r -> Interval l r -> IntersectionType (Interval l r) (Interval l r) #

(HasEqAsymmetric l1 l2, HasEqAsymmetric r1 r2, EqCompareType l1 l2 ~ EqCompareType r1 r2, CanAndOrSameType (EqCompareType l1 l2)) => HasEqAsymmetric (Interval l1 r1) (Interval l2 r2) Source # 
Instance details

Defined in AERN2.Interval

Associated Types

type EqCompareType (Interval l1 r1) (Interval l2 r2) #

Methods

equalTo :: Interval l1 r1 -> Interval l2 r2 -> EqCompareType (Interval l1 r1) (Interval l2 r2) #

notEqualTo :: Interval l1 r1 -> Interval l2 r2 -> EqCompareType (Interval l1 r1) (Interval l2 r2) #

type Rep (Interval l r) Source # 
Instance details

Defined in AERN2.Interval

type Rep (Interval l r) = D1 ('MetaData "Interval" "AERN2.Interval" "aern2-fun-0.2.9.0-4AlMbXgmPZtHbHcHCnPDza" 'False) (C1 ('MetaCons "Interval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 r)))
type IntervalEndpoint (Interval e e) Source # 
Instance details

Defined in AERN2.Interval

type IntervalEndpoint (Interval e e) = e
type IntersectionType (Interval l r) (Interval l r) Source # 
Instance details

Defined in AERN2.Interval

type IntersectionType (Interval l r) (Interval l r) = CN (Interval l r)
type EqCompareType (Interval l1 r1) (Interval l2 r2) Source # 
Instance details

Defined in AERN2.Interval

type EqCompareType (Interval l1 r1) (Interval l2 r2) = EqCompareType l1 l2

width :: CanSub r l => Interval l r -> SubType r l Source #

intersect :: CanIntersectAsymmetric e1 e2 => e1 -> e2 -> IntersectionType e1 e2 #