Copyright | (c) Michal Konecny |
---|---|
License | BSD3 |
Maintainer | mikkonecny@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Numeric.MixedTypes.Power
Contents
Description
Synopsis
- class CanPow b e where
- type CanPowBy t1 t2 = (CanPow t1 t2, PowType t1 t2 ~ t1)
- (^) :: CanPow t1 t2 => t1 -> t2 -> PowType t1 t2
- (^^) :: CanPow t1 t2 => t1 -> t2 -> PPowType t1 t2
- powUsingMul :: CanBeInteger e => t -> (t -> t -> t) -> t -> e -> t
- integerPowCN :: (HasOrderCertainly b Integer, HasOrderCertainly e Integer, HasEqCertainly b Integer, HasEqCertainly e Integer) => (b -> e -> r) -> CN b -> CN e -> CN r
- powUsingMulRecip :: CanBeInteger e => t -> (t -> t -> t) -> (t -> t) -> t -> e -> t
- class CanTestIsIntegerType t where
- isIntegerType :: t -> Bool
- specCanPow :: _ => T t1 -> T t2 -> Spec
Exponentiation
class CanPow b e where Source #
Minimal complete definition
Associated Types
type PowType b e = b
Instances
powUsingMul :: CanBeInteger e => t -> (t -> t -> t) -> t -> e -> t Source #
integerPowCN :: (HasOrderCertainly b Integer, HasOrderCertainly e Integer, HasEqCertainly b Integer, HasEqCertainly e Integer) => (b -> e -> r) -> CN b -> CN e -> CN r Source #
powUsingMulRecip :: CanBeInteger e => t -> (t -> t -> t) -> (t -> t) -> t -> e -> t Source #
class CanTestIsIntegerType t where Source #
Ability to detect whether a numeric type is restricted to (a subset of) integers.
This is useful eg when checking the arguments of the power operator in the CN instance for power.
Minimal complete definition
Nothing
Methods
isIntegerType :: t -> Bool Source #
Instances
CanTestIsIntegerType Rational Source # | |
Defined in Numeric.MixedTypes.Power Methods isIntegerType :: Rational -> Bool Source # | |
CanTestIsIntegerType Integer Source # | |
Defined in Numeric.MixedTypes.Power Methods isIntegerType :: Integer -> Bool Source # | |
CanTestIsIntegerType Double Source # | |
Defined in Numeric.MixedTypes.Power Methods isIntegerType :: Double -> Bool Source # | |
CanTestIsIntegerType Int Source # | |
Defined in Numeric.MixedTypes.Power Methods isIntegerType :: Int -> Bool Source # | |
CanTestIsIntegerType t => CanTestIsIntegerType (CN t) Source # | |
Defined in Numeric.MixedTypes.Power Methods isIntegerType :: CN t -> Bool Source # |