tfp-1.0.0.2: Type-level integers, booleans, lists using type families

Safe HaskellSafe
LanguageHaskell2010

Type.Data.Num

Synopsis

Documentation

type family Negate x Source

Negate x evaluates to the additive inverse of (i.e., minus) x.

Instances

type Negate (Dec x) Source 

type family IsPositive x Source

Instances

type IsPositive (Dec x) Source 

type family IsZero x Source

Instances

type IsZero (Dec x) Source 

type family IsNegative x Source

Instances

type IsNegative (Dec x) Source 

type family IsNatural x Source

Instances

type IsNatural (Dec x) Source 

type family One repr Source

Instances

one :: Proxy repr -> Proxy (One repr) Source

type family Succ x Source

Instances

type Succ (Dec x) = Dec (Succ x) Source 

succ :: Proxy x -> Proxy (Succ x) Source

type family Pred x Source

Instances

type Pred (Dec x) = Dec (Pred x) Source 

pred :: Proxy x -> Proxy (Pred x) Source

type family IsEven x Source

Instances

type IsEven (Dec x) = IsEven x Source 

type family IsOdd x Source

Instances

type IsOdd x = Not (IsEven x) Source 

type family x :+: y Source

Instances

type (Un x) :+: (Un y) = Un ((:+:) x y) Source 
type (Dec x) :+: (Dec y) = Dec ((:+:) x y) Source 

add :: Proxy x -> Proxy y -> Proxy (x :+: y) Source

type family x :-: y Source

Instances

type (Dec x) :-: (Dec y) = Dec ((:-:) x y) Source 

sub :: Proxy x -> Proxy y -> Proxy (x :-: y) Source

type family x :*: y Source

Instances

type (Un x) :*: (Un y) = Un ((:*:) x y) Source 
type (Dec x) :*: (Dec y) = Dec ((:*:) x y) Source 

mul :: Proxy x -> Proxy y -> Proxy (x :*: y) Source

type family Mul2 x Source

Instances

type Mul2 (Dec x) = Dec ((:+:) x x) Source 

mul2 :: Proxy x -> Proxy (Mul2 x) Source

type family Pow2 x Source

Instances

type Pow2 (Dec x) = Dec (Pow2 x) Source 

pow2 :: Proxy x -> Proxy (Pow2 x) Source

type family Log2Ceil x Source

Instances

type Log2Ceil (Dec x) = Dec (Log2Ceil x) Source 

type family DivMod x y Source

divMod :: Proxy x -> Proxy y -> Proxy (DivMod x y) Source

type family Div x y Source

div :: Proxy x -> Proxy y -> Proxy (Div x y) Source

type family Mod x y Source

mod :: Proxy x -> Proxy y -> Proxy (Mod x y) Source

type family Div2 x Source

Instances

type Div2 (Dec x) Source 

div2 :: Proxy x -> Proxy (Div2 x) Source

type family Fac x Source

Instances

type Fac x Source 

fac :: Proxy x -> Proxy (Fac x) Source

newtype Singleton d Source

Constructors

Singleton Integer 

class Representation r where Source

Methods

reifyIntegral :: Proxy r -> Integer -> (forall s. (Integer s, Repr s ~ r) => Proxy s -> a) -> a Source

class Representation (Repr x) => Integer x where Source

Associated Types

type Repr x Source

Instances

class Integer x => Natural x Source

Instances

(Integer x, (~) * (IsNatural x) True) => Natural x Source 

class Integer x => Positive x Source

Instances

(Integer x, (~) * (IsPositive x) True) => Positive x Source 

class Integer x => Negative x Source

Instances

(Integer x, (~) * (IsNegative x) True) => Negative x Source 

fromInteger :: forall x y. (Integer x, Num y) => Proxy x -> y Source

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