| Portability | portable |
|---|---|
| Safe Haskell | None |
| Language | Haskell98 |
Data.TypedDigits
Description
Description
Digits, indexed by their base at the type level.
Synopsis
- data Digit (base :: Nat)
- digit :: forall base. KnownNat base => Int -> Maybe (Digit base)
- digit' :: KnownNat base => Int -> Digit base
- getVal :: Digit base -> Int
- getBase :: KnownNat base => Digit base -> Int
- getBaseT :: forall a base. KnownNat base => a base -> Int
- (<+>) :: KnownNat base => Digit base -> Digit base -> Digit base
- (<->) :: KnownNat base => Digit base -> Digit base -> Digit base
- class KnownNat (n :: Nat)
Documentation
data Digit (base :: Nat) Source #
digits, indexed by their base at the type level
Instances
| KnownNat base => Bounded (Digit base) Source # | |
| KnownNat base => Enum (Digit base) Source # | |
Defined in Data.TypedDigits.Internal Methods succ :: Digit base -> Digit base # pred :: Digit base -> Digit base # fromEnum :: Digit base -> Int # enumFrom :: Digit base -> [Digit base] # enumFromThen :: Digit base -> Digit base -> [Digit base] # enumFromTo :: Digit base -> Digit base -> [Digit base] # enumFromThenTo :: Digit base -> Digit base -> Digit base -> [Digit base] # | |
| Eq (Digit base) Source # | |
| Ord (Digit base) Source # | |
Defined in Data.TypedDigits.Internal | |
| KnownNat base => Show (Digit base) Source # | |
Constructing Digits
digit :: forall base. KnownNat base => Int -> Maybe (Digit base) Source #
digit x: construct a digit. 0 <= x < base must hold
true.
Nicer if TypeApplications is enabled, then you can say:
>>>:set -XDataKinds>>>:set -XTypeApplications>>>digit @9 8Just 8 (base 9)
digit' :: KnownNat base => Int -> Digit base Source #
Like digit, but throws an ErrorCall if the value is
out of range.
sample usage:
>>>:set -XDataKinds>>>:set -XTypeApplications>>>digit' @9 77 (base 9)
Querying Digits
getBaseT :: forall a base. KnownNat base => a base -> Int Source #
getBaseT p: if p is of some type a base,
then reflect the base into a value.
Useful for getting the base, just given a Proxy; e.g.:
>>>:set -XDataKinds>>>:set -XTypeApplications>>>let p = Proxy :: Proxy 3>>>getBaseT p3