mixed-types-num-0.5.9.1: Alternative Prelude with numeric and logic expressions typed bottom-up
Copyright(c) Michal Konecny
LicenseBSD3
Maintainermikkonecny@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Numeric.MixedTypes.Power

Description

 
Synopsis

Exponentiation

class CanPow b e where Source #

A replacement for Prelude's binary ^ and ^^.

Minimal complete definition

pow

Associated Types

type PowType b e Source #

type PowType b e = b

type PPowType b e Source #

type PPowType b e = PowType b e

Methods

pow :: b -> e -> PowType b e Source #

ppow :: b -> e -> PPowType b e Source #

default ppow :: PPowType b e ~ PowType b e => b -> e -> PPowType b e Source #

Instances

Instances details
CanPow Double Double Source # 
Instance details

Defined in Numeric.MixedTypes.Power

CanPow Double Int Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType Double Int Source #

type PPowType Double Int Source #

CanPow Double Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Power

CanPow Double Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Power

CanPow Int Double Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType Int Double Source #

type PPowType Int Double Source #

CanPow Int Int Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType Int Int Source #

type PPowType Int Int Source #

CanPow Int Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType Int Integer Source #

type PPowType Int Integer Source #

CanPow Integer Double Source # 
Instance details

Defined in Numeric.MixedTypes.Power

CanPow Integer Int Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType Integer Int Source #

type PPowType Integer Int Source #

CanPow Integer Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Power

CanPow Rational Double Source # 
Instance details

Defined in Numeric.MixedTypes.Power

CanPow Rational Int Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType Rational Int Source #

type PPowType Rational Int Source #

CanPow Rational Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Power

(CanPow Double e, HasOrderCertainly e Integer, CanTestIsIntegerType e, CanTestInteger e) => CanPow Double (CN e) Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType Double (CN e) Source #

type PPowType Double (CN e) Source #

Methods

pow :: Double -> CN e -> PowType Double (CN e) Source #

ppow :: Double -> CN e -> PPowType Double (CN e) Source #

(CanPow Int e, HasOrderCertainly e Integer, CanTestIsIntegerType e, CanTestInteger e) => CanPow Int (CN e) Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType Int (CN e) Source #

type PPowType Int (CN e) Source #

Methods

pow :: Int -> CN e -> PowType Int (CN e) Source #

ppow :: Int -> CN e -> PPowType Int (CN e) Source #

(CanPow Integer e, HasOrderCertainly e Integer, CanTestIsIntegerType e, CanTestInteger e) => CanPow Integer (CN e) Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType Integer (CN e) Source #

type PPowType Integer (CN e) Source #

Methods

pow :: Integer -> CN e -> PowType Integer (CN e) Source #

ppow :: Integer -> CN e -> PPowType Integer (CN e) Source #

(CanPow Rational e, HasOrderCertainly e Integer, CanTestIsIntegerType e, CanTestInteger e) => CanPow Rational (CN e) Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType Rational (CN e) Source #

type PPowType Rational (CN e) Source #

Methods

pow :: Rational -> CN e -> PowType Rational (CN e) Source #

ppow :: Rational -> CN e -> PPowType Rational (CN e) Source #

(CanPow b Integer, HasOrderCertainly b Integer, HasEqCertainly b Integer, CanTestIsIntegerType b) => CanPow (CN b) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType (CN b) Integer Source #

type PPowType (CN b) Integer Source #

Methods

pow :: CN b -> Integer -> PowType (CN b) Integer Source #

ppow :: CN b -> Integer -> PPowType (CN b) Integer Source #

(CanPow b Int, HasOrderCertainly b Integer, HasEqCertainly b Integer, CanTestIsIntegerType b) => CanPow (CN b) Int Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType (CN b) Int Source #

type PPowType (CN b) Int Source #

Methods

pow :: CN b -> Int -> PowType (CN b) Int Source #

ppow :: CN b -> Int -> PPowType (CN b) Int Source #

(CanPow b Rational, HasOrderCertainly b Integer, HasEqCertainly b Integer, CanTestIsIntegerType b) => CanPow (CN b) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType (CN b) Rational Source #

type PPowType (CN b) Rational Source #

Methods

pow :: CN b -> Rational -> PowType (CN b) Rational Source #

ppow :: CN b -> Rational -> PPowType (CN b) Rational Source #

(CanPow b Double, HasOrderCertainly b Integer, HasEqCertainly b Integer, CanTestIsIntegerType b) => CanPow (CN b) Double Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType (CN b) Double Source #

type PPowType (CN b) Double Source #

Methods

pow :: CN b -> Double -> PowType (CN b) Double Source #

ppow :: CN b -> Double -> PPowType (CN b) Double Source #

CanPow a b => CanPow (Maybe a) (Maybe b) Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType (Maybe a) (Maybe b) Source #

type PPowType (Maybe a) (Maybe b) Source #

Methods

pow :: Maybe a -> Maybe b -> PowType (Maybe a) (Maybe b) Source #

ppow :: Maybe a -> Maybe b -> PPowType (Maybe a) (Maybe b) Source #

(CanPow b e, HasOrderCertainly b Integer, HasOrderCertainly e Integer, HasEqCertainly b Integer, CanTestIsIntegerType b, CanTestIsIntegerType e, CanTestInteger e) => CanPow (CN b) (CN e) Source # 
Instance details

Defined in Numeric.MixedTypes.Power

Associated Types

type PowType (CN b) (CN e) Source #

type PPowType (CN b) (CN e) Source #

Methods

pow :: CN b -> CN e -> PowType (CN b) (CN e) Source #

ppow :: CN b -> CN e -> PPowType (CN b) (CN e) Source #

type CanPowBy t1 t2 = (CanPow t1 t2, PowType t1 t2 ~ t1) Source #

(^) :: CanPow t1 t2 => t1 -> t2 -> PowType t1 t2 infixl 8 Source #

(^^) :: CanPow t1 t2 => t1 -> t2 -> PPowType t1 t2 infixl 8 Source #

powUsingMul :: CanBeInteger e => t -> (t -> t -> t) -> t -> e -> t 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 #

Tests

specCanPow :: _ => T t1 -> T t2 -> Spec Source #

HSpec properties that each implementation of CanPow should satisfy.