Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
- 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.
Representation Decimal | |
type One Decimal |
The wrapper type for decimal type level numbers.
Integer x => Integer (Dec x) | |
(:/=:) x y => (Dec x) :/=: (Dec y) | |
(:==:) x y => (Dec x) :==: (Dec y) | |
(:>:) x y => (Dec x) :>: (Dec y) | |
(:>=:) x y => (Dec x) :>=: (Dec y) | |
(:<=:) x y => (Dec x) :<=: (Dec y) | |
(:<:) x y => (Dec x) :<: (Dec y) | |
type Repr (Dec x) = Decimal | |
type Log2Ceil (Dec x) = Dec (Log2Ceil x) | |
type Pow2 (Dec x) = Dec (Pow2 x) | |
type Div2 (Dec x) | |
type Mul2 (Dec x) = Dec ((:+:) x x) | |
type IsEven (Dec x) = IsEven x | |
type Pred (Dec x) = Dec (Pred x) | |
type Succ (Dec x) = Dec (Succ x) | |
type IsNatural (Dec x) | |
type IsNegative (Dec x) | |
type IsZero (Dec x) | |
type IsPositive (Dec x) | |
type Negate (Dec x) | |
type Compare (Dec x) (Dec y) = Compare x y | |
type (Dec x) :*: (Dec y) = Dec ((:*:) x y) | |
type (Dec x) :-: (Dec y) = Dec ((:-:) x y) | |
type (Dec x) :+: (Dec y) = Dec ((:+:) x y) |
Natural Zero | |
Integer Zero | |
Zero :==: Zero | |
Zero :>=: Zero | |
Zero :<=: Zero | |
Zero :/=: (Pos y ys) | |
Zero :/=: (Neg y ys) | |
Zero :>: (Neg y ys) | |
Zero :>=: (Neg y ys) | |
Zero :<=: (Pos y ys) | |
Zero :<: (Pos y ys) | |
(Pos x xs) :/=: Zero | |
(Neg x xs) :/=: Zero | |
(Pos x xs) :>: Zero | |
(Pos x xs) :>=: Zero | |
(Neg x xs) :<=: Zero | |
(Neg x xs) :<: Zero | |
type ToUnary Zero = Zero | |
type Pow2 Zero | |
type IsEven Zero = True | |
type Pred Zero = Neg Dec1 EndDesc | |
type Succ Zero | |
type Compare Zero Zero = EQ | |
type Zero :*: x = Zero | |
type Zero :+: y = y | |
type Compare Zero (Pos y ys) = LT | |
type Compare Zero (Neg y ys) = GT | |
type Compare (Pos x xs) Zero = GT | |
type Compare (Neg x xs) Zero = LT | |
type (Pos x xs) :*: Zero = Zero | |
type (Neg x xs) :*: Zero = Zero | |
type (Pos x xs) :+: Zero = Pos x xs | |
type (Neg x xs) :+: Zero = Neg x xs |
Zero :/=: (Pos y ys) | |
Zero :<=: (Pos y ys) | |
Zero :<: (Pos y ys) | |
(Pos x, Digits xs) => Positive (Pos x xs) | |
(Pos x, Digits xs) => Natural (Pos x xs) | |
(Pos x, Digits xs) => Integer (Pos x xs) | |
(Pos x xs) :/=: Zero | |
(Pos x xs) :>: Zero | |
(Pos x xs) :>=: Zero | |
(~) * (IsEQ (ComparePos x xs y ys)) False => (Pos x xs) :/=: (Pos y ys) | |
(Pos x xs) :/=: (Neg y ys) | |
(Neg x xs) :/=: (Pos y ys) | |
(~) * (ComparePos x xs y ys) EQ => (Pos x xs) :==: (Pos y ys) | |
(~) * (ComparePos x xs y ys) GT => (Pos x xs) :>: (Pos y ys) | |
(Pos x xs) :>: (Neg y ys) | |
(~) * (GreaterPos y ys x xs) False => (Pos x xs) :>=: (Pos y ys) | |
(Pos x xs) :>=: (Neg y ys) | |
(~) * (GreaterPos x xs y ys) False => (Pos x xs) :<=: (Pos y ys) | |
(Neg x xs) :<=: (Pos y ys) | |
(~) * (ComparePos x xs y ys) LT => (Pos x xs) :<: (Pos y ys) | |
(Neg x xs) :<: (Pos y ys) | |
type Compare Zero (Pos y ys) = LT | |
type ToUnary (Pos x xs) = ToUnaryAcc (ToUnary x) xs | |
type Log2Ceil (Pos x xs) | |
type Pow2 (Pos x xs) | |
type IsEven (Pos x xs) | |
type Pred (Pos x xs) | |
type Succ (Pos x xs) | |
type Compare (Pos x xs) Zero = GT | |
type (Pos x xs) :*: Zero = Zero | |
type (Pos x xs) :+: Zero = Pos x xs | |
type Compare (Pos x xs) (Neg y ys) = GT | |
type Compare (Pos x xs) (Pos y ys) | |
type Compare (Neg x xs) (Pos y ys) = LT | |
type (Pos x xs) :*: (Neg y ys) | |
type (Pos x xs) :*: (Pos y ys) | |
type (Neg x xs) :*: (Pos y ys) | |
type (Pos x xs) :+: (Neg y ys) | |
type (Pos x xs) :+: (Pos y ys) | |
type (Neg x xs) :+: (Pos y ys) |
Zero :/=: (Neg y ys) | |
Zero :>: (Neg y ys) | |
Zero :>=: (Neg y ys) | |
(Pos x, Digits xs) => Negative (Neg x xs) | |
(Pos x, Digits xs) => Integer (Neg x xs) | |
(Neg x xs) :/=: Zero | |
(Neg x xs) :<=: Zero | |
(Neg x xs) :<: Zero | |
(Pos x xs) :/=: (Neg y ys) | |
(~) * (IsEQ (ComparePos x xs y ys)) False => (Neg x xs) :/=: (Neg y ys) | |
(Neg x xs) :/=: (Pos y ys) | |
(~) * (ComparePos x xs y ys) EQ => (Neg x xs) :==: (Neg y ys) | |
(Pos x xs) :>: (Neg y ys) | |
(~) * (ComparePos x xs y ys) LT => (Neg x xs) :>: (Neg y ys) | |
(Pos x xs) :>=: (Neg y ys) | |
(~) * (GreaterPos x xs y ys) False => (Neg x xs) :>=: (Neg y ys) | |
(~) * (GreaterPos y ys x xs) False => (Neg x xs) :<=: (Neg y ys) | |
(Neg x xs) :<=: (Pos y ys) | |
(~) * (ComparePos x xs y ys) GT => (Neg x xs) :<: (Neg y ys) | |
(Neg x xs) :<: (Pos y ys) | |
type Compare Zero (Neg y ys) = GT | |
type IsEven (Neg x xs) | |
type Pred (Neg x xs) | |
type Succ (Neg x xs) | |
type Compare (Neg x xs) Zero = LT | |
type (Neg x xs) :*: Zero = Zero | |
type (Neg x xs) :+: Zero = Neg x xs | |
type Compare (Pos x xs) (Neg y ys) = GT | |
type Compare (Neg x xs) (Pos y ys) = LT | |
type Compare (Neg x xs) (Neg y ys) | |
type (Pos x xs) :*: (Neg y ys) | |
type (Neg x xs) :*: (Pos y ys) | |
type (Neg x xs) :*: (Neg y ys) | |
type (Pos x xs) :+: (Neg y ys) | |
type (Neg x xs) :+: (Pos y ys) | |
type (Neg x xs) :+: (Neg y ys) |
The terminator type for descending decimal digit lists.
(C xh, Digits xl) => Digits ((:>) xh xl) | |
type ToUnaryAcc m ((:>) x xs) = ToUnaryAcc (UnaryAcc m x) xs |
singletonFromProxy :: Integer n => Proxy n -> Singleton n Source
integerFromSingleton :: Integer n => Singleton n -> Integer Source
integralFromSingleton :: (Integer n, Num a) => Singleton n -> a Source
integralFromProxy :: (Integer n, Num a) => Proxy n -> a Source
reifyIntegral :: Integer -> (forall s. Integer s => Proxy s -> w) -> w Source
type family Compare x y Source
type Compare Zero Zero = EQ | |
type Compare Zero (Pos y ys) = LT | |
type Compare Zero (Neg y ys) = GT | |
type Compare (Pos x xs) Zero = GT | |
type Compare (Neg x xs) Zero = LT | |
type Compare (Pos x xs) (Neg y ys) = GT | |
type Compare (Pos x xs) (Pos y ys) | |
type Compare (Neg x xs) (Pos y ys) = LT | |
type Compare (Neg x xs) (Neg y ys) |
Zero :/=: (Pos y ys) | |
Zero :/=: (Neg y ys) | |
(:/=:) x y => (Dec x) :/=: (Dec y) | |
(Pos x xs) :/=: Zero | |
(Neg x xs) :/=: Zero | |
(~) * (IsEQ (ComparePos x xs y ys)) False => (Pos x xs) :/=: (Pos y ys) | |
(Pos x xs) :/=: (Neg y ys) | |
(~) * (IsEQ (ComparePos x xs y ys)) False => (Neg x xs) :/=: (Neg y ys) | |
(Neg x xs) :/=: (Pos y ys) |
type family ToUnaryAcc m n Source
type ToUnaryAcc m EndDesc = m | |
type ToUnaryAcc m ((:>) x xs) = ToUnaryAcc (UnaryAcc m x) xs |