Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type OutOfRangeMsg min maxp1 a n = (('Text "Literal out of range " :<>: ShowRange min maxp1) :<>: 'Text ":") :$$: ('Text " " :<>: ShowTypedNum a n)
- type ShowTypedNum a n = (ShowNum n :<>: 'Text " :: ") :<>: 'ShowType a
- type ShowRange min maxp1 = ((('Text "(" :<>: ShowNum min) :<>: 'Text "..") :<>: ShowNum (maxp1 - 'Pos 1)) :<>: 'Text ")"
- class OutOfRangeErr (min :: Integer) (maxp1 :: Integer) (a :: Type) (n :: Integer)
- class n < maxp1 => CheckLessThanMaxBound (msg :: ErrorMessage) (maxp1 :: Integer) (a :: Type) (n :: Integer)
- class n >= min => CheckAtLeastMinBound (msg :: ErrorMessage) (min :: Integer) (a :: Type) (n :: Integer)
- class a ~ b => AssertEq (c :: Constraint) a b
- type AssertNotApart msg a b = AssertNotApart_ msg (Eql a b) a b
- type family ShowNum (n :: Integer) where ...
- class a ~ b => AssertNotApart_ (msg :: ErrorMessage) eq a b
- type family Eql a b :: Bool where ...
- class a ~ b => FailedToProveEq (err :: Constraint) a b
Bounds Checks
Error Messages
type OutOfRangeMsg min maxp1 a n = (('Text "Literal out of range " :<>: ShowRange min maxp1) :<>: 'Text ":") :$$: ('Text " " :<>: ShowTypedNum a n) Source #
Error Message Utilities
type ShowRange min maxp1 = ((('Text "(" :<>: ShowNum min) :<>: 'Text "..") :<>: ShowNum (maxp1 - 'Pos 1)) :<>: 'Text ")" Source #
Error Constraints
class OutOfRangeErr (min :: Integer) (maxp1 :: Integer) (a :: Type) (n :: Integer) Source #
Instances
(TypeError (OutOfRangeMsg min maxp1 a n) :: Constraint) => OutOfRangeErr min maxp1 a n Source # | |
Defined in DependentLiterals.Bounds |
Inequality Assertions
class n < maxp1 => CheckLessThanMaxBound (msg :: ErrorMessage) (maxp1 :: Integer) (a :: Type) (n :: Integer) Source #
Instances
AssertNotApart msg (Cmp n maxp1) 'LT => CheckLessThanMaxBound msg maxp1 a n Source # | |
Defined in DependentLiterals.Bounds |
class n >= min => CheckAtLeastMinBound (msg :: ErrorMessage) (min :: Integer) (a :: Type) (n :: Integer) Source #
Instances
AssertNotApart msg (n >=? min) 'True => CheckAtLeastMinBound msg min a n Source # | |
Defined in DependentLiterals.Bounds |
class a ~ b => AssertEq (c :: Constraint) a b Source #
Instances
AssertEq c (a :: k) (a :: k) Source # | |
Defined in DependentLiterals.Bounds |
type AssertNotApart msg a b = AssertNotApart_ msg (Eql a b) a b Source #
Implementation Details
class a ~ b => AssertNotApart_ (msg :: ErrorMessage) eq a b Source #
Instances
FailedToProveEq (TypeError msg :: Constraint) a b => AssertNotApart_ msg 'False (a :: k) (b :: k) Source # | |
Defined in DependentLiterals.Bounds | |
a ~ b => AssertNotApart_ msg 'True (a :: k) (b :: k) Source # | |
Defined in DependentLiterals.Bounds |
class a ~ b => FailedToProveEq (err :: Constraint) a b Source #
If you tried to prove a constraint and failed, and want to issue a custom error message for it explicitly, write something like this.
Given "class _c => FailedToProveC (err :: Constraint) ...",
"FailedToProveC (TypeError ...)" is a constraint that pretends to prove c
but instead throws a type error.