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

Safe HaskellSafe
LanguageHaskell2010

Type.Data.Num.Decimal.Number

Synopsis

Documentation

data Decimal Source #

Representation name for decimal type level numbers.

Instances
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 #

type One Decimal Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

data Dec x Source #

The wrapper type for decimal type level numbers.

Instances
Integer a => Show (Dec a) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

showsPrec :: Int -> Proxy (Dec a) -> ShowS Source #

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

Defined in Type.Data.Num.Decimal.Number

Associated Types

type Repr (Dec x) :: Type Source #

x :/=: y => (Dec x) :/=: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

x :==: y => (Dec x) :==: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

x :>: y => (Dec x) :>: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

x :>=: y => (Dec x) :>=: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

x :<=: y => (Dec x) :<=: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

x :<: y => (Dec x) :<: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Repr (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Repr (Dec x) = Decimal
type Log2Ceil (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Log2Ceil (Dec x) = Dec (Log2Ceil x)
type Pow2 (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Pow2 (Dec x) = Dec (Pow2 x)
type Div2 (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Div2 (Dec x)
type Mul2 (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Mul2 (Dec x) = Dec (x :+: x)
type IsEven (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsEven (Dec x) = IsEven x
type Pred (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Pred (Dec x) = Dec (Pred x)
type Succ (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Succ (Dec x) = Dec (Succ x)
type IsNatural (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsNatural (Dec x)
type IsNegative (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsNegative (Dec x)
type IsZero (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsZero (Dec x)
type IsPositive (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsPositive (Dec x)
type Negate (Dec x) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

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

Defined in Type.Data.Num.Decimal.Number

type (Dec x) :*: (Dec y) = Dec (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)
type (Dec x) :+: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

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

Defined in Type.Data.Num.Decimal.Number

type Compare (Dec x) (Dec y) = Compare x y

data Zero Source #

Instances
Natural Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switchNat :: f Zero -> (forall x xs. (Pos x, Digits xs) => f (Pos x xs)) -> f Zero Source #

Integer Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switch :: f Zero -> (forall x xs. (Pos x, Digits xs) => f (Neg x xs)) -> (forall x xs. (Pos x, Digits xs) => f (Pos x xs)) -> f Zero Source #

Zero :==: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :>=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :<=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :/=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :/=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :>: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :>=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :<=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :<: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :/=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :/=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :>: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :>=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :<=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :<: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type ToUnary Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Pow2 Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Pow2 Zero
type IsEven Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Pred Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Succ Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Succ Zero
type Compare Zero Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Zero :*: _y Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Zero :*: _y = Zero
type Zero :+: y Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Zero :+: y = y
type Compare Zero (Pos _y _ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare Zero (Pos _y _ys) = LT
type Compare Zero (Neg _y _ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare Zero (Neg _y _ys) = GT
type Compare (Pos _x _xs) Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Pos _x _xs) Zero = GT
type Compare (Neg _x _xs) Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Neg _x _xs) Zero = LT
type (Pos _x _xs) :*: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos _x _xs) :*: Zero = Zero
type (Neg _x _xs) :*: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg _x _xs) :*: Zero = Zero
type (Pos x xs) :+: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos x xs) :+: Zero = Pos x xs
type (Neg x xs) :+: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg x xs) :+: Zero = Neg x xs

data Pos x xs Source #

Instances
Zero :/=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :<=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :<: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x, Digits xs) => Positive (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switchPos :: (forall x0 xs0. (Pos0 x0, Digits xs0) => f (Pos x0 xs0)) -> f (Pos x xs) Source #

(Pos x, Digits xs) => Natural (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switchNat :: f Zero -> (forall x0 xs0. (Pos0 x0, Digits xs0) => f (Pos x0 xs0)) -> f (Pos x xs) Source #

(Pos x, Digits xs) => Integer (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switch :: f Zero -> (forall x0 xs0. (Pos0 x0, Digits xs0) => f (Neg x0 xs0)) -> (forall x1 xs1. (Pos0 x1, Digits xs1) => f (Pos x1 xs1)) -> f (Pos x xs) Source #

(Pos x xs) :/=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :>: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :>=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

IsEQ (ComparePos x xs y ys) ~ False => (Pos x xs) :/=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :/=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :/=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

ComparePos x xs y ys ~ EQ => (Pos x xs) :==: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

ComparePos x xs y ys ~ GT => (Pos x xs) :>: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :>: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

GreaterPos y ys x xs ~ False => (Pos x xs) :>=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :>=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

GreaterPos x xs y ys ~ False => (Pos x xs) :<=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :<=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

ComparePos x xs y ys ~ LT => (Pos x xs) :<: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :<: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare Zero (Pos _y _ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare Zero (Pos _y _ys) = LT
type ToUnary (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type ToUnary (Pos x xs) = ToUnaryAcc (ToUnary x) xs
type Log2Ceil (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Log2Ceil (Pos x xs)
type Pow2 (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Pow2 (Pos x xs)
type IsEven (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsEven (Pos x xs)
type Pred (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Pred (Pos x xs)
type Succ (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Succ (Pos x xs)
type Compare (Pos _x _xs) Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Pos _x _xs) Zero = GT
type (Pos _x _xs) :*: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos _x _xs) :*: Zero = Zero
type (Pos x xs) :+: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos x xs) :+: Zero = Pos x xs
type Compare (Pos _x _xs) (Neg _y _ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Pos _x _xs) (Neg _y _ys) = GT
type Compare (Pos x xs) (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Pos x xs) (Pos y ys)
type Compare (Neg _x _xs) (Pos _y _ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Neg _x _xs) (Pos _y _ys) = LT
type (Pos x xs) :*: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos x xs) :*: (Neg y ys)
type (Pos x xs) :*: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos x xs) :*: (Pos y ys)
type (Neg x xs) :*: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg x xs) :*: (Pos y ys)
type (Pos x xs) :+: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos x xs) :+: (Pos y ys)
type (Pos x xs) :+: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos x xs) :+: (Neg y ys)
type (Neg x xs) :+: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg x xs) :+: (Pos y ys)

data Neg x xs Source #

Instances
Zero :/=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :>: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :>=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x, Digits xs) => Negative (Neg x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switchNeg :: (forall x0 xs0. (Pos x0, Digits xs0) => f (Neg x0 xs0)) -> f (Neg x xs) Source #

(Pos x, Digits xs) => Integer (Neg x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switch :: f Zero -> (forall x0 xs0. (Pos x0, Digits xs0) => f (Neg x0 xs0)) -> (forall x1 xs1. (Pos x1, Digits xs1) => f (Pos x1 xs1)) -> f (Neg x xs) Source #

(Neg x xs) :/=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :<=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :<: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :/=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

IsEQ (ComparePos x xs y ys) ~ False => (Neg x xs) :/=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :/=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

ComparePos x xs y ys ~ EQ => (Neg x xs) :==: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :>: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

ComparePos x xs y ys ~ LT => (Neg x xs) :>: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :>=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

GreaterPos x xs y ys ~ False => (Neg x xs) :>=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

GreaterPos y ys x xs ~ False => (Neg x xs) :<=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :<=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

ComparePos x xs y ys ~ GT => (Neg x xs) :<: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :<: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare Zero (Neg _y _ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare Zero (Neg _y _ys) = GT
type IsEven (Neg x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsEven (Neg x xs)
type Pred (Neg x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Pred (Neg x xs)
type Succ (Neg x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Succ (Neg x xs)
type Compare (Neg _x _xs) Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Neg _x _xs) Zero = LT
type (Neg _x _xs) :*: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg _x _xs) :*: Zero = Zero
type (Neg x xs) :+: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg x xs) :+: Zero = Neg x xs
type Compare (Pos _x _xs) (Neg _y _ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Pos _x _xs) (Neg _y _ys) = GT
type Compare (Neg _x _xs) (Pos _y _ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Neg _x _xs) (Pos _y _ys) = LT
type Compare (Neg x xs) (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Neg x xs) (Neg y ys)
type (Pos x xs) :*: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos x xs) :*: (Neg y ys)
type (Neg x xs) :*: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg x xs) :*: (Pos y ys)
type (Neg x xs) :*: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg x xs) :*: (Neg y ys)
type (Pos x xs) :+: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos x xs) :+: (Neg y ys)
type (Neg x xs) :+: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg x xs) :+: (Neg y ys)
type (Neg x xs) :+: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg x xs) :+: (Pos y ys)

data EndAsc Source #

The terminator type for ascending decimal digit lists.

Instances
Show EndAsc Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

data ds :< d infixl 9 Source #

data EndDesc Source #

The terminator type for descending decimal digit lists.

Instances
Show EndDesc Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Digits EndDesc Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switchDigits :: f EndDesc -> (forall xh xl. (C xh, Digits xl) => f (xh :> xl)) -> f EndDesc Source #

type ToUnaryAcc m EndDesc Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type ToUnaryAcc m EndDesc = m

data d :> ds infixr 9 Source #

Instances
(C xh, Digits xl) => Digits (xh :> xl) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switchDigits :: f EndDesc -> (forall xh0 xl0. (C xh0, Digits xl0) => f (xh0 :> xl0)) -> f (xh :> xl) Source #

type ToUnaryAcc m (x :> xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type ToUnaryAcc m (x :> xs) = ToUnaryAcc (UnaryAcc m x) xs

newtype Singleton x Source #

Constructors

Singleton Integer 

class Integer n where Source #

Methods

switch :: f Zero -> (forall x xs. (Pos x, Digits xs) => f (Neg x xs)) -> (forall x xs. (Pos x, Digits xs) => f (Pos x xs)) -> f n Source #

Instances
Integer Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switch :: f Zero -> (forall x xs. (Pos x, Digits xs) => f (Neg x xs)) -> (forall x xs. (Pos x, Digits xs) => f (Pos x xs)) -> f Zero Source #

(Pos x, Digits xs) => Integer (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switch :: f Zero -> (forall x0 xs0. (Pos0 x0, Digits xs0) => f (Neg x0 xs0)) -> (forall x1 xs1. (Pos0 x1, Digits xs1) => f (Pos x1 xs1)) -> f (Pos x xs) Source #

(Pos x, Digits xs) => Integer (Neg x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switch :: f Zero -> (forall x0 xs0. (Pos x0, Digits xs0) => f (Neg x0 xs0)) -> (forall x1 xs1. (Pos x1, Digits xs1) => f (Pos x1 xs1)) -> f (Neg x xs) Source #

class Integer n => Natural n where Source #

Methods

switchNat :: f Zero -> (forall x xs. (Pos x, Digits xs) => f (Pos x xs)) -> f n Source #

Instances
Natural Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switchNat :: f Zero -> (forall x xs. (Pos x, Digits xs) => f (Pos x xs)) -> f Zero Source #

(Pos x, Digits xs) => Natural (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switchNat :: f Zero -> (forall x0 xs0. (Pos0 x0, Digits xs0) => f (Pos x0 xs0)) -> f (Pos x xs) Source #

class Natural n => Positive n where Source #

Methods

switchPos :: (forall x xs. (Pos x, Digits xs) => f (Pos x xs)) -> f n Source #

Instances
(Pos x, Digits xs) => Positive (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switchPos :: (forall x0 xs0. (Pos0 x0, Digits xs0) => f (Pos x0 xs0)) -> f (Pos x xs) Source #

class Integer n => Negative n where Source #

Methods

switchNeg :: (forall x xs. (Pos x, Digits xs) => f (Neg x xs)) -> f n Source #

Instances
(Pos x, Digits xs) => Negative (Neg x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switchNeg :: (forall x0 xs0. (Pos x0, Digits xs0) => f (Neg x0 xs0)) -> f (Neg x xs) Source #

reifyIntegral :: Integer -> (forall s. Integer s => Proxy s -> w) -> w Source #

reifyNatural :: Integer -> (forall s. Natural s => Proxy s -> a) -> Maybe a Source #

reifyPositive :: Integer -> (forall s. Positive s => Proxy s -> a) -> Maybe a Source #

reifyNegative :: Integer -> (forall s. Negative s => Proxy s -> a) -> Maybe a Source #

reifyPos :: Integer -> (forall x xs. (Pos x, Digits xs) => Proxy (Pos x xs) -> a) -> Maybe a Source #

reifyNeg :: Integer -> (forall x xs. (Pos x, Digits xs) => Proxy (Neg x xs) -> a) -> Maybe a Source #

class Digits xs where Source #

Methods

switchDigits :: f EndDesc -> (forall xh xl. (C xh, Digits xl) => f (xh :> xl)) -> f xs Source #

Instances
Digits EndDesc Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switchDigits :: f EndDesc -> (forall xh xl. (C xh, Digits xl) => f (xh :> xl)) -> f EndDesc Source #

(C xh, Digits xl) => Digits (xh :> xl) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Methods

switchDigits :: f EndDesc -> (forall xh0 xl0. (C xh0, Digits xl0) => f (xh0 :> xl0)) -> f (xh :> xl) Source #

type family x :+: y Source #

Instances
type Zero :+: y Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Zero :+: y = y
type (Pos x xs) :+: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos x xs) :+: Zero = Pos x xs
type (Neg x xs) :+: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg x xs) :+: Zero = Neg x xs
type (Pos x xs) :+: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos x xs) :+: (Pos y ys)
type (Pos x xs) :+: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos x xs) :+: (Neg y ys)
type (Neg x xs) :+: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg x xs) :+: (Neg y ys)
type (Neg x xs) :+: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg x xs) :+: (Pos y ys)

type (:-:) x y = x :+: Negate y Source #

type family x :*: y Source #

Instances
type Zero :*: _y Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Zero :*: _y = Zero
type (Pos _x _xs) :*: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos _x _xs) :*: Zero = Zero
type (Neg _x _xs) :*: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg _x _xs) :*: Zero = Zero
type (Pos x xs) :*: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos x xs) :*: (Neg y ys)
type (Pos x xs) :*: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Pos x xs) :*: (Pos y ys)
type (Neg x xs) :*: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg x xs) :*: (Pos y ys)
type (Neg x xs) :*: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type (Neg x xs) :*: (Neg y ys)

type family Pred x Source #

Instances
type Pred Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Pred (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Pred (Pos x xs)
type Pred (Neg x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Pred (Neg x xs)

type family Succ x Source #

Instances
type Succ Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Succ Zero
type Succ (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Succ (Pos x xs)
type Succ (Neg x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Succ (Neg x xs)

type family Compare x y Source #

Instances
type Compare Zero Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare Zero (Pos _y _ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare Zero (Pos _y _ys) = LT
type Compare Zero (Neg _y _ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare Zero (Neg _y _ys) = GT
type Compare (Pos _x _xs) Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Pos _x _xs) Zero = GT
type Compare (Neg _x _xs) Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Neg _x _xs) Zero = LT
type Compare (Pos _x _xs) (Neg _y _ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Pos _x _xs) (Neg _y _ys) = GT
type Compare (Pos x xs) (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Pos x xs) (Pos y ys)
type Compare (Neg _x _xs) (Pos _y _ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Neg _x _xs) (Pos _y _ys) = LT
type Compare (Neg x xs) (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Neg x xs) (Neg y ys)

type family IsEven x Source #

Instances
type IsEven Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsEven (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsEven (Pos x xs)
type IsEven (Neg x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type IsEven (Neg x xs)

type family Pow2 x Source #

Instances
type Pow2 Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Pow2 Zero
type Pow2 (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Pow2 (Pos x xs)

type family Log2Ceil x Source #

Instances
type Log2Ceil (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Log2Ceil (Pos x xs)

class x :<: y Source #

Instances
Zero :<: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

x :<: y => (Dec x) :<: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :<: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

ComparePos x xs y ys ~ LT => (Pos x xs) :<: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

ComparePos x xs y ys ~ GT => (Neg x xs) :<: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :<: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

class x :<=: y Source #

Instances
Zero :<=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :<=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

x :<=: y => (Dec x) :<=: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :<=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

GreaterPos x xs y ys ~ False => (Pos x xs) :<=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

GreaterPos y ys x xs ~ False => (Neg x xs) :<=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :<=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

class x :==: y Source #

Instances
Zero :==: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

x :==: y => (Dec x) :==: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

ComparePos x xs y ys ~ EQ => (Pos x xs) :==: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

ComparePos x xs y ys ~ EQ => (Neg x xs) :==: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

class x :>: y Source #

Instances
Zero :>: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

x :>: y => (Dec x) :>: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :>: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

ComparePos x xs y ys ~ GT => (Pos x xs) :>: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :>: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

ComparePos x xs y ys ~ LT => (Neg x xs) :>: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

class x :>=: y Source #

Instances
Zero :>=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :>=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

x :>=: y => (Dec x) :>=: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :>=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

GreaterPos y ys x xs ~ False => (Pos x xs) :>=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :>=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

GreaterPos x xs y ys ~ False => (Neg x xs) :>=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

class x :/=: y Source #

Instances
Zero :/=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

Zero :/=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

x :/=: y => (Dec x) :/=: (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :/=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :/=: Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

IsEQ (ComparePos x xs y ys) ~ False => (Pos x xs) :/=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Pos x xs) :/=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

IsEQ (ComparePos x xs y ys) ~ False => (Neg x xs) :/=: (Neg y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

(Neg x xs) :/=: (Pos y ys) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type family FromUnary n Source #

Instances
type FromUnary Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type FromUnary (Succ n) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type FromUnary (Succ n) = Succ (FromUnary n)

type family ToUnary n Source #

Instances
type ToUnary Zero Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type ToUnary (Pos x xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type ToUnary (Pos x xs) = ToUnaryAcc (ToUnary x) xs

type family ToUnaryAcc m n Source #

Instances
type ToUnaryAcc m EndDesc Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type ToUnaryAcc m EndDesc = m
type ToUnaryAcc m (x :> xs) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type ToUnaryAcc m (x :> xs) = ToUnaryAcc (UnaryAcc m x) xs

type UnaryAcc m x = ToUnary x :+: (m :*: U10) Source #