closed-0.2.1.0: Integers bounded by a closed interval
Safe HaskellNone
LanguageHaskell2010

Closed

Synopsis

Documentation

data Endpoint Source #

Describe whether the endpoint of a Bounds includes or excludes its argument

Constructors

Inclusive Nat

Endpoint includes its argument

Exclusive Nat

Endpoint excludes its argument

data Closed (a :: Nat) (b :: Nat) Source #

Instances

Instances details
(KnownNat a, KnownNat b, a <= b) => Arbitrary (Closed a b) Source # 
Instance details

Defined in Closed.Internal

Methods

arbitrary :: Gen (Closed a b) #

shrink :: Closed a b -> [Closed a b] #

(KnownNat a, KnownNat b, a <= b) => FromJSON (Closed a b) Source # 
Instance details

Defined in Closed.Internal

ToJSON (Closed a b) Source # 
Instance details

Defined in Closed.Internal

Methods

toJSON :: Closed a b -> Value #

toEncoding :: Closed a b -> Encoding #

toJSONList :: [Closed a b] -> Value #

toEncodingList :: [Closed a b] -> Encoding #

omitField :: Closed a b -> Bool #

(KnownNat a, KnownNat b, a <= b) => Bounded (Closed a b) Source #

Generate the lowest and highest inhabitant of a given Closed type

Instance details

Defined in Closed.Internal

Methods

minBound :: Closed a b #

maxBound :: Closed a b #

(KnownNat a, KnownNat b, a <= b) => Enum (Closed a b) Source #

Enumerate values in the range of a given Closed type

Instance details

Defined in Closed.Internal

Methods

succ :: Closed a b -> Closed a b #

pred :: Closed a b -> Closed a b #

toEnum :: Int -> Closed a b #

fromEnum :: Closed a b -> Int #

enumFrom :: Closed a b -> [Closed a b] #

enumFromThen :: Closed a b -> Closed a b -> [Closed a b] #

enumFromTo :: Closed a b -> Closed a b -> [Closed a b] #

enumFromThenTo :: Closed a b -> Closed a b -> Closed a b -> [Closed a b] #

Generic (Closed a b) Source # 
Instance details

Defined in Closed.Internal

Associated Types

type Rep (Closed a b) 
Instance details

Defined in Closed.Internal

type Rep (Closed a b) = D1 ('MetaData "Closed" "Closed.Internal" "closed-0.2.1.0-BFqwATr5qeUJhJLf5NbIcW" 'True) (C1 ('MetaCons "Closed" 'PrefixI 'True) (S1 ('MetaSel ('Just "getClosed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

Methods

from :: Closed a b -> Rep (Closed a b) x #

to :: Rep (Closed a b) x -> Closed a b #

(KnownNat a, KnownNat b, a <= b) => Num (Closed a b) Source #

Bounded arithmetic, e.g. maxBound + 1 == maxBound

Instance details

Defined in Closed.Internal

Methods

(+) :: Closed a b -> Closed a b -> Closed a b #

(-) :: Closed a b -> Closed a b -> Closed a b #

(*) :: Closed a b -> Closed a b -> Closed a b #

negate :: Closed a b -> Closed a b #

abs :: Closed a b -> Closed a b #

signum :: Closed a b -> Closed a b #

fromInteger :: Integer -> Closed a b #

(KnownNat a, KnownNat b, a <= b) => Read (Closed a b) Source # 
Instance details

Defined in Closed.Internal

(KnownNat a, KnownNat b, a <= b) => Integral (Closed a b) Source # 
Instance details

Defined in Closed.Internal

Methods

quot :: Closed a b -> Closed a b -> Closed a b #

rem :: Closed a b -> Closed a b -> Closed a b #

div :: Closed a b -> Closed a b -> Closed a b #

mod :: Closed a b -> Closed a b -> Closed a b #

quotRem :: Closed a b -> Closed a b -> (Closed a b, Closed a b) #

divMod :: Closed a b -> Closed a b -> (Closed a b, Closed a b) #

toInteger :: Closed a b -> Integer #

(KnownNat a, KnownNat b, a <= b) => Real (Closed a b) Source # 
Instance details

Defined in Closed.Internal

Methods

toRational :: Closed a b -> Rational #

Show (Closed a b) Source # 
Instance details

Defined in Closed.Internal

Methods

showsPrec :: Int -> Closed a b -> ShowS #

show :: Closed a b -> String #

showList :: [Closed a b] -> ShowS #

(KnownNat a, KnownNat b, a <= b) => FromField (Closed a b) Source # 
Instance details

Defined in Closed.Internal

Methods

parseField :: Field -> Parser (Closed a b) #

ToField (Closed a b) Source # 
Instance details

Defined in Closed.Internal

Methods

toField :: Closed a b -> Field #

NFData (Closed a b) Source # 
Instance details

Defined in Closed.Internal

Methods

rnf :: Closed a b -> () #

Eq (Closed a b) Source #

Test equality on Closed values in the same range

Instance details

Defined in Closed.Internal

Methods

(==) :: Closed a b -> Closed a b -> Bool #

(/=) :: Closed a b -> Closed a b -> Bool #

Ord (Closed a b) Source #

Compare Closed values in the same range

Instance details

Defined in Closed.Internal

Methods

compare :: Closed a b -> Closed a b -> Ordering #

(<) :: Closed a b -> Closed a b -> Bool #

(<=) :: Closed a b -> Closed a b -> Bool #

(>) :: Closed a b -> Closed a b -> Bool #

(>=) :: Closed a b -> Closed a b -> Bool #

max :: Closed a b -> Closed a b -> Closed a b #

min :: Closed a b -> Closed a b -> Closed a b #

Hashable (Closed a b) Source # 
Instance details

Defined in Closed.Internal

Methods

hashWithSalt :: Int -> Closed a b -> Int #

hash :: Closed a b -> Int #

(KnownNat a, KnownNat b, a <= b) => PersistField (Closed a b) Source # 
Instance details

Defined in Closed.Internal

(KnownNat a, KnownNat b, a <= b) => PersistFieldSql (Closed a b) Source # 
Instance details

Defined in Closed.Internal

Methods

sqlType :: Proxy (Closed a b) -> SqlType #

(KnownNat a, KnownNat b, a <= b) => Random (Closed a b) Source # 
Instance details

Defined in Closed.Internal

Methods

randomR :: RandomGen g => (Closed a b, Closed a b) -> g -> (Closed a b, g) #

random :: RandomGen g => g -> (Closed a b, g) #

randomRs :: RandomGen g => (Closed a b, Closed a b) -> g -> [Closed a b] #

randoms :: RandomGen g => g -> [Closed a b] #

type Rep (Closed a b) Source # 
Instance details

Defined in Closed.Internal

type Rep (Closed a b) = D1 ('MetaData "Closed" "Closed.Internal" "closed-0.2.1.0-BFqwATr5qeUJhJLf5NbIcW" 'True) (C1 ('MetaCons "Closed" 'PrefixI 'True) (S1 ('MetaSel ('Just "getClosed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

type family Bounds (lhs :: Endpoint) (rhs :: Endpoint) where ... Source #

Syntactic sugar to express open and half-open intervals using the Closed type

Equations

Bounds ('Inclusive a) ('Inclusive b) = Closed a b 
Bounds ('Inclusive a) ('Exclusive b) = Closed a (b - 1) 
Bounds ('Exclusive a) ('Inclusive b) = Closed (a + 1) b 
Bounds ('Exclusive a) ('Exclusive b) = Closed (a + 1) (b - 1) 

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 (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b, a <= b) => Integer -> Maybe (Closed a b) Source #

Safely create a Closed value using the specified argument

unsafeClosed :: forall (a :: Nat) (b :: Nat). (HasCallStack, KnownNat a, KnownNat b, a <= b) => Integer -> Closed a b Source #

Create a Closed value throwing an error if the argument is not in range

clamp :: forall (a :: Nat) (b :: Nat) i. (Integral i, KnownNat a, KnownNat b, a <= b) => i -> Closed a b Source #

Clamp an Integral in the range constrained by a Closed interval

lowerBound :: forall (a :: Nat) (b :: Nat). Closed a b -> Proxy a Source #

Proxy for the lower bound of a Closed value

upperBound :: forall (a :: Nat) (b :: Nat). Closed a b -> Proxy b Source #

Proxy for the upper bound of a Closed value

equals :: forall (a :: Nat) (b :: Nat) (o :: Nat) (p :: Nat). Closed a b -> Closed o p -> Bool infix 4 Source #

Test two different types of Closed values for equality.

cmp :: forall (a :: Nat) (b :: Nat) (o :: Nat) (p :: Nat). Closed a b -> Closed o p -> Ordering Source #

Compare two different types of Closed values

natToClosed :: forall (a :: Nat) (b :: Nat) (x :: Nat) proxy. (KnownNat a, KnownNat b, KnownNat x, a <= x, x <= b) => proxy x -> Closed a b Source #

Convert a type-level literal into a Closed value

weakenUpper :: forall (k :: Nat) (a :: Nat) (b :: Nat). (a <= b, b <= k) => Closed a b -> Closed a k Source #

Add inhabitants at the end

weakenLower :: forall (k :: Nat) (a :: Nat) (b :: Nat). (a <= b, k <= a) => Closed a b -> Closed k b Source #

Add inhabitants at the beginning

strengthenUpper :: forall (k :: Nat) (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b, KnownNat k, a <= b, a <= k, k <= b) => Closed a b -> Maybe (Closed a k) Source #

Remove inhabitants from the end. Returns Nothing if the input was removed

strengthenLower :: forall (k :: Nat) (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b, KnownNat k, a <= b, a <= k, k <= b) => Closed a b -> Maybe (Closed k b) Source #

Remove inhabitants from the beginning. Returns Nothing if the input was removed

add :: forall (a :: Nat) (b :: Nat) (o :: Nat) (p :: Nat) (n :: Natural) (m :: Natural). Closed a b -> Closed o p -> Closed (n + o) (m + p) Source #

Add two different types of Closed values

sub :: forall (a :: Nat) (b :: Nat) (o :: Nat) (p :: Nat) (n :: Natural) (m :: Natural). Closed a b -> Closed o p -> Either (Closed (o - n) (p - m)) (Closed (n - o) (m - p)) Source #

Subtract two different types of Closed values Returns Left for negative results, and Right for positive results.

multiply :: forall (a :: Nat) (b :: Nat) (o :: Nat) (p :: Nat). Closed a b -> Closed o p -> Closed (a * o) (b * p) Source #

Multiply two different types of Closed values

isValidClosed :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Closed a b -> Bool Source #

Verifies that a given Closed value is valid. Should always return True unles you bring the Closed.Internal.Closed constructor into scope, or use unsafeCoerce or other nasty hacks