Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Decimal
- decimal :: Proxy n -> Proxy (Dec n)
- data Dec x
- data Zero
- data Pos x xs
- data Neg x xs
- data EndAsc
- data ds :< d
- data EndDesc
- data d :> ds
- newtype Singleton x = Singleton Integer
- singleton :: Integer x => Singleton x
- singletonFromProxy :: Integer n => Proxy n -> Singleton n
- integerFromSingleton :: Integer n => Singleton n -> Integer
- integralFromSingleton :: (Integer n, Num a) => Singleton n -> a
- integralFromProxy :: (Integer n, Num a) => Proxy n -> a
- class Integer n where
- class Integer n => Natural n where
- class Natural n => Positive n where
- class Integer n => Negative n where
- reifyIntegral :: Integer -> (forall s. Integer s => Proxy s -> w) -> w
- reifyNatural :: Integer -> (forall s. Natural s => Proxy s -> a) -> Maybe a
- reifyPositive :: Integer -> (forall s. Positive s => Proxy s -> a) -> Maybe a
- reifyNegative :: Integer -> (forall s. Negative s => Proxy s -> a) -> Maybe a
- reifyPos :: Integer -> (forall x xs. (Pos x, Digits xs) => Proxy (Pos x xs) -> a) -> Maybe a
- reifyNeg :: Integer -> (forall x xs. (Pos x, Digits xs) => Proxy (Neg x xs) -> a) -> Maybe a
- class Digits xs where
- switchDigits :: f EndDesc -> (forall xh xl. (C xh, Digits xl) => f (xh :> xl)) -> f xs
- type family x :+: y
- type (:-:) x y = x :+: Negate y
- type family x :*: y
- type family Pred x
- type family Succ x
- type family Compare x y
- type family IsEven x
- type family Pow2 x
- type family Log2Ceil x
- class x :<: y
- class x :<=: y
- class x :==: y
- class x :>: y
- class x :>=: y
- class x :/=: y
- type family FromUnary n
- type family ToUnary n
- type family ToUnaryAcc m n
- type UnaryAcc m x = ToUnary x :+: (m :*: U10)
Documentation
Representation name for decimal type level numbers.
The wrapper type for decimal type level numbers.
Instances
Instances
Instances
Instances
The terminator type for ascending decimal digit lists.
The terminator type for descending decimal digit lists.
Instances
Show EndDesc Source # | |
Digits EndDesc Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type ToUnaryAcc m EndDesc Source # | |
Defined in Type.Data.Num.Decimal.Number |
data d :> ds infixr 9 Source #
Instances
(C xh, Digits xl) => Digits (xh :> xl) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type ToUnaryAcc m (x :> xs) Source # | |
Defined in Type.Data.Num.Decimal.Number |
class Integer n where Source #
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 #
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 #
Instances
type Zero :+: y Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type (Pos x xs) :+: Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type (Neg x xs) :+: Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type (Pos x xs) :+: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type (Pos x xs) :+: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type (Neg x xs) :+: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type (Neg x xs) :+: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number |
Instances
type Zero :*: _y Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type (Pos _x _xs) :*: Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type (Neg _x _xs) :*: Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type (Pos x xs) :*: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type (Pos x xs) :*: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type (Neg x xs) :*: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type (Neg x xs) :*: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number |
type family Compare x y Source #
Instances
type Compare Zero Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type Compare Zero (Pos _y _ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type Compare Zero (Neg _y _ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type Compare (Pos _x _xs) Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type Compare (Neg _x _xs) Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type Compare (Pos _x _xs) (Neg _y _ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type Compare (Pos x xs) (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type Compare (Neg _x _xs) (Pos _y _ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type Compare (Neg x xs) (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number |
Instances
Zero :<: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
x :<: y => (Dec x) :<: (Dec y) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
(Neg x xs) :<: Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
ComparePos x xs y ys ~ LT => (Pos x xs) :<: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
ComparePos x xs y ys ~ GT => (Neg x xs) :<: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
(Neg x xs) :<: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number |
Instances
Zero :<=: Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
Zero :<=: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
x :<=: y => (Dec x) :<=: (Dec y) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
(Neg x xs) :<=: Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
GreaterPos x xs y ys ~ False => (Pos x xs) :<=: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
GreaterPos y ys x xs ~ False => (Neg x xs) :<=: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
(Neg x xs) :<=: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number |
Instances
Zero :==: Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
x :==: y => (Dec x) :==: (Dec y) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
ComparePos x xs y ys ~ EQ => (Pos x xs) :==: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
ComparePos x xs y ys ~ EQ => (Neg x xs) :==: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number |
Instances
Zero :>: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
x :>: y => (Dec x) :>: (Dec y) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
(Pos x xs) :>: Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
ComparePos x xs y ys ~ GT => (Pos x xs) :>: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
(Pos x xs) :>: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
ComparePos x xs y ys ~ LT => (Neg x xs) :>: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number |
Instances
Zero :>=: Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
Zero :>=: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
x :>=: y => (Dec x) :>=: (Dec y) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
(Pos x xs) :>=: Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
GreaterPos y ys x xs ~ False => (Pos x xs) :>=: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
(Pos x xs) :>=: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
GreaterPos x xs y ys ~ False => (Neg x xs) :>=: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number |
Instances
Zero :/=: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
Zero :/=: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
x :/=: y => (Dec x) :/=: (Dec y) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
(Pos x xs) :/=: Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
(Neg x xs) :/=: Zero Source # | |
Defined in Type.Data.Num.Decimal.Number | |
IsEQ (ComparePos x xs y ys) ~ False => (Pos x xs) :/=: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
(Pos x xs) :/=: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
IsEQ (ComparePos x xs y ys) ~ False => (Neg x xs) :/=: (Neg y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number | |
(Neg x xs) :/=: (Pos y ys) Source # | |
Defined in Type.Data.Num.Decimal.Number |
type family ToUnaryAcc m n Source #
Instances
type ToUnaryAcc m EndDesc Source # | |
Defined in Type.Data.Num.Decimal.Number | |
type ToUnaryAcc m (x :> xs) Source # | |
Defined in Type.Data.Num.Decimal.Number |