Safe Haskell | None |
---|---|
Language | Haskell2010 |
Closed
Synopsis
- data Endpoint
- data Closed (n :: Nat) (m :: Nat)
- type family Bounds (lhs :: Endpoint) (rhs :: Endpoint) where ...
- type Single (n :: Nat) = Bounds ('Inclusive n) ('Inclusive n)
- type FiniteNat (rhs :: Endpoint) = Bounds ('Inclusive 0) rhs
- closed :: forall (n :: Nat) (m :: Nat). (n <= m, KnownNat n, KnownNat m) => Integer -> Maybe (Closed n m)
- unsafeClosed :: forall (n :: Nat) (m :: Nat). (HasCallStack, n <= m, KnownNat n, KnownNat m) => Integer -> Closed n m
- clamp :: forall (n :: Nat) (m :: Nat) a. (KnownNat n, KnownNat m, n <= m, Integral a) => a -> Closed n m
- getClosed :: Closed n m -> Integer
- lowerBound :: forall (n :: Nat) (m :: Nat). Closed n m -> Proxy n
- upperBound :: forall (n :: Nat) (m :: Nat). Closed n m -> Proxy m
- equals :: forall (n :: Nat) (m :: Nat) (o :: Nat) (p :: Nat). Closed n m -> Closed o p -> Bool
- cmp :: forall (n :: Nat) (m :: Nat) (o :: Nat) (p :: Nat). Closed n m -> Closed o p -> Ordering
- natToClosed :: forall (n :: Nat) (m :: Nat) (x :: Nat) proxy. (n <= x, x <= m, KnownNat x, KnownNat n, KnownNat m) => proxy x -> Closed n m
- weakenUpper :: forall (k :: Nat) (n :: Nat) (m :: Nat). (n <= m, m <= k) => Closed n m -> Closed n k
- weakenLower :: forall (k :: Nat) (n :: Nat) (m :: Nat). (n <= m, k <= n) => Closed n m -> Closed k m
- strengthenUpper :: forall (k :: Nat) (n :: Nat) (m :: Nat). (KnownNat n, KnownNat m, KnownNat k, n <= m, n <= k, k <= m) => Closed n m -> Maybe (Closed n k)
- strengthenLower :: forall (k :: Nat) (n :: Nat) (m :: Nat). (KnownNat n, KnownNat m, KnownNat k, n <= m, n <= k, k <= m) => Closed n m -> Maybe (Closed k m)
- add :: forall (n :: Nat) (m :: Nat) (o :: Nat) (p :: Nat). Closed n m -> Closed o p -> Closed (n + o) (m + p)
- sub :: forall (n :: Nat) (m :: Nat) (o :: Nat) (p :: Nat). Closed n m -> Closed o p -> Either (Closed (o - n) (p - m)) (Closed (n - o) (m - p))
- multiply :: forall (n :: Nat) (m :: Nat) (o :: Nat) (p :: Nat). Closed n m -> Closed o p -> Closed (n * o) (m * p)
- isValidClosed :: forall (n :: Nat) (m :: Nat). (KnownNat n, KnownNat m) => Closed n m -> Bool
Documentation
Describe whether the endpoint of a Bounds
includes
or excludes its argument
data Closed (n :: Nat) (m :: Nat) Source #
Instances
type family Bounds (lhs :: Endpoint) (rhs :: Endpoint) where ... Source #
Syntactic sugar to express open and half-open intervals using
the Closed
type
type Single (n :: Nat) = Bounds ('Inclusive n) ('Inclusive n) Source #
Syntactic sugar to express a value that has only one non-bottom
inhabitant using the Closed
type
type FiniteNat (rhs :: Endpoint) = Bounds ('Inclusive 0) rhs Source #
Syntactic sugar to express a value whose lower bound is zero
closed :: forall (n :: Nat) (m :: Nat). (n <= m, KnownNat n, KnownNat m) => Integer -> Maybe (Closed n m) Source #
Safely create a Closed
value using the specified argument
unsafeClosed :: forall (n :: Nat) (m :: Nat). (HasCallStack, n <= m, KnownNat n, KnownNat m) => Integer -> Closed n m Source #
Create a Closed
value throwing an error if the argument is not in range
clamp :: forall (n :: Nat) (m :: Nat) a. (KnownNat n, KnownNat m, n <= m, Integral a) => a -> Closed n m Source #
lowerBound :: forall (n :: Nat) (m :: Nat). Closed n m -> Proxy n Source #
Proxy for the lower bound of a Closed
value
upperBound :: forall (n :: Nat) (m :: Nat). Closed n m -> Proxy m Source #
Proxy for the upper bound of a Closed
value
equals :: forall (n :: Nat) (m :: Nat) (o :: Nat) (p :: Nat). Closed n m -> Closed o p -> Bool infix 4 Source #
Test two different types of Closed
values for equality.
cmp :: forall (n :: Nat) (m :: Nat) (o :: Nat) (p :: Nat). Closed n m -> Closed o p -> Ordering Source #
Compare two different types of Closed
values
natToClosed :: forall (n :: Nat) (m :: Nat) (x :: Nat) proxy. (n <= x, x <= m, KnownNat x, KnownNat n, KnownNat m) => proxy x -> Closed n m Source #
Convert a type-level literal into a Closed
value
weakenUpper :: forall (k :: Nat) (n :: Nat) (m :: Nat). (n <= m, m <= k) => Closed n m -> Closed n k Source #
Add inhabitants at the end
weakenLower :: forall (k :: Nat) (n :: Nat) (m :: Nat). (n <= m, k <= n) => Closed n m -> Closed k m Source #
Add inhabitants at the beginning
strengthenUpper :: forall (k :: Nat) (n :: Nat) (m :: Nat). (KnownNat n, KnownNat m, KnownNat k, n <= m, n <= k, k <= m) => Closed n m -> Maybe (Closed n k) Source #
Remove inhabitants from the end. Returns Nothing
if the input was removed
strengthenLower :: forall (k :: Nat) (n :: Nat) (m :: Nat). (KnownNat n, KnownNat m, KnownNat k, n <= m, n <= k, k <= m) => Closed n m -> Maybe (Closed k m) Source #
Remove inhabitants from the beginning. Returns Nothing
if the input was removed
add :: forall (n :: Nat) (m :: Nat) (o :: Nat) (p :: Nat). Closed n m -> Closed o p -> Closed (n + o) (m + p) Source #
Add two different types of Closed
values
sub :: forall (n :: Nat) (m :: Nat) (o :: Nat) (p :: Nat). Closed n m -> Closed o p -> Either (Closed (o - n) (p - m)) (Closed (n - o) (m - p)) Source #