constraints-0.9.1: Constraint manipulation

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Constraint.Nat

Description

Utilities for working with KnownNat constraints.

This module is only available on GHC 8.0 or later.

Documentation

type family Min :: Nat -> Nat -> Nat where ... Source #

type family Max :: Nat -> Nat -> Nat where ... Source #

type family Lcm :: Nat -> Nat -> Nat where ... Source #

type family Gcd :: Nat -> Nat -> Nat where ... Source #

type Divides n m = n ~ Gcd n m Source #

type family Div :: Nat -> Nat -> Nat where ... Source #

type family Mod :: Nat -> Nat -> Nat where ... Source #

plusNat :: forall n m. (KnownNat n, KnownNat m) :- KnownNat (n + m) Source #

timesNat :: forall n m. (KnownNat n, KnownNat m) :- KnownNat (n * m) Source #

powNat :: forall n m. (KnownNat n, KnownNat m) :- KnownNat (n ^ m) Source #

minNat :: forall n m. (KnownNat n, KnownNat m) :- KnownNat (Min n m) Source #

maxNat :: forall n m. (KnownNat n, KnownNat m) :- KnownNat (Max n m) Source #

gcdNat :: forall n m. (KnownNat n, KnownNat m) :- KnownNat (Gcd n m) Source #

lcmNat :: forall n m. (KnownNat n, KnownNat m) :- KnownNat (Lcm n m) Source #

divNat :: forall n m. (KnownNat n, KnownNat m, 1 <= m) :- KnownNat (Div n m) Source #

modNat :: forall n m. (KnownNat n, KnownNat m, 1 <= m) :- KnownNat (Mod n m) Source #

plusZero :: forall n. Dict ((n + 0) ~ n) Source #

timesZero :: forall n. Dict ((n * 0) ~ 0) Source #

timesOne :: forall n. Dict ((n * 1) ~ n) Source #

powZero :: forall n. Dict ((n ^ 0) ~ 1) Source #

powOne :: forall n. Dict ((n ^ 1) ~ n) Source #

maxZero :: forall n. Dict (Max n 0 ~ n) Source #

minZero :: forall n. Dict (Min n 0 ~ 0) Source #

gcdZero :: forall a. Dict (Gcd 0 a ~ a) Source #

gcdOne :: forall a. Dict (Gcd 1 a ~ 1) Source #

lcmZero :: forall a. Dict (Lcm 0 a ~ 0) Source #

lcmOne :: forall a. Dict (Lcm 1 a ~ a) Source #

plusAssociates :: forall n m o. Dict (((m + n) + o) ~ (m + (n + o))) Source #

timesAssociates :: forall n m o. Dict (((m * n) * o) ~ (m * (n * o))) Source #

minAssociates :: forall n m o. Dict (Min (Min m n) o ~ Min m (Min n o)) Source #

maxAssociates :: forall n m o. Dict (Max (Max m n) o ~ Max m (Max n o)) Source #

gcdAssociates :: forall a b c. Dict (Gcd (Gcd a b) c ~ Gcd a (Gcd b c)) Source #

lcmAssociates :: forall a b c. Dict (Lcm (Lcm a b) c ~ Lcm a (Lcm b c)) Source #

plusCommutes :: forall n m. Dict ((m + n) ~ (n + m)) Source #

timesCommutes :: forall n m. Dict ((m * n) ~ (n * m)) Source #

minCommutes :: forall n m. Dict (Min m n ~ Min n m) Source #

maxCommutes :: forall n m. Dict (Min m n ~ Min n m) Source #

gcdCommutes :: forall a b. Dict (Gcd a b ~ Gcd b a) Source #

lcmCommutes :: forall a b. Dict (Lcm a b ~ Lcm b a) Source #

plusDistributesOverTimes :: forall n m o. Dict ((n * (m + o)) ~ ((n * m) + (n * o))) Source #

timesDistributesOverPow :: forall n m o. Dict ((n ^ (m + o)) ~ ((n ^ m) * (n ^ o))) Source #

timesDistributesOverGcd :: forall n m o. Dict ((n * Gcd m o) ~ Gcd (n * m) (n * o)) Source #

timesDistributesOverLcm :: forall n m o. Dict ((n * Lcm m o) ~ Lcm (n * m) (n * o)) Source #

minDistributesOverPlus :: forall n m o. Dict ((n + Min m o) ~ Min (n + m) (n + o)) Source #

minDistributesOverTimes :: forall n m o. Dict ((n * Min m o) ~ Min (n * m) (n * o)) Source #

minDistributesOverPow1 :: forall n m o. Dict ((Min n m ^ o) ~ Min (n ^ o) (m ^ o)) Source #

minDistributesOverPow2 :: forall n m o. Dict ((n ^ Min m o) ~ Min (n ^ m) (n ^ o)) Source #

minDistributesOverMax :: forall n m o. Dict (Max n (Min m o) ~ Min (Max n m) (Max n o)) Source #

maxDistributesOverPlus :: forall n m o. Dict ((n + Max m o) ~ Max (n + m) (n + o)) Source #

maxDistributesOverTimes :: forall n m o. Dict ((n * Max m o) ~ Max (n * m) (n * o)) Source #

maxDistributesOverPow1 :: forall n m o. Dict ((Max n m ^ o) ~ Max (n ^ o) (m ^ o)) Source #

maxDistributesOverPow2 :: forall n m o. Dict ((n ^ Max m o) ~ Max (n ^ m) (n ^ o)) Source #

maxDistributesOverMin :: forall n m o. Dict (Min n (Max m o) ~ Max (Min n m) (Min n o)) Source #

gcdDistributesOverLcm :: forall a b c. Dict (Gcd (Lcm a b) c ~ Lcm (Gcd a c) (Gcd b c)) Source #

lcmDistributesOverGcd :: forall a b c. Dict (Lcm (Gcd a b) c ~ Gcd (Lcm a c) (Lcm b c)) Source #

minIsIdempotent :: forall n. Dict (Min n n ~ n) Source #

maxIsIdempotent :: forall n. Dict (Max n n ~ n) Source #

lcmIsIdempotent :: forall n. Dict (Lcm n n ~ n) Source #

gcdIsIdempotent :: forall n. Dict (Gcd n n ~ n) Source #

plusIsCancellative :: forall n m o. ((n + m) ~ (n + o)) :- (m ~ o) Source #

timesIsCancellative :: forall n m o. (1 <= n, (n * m) ~ (n * o)) :- (m ~ o) Source #

dividesPlus :: (Divides a b, Divides a c) :- Divides a (b + c) Source #

dividesTimes :: (Divides a b, Divides a c) :- Divides a (b * c) Source #

dividesMin :: (Divides a b, Divides a c) :- Divides a (Min b c) Source #

dividesMax :: (Divides a b, Divides a c) :- Divides a (Max b c) Source #

dividesPow :: (1 <= n, Divides a b) :- Divides a (b ^ n) Source #

dividesGcd :: forall a b c. (Divides a b, Divides a c) :- Divides a (Gcd b c) Source #

dividesLcm :: forall a b c. (Divides a c, Divides b c) :- Divides (Lcm a b) c Source #

plusMonotone1 :: forall a b c. (a <= b) :- ((a + c) <= (b + c)) Source #

plusMonotone2 :: forall a b c. (b <= c) :- ((a + b) <= (a + c)) Source #

timesMonotone1 :: forall a b c. (a <= b) :- ((a * c) <= (b * c)) Source #

timesMonotone2 :: forall a b c. (b <= c) :- ((a * b) <= (a * c)) Source #

powMonotone1 :: forall a b c. (a <= b) :- ((a ^ c) <= (b ^ c)) Source #

powMonotone2 :: forall a b c. (b <= c) :- ((a ^ b) <= (a ^ c)) Source #

minMonotone1 :: forall a b c. (a <= b) :- (Min a c <= Min b c) Source #

minMonotone2 :: forall a b c. (b <= c) :- (Min a b <= Min a c) Source #

maxMonotone1 :: forall a b c. (a <= b) :- (Max a c <= Max b c) Source #

maxMonotone2 :: forall a b c. (b <= c) :- (Max a b <= Max a c) Source #

divMonotone1 :: forall a b c. (a <= b) :- (Div a c <= Div b c) Source #

divMonotone2 :: forall a b c. (b <= c) :- (Div a c <= Div a b) Source #

euclideanNat :: (1 <= c) :- (a ~ ((c * Div a c) + Mod a c)) Source #

plusMod :: forall a b c. (1 <= c) :- (Mod (a + b) c ~ Mod (Mod a c + Mod b c) c) Source #

timesMod :: forall a b c. (1 <= c) :- (Mod (a * b) c ~ Mod (Mod a c * Mod b c) c) Source #

modBound :: forall m n. (1 <= n) :- (Mod m n <= n) Source #

dividesDef :: forall a b. Divides a b :- ((a * Div b a) ~ a) Source #

timesDiv :: forall a b. Dict ((a * Div b a) <= a) Source #

eqLe :: (a ~ b) :- (a <= b) Source #

leEq :: forall a b. (a <= b, b <= a) :- (a ~ b) Source #

leId :: forall a. Dict (a <= a) Source #

leTrans :: forall a b c. (b <= c, a <= b) :- (a <= c) Source #

leZero :: forall a. (a <= 0) :- (a ~ 0) Source #

zeroLe :: forall a. Dict (0 <= a) Source #