Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type family Negate x
- negate :: Proxy x -> Proxy (Negate x)
- type family IsPositive x
- isPositive :: Proxy x -> Proxy (IsPositive x)
- type family IsZero x
- isZero :: Proxy x -> Proxy (IsZero x)
- type family IsNegative x
- isNegative :: Proxy x -> Proxy (IsNegative x)
- type family IsNatural x
- isNatural :: Proxy x -> Proxy (IsNatural x)
- type family One repr
- one :: Proxy repr -> Proxy (One repr)
- type family Succ x
- succ :: Proxy x -> Proxy (Succ x)
- type family Pred x
- pred :: Proxy x -> Proxy (Pred x)
- type family IsEven x
- isEven :: Proxy x -> Proxy (IsEven x)
- type family IsOdd x
- isOdd :: Proxy x -> Proxy (IsOdd x)
- type family x :+: y
- add :: Proxy x -> Proxy y -> Proxy (x :+: y)
- type family x :-: y
- sub :: Proxy x -> Proxy y -> Proxy (x :-: y)
- type family x :*: y
- mul :: Proxy x -> Proxy y -> Proxy (x :*: y)
- type family Mul2 x
- mul2 :: Proxy x -> Proxy (Mul2 x)
- type family Pow2 x
- pow2 :: Proxy x -> Proxy (Pow2 x)
- type family Log2Ceil x
- log2Ceil :: Proxy x -> Proxy (Log2Ceil x)
- type family DivMod x y
- divMod :: Proxy x -> Proxy y -> Proxy (DivMod x y)
- type family Div x y
- div :: Proxy x -> Proxy y -> Proxy (Div x y)
- type family Mod x y
- mod :: Proxy x -> Proxy y -> Proxy (Mod x y)
- type family Div2 x
- div2 :: Proxy x -> Proxy (Div2 x)
- type family Fac x
- fac :: Proxy x -> Proxy (Fac x)
- newtype Singleton d = Singleton Integer
- class Representation r where
- class Representation (Repr x) => Integer x where
- class Integer x => Natural x
- class Integer x => Positive x
- class Integer x => Negative x
- integerFromSingleton :: Integer x => Singleton x -> Integer
- integralFromSingleton :: (Integer x, Num y) => Singleton x -> y
- singletonFromProxy :: Integer x => Proxy x -> Singleton x
- integralFromProxy :: (Integer x, Num y) => Proxy x -> y
- fromInteger :: (Integer x, Num y) => Proxy x -> y
- reifyPositive :: Representation r => Proxy r -> Integer -> (forall s. (Positive s, Repr s ~ r) => Proxy s -> a) -> Maybe a
- reifyNegative :: Representation r => Proxy r -> Integer -> (forall s. (Negative s, Repr s ~ r) => Proxy s -> a) -> Maybe a
- reifyNatural :: Representation r => Proxy r -> Integer -> (forall s. (Natural s, Repr s ~ r) => Proxy s -> a) -> Maybe a
Documentation
Negate x
evaluates to the additive inverse of (i.e., minus) x
.
type family IsPositive x Source #
Instances
type IsPositive (Dec x) Source # | |
Defined in Type.Data.Num.Decimal.Number |
isPositive :: Proxy x -> Proxy (IsPositive x) Source #
type family IsNegative x Source #
Instances
type IsNegative (Dec x) Source # | |
Defined in Type.Data.Num.Decimal.Number |
isNegative :: Proxy x -> Proxy (IsNegative x) Source #
class Representation r where Source #
reifyIntegral :: Proxy r -> Integer -> (forall s. (Integer s, Repr s ~ r) => Proxy s -> a) -> a Source #
Instances
class Representation (Repr x) => Integer x where Source #
class Integer x => Positive x Source #
Instances
(Integer x, IsPositive x ~ True) => Positive x Source # | |
Defined in Type.Data.Num |
class Integer x => Negative x Source #
Instances
(Integer x, IsNegative x ~ True) => Negative x Source # | |
Defined in Type.Data.Num |
fromInteger :: (Integer x, Num y) => Proxy x -> y Source #
synonym for integralFromProxy
, kept for backward compatibility
reifyPositive :: Representation r => Proxy r -> Integer -> (forall s. (Positive s, Repr s ~ r) => Proxy s -> a) -> Maybe a Source #
reifyNegative :: Representation r => Proxy r -> Integer -> (forall s. (Negative s, Repr s ~ r) => Proxy s -> a) -> Maybe a Source #
reifyNatural :: Representation r => Proxy r -> Integer -> (forall s. (Natural s, Repr s ~ r) => Proxy s -> a) -> Maybe a Source #