| Copyright | (c) Justin Le 2016 |
|---|---|
| License | MIT |
| Maintainer | justin@jle.im |
| Stability | unstable |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
GHC.TypeLits.Witnesses
Description
Deprecated: Use the singletons package instead
This module provides witnesses for instances that result from the
various arithmetic operations on GHC TypeLits Nat types. In general,
if you have , GHC can't infer KnownNat n; and if
you have KnownNat (n + 1), as well, GHC can't infer KnownNat m.KnownNat (n + m)
This can be extremely annoying when dealing with libraries and
applications where one regularly adds and subtracts type-level nats and
expects KnownNat instances to follow. For example, vector
concatenation of length-encoded vector types can be:
concat :: (KnownNatn,KnownNatm) => Vector n a -> Vector m a -> Vector (n + m) a
But, now n + m does not have a KnownNat instance...which makes
operations like this extremely less useful!
At the highest level, this module can be used with withNatOp:
getDoubled :: forall n.KnownNatn =>Proxyn ->IntegergetDoubled p =withNatOp(%*) p (Proxy::Proxy2) $ natVal (Proxy::Proxy(n * 2))
With the final argument of withNatOp, you can provide a result
computed in an environment where n * 2 is indeed an instance of
KnownNat.
For more complex usage, you can directly manipulate witnesses and then use them via pattern matching:
let pn =natDict(Proxy::Proxyn) p1 =natDict(Proxy::Proxy1) p2 =natDict(Proxy::Proxy2) in case pn%*p2%+p1 ofDict->natVal(Proxy::Proxy(n * 2 + 1))
In the branch of the case statement, n * 2 + 1 indeed has a KnownNat
instance.
Note that the operators have appropriate fixities to mimic value-level arithmetic operations.
WARNING: %- and entailSub are is implemented in a way such
that negative KnownNats are produced without any errors. The
production of witnesses and entailments will hold, but be aware that any
functions that rely on KnownNat instances to be non-negative can
potentially break.
- withNatOp :: (KnownNat n, KnownNat m) => (Dict (KnownNat n) -> Dict (KnownNat m) -> Dict (KnownNat q)) -> p n -> p m -> (KnownNat q => r) -> r
- natDict :: KnownNat n => p n -> Dict (KnownNat n)
- dictNatVal :: forall n. Dict (KnownNat n) -> Integer
- (%+) :: forall n m. Dict (KnownNat n) -> Dict (KnownNat m) -> Dict (KnownNat (n + m))
- (%-) :: forall n m. Dict (KnownNat n) -> Dict (KnownNat m) -> Dict (KnownNat (n - m))
- (%*) :: forall n m. Dict (KnownNat n) -> Dict (KnownNat m) -> Dict (KnownNat (n * m))
- (%^) :: forall n m. Dict (KnownNat n) -> Dict (KnownNat m) -> Dict (KnownNat (n ^ m))
- entailAdd :: forall n m. (KnownNat n, KnownNat m) :- KnownNat (n + m)
- entailSub :: forall n m. (KnownNat n, KnownNat m) :- KnownNat (n - m)
- entailMul :: forall n m. (KnownNat n, KnownNat m) :- KnownNat (n * m)
- entailExp :: forall n m. (KnownNat n, KnownNat m) :- KnownNat (n ^ m)
Singletons
All of the functionality in this module can be subsumed by the singletons package, by utilizing:
This module is left in this package as an alternative for those who
might, for some reason, not want to add a singletons dependency to
their project. However, if you do much at the type level, using the
singletons library is much preferred, as it provides a unifed
interface for all of the functionality here, generalized to other kinds
besides Nat.
For all functions in this module, a singletons equivalent is included for help migrating.
In general:
- The singletons type
(or its equivalent,Singn) subsumes bothSNatnandProxyn. You can replace bothDict(KnownNatn)andProxynwithDict(KnownNatn)to move to singletons style.SNatn dictNatValandnatValare both justfromSing.- Replace
%+,%-, and%*with their singletons equivalents,%:+,%:-, and%:*from Data.Singletons.Prelude.Num. Note that the current version of singletons does not have an equivalent for%^. - Use
withKnownNatfrom singletons (or just pattern match onSNat) to get aKnownNatinstance from a, the same way you'd get one from aSNatnDict. - The high-level combinator
withNatOpcan simply be replaced with applying your singleton functions (%+etc.) toSNatvalues, and pattern matching on the result, or usingwithKnownNaton the result.
withNatOp :: (KnownNat n, KnownNat m) => (Dict (KnownNat n) -> Dict (KnownNat m) -> Dict (KnownNat q)) -> p n -> p m -> (KnownNat q => r) -> r Source #
A high-level the interface of this module. Give it one of
the witness-generating operators on KnownNats in this module (%+,
%-, %*, or %^), two Proxys containing the KnownNats to
be modified, and receive an environment where the result of the
operation (applied to the KnownNats) has a KnownNat instance.
For example, with
withNatOp(%+) (Proxy::Proxyn) (Proxy::Proxy1) r
in r, n + 1 has a KnownNat instance:
withNatOp(%+) (Proxy::Proxyn) (Proxy::Proxy1) $natVal(Proxy::Proxy(n + 1)) -- => will return theIntegercorrepsonding to n + 1
Normally, if n is a KnownNat instance, it is not in general
inferrable that n + 1 also has a KnownNat instance. This combinator
makes it so.
For multiple operations on values, this can be chained:
withNatOp(%*) (Proxy::Proxyn) (Proxy::Proxy2) $withNatOp(%+) (Proxy::Proxy(n*2)) (Proxy::Proxy1) $natVal(Proxy::Proxy(n * 2 + 1))
But, at this point, it's easier and simpler to just directly use the operators and pattern match:
let pn =natDict(Proxy::Proxyn) p1 =natDict(Proxy::Proxy1) p2 =natDict(Proxy::Proxy2) in case pn%*p2%+p1 ofDict->natVal(Proxy::Proxy(n * 2 + 1))
(Note that associativity and fixity for the witness-generating operators are set to match that of normal addition and multiplication, etc.)
With singletons, is withNatOp f x y.withKnownNat (f x y)
So, instead of
withNatOp(%+) (Proxy::Proxyn) (Proxy::Proxy1) $natVal(Proxy::Proxy(n + 1))
You can just use
withKnownNat(SNatn) ('SNat1) $natVal(Proxy::Proxy(n + 1))
natVal can of course be replaced with fromSing.
Direct witnesses
Witness generators
(%+) :: forall n m. Dict (KnownNat n) -> Dict (KnownNat m) -> Dict (KnownNat (n + m)) infixl 6 Source #
Given witnesses for and KnownNat n, generates
a witness for KnownNat m.KnownNat (n + m)
Follows proper association and fixity for usage with other similar operators.
With singletons, this is %:+ from Data.Singletons.Prelude.Num.
(%-) :: forall n m. Dict (KnownNat n) -> Dict (KnownNat m) -> Dict (KnownNat (n - m)) infixl 6 Source #
Given witnesses for and KnownNat n, generates
a witness for KnownNat m.KnownNat (n - m)
Note that this is implemented in a way such that negative KnownNats
are produced without any errors.
Follows proper association and fixity for usage with other similar operators.
With singletons, this is %:- from Data.Singletons.Prelude.Num.
(%*) :: forall n m. Dict (KnownNat n) -> Dict (KnownNat m) -> Dict (KnownNat (n * m)) infixl 7 Source #
Given witnesses for and KnownNat n, generates
a witness for KnownNat m.KnownNat (n * m)
Follows proper association and fixity for usage with other similar operators.
With singletons, this is %:* from Data.Singletons.Prelude.Num.
(%^) :: forall n m. Dict (KnownNat n) -> Dict (KnownNat m) -> Dict (KnownNat (n ^ m)) infixr 8 Source #
Entailments
entailAdd :: forall n m. (KnownNat n, KnownNat m) :- KnownNat (n + m) Source #
An entailment for addition of KnownNat instances.