Copyright | (c) Justin Le 2024 |
---|---|
License | MIT |
Maintainer | justin@jle.im |
Stability | unstable |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module provides the ability to refine given KnownNat
instances
using GHC.TypeLits's comparison API, and also the ability to prove
inequalities and upper/lower limits.
If a library function requires 1
constraint, but only
<=
n
is available:KnownNat
n
foo :: (KnownNat n, 1<=
n) =>Proxy
n -> Int bar :: KnownNat n => Proxy n -> Int bar n = case (Proxy :: Proxy 1)%<=?
n ofLE
Refl
-> foo nNLE
_ -> 0
foo
requires that 1 <= n
, but bar
has to handle all cases of n
.
%<=?
lets you compare the KnownNat
s in two Proxy
s and returns
a :<=?
, which has two constructors, LE
and NLE
.
If you pattern match on the result, in the LE
branch, the constraint
1 <= n
will be satisfied according to GHC, so bar
can safely call
foo
, and GHC will recognize that 1 <= n
.
In the NLE
branch, the constraint that 1 > n
is satisfied, so any
functions that require that constraint would be callable.
For convenience, isLE
and isNLE
are also offered:
bar :: KnownNat n => Proxy n -> Int bar n = caseisLE
(Proxy :: Proxy 1) n ofJust
Refl -> foo nNothing
-> 0
Similarly, if a library function requires something involving CmpNat
,
you can use cmpNat
and the SCmpNat
type:
foo1 :: (KnownNat n,CmpNat
5 n ~ LT) => Proxy n -> Int foo2 :: (KnownNat n, CmpNat 5 n ~ GT) => Proxy n -> Int bar :: KnownNat n => Proxy n -> Int bar n = casecmpNat
(Proxy :: Proxy 5) n ofCLT
Refl -> foo1 nCEQ
Refl -> 0CGT
Refl -> foo2 n
You can use the Refl
that cmpNat
gives you with flipCmpNat
and
cmpNatLE
to "flip" the inequality or turn it into something compatible
with <=?
(useful for when you have to work with libraries that mix the
two methods) or cmpNatEq
and eqCmpNat
to get to/from witnesses for
equality of the two Nat
s.
This module is useful for helping bridge between libraries that use
different Nat
-based comparison systems in their type constraints.
Synopsis
- data (:<=?) :: Nat -> Nat -> Type where
- (%<=?) :: (KnownNat m, KnownNat n) => p m -> q n -> m :<=? n
- isLE :: (KnownNat m, KnownNat n) => p m -> q n -> Maybe ((m <=? n) :~: 'True)
- isNLE :: (KnownNat m, KnownNat n) => p m -> q n -> Maybe ((m <=? n) :~: 'False)
- data SCmpNat :: Nat -> Nat -> Type where
- cmpNat :: (KnownNat m, KnownNat n) => p m -> q n -> SCmpNat m n
- flipCmpNat :: SCmpNat m n -> SCmpNat n m
- cmpNatEq :: (CmpNat m n :~: 'EQ) -> m :~: n
- eqCmpNat :: (m :~: n) -> CmpNat m n :~: 'EQ
- reflCmpNat :: (m :~: n) -> SCmpNat m n
- cmpNatLE :: SCmpNat m n -> m :<=? n
- cmpNatGOrdering :: SCmpNat n m -> GOrdering n m
<=
and <=?
data (:<=?) :: Nat -> Nat -> Type where Source #
Two possible ordered relationships between two natural numbers.
(%<=?) :: (KnownNat m, KnownNat n) => p m -> q n -> m :<=? n Source #
Compare m
and n
, classifying their relationship into some
constructor of :<=?
.
Convenience functions
CmpNat
data SCmpNat :: Nat -> Nat -> Type where Source #
Three possible ordered relationships between two natural numbers.
cmpNat :: (KnownNat m, KnownNat n) => p m -> q n -> SCmpNat m n Source #
Compare m
and n
, classifying their relationship into some
constructor of SCmpNat
.
Manipulating witnesses
flipCmpNat :: SCmpNat m n -> SCmpNat n m Source #
Flip an inequality.