Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
This module provides a type-level representation for term-level
Integer
s. This type-level representation is also named Integer
,
So import this module qualified to avoid name conflicts.
import KindInteger qualified as KI
The implementation details are the same as the ones for type-level Natural
s
in GHC.TypeNats as of base-4.18
, and it will continue to evolve together
with base
, trying to follow its API as much as possible until the day
base
provides its own type-level integer, making this module redundant.
Synopsis
- data Integer
- type P (x :: Natural) = 'P_ x :: Integer
- type N (x :: Natural) = 'N_ x :: Integer
- type family Normalize (i :: Integer) :: Integer where ...
- toPrelude :: Integer -> Integer
- fromPrelude :: Integer -> Integer
- showsPrecTypeLit :: Int -> Integer -> ShowS
- class KnownInteger (i :: Integer) where
- integerSing :: SInteger i
- integerVal :: forall i proxy. KnownInteger i => proxy i -> Integer
- data SomeInteger = forall n.KnownInteger n => SomeInteger (Proxy n)
- someIntegerVal :: Integer -> SomeInteger
- sameInteger :: forall a b proxy1 proxy2. (KnownInteger a, KnownInteger b) => proxy1 a -> proxy2 b -> Maybe (a :~: b)
- data SInteger (i :: Integer)
- pattern SInteger :: forall i. () => KnownInteger i => SInteger i
- fromSInteger :: SInteger i -> Integer
- withSomeSInteger :: forall rep (r :: TYPE rep). Integer -> (forall n. SInteger n -> r) -> r
- withKnownInteger :: forall i rep (r :: TYPE rep). SInteger i -> (KnownInteger i => r) -> r
- type (+) (a :: Integer) (b :: Integer) = Add_ (Normalize a) (Normalize b) :: Integer
- type * (a :: Integer) (b :: Integer) = Mul_ (Normalize a) (Normalize b) :: Integer
- type (^) (a :: Integer) (b :: Integer) = Pow_ (Normalize a) (Normalize b) :: Integer
- type (-) (a :: Integer) (b :: Integer) = a + Negate b :: Integer
- type Odd (x :: Integer) = Mod (Abs x) 2 ==? 1 :: Bool
- type Even (x :: Integer) = Mod (Abs x) 2 ==? 0 :: Bool
- type family Abs (x :: Integer) :: Natural where ...
- type family Sign (x :: Integer) :: Integer where ...
- type family Negate (x :: Integer) :: Integer where ...
- type GCD (a :: Integer) (b :: Integer) = NatGCD (Abs a) (Abs b) :: Natural
- type LCM (a :: Integer) (b :: Integer) = NatLCM (Abs a) (Abs b) :: Natural
- type Log2 (a :: Integer) = Log2_ (Normalize a) :: Integer
- type Div (r :: Round) (a :: Integer) (b :: Integer) = Div_ r (Normalize a) (Normalize b) :: Integer
- type Rem (r :: Round) (a :: Integer) (b :: Integer) = a - (b * Div r a b) :: Integer
- type DivRem (r :: Round) (a :: Integer) (b :: Integer) = '(Div r a b, Rem r a b) :: (Integer, Integer)
- data Round
- div :: Round -> Integer -> Integer -> Integer
- rem :: Round -> Integer -> Integer -> Integer
- divRem :: Round -> Integer -> Integer -> (Integer, Integer)
- type CmpInteger (a :: Integer) (b :: Integer) = CmpInteger_ (Normalize a) (Normalize b) :: Ordering
- cmpInteger :: forall a b proxy1 proxy2. (KnownInteger a, KnownInteger b) => proxy1 a -> proxy2 b -> OrderingI a b
- type (==?) (a :: k) (b :: k) = OrdCond (Compare a b) 'False 'True 'False :: Bool
- type (==) (a :: k) (b :: k) = (a ==? b) ~ 'True :: Constraint
- type (/=?) (a :: k) (b :: k) = OrdCond (Compare a b) 'True 'False 'True :: Bool
- type (/=) (a :: k) (b :: k) = (a /=? b) ~ 'True :: Constraint
Integer kind
Type-level version of Integer
, only ever used as a kind
for P
and N
- A positive number +x is represented as
.P
x - A negative number -x is represented as
.N
x - Zero can be represented as
orP
0
. For consistency, all zero outputs from type families in this KindInteger module use theN
0
, but don't assume that this will be the case elsewhere. So, if you need to treat zero specially in some situation, be sure to handle both theP
0
andP
0
cases.N
0
NB: Integer
is mostly used as a kind, with its types constructed
using P
and N
. However, it might also be used as type, with its terms
constructed using fromPrelude
. One reason why you may want a Integer
at the term-level is so that you embed it in larger data-types (for example,
the KindRational module from the
kind-rational
library embeds this Integer
in its Rational
type)
Instances
Read Integer Source # | |
Show Integer Source # | |
Eq Integer Source # | |
Ord Integer Source # | |
TestCoercion SInteger Source # | |
Defined in KindInteger | |
TestEquality SInteger Source # | |
Defined in KindInteger | |
type Compare (a :: Integer) (b :: Integer) Source # | Data.Type.Ord support for type-level |
Defined in KindInteger |
type family Normalize (i :: Integer) :: Integer where ... Source #
Make sure zero is represented as
, not as P
0N
0
Notice that all the tools in the KindInteger can readily handle
non-Normalize
d inputs. This Normalize
type-family is offered offered
only as a convenience in case you want to simplify your dealing with
zeros.
Prelude support
toPrelude :: Integer -> Integer Source #
Convert a term-level KindInteger Integer
into a term-level
Prelude Integer
.
fromPrelude
.toPrelude
==id
toPrelude
.fromPrelude
==id
fromPrelude :: Integer -> Integer Source #
Obtain a term-level KindInteger Integer
from a term-level
Prelude Integer
. This can fail if the Prelude Integer
is
infinite, or if it is so big that it would exhaust system resources.
fromPrelude
.toPrelude
==id
toPrelude
.fromPrelude
==id
This function can be handy if you are passing KindInteger's Integer
around for some reason. But, other than this, KindInteger doesn't offer
any tool to deal with the internals of its Integer
.
showsPrecTypeLit :: Int -> Integer -> ShowS Source #
Shows the Integer
as it appears literally at the type-level.
This is different from normal show
for Integer
, which shows
the term-level value.
shows
0 (fromPrelude
8) "z" == "8z"showsPrecTypeLit
0 (fromPrelude
8) "z" == "P 8z"
Types ⇔ Terms
class KnownInteger (i :: Integer) where Source #
This class gives the integer associated with a type-level integer. There are instances of the class for every integer.
integerSing :: SInteger i Source #
Instances
KnownNat x => KnownInteger (N x) Source # | Negative numbers and zero. |
Defined in KindInteger integerSing :: SInteger (N x) Source # | |
KnownNat x => KnownInteger (P x) Source # | Positive numbers and zero. |
Defined in KindInteger integerSing :: SInteger (P x) Source # |
integerVal :: forall i proxy. KnownInteger i => proxy i -> Integer Source #
data SomeInteger Source #
This type represents unknown type-level Integer
.
forall n.KnownInteger n => SomeInteger (Proxy n) |
Instances
Read SomeInteger Source # | |
Defined in KindInteger readsPrec :: Int -> ReadS SomeInteger # readList :: ReadS [SomeInteger] # readPrec :: ReadPrec SomeInteger # readListPrec :: ReadPrec [SomeInteger] # | |
Show SomeInteger Source # | |
Defined in KindInteger showsPrec :: Int -> SomeInteger -> ShowS # show :: SomeInteger -> String # showList :: [SomeInteger] -> ShowS # | |
Eq SomeInteger Source # | |
Defined in KindInteger (==) :: SomeInteger -> SomeInteger -> Bool # (/=) :: SomeInteger -> SomeInteger -> Bool # | |
Ord SomeInteger Source # | |
Defined in KindInteger compare :: SomeInteger -> SomeInteger -> Ordering # (<) :: SomeInteger -> SomeInteger -> Bool # (<=) :: SomeInteger -> SomeInteger -> Bool # (>) :: SomeInteger -> SomeInteger -> Bool # (>=) :: SomeInteger -> SomeInteger -> Bool # max :: SomeInteger -> SomeInteger -> SomeInteger # min :: SomeInteger -> SomeInteger -> SomeInteger # |
someIntegerVal :: Integer -> SomeInteger Source #
sameInteger :: forall a b proxy1 proxy2. (KnownInteger a, KnownInteger b) => proxy1 a -> proxy2 b -> Maybe (a :~: b) Source #
Singletons
data SInteger (i :: Integer) Source #
Singleton type for a type-level Integer
i
.
Instances
TestCoercion SInteger Source # | |
Defined in KindInteger | |
TestEquality SInteger Source # | |
Defined in KindInteger | |
Show (SInteger i) Source # | |
pattern SInteger :: forall i. () => KnownInteger i => SInteger i Source #
A explicitly bidirectional pattern synonym relating an SInteger
to a
KnownInteger
constraint.
As an expression: Constructs an explicit
value from an
implicit SInteger
i
constraint:KnownInteger
i
SInteger
@i ::KnownInteger
i =>SInteger
i
As a pattern: Matches on an explicit
value bringing
an implicit SInteger
i
constraint into scope:KnownInteger
i
f :: SInteger
i -> ..
f SInteger = {- SInteger i in scope -}
fromSInteger :: SInteger i -> Integer Source #
withSomeSInteger :: forall rep (r :: TYPE rep). Integer -> (forall n. SInteger n -> r) -> r Source #
withKnownInteger :: forall i rep (r :: TYPE rep). SInteger i -> (KnownInteger i => r) -> r Source #
Convert an explicit
value into an implicit
SInteger
i
constraint.KnownInteger
i
Arithmethic
type (+) (a :: Integer) (b :: Integer) = Add_ (Normalize a) (Normalize b) :: Integer infixl 6 Source #
Addition of type-level Integer
s.
type * (a :: Integer) (b :: Integer) = Mul_ (Normalize a) (Normalize b) :: Integer infixl 7 Source #
Multiplication of type-level Integer
s.
type (^) (a :: Integer) (b :: Integer) = Pow_ (Normalize a) (Normalize b) :: Integer infixr 8 Source #
type (-) (a :: Integer) (b :: Integer) = a + Negate b :: Integer infixl 6 Source #
Subtraction of type-level Integer
s.
type Odd (x :: Integer) = Mod (Abs x) 2 ==? 1 :: Bool Source #
Whether a type-level Natural
is odd. Zero is not considered odd.
type Even (x :: Integer) = Mod (Abs x) 2 ==? 0 :: Bool Source #
Whether a type-level Natural
is even. Zero is considered even.
Division
type Div (r :: Round) (a :: Integer) (b :: Integer) = Div_ r (Normalize a) (Normalize b) :: Integer infixl 7 Source #
type Rem (r :: Round) (a :: Integer) (b :: Integer) = a - (b * Div r a b) :: Integer infixl 7 Source #
type DivRem (r :: Round) (a :: Integer) (b :: Integer) = '(Div r a b, Rem r a b) :: (Integer, Integer) Source #
RoundUp | Round up towards positive infinity. |
RoundDown | Round down towards negative infinity. Also known as Prelude's
|
RoundZero | Round towards zero. Also known as Prelude's |
RoundAway | Round away from zero. |
RoundHalfUp | Round towards the closest integer. If halfway between two integers, round up towards positive infinity. |
RoundHalfDown | Round towards the closest integer. If halfway between two integers, round down towards negative infinity. |
RoundHalfZero | Round towards the closest integer. If halfway between two integers, round towards zero. |
RoundHalfAway | Round towards the closest integer. If halfway between two integers, round away from zero. |
RoundHalfEven | Round towards the closest integer. If halfway between two integers,
round towards the closest even integer. Also known as Prelude's
|
RoundHalfOdd | Round towards the closest integer. If halfway between two integers, round towards the closest odd integer. |
Term-level
Comparisons
type CmpInteger (a :: Integer) (b :: Integer) = CmpInteger_ (Normalize a) (Normalize b) :: Ordering Source #
Comparison of type-level Integer
s, as a function.
cmpInteger :: forall a b proxy1 proxy2. (KnownInteger a, KnownInteger b) => proxy1 a -> proxy2 b -> OrderingI a b Source #
Like sameInteger
, but if the type-level Integer
s aren't equal, this
additionally provides proof of LT
or GT
.
Extra
type (==?) (a :: k) (b :: k) = OrdCond (Compare a b) 'False 'True 'False :: Bool infixr 4 Source #
This should be exported by Data.Type.Ord.
type (==) (a :: k) (b :: k) = (a ==? b) ~ 'True :: Constraint infixr 4 Source #
This should be exported by Data.Type.Ord.
type (/=?) (a :: k) (b :: k) = OrdCond (Compare a b) 'True 'False 'True :: Bool infixr 4 Source #
This should be exported by Data.Type.Ord.
type (/=) (a :: k) (b :: k) = (a /=? b) ~ 'True :: Constraint infixr 4 Source #
This should be exported by Data.Type.Ord.