tfp-1.0.1: 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 # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Negate (Dec x)

type family IsPositive x Source #

Instances
type IsPositive (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsPositive (Dec x)

type family IsZero x Source #

Instances
type IsZero (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsZero (Dec x)

type family IsNegative x Source #

Instances
type IsNegative (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsNegative (Dec x)

type family IsNatural x Source #

Instances
type IsNatural (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsNatural (Dec x)

type family One repr Source #

Instances
type One Decimal Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

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

type family Succ x Source #

Instances
type Succ (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

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

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

type family Pred x Source #

Instances
type Pred (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

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

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

type family IsEven x Source #

Instances
type IsEven (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsEven (Dec x) = IsEven x

type family IsOdd x Source #

Instances
type IsOdd x Source # 
Instance details

Defined in Type.Data.Num

type IsOdd x = Not (IsEven x)

type family x :+: y Source #

Instances
type (Un x) :+: (Un y) Source # 
Instance details

Defined in Type.Data.Num.Unary

type (Un x) :+: (Un y) = Un (x :+: y)
type (Dec x) :+: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

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

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

type family x :-: y Source #

Instances
type (Dec x) :-: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

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

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

type family x :*: y Source #

Instances
type (Un x) :*: (Un y) Source # 
Instance details

Defined in Type.Data.Num.Unary

type (Un x) :*: (Un y) = Un (x :*: y)
type (Dec x) :*: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

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

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

type family Mul2 x Source #

Instances
type Mul2 (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

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

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

type family Pow2 x Source #

Instances
type Pow2 (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

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

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

type family Log2Ceil x Source #

Instances
type Log2Ceil (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

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

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 # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Div2 (Dec x)

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

type family Fac x Source #

Instances
type Fac x Source # 
Instance details

Defined in Type.Data.Num

type Fac x

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 #

Instances
Representation Unary Source # 
Instance details

Defined in Type.Data.Num.Unary

Methods

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

Representation Decimal Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

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

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

Associated Types

type Repr x Source #

Instances
Natural n => Integer (Un n) Source # 
Instance details

Defined in Type.Data.Num.Unary

Associated Types

type Repr (Un n) :: Type Source #

Methods

singleton :: Singleton (Un n) Source #

Integer x => Integer (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Associated Types

type Repr (Dec x) :: Type Source #

class Integer x => Natural x Source #

Instances
(Integer x, IsNatural x ~ True) => Natural x Source # 
Instance details

Defined in Type.Data.Num

class Integer x => Positive x Source #

Instances
(Integer x, IsPositive x ~ True) => Positive x Source # 
Instance details

Defined in Type.Data.Num

class Integer x => Negative x Source #

Instances
(Integer x, IsNegative x ~ True) => Negative x Source # 
Instance details

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 #