| Arbitrary CReal Source # | |
Instance detailsDefined in AERN2.Real.Tests |
| CanSelect CKleenean Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| CanSelectCountable CKleenean Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| RealNumber CReal Source # | |
Instance detailsDefined in AERN2.Real |
| CanAndOrCountable CKleenean Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| Floating CReal Source # | |
Instance detailsDefined in AERN2.Real.Elementary |
| Num CReal Source # | |
Instance detailsDefined in AERN2.Real.Field |
| Fractional CReal Source # | |
Instance detailsDefined in AERN2.Real.Field |
| CanExp CReal Source # | |
Instance detailsDefined in AERN2.Real.Elementary |
| CanLog CReal Source # | |
Instance detailsDefined in AERN2.Real.Elementary |
| CanSinCos CReal Source # | |
Instance detailsDefined in AERN2.Real.Elementary |
| CanSqrt CReal Source # | |
Instance detailsDefined in AERN2.Real.Elementary |
| Field CReal Source # | |
Instance detailsDefined in AERN2.Real.Field |
| OrderedField CReal Source # | |
Instance detailsDefined in AERN2.Real.Field |
| OrderedRing CReal Source # | |
Instance detailsDefined in AERN2.Real.Field |
| Ring CReal Source # | |
Instance detailsDefined in AERN2.Real.Field |
| HasLimits Rational CReal Source # | |
Instance detailsDefined in AERN2.Real.Limit |
| HasLimits Integer CReal Source # | |
Instance detailsDefined in AERN2.Real.Limit |
| HasLimits Int CReal Source # | |
Instance detailsDefined in AERN2.Real.Limit |
| ConvertibleExactly Dyadic CReal Source # | |
Instance detailsDefined in AERN2.Real.Type |
| ConvertibleExactly CReal CReal Source # | |
Instance detailsDefined in AERN2.Real.Type |
| ConvertibleExactly Rational CReal Source # | |
Instance detailsDefined in AERN2.Real.Type |
| ConvertibleExactly Integer CReal Source # | |
Instance detailsDefined in AERN2.Real.Type |
| ConvertibleExactly Int CReal Source # | |
Instance detailsDefined in AERN2.Real.Type |
| ConvertibleExactly t Kleenean => ConvertibleExactly t CKleenean Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| ConvertibleWithPrecision CReal (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Type |
| CanTakeErrors NumErrors (CSequence t) Source # | |
Instance detailsDefined in AERN2.Real.Type |
| CanAddAsymmetric MPBall b => CanAddAsymmetric MPBall (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| CanAddAsymmetric Dyadic a => CanAddAsymmetric Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric Rational a => CanAddAsymmetric Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric Integer a => CanAddAsymmetric Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric Int a => CanAddAsymmetric Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub MPBall b => CanSub MPBall (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| CanSub Dyadic a => CanSub Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub Rational a => CanSub Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub Integer a => CanSub Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub Int a => CanSub Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAndOrAsymmetric Kleenean t2 => CanAndOrAsymmetric Kleenean (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| CanAndOrAsymmetric Bool t2 => CanAndOrAsymmetric Bool (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| (CanDiv MPBall b, CanTestZero b) => CanDiv MPBall (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| (CanDiv Dyadic a, CanTestZero a) => CanDiv Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanDiv Rational a, CanTestZero a) => CanDiv Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanDiv Integer a, CanTestZero a) => CanDiv Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanDiv Int a, CanTestZero a) => CanDiv Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (HasEqAsymmetric MPBall b, CanTestCertainly (EqCompareType MPBall b)) => HasEqAsymmetric MPBall (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric Dyadic a, IsBool (CSequence (EqCompareType Dyadic a)), CanTestCertainly (EqCompareType Dyadic a)) => HasEqAsymmetric Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric Rational a, IsBool (CSequence (EqCompareType Rational a)), CanTestCertainly (EqCompareType Rational a)) => HasEqAsymmetric Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric Integer a, IsBool (CSequence (EqCompareType Integer a)), CanTestCertainly (EqCompareType Integer a)) => HasEqAsymmetric Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric Int a, IsBool (CSequence (EqCompareType Int a)), CanTestCertainly (EqCompareType Int a)) => HasEqAsymmetric Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasCReals t, HasIntegers t) => ConvertibleExactly CReal (Complex t) Source # | |
Instance detailsDefined in AERN2.Complex |
| CanUnionCNSameType t => HasIfThenElse CKleenean (CSequence t) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| HasIfThenElse CKleenean t => HasIfThenElse CKleenean (Maybe t) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| HasIfThenElse CKleenean t => HasIfThenElse CKleenean [t] Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| CanMinMaxAsymmetric MPBall a => CanMinMaxAsymmetric MPBall (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric Dyadic a => CanMinMaxAsymmetric Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric Rational a => CanMinMaxAsymmetric Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric Integer a => CanMinMaxAsymmetric Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric Int a => CanMinMaxAsymmetric Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMulAsymmetric MPBall b => CanMulAsymmetric MPBall (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| (CanMulAsymmetric Dyadic a, CanGiveUpIfVeryInaccurate (MulType Dyadic a)) => CanMulAsymmetric Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanMulAsymmetric Rational a, CanGiveUpIfVeryInaccurate (MulType Rational a)) => CanMulAsymmetric Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanMulAsymmetric Integer a, CanGiveUpIfVeryInaccurate (MulType Integer a)) => CanMulAsymmetric Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanMulAsymmetric Int a, CanGiveUpIfVeryInaccurate (MulType Int a)) => CanMulAsymmetric Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (HasOrderAsymmetric MPBall b, CanTestCertainly (OrderCompareType MPBall b)) => HasOrderAsymmetric MPBall (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric Dyadic a, IsBool (CSequence (OrderCompareType Dyadic a)), CanTestCertainly (OrderCompareType Dyadic a)) => HasOrderAsymmetric Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric Rational a, IsBool (CSequence (OrderCompareType Rational a)), CanTestCertainly (OrderCompareType Rational a)) => HasOrderAsymmetric Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric Integer a, IsBool (CSequence (OrderCompareType Integer a)), CanTestCertainly (OrderCompareType Integer a)) => HasOrderAsymmetric Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric Int a, IsBool (CSequence (OrderCompareType Int a)), CanTestCertainly (OrderCompareType Int a)) => HasOrderAsymmetric Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (CanPow Rational e, HasOrderCertainly e Integer, CanTestIsIntegerType e, CanTestInteger e) => CanPow Rational (CSequence e) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanPow Integer e, HasOrderCertainly e Integer, CanTestIsIntegerType e, CanTestInteger e) => CanPow Integer (CSequence e) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanPow Int e, HasOrderCertainly e Integer, CanTestIsIntegerType e, CanTestInteger e) => CanPow Int (CSequence e) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| HasLimits Rational (CReal -> CReal) Source # | |
Instance detailsDefined in AERN2.Real.Limit |
| (HasIfThenElse CKleenean t1, HasIfThenElse CKleenean t2) => HasIfThenElse CKleenean (t1, t2) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| HasIfThenElse CKleenean v => HasIfThenElse CKleenean (k -> v) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| Show t => Show (CSequence t) Source # | |
Instance detailsDefined in AERN2.Real.Type |
| CanClearPotentialErrors (CSequence t) Source # | |
Instance detailsDefined in AERN2.Real.Type |
| HasEqCertainly a a => Eq (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqCertainly a a, HasOrderCertainly a a) => Ord (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanNeg t => CanNeg (CSequence t) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| CanAbs t1 => CanAbs (CSequence t1) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanTestIsIntegerType t => CanTestIsIntegerType (CSequence t) Source # | |
Instance detailsDefined in AERN2.Real.Type |
| HasAccuracy t => CanExtractApproximation (CSequence t) Accuracy Source # | |
|
| CanExtractApproximation (CSequence t) Precision Source # | |
|
| CanAddAsymmetric a Dyadic => CanAddAsymmetric (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric a Rational => CanAddAsymmetric (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric a Integer => CanAddAsymmetric (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric a Int => CanAddAsymmetric (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric b MPBall => CanAddAsymmetric (CSequence b) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Field |
| CanSub a Dyadic => CanSub (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub a Rational => CanSub (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub a Integer => CanSub (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub a Int => CanSub (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub b MPBall => CanSub (CSequence b) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Field |
| CanAndOrAsymmetric t1 Kleenean => CanAndOrAsymmetric (CSequence t1) Kleenean Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| CanAndOrAsymmetric t1 Bool => CanAndOrAsymmetric (CSequence t1) Bool Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| CanDiv a Dyadic => CanDiv (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanDiv a Rational => CanDiv (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanDiv a Integer => CanDiv (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanDiv a Int => CanDiv (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanDiv b MPBall => CanDiv (CSequence b) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Field |
| (HasEqAsymmetric a MPBall, CanTestCertainly (EqCompareType a MPBall)) => HasEqAsymmetric (CSequence a) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric a Dyadic, IsBool (CSequence (EqCompareType a Dyadic)), CanTestCertainly (EqCompareType a Dyadic)) => HasEqAsymmetric (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric a Rational, IsBool (CSequence (EqCompareType a Rational)), CanTestCertainly (EqCompareType a Rational)) => HasEqAsymmetric (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric a Integer, IsBool (CSequence (EqCompareType a Integer)), CanTestCertainly (EqCompareType a Integer)) => HasEqAsymmetric (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric a Int, IsBool (CSequence (EqCompareType a Int)), CanTestCertainly (EqCompareType a Int)) => HasEqAsymmetric (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| ConvertibleExactly (WithAnyPrec (CN MPBall)) CReal Source # | |
Instance detailsDefined in AERN2.Real.Type |
| CanMinMaxAsymmetric a MPBall => CanMinMaxAsymmetric (CSequence a) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric a Dyadic => CanMinMaxAsymmetric (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric a Rational => CanMinMaxAsymmetric (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric a Integer => CanMinMaxAsymmetric (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric a Int => CanMinMaxAsymmetric (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (CanMulAsymmetric a Dyadic, CanGiveUpIfVeryInaccurate (MulType a Dyadic)) => CanMulAsymmetric (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanMulAsymmetric a Rational, CanGiveUpIfVeryInaccurate (MulType a Rational)) => CanMulAsymmetric (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanMulAsymmetric a Integer, CanGiveUpIfVeryInaccurate (MulType a Integer)) => CanMulAsymmetric (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanMulAsymmetric a Int, CanGiveUpIfVeryInaccurate (MulType a Int)) => CanMulAsymmetric (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanMulAsymmetric b MPBall => CanMulAsymmetric (CSequence b) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Field |
| (HasOrderAsymmetric a MPBall, CanTestCertainly (OrderCompareType a MPBall)) => HasOrderAsymmetric (CSequence a) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric a Dyadic, IsBool (CSequence (OrderCompareType a Dyadic)), CanTestCertainly (OrderCompareType a Dyadic)) => HasOrderAsymmetric (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric a Rational, IsBool (CSequence (OrderCompareType a Rational)), CanTestCertainly (OrderCompareType a Rational)) => HasOrderAsymmetric (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric a Integer, IsBool (CSequence (OrderCompareType a Integer)), CanTestCertainly (OrderCompareType a Integer)) => HasOrderAsymmetric (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric a Int, IsBool (CSequence (OrderCompareType a Int)), CanTestCertainly (OrderCompareType a Int)) => HasOrderAsymmetric (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (CanPow b Rational, HasOrderCertainly b Integer, HasEqCertainly b Integer, CanTestIsIntegerType b) => CanPow (CSequence b) Rational Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanPow b Integer, HasOrderCertainly b Integer, HasEqCertainly b Integer, CanTestIsIntegerType b) => CanPow (CSequence b) Integer Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanPow b Int, HasOrderCertainly b Integer, HasEqCertainly b Integer, CanTestIsIntegerType b) => CanPow (CSequence b) Int Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric a Dyadic => CanAddAsymmetric (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric a Rational => CanAddAsymmetric (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric a Integer => CanAddAsymmetric (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric a Int => CanAddAsymmetric (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric b MPBall => CanAddAsymmetric (CSequence b) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| CanAddAsymmetric t1 t2 => CanAddAsymmetric (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| CanAddAsymmetric MPBall b => CanAddAsymmetric (CN MPBall) (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| CanAddAsymmetric Dyadic a => CanAddAsymmetric (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric Rational a => CanAddAsymmetric (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric Integer a => CanAddAsymmetric (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanAddAsymmetric Int a => CanAddAsymmetric (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub a Dyadic => CanSub (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub a Rational => CanSub (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub a Integer => CanSub (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub a Int => CanSub (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub b MPBall => CanSub (CSequence b) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| CanSub t1 t2 => CanSub (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| CanSub MPBall b => CanSub (CN MPBall) (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| CanSub Dyadic a => CanSub (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub Rational a => CanSub (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub Integer a => CanSub (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanSub Int a => CanSub (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanAndOrAsymmetric t1 t2, CanTestCertainly t1, HasBools t2) => CanAndOrAsymmetric (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| CanDiv a Dyadic => CanDiv (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanDiv a Rational => CanDiv (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanDiv a Integer => CanDiv (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanDiv a Int => CanDiv (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| CanDiv b MPBall => CanDiv (CSequence b) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| (CanDiv t1 t2, CanTestZero t2) => CanDiv (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| (CanDiv MPBall b, CanTestZero b) => CanDiv (CN MPBall) (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| (CanDiv Dyadic a, CanTestZero a) => CanDiv (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanDiv Rational a, CanTestZero a) => CanDiv (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanDiv Integer a, CanTestZero a) => CanDiv (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanDiv Int a, CanTestZero a) => CanDiv (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (HasEqAsymmetric a MPBall, CanTestCertainly (EqCompareType a MPBall)) => HasEqAsymmetric (CSequence a) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric a Dyadic, IsBool (CSequence (EqCompareType a Dyadic)), CanTestCertainly (EqCompareType a Dyadic)) => HasEqAsymmetric (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric a Rational, IsBool (CSequence (EqCompareType a Rational)), CanTestCertainly (EqCompareType a Rational)) => HasEqAsymmetric (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric a Integer, IsBool (CSequence (EqCompareType a Integer)), CanTestCertainly (EqCompareType a Integer)) => HasEqAsymmetric (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric a Int, IsBool (CSequence (EqCompareType a Int)), CanTestCertainly (EqCompareType a Int)) => HasEqAsymmetric (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric t1 t2, IsBool (CSequence (EqCompareType t1 t2)), CanTestCertainly (EqCompareType t1 t2)) => HasEqAsymmetric (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric MPBall b, CanTestCertainly (EqCompareType MPBall b)) => HasEqAsymmetric (CN MPBall) (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric Dyadic a, IsBool (CSequence (EqCompareType Dyadic a)), CanTestCertainly (EqCompareType Dyadic a)) => HasEqAsymmetric (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric Rational a, IsBool (CSequence (EqCompareType Rational a)), CanTestCertainly (EqCompareType Rational a)) => HasEqAsymmetric (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric Integer a, IsBool (CSequence (EqCompareType Integer a)), CanTestCertainly (EqCompareType Integer a)) => HasEqAsymmetric (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasEqAsymmetric Int a, IsBool (CSequence (EqCompareType Int a)), CanTestCertainly (EqCompareType Int a)) => HasEqAsymmetric (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric a MPBall => CanMinMaxAsymmetric (CSequence a) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric a Dyadic => CanMinMaxAsymmetric (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric a Rational => CanMinMaxAsymmetric (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric a Integer => CanMinMaxAsymmetric (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric a Int => CanMinMaxAsymmetric (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric t1 t2 => CanMinMaxAsymmetric (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric MPBall a => CanMinMaxAsymmetric (CN MPBall) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric Dyadic a => CanMinMaxAsymmetric (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric Rational a => CanMinMaxAsymmetric (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric Integer a => CanMinMaxAsymmetric (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| CanMinMaxAsymmetric Int a => CanMinMaxAsymmetric (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (CanMulAsymmetric a Dyadic, CanGiveUpIfVeryInaccurate (MulType a Dyadic)) => CanMulAsymmetric (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanMulAsymmetric a Rational, CanGiveUpIfVeryInaccurate (MulType a Rational)) => CanMulAsymmetric (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanMulAsymmetric a Integer, CanGiveUpIfVeryInaccurate (MulType a Integer)) => CanMulAsymmetric (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanMulAsymmetric a Int, CanGiveUpIfVeryInaccurate (MulType a Int)) => CanMulAsymmetric (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanMulAsymmetric b MPBall, CanGiveUpIfVeryInaccurate (MulType b MPBall)) => CanMulAsymmetric (CSequence b) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| (CanMulAsymmetric t1 t2, CanGiveUpIfVeryInaccurate (MulType t1 t2)) => CanMulAsymmetric (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| (CanMulAsymmetric MPBall b, CanGiveUpIfVeryInaccurate (MulType MPBall b)) => CanMulAsymmetric (CN MPBall) (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| (CanMulAsymmetric Dyadic a, CanGiveUpIfVeryInaccurate (MulType Dyadic a)) => CanMulAsymmetric (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanMulAsymmetric Rational a, CanGiveUpIfVeryInaccurate (MulType Rational a)) => CanMulAsymmetric (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanMulAsymmetric Integer a, CanGiveUpIfVeryInaccurate (MulType Integer a)) => CanMulAsymmetric (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (CanMulAsymmetric Int a, CanGiveUpIfVeryInaccurate (MulType Int a)) => CanMulAsymmetric (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| (HasOrderAsymmetric a MPBall, CanTestCertainly (OrderCompareType a MPBall)) => HasOrderAsymmetric (CSequence a) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric a Dyadic, IsBool (CSequence (OrderCompareType a Dyadic)), CanTestCertainly (OrderCompareType a Dyadic)) => HasOrderAsymmetric (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric a Rational, IsBool (CSequence (OrderCompareType a Rational)), CanTestCertainly (OrderCompareType a Rational)) => HasOrderAsymmetric (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric a Integer, IsBool (CSequence (OrderCompareType a Integer)), CanTestCertainly (OrderCompareType a Integer)) => HasOrderAsymmetric (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric a Int, IsBool (CSequence (OrderCompareType a Int)), CanTestCertainly (OrderCompareType a Int)) => HasOrderAsymmetric (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric t1 t2, IsBool (CSequence (OrderCompareType t1 t2)), CanTestCertainly (OrderCompareType t1 t2)) => HasOrderAsymmetric (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric MPBall b, CanTestCertainly (OrderCompareType MPBall b)) => HasOrderAsymmetric (CN MPBall) (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric Dyadic a, IsBool (CSequence (OrderCompareType Dyadic a)), CanTestCertainly (OrderCompareType Dyadic a)) => HasOrderAsymmetric (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric Rational a, IsBool (CSequence (OrderCompareType Rational a)), CanTestCertainly (OrderCompareType Rational a)) => HasOrderAsymmetric (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric Integer a, IsBool (CSequence (OrderCompareType Integer a)), CanTestCertainly (OrderCompareType Integer a)) => HasOrderAsymmetric (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (HasOrderAsymmetric Int a, IsBool (CSequence (OrderCompareType Int a)), CanTestCertainly (OrderCompareType Int a)) => HasOrderAsymmetric (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| (CanPow b e, HasOrderCertainly b Integer, HasOrderCertainly e Integer, HasEqCertainly b Integer, CanTestInteger e, CanTestIsIntegerType b, CanTestIsIntegerType e) => CanPow (CSequence b) (CSequence e) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| ConvertibleExactly (WithSample CReal Rational) CReal Source # | |
Instance detailsDefined in AERN2.Real.Type |
| ConvertibleExactly (WithSample CReal Integer) CReal Source # | |
Instance detailsDefined in AERN2.Real.Type |
| type SelectCountableType CKleenean Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| type SelectType CKleenean Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| type ExpType CReal Source # | |
Instance detailsDefined in AERN2.Real.Elementary |
| type LogType CReal Source # | |
Instance detailsDefined in AERN2.Real.Elementary |
| type SinCosType CReal Source # | |
Instance detailsDefined in AERN2.Real.Elementary |
| type SqrtType CReal Source # | |
Instance detailsDefined in AERN2.Real.Elementary |
| type LimitType Rational CReal Source # | |
Instance detailsDefined in AERN2.Real.Limit |
| type LimitType Integer CReal Source # | |
Instance detailsDefined in AERN2.Real.Limit |
| type LimitType Int CReal Source # | |
Instance detailsDefined in AERN2.Real.Limit |
| type AddType MPBall (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type AddType Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType MPBall (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type SubType Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AndOrType Kleenean (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| type AndOrType Bool (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| type DivType MPBall (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type DivType Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type EqCompareType MPBall (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type IfThenElseType CKleenean (CSequence t) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| type IfThenElseType CKleenean (Maybe t) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| type IfThenElseType CKleenean [t] Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| type MinMaxType MPBall (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MulType MPBall (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type MulType Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type OrderCompareType MPBall (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType Dyadic (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType Rational (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType Integer (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType Int (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type PPowType Rational (CSequence e) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type PPowType Integer (CSequence e) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type PPowType Int (CSequence e) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type PowType Rational (CSequence e) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type PowType Integer (CSequence e) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type PowType Int (CSequence e) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type LimitType Rational (CReal -> CReal) Source # | |
Instance detailsDefined in AERN2.Real.Limit |
| type IfThenElseType CKleenean (t1, t2) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| type IfThenElseType CKleenean (k -> v) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| type NegType (CSequence t) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| type AbsType (CSequence t1) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type ExtractedApproximation (CSequence t) Accuracy Source # | |
|
| type ExtractedApproximation (CSequence t) Precision Source # | |
|
| type AddType (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType (CSequence b) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type SubType (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType (CSequence b) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type AndOrType (CSequence t1) Kleenean Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| type AndOrType (CSequence t1) Bool Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| type DivType (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType (CSequence b) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type EqCompareType (CSequence a) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CSequence a) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MulType (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType (CSequence b) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type OrderCompareType (CSequence a) MPBall Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CSequence a) Dyadic Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CSequence a) Rational Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CSequence a) Integer Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CSequence a) Int Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type PPowType (CSequence b) Rational Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type PPowType (CSequence b) Integer Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type PPowType (CSequence b) Int Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type PowType (CSequence b) Rational Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type PowType (CSequence b) Integer Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type PowType (CSequence b) Int Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType (CSequence b) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type AddType (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type AddType (CN MPBall) (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type AddType (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AddType (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType (CSequence b) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type SubType (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type SubType (CN MPBall) (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type SubType (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type SubType (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type AndOrType (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.CKleenean |
| type DivType (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType (CSequence b) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type DivType (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type DivType (CN MPBall) (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type DivType (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type DivType (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type EqCompareType (CSequence a) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CN MPBall) (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type EqCompareType (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CSequence a) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CN MPBall) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MinMaxType (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type MulType (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType (CSequence b) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type MulType (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type MulType (CN MPBall) (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type MulType (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type MulType (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.FieldTH |
| type OrderCompareType (CSequence a) (CN MPBall) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CSequence a) (CN Dyadic) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CSequence a) (CN Rational) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CSequence a) (CN Integer) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CSequence a) (CN Int) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CSequence t1) (CSequence t2) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CN MPBall) (CSequence b) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CN Dyadic) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CN Rational) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CN Integer) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type OrderCompareType (CN Int) (CSequence a) Source # | |
Instance detailsDefined in AERN2.Real.Comparisons |
| type PPowType (CSequence b) (CSequence e) Source # | |
Instance detailsDefined in AERN2.Real.Field |
| type PowType (CSequence b) (CSequence e) Source # | |
Instance detailsDefined in AERN2.Real.Field |