i-0.1: Haskell interval types. Bounds checking.
Safe HaskellSafe-Inferred
LanguageGHC2021

I

Description

I am a Haskell module designed to be imported as follows:

import I (I)
import I qualified

I exist so that you don't have to manually check that a value is within an interval. For example:

I Int (N 5) (P 5)
An Int known to be in the interval [-5, +5].
I Natural 100 'Nothing
A Natural known to be in the interval [100, +infinity).
I Rational ('Just '( 'False, 0 / 1)) ('Just '( 'True, 1 / 2))
A Rational known to be in the interval (0, +0.5].
Synopsis

Interval

data I (x :: Type) (l :: L x) (r :: R x) Source #

A value of type x known to be within the interval determined by the left end l and right end r.

Instances

Instances details
(Known x l r (MinI x l r), Known x l r (MaxI x l r)) => Bounded (I x l r) Source # 
Instance details

Defined in I.Internal

Methods

minBound :: I x l r #

maxBound :: I x l r #

Show x => Show (I x l r) Source # 
Instance details

Defined in I.Internal

Methods

showsPrec :: Int -> I x l r -> ShowS #

show :: I x l r -> String #

showList :: [I x l r] -> ShowS #

Eq x => Eq (I x l r) Source # 
Instance details

Defined in I.Internal

Methods

(==) :: I x l r -> I x l r -> Bool #

(/=) :: I x l r -> I x l r -> Bool #

Ord x => Ord (I x l r) Source # 
Instance details

Defined in I.Internal

Methods

compare :: I x l r -> I x l r -> Ordering #

(<) :: I x l r -> I x l r -> Bool #

(<=) :: I x l r -> I x l r -> Bool #

(>) :: I x l r -> I x l r -> Bool #

(>=) :: I x l r -> I x l r -> Bool #

max :: I x l r -> I x l r -> I x l r #

min :: I x l r -> I x l r -> I x l r #

type family T (x :: Type) :: k Source #

The kind of the type-level representation of x in I x l r, as it appears in Known x l r t.

Instances

Instances details
(Interval CChar l r, KnownCtx CChar l r t) => Known CChar (l :: L CChar :: Type) (r :: R CChar :: Type) (t :: T CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Associated Types

type KnownCtx CChar l r t Source #

Methods

known' :: Proxy t -> I CChar l r Source #

(Interval CInt l r, KnownCtx CInt l r t) => Known CInt (l :: L CInt :: Type) (r :: R CInt :: Type) (t :: T CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Associated Types

type KnownCtx CInt l r t Source #

Methods

known' :: Proxy t -> I CInt l r Source #

(Interval CIntMax l r, KnownCtx CIntMax l r t) => Known CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) (t :: T CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Associated Types

type KnownCtx CIntMax l r t Source #

Methods

known' :: Proxy t -> I CIntMax l r Source #

(Interval CIntPtr l r, KnownCtx CIntPtr l r t) => Known CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) (t :: T CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Associated Types

type KnownCtx CIntPtr l r t Source #

Methods

known' :: Proxy t -> I CIntPtr l r Source #

(Interval CLLong l r, KnownCtx CLLong l r t) => Known CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) (t :: T CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Associated Types

type KnownCtx CLLong l r t Source #

Methods

known' :: Proxy t -> I CLLong l r Source #

(Interval CLong l r, KnownCtx CLong l r t) => Known CLong (l :: L CLong :: Type) (r :: R CLong :: Type) (t :: T CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Associated Types

type KnownCtx CLong l r t Source #

Methods

known' :: Proxy t -> I CLong l r Source #

(Interval CPtrdiff l r, KnownCtx CPtrdiff l r t) => Known CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) (t :: T CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Associated Types

type KnownCtx CPtrdiff l r t Source #

Methods

known' :: Proxy t -> I CPtrdiff l r Source #

(Interval CSChar l r, KnownCtx CSChar l r t) => Known CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) (t :: T CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Associated Types

type KnownCtx CSChar l r t Source #

Methods

known' :: Proxy t -> I CSChar l r Source #

(Interval CShort l r, KnownCtx CShort l r t) => Known CShort (l :: L CShort :: Type) (r :: R CShort :: Type) (t :: T CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Associated Types

type KnownCtx CShort l r t Source #

Methods

known' :: Proxy t -> I CShort l r Source #

(Interval CSize l r, KnownCtx CSize l r t) => Known CSize (l :: L CSize :: Type) (r :: R CSize :: Type) (t :: T CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Associated Types

type KnownCtx CSize l r t Source #

Methods

known' :: Proxy t -> I CSize l r Source #

(Interval CUChar l r, KnownCtx CUChar l r t) => Known CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) (t :: T CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Associated Types

type KnownCtx CUChar l r t Source #

Methods

known' :: Proxy t -> I CUChar l r Source #

(Interval CUInt l r, KnownCtx CUInt l r t) => Known CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) (t :: T CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Associated Types

type KnownCtx CUInt l r t Source #

Methods

known' :: Proxy t -> I CUInt l r Source #

(Interval CUIntMax l r, KnownCtx CUIntMax l r t) => Known CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) (t :: T CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Associated Types

type KnownCtx CUIntMax l r t Source #

Methods

known' :: Proxy t -> I CUIntMax l r Source #

(Interval CUIntPtr l r, KnownCtx CUIntPtr l r t) => Known CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) (t :: T CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Associated Types

type KnownCtx CUIntPtr l r t Source #

Methods

known' :: Proxy t -> I CUIntPtr l r Source #

(Interval CULLong l r, KnownCtx CULLong l r t) => Known CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) (t :: T CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Associated Types

type KnownCtx CULLong l r t Source #

Methods

known' :: Proxy t -> I CULLong l r Source #

(Interval CULong l r, KnownCtx CULong l r t) => Known CULong (l :: L CULong :: Type) (r :: R CULong :: Type) (t :: T CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Associated Types

type KnownCtx CULong l r t Source #

Methods

known' :: Proxy t -> I CULong l r Source #

(Interval CUShort l r, KnownCtx CUShort l r t) => Known CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) (t :: T CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Associated Types

type KnownCtx CUShort l r t Source #

Methods

known' :: Proxy t -> I CUShort l r Source #

(Interval CWchar l r, KnownCtx CWchar l r t) => Known CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) (t :: T CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Associated Types

type KnownCtx CWchar l r t Source #

Methods

known' :: Proxy t -> I CWchar l r Source #

(Interval Int16 l r, KnownCtx Int16 l r t) => Known Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) (t :: T Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Associated Types

type KnownCtx Int16 l r t Source #

Methods

known' :: Proxy t -> I Int16 l r Source #

(Interval Int32 l r, KnownCtx Int32 l r t) => Known Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) (t :: T Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Associated Types

type KnownCtx Int32 l r t Source #

Methods

known' :: Proxy t -> I Int32 l r Source #

(Interval Int64 l r, KnownCtx Int64 l r t) => Known Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) (t :: T Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Associated Types

type KnownCtx Int64 l r t Source #

Methods

known' :: Proxy t -> I Int64 l r Source #

(Interval Int8 l r, KnownCtx Int8 l r t) => Known Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) (t :: T Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Associated Types

type KnownCtx Int8 l r t Source #

Methods

known' :: Proxy t -> I Int8 l r Source #

(Interval Word16 l r, KnownCtx Word16 l r t) => Known Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) (t :: T Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Associated Types

type KnownCtx Word16 l r t Source #

Methods

known' :: Proxy t -> I Word16 l r Source #

(Interval Word32 l r, KnownCtx Word32 l r t) => Known Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) (t :: T Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Associated Types

type KnownCtx Word32 l r t Source #

Methods

known' :: Proxy t -> I Word32 l r Source #

(Interval Word64 l r, KnownCtx Word64 l r t) => Known Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) (t :: T Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Associated Types

type KnownCtx Word64 l r t Source #

Methods

known' :: Proxy t -> I Word64 l r Source #

(Interval Word8 l r, KnownCtx Word8 l r t) => Known Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) (t :: T Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Associated Types

type KnownCtx Word8 l r t Source #

Methods

known' :: Proxy t -> I Word8 l r Source #

(Interval Int l r, KnownCtx Int l r t) => Known Int (l :: L Int :: Type) (r :: R Int :: Type) (t :: T Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Associated Types

type KnownCtx Int l r t Source #

Methods

known' :: Proxy t -> I Int l r Source #

(Interval Word l r, KnownCtx Word l r t) => Known Word (l :: L Word :: Type) (r :: R Word :: Type) (t :: T Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Associated Types

type KnownCtx Word l r t Source #

Methods

known' :: Proxy t -> I Word l r Source #

(Interval Natural l ('Nothing :: Maybe Natural), KnownCtx Natural l ('Nothing :: Maybe Natural) t) => Known Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

Associated Types

type KnownCtx Natural l 'Nothing t Source #

Methods

known' :: Proxy t -> I Natural l 'Nothing Source #

(Interval Natural l ('Just r), KnownCtx Natural l ('Just r) t) => Known Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

Associated Types

type KnownCtx Natural l ('Just r) t Source #

Methods

known' :: Proxy t -> I Natural l ('Just r) Source #

KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) t => Known Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational 'Nothing 'Nothing t Source #

KnownCtx Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) t => Known Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer 'Nothing 'Nothing t Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)), KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)) t) => Known Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational 'Nothing ('Just '('False, r)) t Source #

Methods

known' :: Proxy t -> I Rational0 'Nothing ('Just '('False, r)) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)), KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) t) => Known Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational 'Nothing ('Just '('True, r)) t Source #

Methods

known' :: Proxy t -> I Rational0 'Nothing ('Just '('True, r)) Source #

(Interval Integer ('Nothing :: Maybe Integer) ('Just r), KnownCtx Integer ('Nothing :: Maybe Integer) ('Just r) t) => Known Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer 'Nothing ('Just r) t Source #

Methods

known' :: Proxy t -> I Integer0 'Nothing ('Just r) Source #

(Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)), KnownCtx Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)) t) => Known Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('False, l)) 'Nothing t Source #

Methods

known' :: Proxy t -> I Rational0 ('Just '('False, l)) 'Nothing Source #

(Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)), KnownCtx Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) t) => Known Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('True, l)) 'Nothing t Source #

Methods

known' :: Proxy t -> I Rational0 ('Just '('True, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), KnownCtx Integer ('Just l) ('Nothing :: Maybe Integer) t) => Known Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer ('Just l) 'Nothing t Source #

Methods

known' :: Proxy t -> I Integer0 ('Just l) 'Nothing Source #

(Interval Rational ('Just '('False, l)) ('Just '('False, r)), KnownCtx Rational ('Just '('False, l)) ('Just '('False, r)) t) => Known Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('False, l)) ('Just '('False, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

(Interval Rational ('Just '('False, l)) ('Just '('True, r)), KnownCtx Rational ('Just '('False, l)) ('Just '('True, r)) t) => Known Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('False, l)) ('Just '('True, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

(Interval Rational ('Just '('True, l)) ('Just '('False, r)), KnownCtx Rational ('Just '('True, l)) ('Just '('False, r)) t) => Known Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('True, l)) ('Just '('False, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

(Interval Rational ('Just '('True, l)) ('Just '('True, r)), KnownCtx Rational ('Just '('True, l)) ('Just '('True, r)) t) => Known Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('True, l)) ('Just '('True, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

(Interval Integer ('Just l) ('Just r), KnownCtx Integer ('Just l) ('Just r) t) => Known Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer ('Just l) ('Just r) t Source #

Methods

known' :: Proxy t -> I Integer ('Just l) ('Just r) Source #

type T Int16 Source # 
Instance details

Defined in I.Internal

type T Int16 = Integer
type T Int32 Source # 
Instance details

Defined in I.Internal

type T Int32 = Integer
type T Int64 Source # 
Instance details

Defined in I.Internal

type T Int64 = Integer
type T Int8 Source # 
Instance details

Defined in I.Internal

type T Int8 = Integer
type T Rational Source # 
Instance details

Defined in I.Internal

type T Word16 Source # 
Instance details

Defined in I.Internal

type T Word32 Source # 
Instance details

Defined in I.Internal

type T Word64 Source # 
Instance details

Defined in I.Internal

type T Word8 Source # 
Instance details

Defined in I.Internal

type T Word8 = Natural
type T Integer Source # 
Instance details

Defined in I.Internal

type T Natural Source # 
Instance details

Defined in I.Internal

type T Int Source # 
Instance details

Defined in I.Internal

type T Int = Integer
type T Word Source # 
Instance details

Defined in I.Internal

type T Word = Natural
type T CChar Source # 
Instance details

Defined in I.Internal

type T CChar = T Int8 :: k
type T CClock Source # 
Instance details

Defined in I.Internal

type T CClock = T Int64 :: k
type T CInt Source # 
Instance details

Defined in I.Internal

type T CInt = T Int32 :: k
type T CIntMax Source # 
Instance details

Defined in I.Internal

type T CIntMax = T Int64 :: k
type T CIntPtr Source # 
Instance details

Defined in I.Internal

type T CIntPtr = T Int64 :: k
type T CLLong Source # 
Instance details

Defined in I.Internal

type T CLLong = T Int64 :: k
type T CLong Source # 
Instance details

Defined in I.Internal

type T CLong = T Int64 :: k
type T CPtrdiff Source # 
Instance details

Defined in I.Internal

type T CPtrdiff = T Int64 :: k
type T CSChar Source # 
Instance details

Defined in I.Internal

type T CSChar = T Int8 :: k
type T CSUSeconds Source # 
Instance details

Defined in I.Internal

type T CSUSeconds = T Int64 :: k
type T CShort Source # 
Instance details

Defined in I.Internal

type T CShort = T Int16 :: k
type T CSize Source # 
Instance details

Defined in I.Internal

type T CSize = T Word64 :: k
type T CTime Source # 
Instance details

Defined in I.Internal

type T CTime = T Int64 :: k
type T CUChar Source # 
Instance details

Defined in I.Internal

type T CUChar = T Word8 :: k
type T CUInt Source # 
Instance details

Defined in I.Internal

type T CUInt = T Word32 :: k
type T CUIntMax Source # 
Instance details

Defined in I.Internal

type T CUIntMax = T Word64 :: k
type T CUIntPtr Source # 
Instance details

Defined in I.Internal

type T CUIntPtr = T Word64 :: k
type T CULLong Source # 
Instance details

Defined in I.Internal

type T CULLong = T Word64 :: k
type T CULong Source # 
Instance details

Defined in I.Internal

type T CULong = T Word64 :: k
type T CUSeconds Source # 
Instance details

Defined in I.Internal

type T CUSeconds = T Word32 :: k
type T CUShort Source # 
Instance details

Defined in I.Internal

type T CUShort = T Word16 :: k
type T CWchar Source # 
Instance details

Defined in I.Internal

type T CWchar = T Int32 :: k
type KnownCtx CChar (l :: L CChar :: Type) (r :: R CChar :: Type) (t :: T CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

type KnownCtx CChar (l :: L CChar :: Type) (r :: R CChar :: Type) (t :: T CChar :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CInt (l :: L CInt :: Type) (r :: R CInt :: Type) (t :: T CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

type KnownCtx CInt (l :: L CInt :: Type) (r :: R CInt :: Type) (t :: T CInt :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) (t :: T CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

type KnownCtx CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) (t :: T CIntMax :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) (t :: T CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

type KnownCtx CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) (t :: T CIntPtr :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) (t :: T CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

type KnownCtx CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) (t :: T CLLong :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CLong (l :: L CLong :: Type) (r :: R CLong :: Type) (t :: T CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

type KnownCtx CLong (l :: L CLong :: Type) (r :: R CLong :: Type) (t :: T CLong :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) (t :: T CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

type KnownCtx CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) (t :: T CPtrdiff :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) (t :: T CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

type KnownCtx CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) (t :: T CSChar :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CShort (l :: L CShort :: Type) (r :: R CShort :: Type) (t :: T CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

type KnownCtx CShort (l :: L CShort :: Type) (r :: R CShort :: Type) (t :: T CShort :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CSize (l :: L CSize :: Type) (r :: R CSize :: Type) (t :: T CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

type KnownCtx CSize (l :: L CSize :: Type) (r :: R CSize :: Type) (t :: T CSize :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) (t :: T CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

type KnownCtx CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) (t :: T CUChar :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) (t :: T CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

type KnownCtx CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) (t :: T CUInt :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) (t :: T CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

type KnownCtx CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) (t :: T CUIntMax :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) (t :: T CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

type KnownCtx CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) (t :: T CUIntPtr :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) (t :: T CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

type KnownCtx CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) (t :: T CULLong :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CULong (l :: L CULong :: Type) (r :: R CULong :: Type) (t :: T CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

type KnownCtx CULong (l :: L CULong :: Type) (r :: R CULong :: Type) (t :: T CULong :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) (t :: T CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

type KnownCtx CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) (t :: T CUShort :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) (t :: T CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

type KnownCtx CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) (t :: T CWchar :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) (t :: T Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

type KnownCtx Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) (t :: T Int16 :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) (t :: T Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

type KnownCtx Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) (t :: T Int32 :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) (t :: T Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

type KnownCtx Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) (t :: T Int64 :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) (t :: T Int8 :: Type) Source # 
Instance details

Defined in I.Int8

type KnownCtx Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) (t :: T Int8 :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) (t :: T Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

type KnownCtx Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) (t :: T Word16 :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) (t :: T Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

type KnownCtx Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) (t :: T Word32 :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) (t :: T Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

type KnownCtx Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) (t :: T Word64 :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) (t :: T Word8 :: Type) Source # 
Instance details

Defined in I.Word8

type KnownCtx Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) (t :: T Word8 :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Int (l :: L Int :: Type) (r :: R Int :: Type) (t :: T Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

type KnownCtx Int (l :: L Int :: Type) (r :: R Int :: Type) (t :: T Int :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Word (l :: L Word :: Type) (r :: R Word :: Type) (t :: T Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

type KnownCtx Word (l :: L Word :: Type) (r :: R Word :: Type) (t :: T Word :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

type KnownCtx Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) (t :: T Natural :: Type) = (KnownNat t, l <= t)
type KnownCtx Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

type KnownCtx Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) (t :: T Natural :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, t < r)
type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, t <= r)
type KnownCtx Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

type KnownCtx Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) = (KnownInteger t, t <= r)
type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) = (KnownRational t, l < t)
type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) = (KnownRational t, l <= t)
type KnownCtx Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

type KnownCtx Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) = (KnownInteger t, l <= t)
type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, l < t, t < r)
type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, l < t, t <= r)
type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, l <= t, t < r)
type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, l <= t, t <= r)
type KnownCtx Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

type KnownCtx Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) = (KnownInteger t, l <= t, t <= r)

type family MinT (x :: Type) :: T x Source #

Type-level verison of minBound :: x. If x is unbounded on the left end, then it's ok to leave MinT x undefined. If defined, it should match what MinL means.

Instances

Instances details
type MinT CChar Source # 
Instance details

Defined in I.Internal

type MinT CClock Source # 
Instance details

Defined in I.Internal

type MinT CInt Source # 
Instance details

Defined in I.Internal

type MinT CIntMax Source # 
Instance details

Defined in I.Internal

type MinT CIntPtr Source # 
Instance details

Defined in I.Internal

type MinT CLLong Source # 
Instance details

Defined in I.Internal

type MinT CLong Source # 
Instance details

Defined in I.Internal

type MinT CPtrdiff Source # 
Instance details

Defined in I.Internal

type MinT CSChar Source # 
Instance details

Defined in I.Internal

type MinT CSUSeconds Source # 
Instance details

Defined in I.Internal

type MinT CShort Source # 
Instance details

Defined in I.Internal

type MinT CSize Source # 
Instance details

Defined in I.Internal

type MinT CTime Source # 
Instance details

Defined in I.Internal

type MinT CUChar Source # 
Instance details

Defined in I.Internal

type MinT CUInt Source # 
Instance details

Defined in I.Internal

type MinT CUIntMax Source # 
Instance details

Defined in I.Internal

type MinT CUIntPtr Source # 
Instance details

Defined in I.Internal

type MinT CULLong Source # 
Instance details

Defined in I.Internal

type MinT CULong Source # 
Instance details

Defined in I.Internal

type MinT CUSeconds Source # 
Instance details

Defined in I.Internal

type MinT CUShort Source # 
Instance details

Defined in I.Internal

type MinT CWchar Source # 
Instance details

Defined in I.Internal

type MinT Int16 Source # 
Instance details

Defined in I.Internal

type MinT Int16 = N 32768
type MinT Int32 Source # 
Instance details

Defined in I.Internal

type MinT Int32 = N 2147483648
type MinT Int64 Source # 
Instance details

Defined in I.Internal

type MinT Int64 = N 9223372036854775808
type MinT Int8 Source # 
Instance details

Defined in I.Internal

type MinT Int8 = N 128
type MinT Word16 Source # 
Instance details

Defined in I.Internal

type MinT Word16 = 0
type MinT Word32 Source # 
Instance details

Defined in I.Internal

type MinT Word32 = 0
type MinT Word64 Source # 
Instance details

Defined in I.Internal

type MinT Word64 = 0
type MinT Word8 Source # 
Instance details

Defined in I.Internal

type MinT Word8 = 0
type MinT Natural Source # 
Instance details

Defined in I.Internal

type MinT Natural = 0
type MinT Int Source # 
Instance details

Defined in I.Internal

type MinT Int = N (Div (2 ^ 64) 2)
type MinT Word Source # 
Instance details

Defined in I.Internal

type MinT Word = 0

type family MaxT (x :: Type) :: T x Source #

Type-level verison of maxBound :: x. If x is unbounded on the right end, then it's ok to leave MaxT x undefined. If defined, it should match what MaxR means.

Instances

Instances details
type MaxT CChar Source # 
Instance details

Defined in I.Internal

type MaxT CClock Source # 
Instance details

Defined in I.Internal

type MaxT CInt Source # 
Instance details

Defined in I.Internal

type MaxT CIntMax Source # 
Instance details

Defined in I.Internal

type MaxT CIntPtr Source # 
Instance details

Defined in I.Internal

type MaxT CLLong Source # 
Instance details

Defined in I.Internal

type MaxT CLong Source # 
Instance details

Defined in I.Internal

type MaxT CPtrdiff Source # 
Instance details

Defined in I.Internal

type MaxT CSChar Source # 
Instance details

Defined in I.Internal

type MaxT CSUSeconds Source # 
Instance details

Defined in I.Internal

type MaxT CShort Source # 
Instance details

Defined in I.Internal

type MaxT CSize Source # 
Instance details

Defined in I.Internal

type MaxT CTime Source # 
Instance details

Defined in I.Internal

type MaxT CUChar Source # 
Instance details

Defined in I.Internal

type MaxT CUInt Source # 
Instance details

Defined in I.Internal

type MaxT CUIntMax Source # 
Instance details

Defined in I.Internal

type MaxT CUIntPtr Source # 
Instance details

Defined in I.Internal

type MaxT CULLong Source # 
Instance details

Defined in I.Internal

type MaxT CULong Source # 
Instance details

Defined in I.Internal

type MaxT CUSeconds Source # 
Instance details

Defined in I.Internal

type MaxT CUShort Source # 
Instance details

Defined in I.Internal

type MaxT CWchar Source # 
Instance details

Defined in I.Internal

type MaxT Int16 Source # 
Instance details

Defined in I.Internal

type MaxT Int16 = P 32767
type MaxT Int32 Source # 
Instance details

Defined in I.Internal

type MaxT Int32 = P 2147483647
type MaxT Int64 Source # 
Instance details

Defined in I.Internal

type MaxT Int64 = P 9223372036854775807
type MaxT Int8 Source # 
Instance details

Defined in I.Internal

type MaxT Int8 = P 127
type MaxT Word16 Source # 
Instance details

Defined in I.Internal

type MaxT Word16 = 65535
type MaxT Word32 Source # 
Instance details

Defined in I.Internal

type MaxT Word32 = 4294967295
type MaxT Word64 Source # 
Instance details

Defined in I.Internal

type MaxT Word64 = 18446744073709551615
type MaxT Word8 Source # 
Instance details

Defined in I.Internal

type MaxT Word8 = 255
type MaxT Int Source # 
Instance details

Defined in I.Internal

type MaxT Int = P (Div (2 ^ 64) 2 - 1)
type MaxT Word Source # 
Instance details

Defined in I.Internal

type MaxT Word = (2 ^ 64) - 1

type family L (x :: Type) :: k Source #

The kind of l in I x l r.

Instances

Instances details
Interval CChar l r => Clamp CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

clamp :: CChar -> I CChar l r Source #

Interval CInt l r => Clamp CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

clamp :: CInt -> I CInt l r Source #

Interval CIntMax l r => Clamp CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

clamp :: CIntMax -> I CIntMax l r Source #

Interval CIntPtr l r => Clamp CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

clamp :: CIntPtr -> I CIntPtr l r Source #

Interval CLLong l r => Clamp CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

clamp :: CLLong -> I CLLong l r Source #

Interval CLong l r => Clamp CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

clamp :: CLong -> I CLong l r Source #

Interval CPtrdiff l r => Clamp CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

clamp :: CPtrdiff -> I CPtrdiff l r Source #

Interval CSChar l r => Clamp CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

clamp :: CSChar -> I CSChar l r Source #

Interval CShort l r => Clamp CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

clamp :: CShort -> I CShort l r Source #

Interval CSize l r => Clamp CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

clamp :: CSize -> I CSize l r Source #

Interval CUChar l r => Clamp CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

clamp :: CUChar -> I CUChar l r Source #

Interval CUInt l r => Clamp CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

clamp :: CUInt -> I CUInt l r Source #

Interval CUIntMax l r => Clamp CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

clamp :: CUIntMax -> I CUIntMax l r Source #

Interval CUIntPtr l r => Clamp CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

clamp :: CUIntPtr -> I CUIntPtr l r Source #

Interval CULLong l r => Clamp CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

clamp :: CULLong -> I CULLong l r Source #

Interval CULong l r => Clamp CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

clamp :: CULong -> I CULong l r Source #

Interval CUShort l r => Clamp CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

clamp :: CUShort -> I CUShort l r Source #

Interval CWchar l r => Clamp CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

clamp :: CWchar -> I CWchar l r Source #

Interval Int16 l r => Clamp Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

clamp :: Int16 -> I Int16 l r Source #

Interval Int32 l r => Clamp Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

clamp :: Int32 -> I Int32 l r Source #

Interval Int64 l r => Clamp Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

clamp :: Int64 -> I Int64 l r Source #

Interval Int8 l r => Clamp Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

clamp :: Int8 -> I Int8 l r Source #

Interval Word16 l r => Clamp Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

clamp :: Word16 -> I Word16 l r Source #

Interval Word32 l r => Clamp Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

clamp :: Word32 -> I Word32 l r Source #

Interval Word64 l r => Clamp Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

clamp :: Word64 -> I Word64 l r Source #

Interval Word8 l r => Clamp Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

clamp :: Word8 -> I Word8 l r Source #

Interval Int l r => Clamp Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

clamp :: Int -> I Int l r Source #

Interval Word l r => Clamp Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

clamp :: Word -> I Word l r Source #

(Interval CChar l r, l /= r) => Discrete CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

pred' :: I CChar l r -> Maybe (I CChar l r) Source #

succ' :: I CChar l r -> Maybe (I CChar l r) Source #

(Interval CInt l r, l /= r) => Discrete CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

pred' :: I CInt l r -> Maybe (I CInt l r) Source #

succ' :: I CInt l r -> Maybe (I CInt l r) Source #

(Interval CIntMax l r, l /= r) => Discrete CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

pred' :: I CIntMax l r -> Maybe (I CIntMax l r) Source #

succ' :: I CIntMax l r -> Maybe (I CIntMax l r) Source #

(Interval CIntPtr l r, l /= r) => Discrete CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

pred' :: I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

succ' :: I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

(Interval CLLong l r, l /= r) => Discrete CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

pred' :: I CLLong l r -> Maybe (I CLLong l r) Source #

succ' :: I CLLong l r -> Maybe (I CLLong l r) Source #

(Interval CLong l r, l /= r) => Discrete CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

pred' :: I CLong l r -> Maybe (I CLong l r) Source #

succ' :: I CLong l r -> Maybe (I CLong l r) Source #

(Interval CPtrdiff l r, l /= r) => Discrete CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

pred' :: I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

succ' :: I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

(Interval CSChar l r, l /= r) => Discrete CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

pred' :: I CSChar l r -> Maybe (I CSChar l r) Source #

succ' :: I CSChar l r -> Maybe (I CSChar l r) Source #

(Interval CShort l r, l /= r) => Discrete CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

pred' :: I CShort l r -> Maybe (I CShort l r) Source #

succ' :: I CShort l r -> Maybe (I CShort l r) Source #

(Interval CSize l r, l /= r) => Discrete CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

pred' :: I CSize l r -> Maybe (I CSize l r) Source #

succ' :: I CSize l r -> Maybe (I CSize l r) Source #

(Interval CUChar l r, l /= r) => Discrete CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

pred' :: I CUChar l r -> Maybe (I CUChar l r) Source #

succ' :: I CUChar l r -> Maybe (I CUChar l r) Source #

(Interval CUInt l r, l /= r) => Discrete CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

pred' :: I CUInt l r -> Maybe (I CUInt l r) Source #

succ' :: I CUInt l r -> Maybe (I CUInt l r) Source #

(Interval CUIntMax l r, l /= r) => Discrete CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

pred' :: I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

succ' :: I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

(Interval CUIntPtr l r, l /= r) => Discrete CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

pred' :: I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

succ' :: I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

(Interval CULLong l r, l /= r) => Discrete CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

pred' :: I CULLong l r -> Maybe (I CULLong l r) Source #

succ' :: I CULLong l r -> Maybe (I CULLong l r) Source #

(Interval CULong l r, l /= r) => Discrete CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

pred' :: I CULong l r -> Maybe (I CULong l r) Source #

succ' :: I CULong l r -> Maybe (I CULong l r) Source #

(Interval CUShort l r, l /= r) => Discrete CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

pred' :: I CUShort l r -> Maybe (I CUShort l r) Source #

succ' :: I CUShort l r -> Maybe (I CUShort l r) Source #

(Interval CWchar l r, l /= r) => Discrete CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

pred' :: I CWchar l r -> Maybe (I CWchar l r) Source #

succ' :: I CWchar l r -> Maybe (I CWchar l r) Source #

(Interval Int16 l r, l /= r) => Discrete Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

pred' :: I Int16 l r -> Maybe (I Int16 l r) Source #

succ' :: I Int16 l r -> Maybe (I Int16 l r) Source #

(Interval Int32 l r, l /= r) => Discrete Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

pred' :: I Int32 l r -> Maybe (I Int32 l r) Source #

succ' :: I Int32 l r -> Maybe (I Int32 l r) Source #

(Interval Int64 l r, l /= r) => Discrete Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

pred' :: I Int64 l r -> Maybe (I Int64 l r) Source #

succ' :: I Int64 l r -> Maybe (I Int64 l r) Source #

(Interval Int8 l r, l /= r) => Discrete Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

pred' :: I Int8 l r -> Maybe (I Int8 l r) Source #

succ' :: I Int8 l r -> Maybe (I Int8 l r) Source #

(Interval Word16 l r, l /= r) => Discrete Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

pred' :: I Word16 l r -> Maybe (I Word16 l r) Source #

succ' :: I Word16 l r -> Maybe (I Word16 l r) Source #

(Interval Word32 l r, l /= r) => Discrete Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

pred' :: I Word32 l r -> Maybe (I Word32 l r) Source #

succ' :: I Word32 l r -> Maybe (I Word32 l r) Source #

(Interval Word64 l r, l /= r) => Discrete Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

pred' :: I Word64 l r -> Maybe (I Word64 l r) Source #

succ' :: I Word64 l r -> Maybe (I Word64 l r) Source #

(Interval Word8 l r, l /= r) => Discrete Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

pred' :: I Word8 l r -> Maybe (I Word8 l r) Source #

succ' :: I Word8 l r -> Maybe (I Word8 l r) Source #

(Interval Int l r, l /= r) => Discrete Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

pred' :: I Int l r -> Maybe (I Int l r) Source #

succ' :: I Int l r -> Maybe (I Int l r) Source #

(Interval Word l r, l /= r) => Discrete Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

pred' :: I Word l r -> Maybe (I Word l r) Source #

succ' :: I Word l r -> Maybe (I Word l r) Source #

IntervalCtx CChar l r => Interval CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Associated Types

type IntervalCtx CChar l r Source #

type MinI CChar l r :: T x :: Type Source #

type MaxI CChar l r :: T x :: Type Source #

Methods

inhabitant :: I CChar l r Source #

from :: CChar -> Maybe (I CChar l r) Source #

plus' :: I CChar l r -> I CChar l r -> Maybe (I CChar l r) Source #

mult' :: I CChar l r -> I CChar l r -> Maybe (I CChar l r) Source #

minus' :: I CChar l r -> I CChar l r -> Maybe (I CChar l r) Source #

negate' :: I CChar l r -> Maybe (I CChar l r) Source #

recip' :: I CChar l r -> Maybe (I CChar l r) Source #

div' :: I CChar l r -> I CChar l r -> Maybe (I CChar l r) Source #

IntervalCtx CInt l r => Interval CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Associated Types

type IntervalCtx CInt l r Source #

type MinI CInt l r :: T x :: Type Source #

type MaxI CInt l r :: T x :: Type Source #

Methods

inhabitant :: I CInt l r Source #

from :: CInt -> Maybe (I CInt l r) Source #

plus' :: I CInt l r -> I CInt l r -> Maybe (I CInt l r) Source #

mult' :: I CInt l r -> I CInt l r -> Maybe (I CInt l r) Source #

minus' :: I CInt l r -> I CInt l r -> Maybe (I CInt l r) Source #

negate' :: I CInt l r -> Maybe (I CInt l r) Source #

recip' :: I CInt l r -> Maybe (I CInt l r) Source #

div' :: I CInt l r -> I CInt l r -> Maybe (I CInt l r) Source #

IntervalCtx CIntMax l r => Interval CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Associated Types

type IntervalCtx CIntMax l r Source #

type MinI CIntMax l r :: T x :: Type Source #

type MaxI CIntMax l r :: T x :: Type Source #

Methods

inhabitant :: I CIntMax l r Source #

from :: CIntMax -> Maybe (I CIntMax l r) Source #

plus' :: I CIntMax l r -> I CIntMax l r -> Maybe (I CIntMax l r) Source #

mult' :: I CIntMax l r -> I CIntMax l r -> Maybe (I CIntMax l r) Source #

minus' :: I CIntMax l r -> I CIntMax l r -> Maybe (I CIntMax l r) Source #

negate' :: I CIntMax l r -> Maybe (I CIntMax l r) Source #

recip' :: I CIntMax l r -> Maybe (I CIntMax l r) Source #

div' :: I CIntMax l r -> I CIntMax l r -> Maybe (I CIntMax l r) Source #

IntervalCtx CIntPtr l r => Interval CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Associated Types

type IntervalCtx CIntPtr l r Source #

type MinI CIntPtr l r :: T x :: Type Source #

type MaxI CIntPtr l r :: T x :: Type Source #

Methods

inhabitant :: I CIntPtr l r Source #

from :: CIntPtr -> Maybe (I CIntPtr l r) Source #

plus' :: I CIntPtr l r -> I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

mult' :: I CIntPtr l r -> I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

minus' :: I CIntPtr l r -> I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

negate' :: I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

recip' :: I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

div' :: I CIntPtr l r -> I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

IntervalCtx CLLong l r => Interval CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Associated Types

type IntervalCtx CLLong l r Source #

type MinI CLLong l r :: T x :: Type Source #

type MaxI CLLong l r :: T x :: Type Source #

Methods

inhabitant :: I CLLong l r Source #

from :: CLLong -> Maybe (I CLLong l r) Source #

plus' :: I CLLong l r -> I CLLong l r -> Maybe (I CLLong l r) Source #

mult' :: I CLLong l r -> I CLLong l r -> Maybe (I CLLong l r) Source #

minus' :: I CLLong l r -> I CLLong l r -> Maybe (I CLLong l r) Source #

negate' :: I CLLong l r -> Maybe (I CLLong l r) Source #

recip' :: I CLLong l r -> Maybe (I CLLong l r) Source #

div' :: I CLLong l r -> I CLLong l r -> Maybe (I CLLong l r) Source #

IntervalCtx CLong l r => Interval CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Associated Types

type IntervalCtx CLong l r Source #

type MinI CLong l r :: T x :: Type Source #

type MaxI CLong l r :: T x :: Type Source #

Methods

inhabitant :: I CLong l r Source #

from :: CLong -> Maybe (I CLong l r) Source #

plus' :: I CLong l r -> I CLong l r -> Maybe (I CLong l r) Source #

mult' :: I CLong l r -> I CLong l r -> Maybe (I CLong l r) Source #

minus' :: I CLong l r -> I CLong l r -> Maybe (I CLong l r) Source #

negate' :: I CLong l r -> Maybe (I CLong l r) Source #

recip' :: I CLong l r -> Maybe (I CLong l r) Source #

div' :: I CLong l r -> I CLong l r -> Maybe (I CLong l r) Source #

IntervalCtx CPtrdiff l r => Interval CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Associated Types

type IntervalCtx CPtrdiff l r Source #

type MinI CPtrdiff l r :: T x :: Type Source #

type MaxI CPtrdiff l r :: T x :: Type Source #

Methods

inhabitant :: I CPtrdiff l r Source #

from :: CPtrdiff -> Maybe (I CPtrdiff l r) Source #

plus' :: I CPtrdiff l r -> I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

mult' :: I CPtrdiff l r -> I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

minus' :: I CPtrdiff l r -> I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

negate' :: I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

recip' :: I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

div' :: I CPtrdiff l r -> I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

IntervalCtx CSChar l r => Interval CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Associated Types

type IntervalCtx CSChar l r Source #

type MinI CSChar l r :: T x :: Type Source #

type MaxI CSChar l r :: T x :: Type Source #

Methods

inhabitant :: I CSChar l r Source #

from :: CSChar -> Maybe (I CSChar l r) Source #

plus' :: I CSChar l r -> I CSChar l r -> Maybe (I CSChar l r) Source #

mult' :: I CSChar l r -> I CSChar l r -> Maybe (I CSChar l r) Source #

minus' :: I CSChar l r -> I CSChar l r -> Maybe (I CSChar l r) Source #

negate' :: I CSChar l r -> Maybe (I CSChar l r) Source #

recip' :: I CSChar l r -> Maybe (I CSChar l r) Source #

div' :: I CSChar l r -> I CSChar l r -> Maybe (I CSChar l r) Source #

IntervalCtx CShort l r => Interval CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Associated Types

type IntervalCtx CShort l r Source #

type MinI CShort l r :: T x :: Type Source #

type MaxI CShort l r :: T x :: Type Source #

Methods

inhabitant :: I CShort l r Source #

from :: CShort -> Maybe (I CShort l r) Source #

plus' :: I CShort l r -> I CShort l r -> Maybe (I CShort l r) Source #

mult' :: I CShort l r -> I CShort l r -> Maybe (I CShort l r) Source #

minus' :: I CShort l r -> I CShort l r -> Maybe (I CShort l r) Source #

negate' :: I CShort l r -> Maybe (I CShort l r) Source #

recip' :: I CShort l r -> Maybe (I CShort l r) Source #

div' :: I CShort l r -> I CShort l r -> Maybe (I CShort l r) Source #

IntervalCtx CSize l r => Interval CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Associated Types

type IntervalCtx CSize l r Source #

type MinI CSize l r :: T x :: Type Source #

type MaxI CSize l r :: T x :: Type Source #

Methods

inhabitant :: I CSize l r Source #

from :: CSize -> Maybe (I CSize l r) Source #

plus' :: I CSize l r -> I CSize l r -> Maybe (I CSize l r) Source #

mult' :: I CSize l r -> I CSize l r -> Maybe (I CSize l r) Source #

minus' :: I CSize l r -> I CSize l r -> Maybe (I CSize l r) Source #

negate' :: I CSize l r -> Maybe (I CSize l r) Source #

recip' :: I CSize l r -> Maybe (I CSize l r) Source #

div' :: I CSize l r -> I CSize l r -> Maybe (I CSize l r) Source #

IntervalCtx CUChar l r => Interval CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Associated Types

type IntervalCtx CUChar l r Source #

type MinI CUChar l r :: T x :: Type Source #

type MaxI CUChar l r :: T x :: Type Source #

Methods

inhabitant :: I CUChar l r Source #

from :: CUChar -> Maybe (I CUChar l r) Source #

plus' :: I CUChar l r -> I CUChar l r -> Maybe (I CUChar l r) Source #

mult' :: I CUChar l r -> I CUChar l r -> Maybe (I CUChar l r) Source #

minus' :: I CUChar l r -> I CUChar l r -> Maybe (I CUChar l r) Source #

negate' :: I CUChar l r -> Maybe (I CUChar l r) Source #

recip' :: I CUChar l r -> Maybe (I CUChar l r) Source #

div' :: I CUChar l r -> I CUChar l r -> Maybe (I CUChar l r) Source #

IntervalCtx CUInt l r => Interval CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Associated Types

type IntervalCtx CUInt l r Source #

type MinI CUInt l r :: T x :: Type Source #

type MaxI CUInt l r :: T x :: Type Source #

Methods

inhabitant :: I CUInt l r Source #

from :: CUInt -> Maybe (I CUInt l r) Source #

plus' :: I CUInt l r -> I CUInt l r -> Maybe (I CUInt l r) Source #

mult' :: I CUInt l r -> I CUInt l r -> Maybe (I CUInt l r) Source #

minus' :: I CUInt l r -> I CUInt l r -> Maybe (I CUInt l r) Source #

negate' :: I CUInt l r -> Maybe (I CUInt l r) Source #

recip' :: I CUInt l r -> Maybe (I CUInt l r) Source #

div' :: I CUInt l r -> I CUInt l r -> Maybe (I CUInt l r) Source #

IntervalCtx CUIntMax l r => Interval CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Associated Types

type IntervalCtx CUIntMax l r Source #

type MinI CUIntMax l r :: T x :: Type Source #

type MaxI CUIntMax l r :: T x :: Type Source #

Methods

inhabitant :: I CUIntMax l r Source #

from :: CUIntMax -> Maybe (I CUIntMax l r) Source #

plus' :: I CUIntMax l r -> I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

mult' :: I CUIntMax l r -> I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

minus' :: I CUIntMax l r -> I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

negate' :: I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

recip' :: I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

div' :: I CUIntMax l r -> I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

IntervalCtx CUIntPtr l r => Interval CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Associated Types

type IntervalCtx CUIntPtr l r Source #

type MinI CUIntPtr l r :: T x :: Type Source #

type MaxI CUIntPtr l r :: T x :: Type Source #

Methods

inhabitant :: I CUIntPtr l r Source #

from :: CUIntPtr -> Maybe (I CUIntPtr l r) Source #

plus' :: I CUIntPtr l r -> I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

mult' :: I CUIntPtr l r -> I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

minus' :: I CUIntPtr l r -> I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

negate' :: I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

recip' :: I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

div' :: I CUIntPtr l r -> I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

IntervalCtx CULLong l r => Interval CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Associated Types

type IntervalCtx CULLong l r Source #

type MinI CULLong l r :: T x :: Type Source #

type MaxI CULLong l r :: T x :: Type Source #

Methods

inhabitant :: I CULLong l r Source #

from :: CULLong -> Maybe (I CULLong l r) Source #

plus' :: I CULLong l r -> I CULLong l r -> Maybe (I CULLong l r) Source #

mult' :: I CULLong l r -> I CULLong l r -> Maybe (I CULLong l r) Source #

minus' :: I CULLong l r -> I CULLong l r -> Maybe (I CULLong l r) Source #

negate' :: I CULLong l r -> Maybe (I CULLong l r) Source #

recip' :: I CULLong l r -> Maybe (I CULLong l r) Source #

div' :: I CULLong l r -> I CULLong l r -> Maybe (I CULLong l r) Source #

IntervalCtx CULong l r => Interval CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Associated Types

type IntervalCtx CULong l r Source #

type MinI CULong l r :: T x :: Type Source #

type MaxI CULong l r :: T x :: Type Source #

Methods

inhabitant :: I CULong l r Source #

from :: CULong -> Maybe (I CULong l r) Source #

plus' :: I CULong l r -> I CULong l r -> Maybe (I CULong l r) Source #

mult' :: I CULong l r -> I CULong l r -> Maybe (I CULong l r) Source #

minus' :: I CULong l r -> I CULong l r -> Maybe (I CULong l r) Source #

negate' :: I CULong l r -> Maybe (I CULong l r) Source #

recip' :: I CULong l r -> Maybe (I CULong l r) Source #

div' :: I CULong l r -> I CULong l r -> Maybe (I CULong l r) Source #

IntervalCtx CUShort l r => Interval CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Associated Types

type IntervalCtx CUShort l r Source #

type MinI CUShort l r :: T x :: Type Source #

type MaxI CUShort l r :: T x :: Type Source #

Methods

inhabitant :: I CUShort l r Source #

from :: CUShort -> Maybe (I CUShort l r) Source #

plus' :: I CUShort l r -> I CUShort l r -> Maybe (I CUShort l r) Source #

mult' :: I CUShort l r -> I CUShort l r -> Maybe (I CUShort l r) Source #

minus' :: I CUShort l r -> I CUShort l r -> Maybe (I CUShort l r) Source #

negate' :: I CUShort l r -> Maybe (I CUShort l r) Source #

recip' :: I CUShort l r -> Maybe (I CUShort l r) Source #

div' :: I CUShort l r -> I CUShort l r -> Maybe (I CUShort l r) Source #

IntervalCtx CWchar l r => Interval CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Associated Types

type IntervalCtx CWchar l r Source #

type MinI CWchar l r :: T x :: Type Source #

type MaxI CWchar l r :: T x :: Type Source #

Methods

inhabitant :: I CWchar l r Source #

from :: CWchar -> Maybe (I CWchar l r) Source #

plus' :: I CWchar l r -> I CWchar l r -> Maybe (I CWchar l r) Source #

mult' :: I CWchar l r -> I CWchar l r -> Maybe (I CWchar l r) Source #

minus' :: I CWchar l r -> I CWchar l r -> Maybe (I CWchar l r) Source #

negate' :: I CWchar l r -> Maybe (I CWchar l r) Source #

recip' :: I CWchar l r -> Maybe (I CWchar l r) Source #

div' :: I CWchar l r -> I CWchar l r -> Maybe (I CWchar l r) Source #

IntervalCtx Int16 l r => Interval Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Associated Types

type IntervalCtx Int16 l r Source #

type MinI Int16 l r :: T x :: Type Source #

type MaxI Int16 l r :: T x :: Type Source #

Methods

inhabitant :: I Int16 l r Source #

from :: Int16 -> Maybe (I Int16 l r) Source #

plus' :: I Int16 l r -> I Int16 l r -> Maybe (I Int16 l r) Source #

mult' :: I Int16 l r -> I Int16 l r -> Maybe (I Int16 l r) Source #

minus' :: I Int16 l r -> I Int16 l r -> Maybe (I Int16 l r) Source #

negate' :: I Int16 l r -> Maybe (I Int16 l r) Source #

recip' :: I Int16 l r -> Maybe (I Int16 l r) Source #

div' :: I Int16 l r -> I Int16 l r -> Maybe (I Int16 l r) Source #

IntervalCtx Int32 l r => Interval Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Associated Types

type IntervalCtx Int32 l r Source #

type MinI Int32 l r :: T x :: Type Source #

type MaxI Int32 l r :: T x :: Type Source #

Methods

inhabitant :: I Int32 l r Source #

from :: Int32 -> Maybe (I Int32 l r) Source #

plus' :: I Int32 l r -> I Int32 l r -> Maybe (I Int32 l r) Source #

mult' :: I Int32 l r -> I Int32 l r -> Maybe (I Int32 l r) Source #

minus' :: I Int32 l r -> I Int32 l r -> Maybe (I Int32 l r) Source #

negate' :: I Int32 l r -> Maybe (I Int32 l r) Source #

recip' :: I Int32 l r -> Maybe (I Int32 l r) Source #

div' :: I Int32 l r -> I Int32 l r -> Maybe (I Int32 l r) Source #

IntervalCtx Int64 l r => Interval Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Associated Types

type IntervalCtx Int64 l r Source #

type MinI Int64 l r :: T x :: Type Source #

type MaxI Int64 l r :: T x :: Type Source #

Methods

inhabitant :: I Int64 l r Source #

from :: Int64 -> Maybe (I Int64 l r) Source #

plus' :: I Int64 l r -> I Int64 l r -> Maybe (I Int64 l r) Source #

mult' :: I Int64 l r -> I Int64 l r -> Maybe (I Int64 l r) Source #

minus' :: I Int64 l r -> I Int64 l r -> Maybe (I Int64 l r) Source #

negate' :: I Int64 l r -> Maybe (I Int64 l r) Source #

recip' :: I Int64 l r -> Maybe (I Int64 l r) Source #

div' :: I Int64 l r -> I Int64 l r -> Maybe (I Int64 l r) Source #

IntervalCtx Int8 l r => Interval Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Associated Types

type IntervalCtx Int8 l r Source #

type MinI Int8 l r :: T x :: Type Source #

type MaxI Int8 l r :: T x :: Type Source #

Methods

inhabitant :: I Int8 l r Source #

from :: Int8 -> Maybe (I Int8 l r) Source #

plus' :: I Int8 l r -> I Int8 l r -> Maybe (I Int8 l r) Source #

mult' :: I Int8 l r -> I Int8 l r -> Maybe (I Int8 l r) Source #

minus' :: I Int8 l r -> I Int8 l r -> Maybe (I Int8 l r) Source #

negate' :: I Int8 l r -> Maybe (I Int8 l r) Source #

recip' :: I Int8 l r -> Maybe (I Int8 l r) Source #

div' :: I Int8 l r -> I Int8 l r -> Maybe (I Int8 l r) Source #

IntervalCtx Word16 l r => Interval Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Associated Types

type IntervalCtx Word16 l r Source #

type MinI Word16 l r :: T x :: Type Source #

type MaxI Word16 l r :: T x :: Type Source #

Methods

inhabitant :: I Word16 l r Source #

from :: Word16 -> Maybe (I Word16 l r) Source #

plus' :: I Word16 l r -> I Word16 l r -> Maybe (I Word16 l r) Source #

mult' :: I Word16 l r -> I Word16 l r -> Maybe (I Word16 l r) Source #

minus' :: I Word16 l r -> I Word16 l r -> Maybe (I Word16 l r) Source #

negate' :: I Word16 l r -> Maybe (I Word16 l r) Source #

recip' :: I Word16 l r -> Maybe (I Word16 l r) Source #

div' :: I Word16 l r -> I Word16 l r -> Maybe (I Word16 l r) Source #

IntervalCtx Word32 l r => Interval Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Associated Types

type IntervalCtx Word32 l r Source #

type MinI Word32 l r :: T x :: Type Source #

type MaxI Word32 l r :: T x :: Type Source #

Methods

inhabitant :: I Word32 l r Source #

from :: Word32 -> Maybe (I Word32 l r) Source #

plus' :: I Word32 l r -> I Word32 l r -> Maybe (I Word32 l r) Source #

mult' :: I Word32 l r -> I Word32 l r -> Maybe (I Word32 l r) Source #

minus' :: I Word32 l r -> I Word32 l r -> Maybe (I Word32 l r) Source #

negate' :: I Word32 l r -> Maybe (I Word32 l r) Source #

recip' :: I Word32 l r -> Maybe (I Word32 l r) Source #

div' :: I Word32 l r -> I Word32 l r -> Maybe (I Word32 l r) Source #

IntervalCtx Word64 l r => Interval Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Associated Types

type IntervalCtx Word64 l r Source #

type MinI Word64 l r :: T x :: Type Source #

type MaxI Word64 l r :: T x :: Type Source #

Methods

inhabitant :: I Word64 l r Source #

from :: Word64 -> Maybe (I Word64 l r) Source #

plus' :: I Word64 l r -> I Word64 l r -> Maybe (I Word64 l r) Source #

mult' :: I Word64 l r -> I Word64 l r -> Maybe (I Word64 l r) Source #

minus' :: I Word64 l r -> I Word64 l r -> Maybe (I Word64 l r) Source #

negate' :: I Word64 l r -> Maybe (I Word64 l r) Source #

recip' :: I Word64 l r -> Maybe (I Word64 l r) Source #

div' :: I Word64 l r -> I Word64 l r -> Maybe (I Word64 l r) Source #

IntervalCtx Word8 l r => Interval Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Associated Types

type IntervalCtx Word8 l r Source #

type MinI Word8 l r :: T x :: Type Source #

type MaxI Word8 l r :: T x :: Type Source #

Methods

inhabitant :: I Word8 l r Source #

from :: Word8 -> Maybe (I Word8 l r) Source #

plus' :: I Word8 l r -> I Word8 l r -> Maybe (I Word8 l r) Source #

mult' :: I Word8 l r -> I Word8 l r -> Maybe (I Word8 l r) Source #

minus' :: I Word8 l r -> I Word8 l r -> Maybe (I Word8 l r) Source #

negate' :: I Word8 l r -> Maybe (I Word8 l r) Source #

recip' :: I Word8 l r -> Maybe (I Word8 l r) Source #

div' :: I Word8 l r -> I Word8 l r -> Maybe (I Word8 l r) Source #

IntervalCtx Int l r => Interval Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Associated Types

type IntervalCtx Int l r Source #

type MinI Int l r :: T x :: Type Source #

type MaxI Int l r :: T x :: Type Source #

Methods

inhabitant :: I Int l r Source #

from :: Int -> Maybe (I Int l r) Source #

plus' :: I Int l r -> I Int l r -> Maybe (I Int l r) Source #

mult' :: I Int l r -> I Int l r -> Maybe (I Int l r) Source #

minus' :: I Int l r -> I Int l r -> Maybe (I Int l r) Source #

negate' :: I Int l r -> Maybe (I Int l r) Source #

recip' :: I Int l r -> Maybe (I Int l r) Source #

div' :: I Int l r -> I Int l r -> Maybe (I Int l r) Source #

IntervalCtx Word l r => Interval Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Associated Types

type IntervalCtx Word l r Source #

type MinI Word l r :: T x :: Type Source #

type MaxI Word l r :: T x :: Type Source #

Methods

inhabitant :: I Word l r Source #

from :: Word -> Maybe (I Word l r) Source #

plus' :: I Word l r -> I Word l r -> Maybe (I Word l r) Source #

mult' :: I Word l r -> I Word l r -> Maybe (I Word l r) Source #

minus' :: I Word l r -> I Word l r -> Maybe (I Word l r) Source #

negate' :: I Word l r -> Maybe (I Word l r) Source #

recip' :: I Word l r -> Maybe (I Word l r) Source #

div' :: I Word l r -> I Word l r -> Maybe (I Word l r) Source #

(Zero CChar l r, l == Negate r) => Negate CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

negate :: I CChar l r -> I CChar l r Source #

(Zero CInt l r, l == Negate r) => Negate CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

negate :: I CInt l r -> I CInt l r Source #

(Zero CIntMax l r, l == Negate r) => Negate CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

negate :: I CIntMax l r -> I CIntMax l r Source #

(Zero CIntPtr l r, l == Negate r) => Negate CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

negate :: I CIntPtr l r -> I CIntPtr l r Source #

(Zero CLLong l r, l == Negate r) => Negate CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

negate :: I CLLong l r -> I CLLong l r Source #

(Zero CLong l r, l == Negate r) => Negate CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

negate :: I CLong l r -> I CLong l r Source #

(Zero CPtrdiff l r, l == Negate r) => Negate CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

negate :: I CPtrdiff l r -> I CPtrdiff l r Source #

(Zero CSChar l r, l == Negate r) => Negate CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

negate :: I CSChar l r -> I CSChar l r Source #

(Zero CShort l r, l == Negate r) => Negate CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

negate :: I CShort l r -> I CShort l r Source #

(Zero CWchar l r, l == Negate r) => Negate CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

negate :: I CWchar l r -> I CWchar l r Source #

(Zero Int16 l r, l == Negate r) => Negate Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

negate :: I Int16 l r -> I Int16 l r Source #

(Zero Int32 l r, l == Negate r) => Negate Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

negate :: I Int32 l r -> I Int32 l r Source #

(Zero Int64 l r, l == Negate r) => Negate Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

negate :: I Int64 l r -> I Int64 l r Source #

(Zero Int8 l r, l == Negate r) => Negate Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

negate :: I Int8 l r -> I Int8 l r Source #

(Zero Int l r, l == Negate r) => Negate Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

negate :: I Int l r -> I Int l r Source #

(Interval CChar l r, l <= P 1, P 1 <= r) => One CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

one :: I CChar l r Source #

(Interval CInt l r, l <= P 1, P 1 <= r) => One CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

one :: I CInt l r Source #

(Interval CIntMax l r, l <= P 1, P 1 <= r) => One CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

one :: I CIntMax l r Source #

(Interval CIntPtr l r, l <= P 1, P 1 <= r) => One CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

one :: I CIntPtr l r Source #

(Interval CLLong l r, l <= P 1, P 1 <= r) => One CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

one :: I CLLong l r Source #

(Interval CLong l r, l <= P 1, P 1 <= r) => One CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

one :: I CLong l r Source #

(Interval CPtrdiff l r, l <= P 1, P 1 <= r) => One CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

one :: I CPtrdiff l r Source #

(Interval CSChar l r, l <= P 1, P 1 <= r) => One CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

one :: I CSChar l r Source #

(Interval CShort l r, l <= P 1, P 1 <= r) => One CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

one :: I CShort l r Source #

(Interval CSize l r, l <= 1, 1 <= r) => One CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

one :: I CSize l r Source #

(Interval CUChar l r, l <= 1, 1 <= r) => One CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

one :: I CUChar l r Source #

(Interval CUInt l r, l <= 1, 1 <= r) => One CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

one :: I CUInt l r Source #

(Interval CUIntMax l r, l <= 1, 1 <= r) => One CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

one :: I CUIntMax l r Source #

(Interval CUIntPtr l r, l <= 1, 1 <= r) => One CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

one :: I CUIntPtr l r Source #

(Interval CULLong l r, l <= 1, 1 <= r) => One CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

one :: I CULLong l r Source #

(Interval CULong l r, l <= 1, 1 <= r) => One CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

one :: I CULong l r Source #

(Interval CUShort l r, l <= 1, 1 <= r) => One CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

one :: I CUShort l r Source #

(Interval CWchar l r, l <= P 1, P 1 <= r) => One CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

one :: I CWchar l r Source #

(Interval Int16 l r, l <= P 1, P 1 <= r) => One Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

one :: I Int16 l r Source #

(Interval Int32 l r, l <= P 1, P 1 <= r) => One Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

one :: I Int32 l r Source #

(Interval Int64 l r, l <= P 1, P 1 <= r) => One Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

one :: I Int64 l r Source #

(Interval Int8 l r, l <= P 1, P 1 <= r) => One Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

one :: I Int8 l r Source #

(Interval Word16 l r, l <= 1, 1 <= r) => One Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

one :: I Word16 l r Source #

(Interval Word32 l r, l <= 1, 1 <= r) => One Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

one :: I Word32 l r Source #

(Interval Word64 l r, l <= 1, 1 <= r) => One Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

one :: I Word64 l r Source #

(Interval Word8 l r, l <= 1, 1 <= r) => One Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

one :: I Word8 l r Source #

(Interval Int l r, l <= P 1, P 1 <= r) => One Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

one :: I Int l r Source #

(Interval Word l r, l <= 1, 1 <= r) => One Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

one :: I Word l r Source #

Interval CChar l r => Shove CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

shove :: CChar -> I CChar l r Source #

Interval CInt l r => Shove CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

shove :: CInt -> I CInt l r Source #

Interval CIntMax l r => Shove CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

shove :: CIntMax -> I CIntMax l r Source #

Interval CIntPtr l r => Shove CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

shove :: CIntPtr -> I CIntPtr l r Source #

Interval CLLong l r => Shove CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

shove :: CLLong -> I CLLong l r Source #

Interval CLong l r => Shove CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

shove :: CLong -> I CLong l r Source #

Interval CPtrdiff l r => Shove CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

shove :: CPtrdiff -> I CPtrdiff l r Source #

Interval CSChar l r => Shove CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

shove :: CSChar -> I CSChar l r Source #

Interval CShort l r => Shove CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

shove :: CShort -> I CShort l r Source #

Interval CSize l r => Shove CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

shove :: CSize -> I CSize l r Source #

Interval CUChar l r => Shove CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

shove :: CUChar -> I CUChar l r Source #

Interval CUInt l r => Shove CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

shove :: CUInt -> I CUInt l r Source #

Interval CUIntMax l r => Shove CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

shove :: CUIntMax -> I CUIntMax l r Source #

Interval CUIntPtr l r => Shove CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

shove :: CUIntPtr -> I CUIntPtr l r Source #

Interval CULLong l r => Shove CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

shove :: CULLong -> I CULLong l r Source #

Interval CULong l r => Shove CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

shove :: CULong -> I CULong l r Source #

Interval CUShort l r => Shove CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

shove :: CUShort -> I CUShort l r Source #

Interval CWchar l r => Shove CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

shove :: CWchar -> I CWchar l r Source #

Interval Int16 l r => Shove Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

shove :: Int16 -> I Int16 l r Source #

Interval Int32 l r => Shove Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

shove :: Int32 -> I Int32 l r Source #

Interval Int64 l r => Shove Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

shove :: Int64 -> I Int64 l r Source #

Interval Int8 l r => Shove Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

shove :: Int8 -> I Int8 l r Source #

Interval Word16 l r => Shove Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

shove :: Word16 -> I Word16 l r Source #

Interval Word32 l r => Shove Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

shove :: Word32 -> I Word32 l r Source #

Interval Word64 l r => Shove Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

shove :: Word64 -> I Word64 l r Source #

Interval Word8 l r => Shove Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

shove :: Word8 -> I Word8 l r Source #

Interval Int l r => Shove Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

shove :: Int -> I Int l r Source #

Interval Word l r => Shove Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

shove :: Word -> I Word l r Source #

Interval CChar l r => With CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

with :: I CChar l r -> (forall (t :: T CChar). Known CChar l r t => Proxy t -> b) -> b Source #

Interval CInt l r => With CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

with :: I CInt l r -> (forall (t :: T CInt). Known CInt l r t => Proxy t -> b) -> b Source #

Interval CIntMax l r => With CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

with :: I CIntMax l r -> (forall (t :: T CIntMax). Known CIntMax l r t => Proxy t -> b) -> b Source #

Interval CIntPtr l r => With CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

with :: I CIntPtr l r -> (forall (t :: T CIntPtr). Known CIntPtr l r t => Proxy t -> b) -> b Source #

Interval CLLong l r => With CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

with :: I CLLong l r -> (forall (t :: T CLLong). Known CLLong l r t => Proxy t -> b) -> b Source #

Interval CLong l r => With CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

with :: I CLong l r -> (forall (t :: T CLong). Known CLong l r t => Proxy t -> b) -> b Source #

Interval CPtrdiff l r => With CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

with :: I CPtrdiff l r -> (forall (t :: T CPtrdiff). Known CPtrdiff l r t => Proxy t -> b) -> b Source #

Interval CSChar l r => With CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

with :: I CSChar l r -> (forall (t :: T CSChar). Known CSChar l r t => Proxy t -> b) -> b Source #

Interval CShort l r => With CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

with :: I CShort l r -> (forall (t :: T CShort). Known CShort l r t => Proxy t -> b) -> b Source #

Interval CSize l r => With CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

with :: I CSize l r -> (forall (t :: T CSize). Known CSize l r t => Proxy t -> b) -> b Source #

Interval CUChar l r => With CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

with :: I CUChar l r -> (forall (t :: T CUChar). Known CUChar l r t => Proxy t -> b) -> b Source #

Interval CUInt l r => With CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

with :: I CUInt l r -> (forall (t :: T CUInt). Known CUInt l r t => Proxy t -> b) -> b Source #

Interval CUIntMax l r => With CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

with :: I CUIntMax l r -> (forall (t :: T CUIntMax). Known CUIntMax l r t => Proxy t -> b) -> b Source #

Interval CUIntPtr l r => With CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

with :: I CUIntPtr l r -> (forall (t :: T CUIntPtr). Known CUIntPtr l r t => Proxy t -> b) -> b Source #

Interval CULLong l r => With CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

with :: I CULLong l r -> (forall (t :: T CULLong). Known CULLong l r t => Proxy t -> b) -> b Source #

Interval CULong l r => With CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

with :: I CULong l r -> (forall (t :: T CULong). Known CULong l r t => Proxy t -> b) -> b Source #

Interval CUShort l r => With CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

with :: I CUShort l r -> (forall (t :: T CUShort). Known CUShort l r t => Proxy t -> b) -> b Source #

Interval CWchar l r => With CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

with :: I CWchar l r -> (forall (t :: T CWchar). Known CWchar l r t => Proxy t -> b) -> b Source #

Interval Int16 l r => With Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

with :: I Int16 l r -> (forall (t :: T Int16). Known Int16 l r t => Proxy t -> b) -> b Source #

Interval Int32 l r => With Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

with :: I Int32 l r -> (forall (t :: T Int32). Known Int32 l r t => Proxy t -> b) -> b Source #

Interval Int64 l r => With Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

with :: I Int64 l r -> (forall (t :: T Int64). Known Int64 l r t => Proxy t -> b) -> b Source #

Interval Int8 l r => With Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

with :: I Int8 l r -> (forall (t :: T Int8). Known Int8 l r t => Proxy t -> b) -> b Source #

Interval Word16 l r => With Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

with :: I Word16 l r -> (forall (t :: T Word16). Known Word16 l r t => Proxy t -> b) -> b Source #

Interval Word32 l r => With Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

with :: I Word32 l r -> (forall (t :: T Word32). Known Word32 l r t => Proxy t -> b) -> b Source #

Interval Word64 l r => With Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

with :: I Word64 l r -> (forall (t :: T Word64). Known Word64 l r t => Proxy t -> b) -> b Source #

Interval Word8 l r => With Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

with :: I Word8 l r -> (forall (t :: T Word8). Known Word8 l r t => Proxy t -> b) -> b Source #

Interval Int l r => With Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

with :: I Int l r -> (forall (t :: T Int). Known Int l r t => Proxy t -> b) -> b Source #

Interval Word l r => With Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

with :: I Word l r -> (forall (t :: T Word). Known Word l r t => Proxy t -> b) -> b Source #

(Interval CChar l r, l <= P 0, P 0 <= r) => Zero CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

zero :: I CChar l r Source #

(Interval CInt l r, l <= P 0, P 0 <= r) => Zero CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

zero :: I CInt l r Source #

(Interval CIntMax l r, l <= P 0, P 0 <= r) => Zero CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

zero :: I CIntMax l r Source #

(Interval CIntPtr l r, l <= P 0, P 0 <= r) => Zero CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

zero :: I CIntPtr l r Source #

(Interval CLLong l r, l <= P 0, P 0 <= r) => Zero CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

zero :: I CLLong l r Source #

(Interval CLong l r, l <= P 0, P 0 <= r) => Zero CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

zero :: I CLong l r Source #

(Interval CPtrdiff l r, l <= P 0, P 0 <= r) => Zero CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

zero :: I CPtrdiff l r Source #

(Interval CSChar l r, l <= P 0, P 0 <= r) => Zero CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

zero :: I CSChar l r Source #

(Interval CShort l r, l <= P 0, P 0 <= r) => Zero CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

zero :: I CShort l r Source #

Interval CSize 0 r => Zero CSize 0 (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

zero :: I CSize 0 r Source #

Interval CUChar 0 r => Zero CUChar 0 (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

zero :: I CUChar 0 r Source #

Interval CUInt 0 r => Zero CUInt 0 (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

zero :: I CUInt 0 r Source #

Interval CUIntMax 0 r => Zero CUIntMax 0 (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

zero :: I CUIntMax 0 r Source #

Interval CUIntPtr 0 r => Zero CUIntPtr 0 (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

zero :: I CUIntPtr 0 r Source #

Interval CULLong 0 r => Zero CULLong 0 (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

zero :: I CULLong 0 r Source #

Interval CULong 0 r => Zero CULong 0 (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

zero :: I CULong 0 r Source #

Interval CUShort 0 r => Zero CUShort 0 (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

zero :: I CUShort 0 r Source #

(Interval CWchar l r, l <= P 0, P 0 <= r) => Zero CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

zero :: I CWchar l r Source #

(Interval Int16 l r, l <= P 0, P 0 <= r) => Zero Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

zero :: I Int16 l r Source #

(Interval Int32 l r, l <= P 0, P 0 <= r) => Zero Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

zero :: I Int32 l r Source #

(Interval Int64 l r, l <= P 0, P 0 <= r) => Zero Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

zero :: I Int64 l r Source #

(Interval Int8 l r, l <= P 0, P 0 <= r) => Zero Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

zero :: I Int8 l r Source #

Interval Word16 0 r => Zero Word16 0 (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

zero :: I Word16 0 r Source #

Interval Word32 0 r => Zero Word32 0 (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

zero :: I Word32 0 r Source #

Interval Word64 0 r => Zero Word64 0 (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

zero :: I Word64 0 r Source #

Interval Word8 0 r => Zero Word8 0 (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

zero :: I Word8 0 r Source #

Interval Natural 0 r => Zero Natural 0 (r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

zero :: I Natural 0 r Source #

(Interval Int l r, l <= P 0, P 0 <= r) => Zero Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

zero :: I Int l r Source #

Interval Word 0 r => Zero Word 0 (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

zero :: I Word 0 r Source #

(Interval CChar l r, KnownCtx CChar l r t) => Known CChar (l :: L CChar :: Type) (r :: R CChar :: Type) (t :: T CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Associated Types

type KnownCtx CChar l r t Source #

Methods

known' :: Proxy t -> I CChar l r Source #

(Interval CInt l r, KnownCtx CInt l r t) => Known CInt (l :: L CInt :: Type) (r :: R CInt :: Type) (t :: T CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Associated Types

type KnownCtx CInt l r t Source #

Methods

known' :: Proxy t -> I CInt l r Source #

(Interval CIntMax l r, KnownCtx CIntMax l r t) => Known CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) (t :: T CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Associated Types

type KnownCtx CIntMax l r t Source #

Methods

known' :: Proxy t -> I CIntMax l r Source #

(Interval CIntPtr l r, KnownCtx CIntPtr l r t) => Known CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) (t :: T CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Associated Types

type KnownCtx CIntPtr l r t Source #

Methods

known' :: Proxy t -> I CIntPtr l r Source #

(Interval CLLong l r, KnownCtx CLLong l r t) => Known CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) (t :: T CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Associated Types

type KnownCtx CLLong l r t Source #

Methods

known' :: Proxy t -> I CLLong l r Source #

(Interval CLong l r, KnownCtx CLong l r t) => Known CLong (l :: L CLong :: Type) (r :: R CLong :: Type) (t :: T CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Associated Types

type KnownCtx CLong l r t Source #

Methods

known' :: Proxy t -> I CLong l r Source #

(Interval CPtrdiff l r, KnownCtx CPtrdiff l r t) => Known CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) (t :: T CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Associated Types

type KnownCtx CPtrdiff l r t Source #

Methods

known' :: Proxy t -> I CPtrdiff l r Source #

(Interval CSChar l r, KnownCtx CSChar l r t) => Known CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) (t :: T CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Associated Types

type KnownCtx CSChar l r t Source #

Methods

known' :: Proxy t -> I CSChar l r Source #

(Interval CShort l r, KnownCtx CShort l r t) => Known CShort (l :: L CShort :: Type) (r :: R CShort :: Type) (t :: T CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Associated Types

type KnownCtx CShort l r t Source #

Methods

known' :: Proxy t -> I CShort l r Source #

(Interval CSize l r, KnownCtx CSize l r t) => Known CSize (l :: L CSize :: Type) (r :: R CSize :: Type) (t :: T CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Associated Types

type KnownCtx CSize l r t Source #

Methods

known' :: Proxy t -> I CSize l r Source #

(Interval CUChar l r, KnownCtx CUChar l r t) => Known CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) (t :: T CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Associated Types

type KnownCtx CUChar l r t Source #

Methods

known' :: Proxy t -> I CUChar l r Source #

(Interval CUInt l r, KnownCtx CUInt l r t) => Known CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) (t :: T CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Associated Types

type KnownCtx CUInt l r t Source #

Methods

known' :: Proxy t -> I CUInt l r Source #

(Interval CUIntMax l r, KnownCtx CUIntMax l r t) => Known CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) (t :: T CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Associated Types

type KnownCtx CUIntMax l r t Source #

Methods

known' :: Proxy t -> I CUIntMax l r Source #

(Interval CUIntPtr l r, KnownCtx CUIntPtr l r t) => Known CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) (t :: T CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Associated Types

type KnownCtx CUIntPtr l r t Source #

Methods

known' :: Proxy t -> I CUIntPtr l r Source #

(Interval CULLong l r, KnownCtx CULLong l r t) => Known CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) (t :: T CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Associated Types

type KnownCtx CULLong l r t Source #

Methods

known' :: Proxy t -> I CULLong l r Source #

(Interval CULong l r, KnownCtx CULong l r t) => Known CULong (l :: L CULong :: Type) (r :: R CULong :: Type) (t :: T CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Associated Types

type KnownCtx CULong l r t Source #

Methods

known' :: Proxy t -> I CULong l r Source #

(Interval CUShort l r, KnownCtx CUShort l r t) => Known CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) (t :: T CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Associated Types

type KnownCtx CUShort l r t Source #

Methods

known' :: Proxy t -> I CUShort l r Source #

(Interval CWchar l r, KnownCtx CWchar l r t) => Known CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) (t :: T CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Associated Types

type KnownCtx CWchar l r t Source #

Methods

known' :: Proxy t -> I CWchar l r Source #

(Interval Int16 l r, KnownCtx Int16 l r t) => Known Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) (t :: T Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Associated Types

type KnownCtx Int16 l r t Source #

Methods

known' :: Proxy t -> I Int16 l r Source #

(Interval Int32 l r, KnownCtx Int32 l r t) => Known Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) (t :: T Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Associated Types

type KnownCtx Int32 l r t Source #

Methods

known' :: Proxy t -> I Int32 l r Source #

(Interval Int64 l r, KnownCtx Int64 l r t) => Known Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) (t :: T Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Associated Types

type KnownCtx Int64 l r t Source #

Methods

known' :: Proxy t -> I Int64 l r Source #

(Interval Int8 l r, KnownCtx Int8 l r t) => Known Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) (t :: T Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Associated Types

type KnownCtx Int8 l r t Source #

Methods

known' :: Proxy t -> I Int8 l r Source #

(Interval Word16 l r, KnownCtx Word16 l r t) => Known Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) (t :: T Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Associated Types

type KnownCtx Word16 l r t Source #

Methods

known' :: Proxy t -> I Word16 l r Source #

(Interval Word32 l r, KnownCtx Word32 l r t) => Known Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) (t :: T Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Associated Types

type KnownCtx Word32 l r t Source #

Methods

known' :: Proxy t -> I Word32 l r Source #

(Interval Word64 l r, KnownCtx Word64 l r t) => Known Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) (t :: T Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Associated Types

type KnownCtx Word64 l r t Source #

Methods

known' :: Proxy t -> I Word64 l r Source #

(Interval Word8 l r, KnownCtx Word8 l r t) => Known Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) (t :: T Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Associated Types

type KnownCtx Word8 l r t Source #

Methods

known' :: Proxy t -> I Word8 l r Source #

(Interval Int l r, KnownCtx Int l r t) => Known Int (l :: L Int :: Type) (r :: R Int :: Type) (t :: T Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Associated Types

type KnownCtx Int l r t Source #

Methods

known' :: Proxy t -> I Int l r Source #

(Interval Word l r, KnownCtx Word l r t) => Known Word (l :: L Word :: Type) (r :: R Word :: Type) (t :: T Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Associated Types

type KnownCtx Word l r t Source #

Methods

known' :: Proxy t -> I Word l r Source #

(Interval CChar ld rd, Interval CChar lu ru, lu <= ld, rd <= ru) => Up CChar (ld :: L CChar :: Type) (rd :: R CChar :: Type) (lu :: L CChar :: Type) (ru :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

up :: I CChar ld rd -> I CChar lu ru Source #

(Interval CInt ld rd, Interval CInt lu ru, lu <= ld, rd <= ru) => Up CInt (ld :: L CInt :: Type) (rd :: R CInt :: Type) (lu :: L CInt :: Type) (ru :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

up :: I CInt ld rd -> I CInt lu ru Source #

(Interval CIntMax ld rd, Interval CIntMax lu ru, lu <= ld, rd <= ru) => Up CIntMax (ld :: L CIntMax :: Type) (rd :: R CIntMax :: Type) (lu :: L CIntMax :: Type) (ru :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

up :: I CIntMax ld rd -> I CIntMax lu ru Source #

(Interval CIntPtr ld rd, Interval CIntPtr lu ru, lu <= ld, rd <= ru) => Up CIntPtr (ld :: L CIntPtr :: Type) (rd :: R CIntPtr :: Type) (lu :: L CIntPtr :: Type) (ru :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

up :: I CIntPtr ld rd -> I CIntPtr lu ru Source #

(Interval CLLong ld rd, Interval CLLong lu ru, lu <= ld, rd <= ru) => Up CLLong (ld :: L CLLong :: Type) (rd :: R CLLong :: Type) (lu :: L CLLong :: Type) (ru :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

up :: I CLLong ld rd -> I CLLong lu ru Source #

(Interval CLong ld rd, Interval CLong lu ru, lu <= ld, rd <= ru) => Up CLong (ld :: L CLong :: Type) (rd :: R CLong :: Type) (lu :: L CLong :: Type) (ru :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

up :: I CLong ld rd -> I CLong lu ru Source #

(Interval CPtrdiff ld rd, Interval CPtrdiff lu ru, lu <= ld, rd <= ru) => Up CPtrdiff (ld :: L CPtrdiff :: Type) (rd :: R CPtrdiff :: Type) (lu :: L CPtrdiff :: Type) (ru :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

up :: I CPtrdiff ld rd -> I CPtrdiff lu ru Source #

(Interval CSChar ld rd, Interval CSChar lu ru, lu <= ld, rd <= ru) => Up CSChar (ld :: L CSChar :: Type) (rd :: R CSChar :: Type) (lu :: L CSChar :: Type) (ru :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

up :: I CSChar ld rd -> I CSChar lu ru Source #

(Interval CShort ld rd, Interval CShort lu ru, lu <= ld, rd <= ru) => Up CShort (ld :: L CShort :: Type) (rd :: R CShort :: Type) (lu :: L CShort :: Type) (ru :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

up :: I CShort ld rd -> I CShort lu ru Source #

(Interval CSize ld rd, Interval CSize lu ru, lu <= ld, rd <= ru) => Up CSize (ld :: L CSize :: Type) (rd :: R CSize :: Type) (lu :: L CSize :: Type) (ru :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

up :: I CSize ld rd -> I CSize lu ru Source #

(Interval CUChar ld rd, Interval CUChar lu ru, lu <= ld, rd <= ru) => Up CUChar (ld :: L CUChar :: Type) (rd :: R CUChar :: Type) (lu :: L CUChar :: Type) (ru :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

up :: I CUChar ld rd -> I CUChar lu ru Source #

(Interval CUInt ld rd, Interval CUInt lu ru, lu <= ld, rd <= ru) => Up CUInt (ld :: L CUInt :: Type) (rd :: R CUInt :: Type) (lu :: L CUInt :: Type) (ru :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

up :: I CUInt ld rd -> I CUInt lu ru Source #

(Interval CUIntMax ld rd, Interval CUIntMax lu ru, lu <= ld, rd <= ru) => Up CUIntMax (ld :: L CUIntMax :: Type) (rd :: R CUIntMax :: Type) (lu :: L CUIntMax :: Type) (ru :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

up :: I CUIntMax ld rd -> I CUIntMax lu ru Source #

(Interval CUIntPtr ld rd, Interval CUIntPtr lu ru, lu <= ld, rd <= ru) => Up CUIntPtr (ld :: L CUIntPtr :: Type) (rd :: R CUIntPtr :: Type) (lu :: L CUIntPtr :: Type) (ru :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

up :: I CUIntPtr ld rd -> I CUIntPtr lu ru Source #

(Interval CULLong ld rd, Interval CULLong lu ru, lu <= ld, rd <= ru) => Up CULLong (ld :: L CULLong :: Type) (rd :: R CULLong :: Type) (lu :: L CULLong :: Type) (ru :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

up :: I CULLong ld rd -> I CULLong lu ru Source #

(Interval CULong ld rd, Interval CULong lu ru, lu <= ld, rd <= ru) => Up CULong (ld :: L CULong :: Type) (rd :: R CULong :: Type) (lu :: L CULong :: Type) (ru :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

up :: I CULong ld rd -> I CULong lu ru Source #

(Interval CUShort ld rd, Interval CUShort lu ru, lu <= ld, rd <= ru) => Up CUShort (ld :: L CUShort :: Type) (rd :: R CUShort :: Type) (lu :: L CUShort :: Type) (ru :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

up :: I CUShort ld rd -> I CUShort lu ru Source #

(Interval CWchar ld rd, Interval CWchar lu ru, lu <= ld, rd <= ru) => Up CWchar (ld :: L CWchar :: Type) (rd :: R CWchar :: Type) (lu :: L CWchar :: Type) (ru :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

up :: I CWchar ld rd -> I CWchar lu ru Source #

(Interval Int16 ld rd, Interval Int16 lu ru, lu <= ld, rd <= ru) => Up Int16 (ld :: L Int16 :: Type) (rd :: R Int16 :: Type) (lu :: L Int16 :: Type) (ru :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

up :: I Int16 ld rd -> I Int16 lu ru Source #

(Interval Int32 ld rd, Interval Int32 lu ru, lu <= ld, rd <= ru) => Up Int32 (ld :: L Int32 :: Type) (rd :: R Int32 :: Type) (lu :: L Int32 :: Type) (ru :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

up :: I Int32 ld rd -> I Int32 lu ru Source #

(Interval Int64 ld rd, Interval Int64 lu ru, lu <= ld, rd <= ru) => Up Int64 (ld :: L Int64 :: Type) (rd :: R Int64 :: Type) (lu :: L Int64 :: Type) (ru :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

up :: I Int64 ld rd -> I Int64 lu ru Source #

(Interval Int8 ld rd, Interval Int8 lu ru, lu <= ld, rd <= ru) => Up Int8 (ld :: L Int8 :: Type) (rd :: R Int8 :: Type) (lu :: L Int8 :: Type) (ru :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

up :: I Int8 ld rd -> I Int8 lu ru Source #

(Interval Word16 ld rd, Interval Word16 lu ru, lu <= ld, rd <= ru) => Up Word16 (ld :: L Word16 :: Type) (rd :: R Word16 :: Type) (lu :: L Word16 :: Type) (ru :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

up :: I Word16 ld rd -> I Word16 lu ru Source #

(Interval Word32 ld rd, Interval Word32 lu ru, lu <= ld, rd <= ru) => Up Word32 (ld :: L Word32 :: Type) (rd :: R Word32 :: Type) (lu :: L Word32 :: Type) (ru :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

up :: I Word32 ld rd -> I Word32 lu ru Source #

(Interval Word64 ld rd, Interval Word64 lu ru, lu <= ld, rd <= ru) => Up Word64 (ld :: L Word64 :: Type) (rd :: R Word64 :: Type) (lu :: L Word64 :: Type) (ru :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

up :: I Word64 ld rd -> I Word64 lu ru Source #

(Interval Word8 ld rd, Interval Word8 lu ru, lu <= ld, rd <= ru) => Up Word8 (ld :: L Word8 :: Type) (rd :: R Word8 :: Type) (lu :: L Word8 :: Type) (ru :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

up :: I Word8 ld rd -> I Word8 lu ru Source #

(Interval Int ld rd, Interval Int lu ru, lu <= ld, rd <= ru) => Up Int (ld :: L Int :: Type) (rd :: R Int :: Type) (lu :: L Int :: Type) (ru :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

up :: I Int ld rd -> I Int lu ru Source #

(Interval Word ld rd, Interval Word lu ru, lu <= ld, rd <= ru) => Up Word (ld :: L Word :: Type) (rd :: R Word :: Type) (lu :: L Word :: Type) (ru :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

up :: I Word ld rd -> I Word lu ru Source #

(lu <= ld, Interval Natural ld yrd, Interval Natural lu ('Nothing :: Maybe Natural)) => Up Natural (ld :: L Natural :: Type) (yrd :: R Natural :: Type) (lu :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Methods

up :: I Natural ld yrd -> I Natural lu 'Nothing Source #

(Interval Rational yld yrd, Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational))) => Up Rational (yld :: L Rational :: Type) (yrd :: R Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 yld yrd -> I Rational0 'Nothing 'Nothing Source #

(Interval Integer yld yrd, Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer)) => Up Integer (yld :: L Integer :: Type) (yrd :: R Integer :: Type) ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

up :: I Integer0 yld yrd -> I Integer0 'Nothing 'Nothing Source #

Interval Natural l ('Nothing :: Maybe Natural) => Clamp Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Interval Natural l ('Nothing :: Maybe Natural) => Discrete Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

IntervalCtx Natural l ('Nothing :: Maybe Natural) => Interval Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Associated Types

type IntervalCtx Natural l 'Nothing Source #

type MinI Natural l 'Nothing :: T x :: Type Source #

type MaxI Natural l 'Nothing :: T x :: Type Source #

Interval Natural l ('Nothing :: Maybe Natural) => Mult Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

(Interval Natural l ('Nothing :: Maybe Natural), l <= 1) => One Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Methods

one :: I Natural l 'Nothing Source #

Interval Natural l ('Nothing :: Maybe Natural) => Plus Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Interval Natural l ('Nothing :: Maybe Natural) => Shove Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Discrete Integer l ('Nothing :: Maybe Integer) => Succ Integer (l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Discrete Natural l ('Nothing :: Maybe Natural) => Succ Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Interval Natural l ('Nothing :: Maybe Natural) => With Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Methods

with :: I Natural l 'Nothing -> (forall (t :: T Natural). Known Natural l 'Nothing t => Proxy t -> b) -> b Source #

(Interval Natural l ('Nothing :: Maybe Natural), KnownCtx Natural l ('Nothing :: Maybe Natural) t) => Known Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

Associated Types

type KnownCtx Natural l 'Nothing t Source #

Methods

known' :: Proxy t -> I Natural l 'Nothing Source #

Interval Natural l ('Just r) => Clamp Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

clamp :: Natural -> I Natural l ('Just r) Source #

(Interval Natural l ('Just r), l /= r) => Discrete Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

pred' :: I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

succ' :: I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

IntervalCtx Natural l ('Just r) => Interval Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Associated Types

type IntervalCtx Natural l ('Just r) Source #

type MinI Natural l ('Just r) :: T x :: Type Source #

type MaxI Natural l ('Just r) :: T x :: Type Source #

Methods

inhabitant :: I Natural l ('Just r) Source #

from :: Natural -> Maybe (I Natural l ('Just r)) Source #

plus' :: I Natural l ('Just r) -> I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

mult' :: I Natural l ('Just r) -> I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

minus' :: I Natural l ('Just r) -> I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

negate' :: I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

recip' :: I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

div' :: I Natural l ('Just r) -> I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

(Interval Natural l ('Just r), l <= 1, 1 <= r) => One Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

one :: I Natural l ('Just r) Source #

Interval Natural l ('Just r) => Shove Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

shove :: Natural -> I Natural l ('Just r) Source #

Interval Natural l ('Just r) => With Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

with :: I Natural l ('Just r) -> (forall (t :: T Natural). Known Natural l ('Just r) t => Proxy t -> b) -> b Source #

(Interval Natural l ('Just r), KnownCtx Natural l ('Just r) t) => Known Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

Associated Types

type KnownCtx Natural l ('Just r) t Source #

Methods

known' :: Proxy t -> I Natural l ('Just r) Source #

(lu <= ld, rd <= ru, Interval Natural ld ('Just rd), Interval Natural lu ('Just ru)) => Up Natural (ld :: L Natural :: Type) ('Just rd :: R Natural :: Type) (lu :: L Natural :: Type) ('Just ru :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

up :: I Natural ld ('Just rd) -> I Natural lu ('Just ru) Source #

(Interval Rational yld ('Just '('False, rd)), Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, ru)), ru <= rd) => Up Rational (yld :: L Rational :: Type) ('Just '('False, rd) :: R Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 yld ('Just '('False, rd)) -> I Rational0 'Nothing ('Just '('False, ru)) Source #

(Interval Rational yld ('Just '(ird, rd)), Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, ru)), ru <= rd) => Up Rational (yld :: L Rational :: Type) ('Just '(ird, rd) :: R Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 yld ('Just '(ird, rd)) -> I Rational0 'Nothing ('Just '('True, ru)) Source #

(rd <= ru, Interval Integer yld ('Just rd), Interval Integer ('Nothing :: Maybe Integer) ('Just ru)) => Up Integer (yld :: L Integer :: Type) ('Just rd :: R Integer :: Type) ('Nothing :: Maybe Integer) ('Just ru :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

up :: I Integer0 yld ('Just rd) -> I Integer0 'Nothing ('Just ru) Source #

Discrete Integer ('Nothing :: Maybe Integer) r => Pred Integer ('Nothing :: Maybe Integer) (r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) => Clamp Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) => Clamp Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Discrete Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Minus Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Minus Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Mult Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Mult Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Negate Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Negate Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

One Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

One Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Plus Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Plus Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Shove Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) => Shove Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

With Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 'Nothing 'Nothing -> (forall (t :: T Rational0). Known Rational0 'Nothing 'Nothing t => Proxy t -> b) -> b Source #

With Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

with :: I Integer0 'Nothing 'Nothing -> (forall (t :: T Integer0). Known Integer0 'Nothing 'Nothing t => Proxy t -> b) -> b Source #

Zero Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Zero Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) t => Known Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational 'Nothing 'Nothing t Source #

KnownCtx Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) t => Known Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer 'Nothing 'Nothing t Source #

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) => Clamp Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

clamp :: Rational0 -> I Rational0 'Nothing ('Just '('True, r)) Source #

Interval Integer ('Nothing :: Maybe Integer) ('Just r) => Clamp Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Interval Integer ('Nothing :: Maybe Integer) ('Just r) => Discrete Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

IntervalCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)) => Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational 'Nothing ('Just '('False, r)) Source #

type MinI Rational 'Nothing ('Just '('False, r)) :: T x :: Type Source #

type MaxI Rational 'Nothing ('Just '('False, r)) :: T x :: Type Source #

IntervalCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) => Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational 'Nothing ('Just '('True, r)) Source #

type MinI Rational 'Nothing ('Just '('True, r)) :: T x :: Type Source #

type MaxI Rational 'Nothing ('Just '('True, r)) :: T x :: Type Source #

IntervalCtx Integer ('Nothing :: Maybe Integer) ('Just r) => Interval Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type IntervalCtx Integer 'Nothing ('Just r) Source #

type MinI Integer 'Nothing ('Just r) :: T x :: Type Source #

type MaxI Integer 'Nothing ('Just r) :: T x :: Type Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)), (1 / 1) < r) => One Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational0 'Nothing ('Just '('False, r)) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)), (1 / 1) <= r) => One Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational0 'Nothing ('Just '('True, r)) Source #

(Interval Integer ('Nothing :: Maybe Integer) ('Just r), P 1 <= r) => One Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

one :: I Integer0 'Nothing ('Just r) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '(ir, r)), r <= (0 / 1)) => Plus Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '(ir, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

plus :: I Rational0 'Nothing ('Just '(ir, r)) -> I Rational0 'Nothing ('Just '(ir, r)) -> I Rational0 'Nothing ('Just '(ir, r)) Source #

(Interval Integer ('Nothing :: Maybe Integer) ('Just r), r <= P 0) => Plus Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

plus :: I Integer0 'Nothing ('Just r) -> I Integer0 'Nothing ('Just r) -> I Integer0 'Nothing ('Just r) Source #

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)) => Shove Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational0 -> I Rational0 'Nothing ('Just '('False, r)) Source #

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) => Shove Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational0 -> I Rational0 'Nothing ('Just '('True, r)) Source #

Interval Integer ('Nothing :: Maybe Integer) ('Just r) => Shove Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)) => With Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 'Nothing ('Just '('False, r)) -> (forall (t :: T Rational0). Known Rational0 'Nothing ('Just '('False, r)) t => Proxy t -> b) -> b Source #

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) => With Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 'Nothing ('Just '('True, r)) -> (forall (t :: T Rational0). Known Rational0 'Nothing ('Just '('True, r)) t => Proxy t -> b) -> b Source #

Interval Integer ('Nothing :: Maybe Integer) ('Just r) => With Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

with :: I Integer0 'Nothing ('Just r) -> (forall (t :: T Integer0). Known Integer0 'Nothing ('Just r) t => Proxy t -> b) -> b Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)), (0 / 1) < r) => Zero Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational0 'Nothing ('Just '('False, r)) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)), (0 / 1) <= r) => Zero Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational0 'Nothing ('Just '('True, r)) Source #

(Interval Integer ('Nothing :: Maybe Integer) ('Just r), P 0 <= r) => Zero Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

zero :: I Integer0 'Nothing ('Just r) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)), KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)) t) => Known Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational 'Nothing ('Just '('False, r)) t Source #

Methods

known' :: Proxy t -> I Rational0 'Nothing ('Just '('False, r)) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)), KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) t) => Known Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational 'Nothing ('Just '('True, r)) t Source #

Methods

known' :: Proxy t -> I Rational0 'Nothing ('Just '('True, r)) Source #

(Interval Integer ('Nothing :: Maybe Integer) ('Just r), KnownCtx Integer ('Nothing :: Maybe Integer) ('Just r) t) => Known Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer 'Nothing ('Just r) t Source #

Methods

known' :: Proxy t -> I Integer0 'Nothing ('Just r) Source #

(Interval Rational ('Just '('False, ld)) yrd, Interval Rational ('Just '('False, lu)) ('Nothing :: Maybe (Bool, Rational)), lu <= ld) => Up Rational ('Just '('False, ld) :: L Rational :: Type) (yrd :: R Rational :: Type) ('Just '('False, lu) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 ('Just '('False, ld)) yrd -> I Rational0 ('Just '('False, lu)) 'Nothing Source #

(Interval Rational ('Just '(ild, ld)) yrd, Interval Rational ('Just '('True, lu)) ('Nothing :: Maybe (Bool, Rational)), lu <= ld) => Up Rational ('Just '(ild, ld) :: L Rational :: Type) (yrd :: R Rational :: Type) ('Just '('True, lu) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 ('Just '(ild, ld)) yrd -> I Rational0 ('Just '('True, lu)) 'Nothing Source #

(lu <= ld, Interval Integer ('Just ld) yrd, Interval Integer ('Just lu) ('Nothing :: Maybe Integer)) => Up Integer ('Just ld :: L Integer :: Type) (yrd :: R Integer :: Type) ('Just lu :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

up :: I Integer0 ('Just ld) yrd -> I Integer0 ('Just lu) 'Nothing Source #

Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) => Clamp Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

clamp :: Rational0 -> I Rational0 ('Just '('True, l)) 'Nothing Source #

Interval Integer ('Just l) ('Nothing :: Maybe Integer) => Clamp Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Interval Integer ('Just l) ('Nothing :: Maybe Integer) => Discrete Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

IntervalCtx Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)) => Interval Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('False, l)) 'Nothing Source #

type MinI Rational ('Just '('False, l)) 'Nothing :: T x :: Type Source #

type MaxI Rational ('Just '('False, l)) 'Nothing :: T x :: Type Source #

IntervalCtx Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) => Interval Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('True, l)) 'Nothing Source #

type MinI Rational ('Just '('True, l)) 'Nothing :: T x :: Type Source #

type MaxI Rational ('Just '('True, l)) 'Nothing :: T x :: Type Source #

IntervalCtx Integer ('Just l) ('Nothing :: Maybe Integer) => Interval Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Associated Types

type IntervalCtx Integer ('Just l) 'Nothing Source #

type MinI Integer ('Just l) 'Nothing :: T x :: Type Source #

type MaxI Integer ('Just l) 'Nothing :: T x :: Type Source #

(Interval Rational ('Just '(il, l)) ('Nothing :: Maybe (Bool, Rational)), (1 / 1) <= l) => Mult Rational ('Just '(il, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

mult :: I Rational0 ('Just '(il, l)) 'Nothing -> I Rational0 ('Just '(il, l)) 'Nothing -> I Rational0 ('Just '(il, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), P 0 <= l) => Mult Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

mult :: I Integer0 ('Just l) 'Nothing -> I Integer0 ('Just l) 'Nothing -> I Integer0 ('Just l) 'Nothing Source #

(Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)), l < (1 / 1)) => One Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational0 ('Just '('False, l)) 'Nothing Source #

(Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)), l <= (1 / 1)) => One Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational0 ('Just '('True, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), l <= P 1) => One Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

one :: I Integer0 ('Just l) 'Nothing Source #

(Interval Rational ('Just '(il, l)) ('Nothing :: Maybe (Bool, Rational)), (0 / 1) <= l) => Plus Rational ('Just '(il, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

plus :: I Rational0 ('Just '(il, l)) 'Nothing -> I Rational0 ('Just '(il, l)) 'Nothing -> I Rational0 ('Just '(il, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), P 0 <= l) => Plus Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

plus :: I Integer0 ('Just l) 'Nothing -> I Integer0 ('Just l) 'Nothing -> I Integer0 ('Just l) 'Nothing Source #

Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)) => Shove Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational0 -> I Rational0 ('Just '('False, l)) 'Nothing Source #

Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) => Shove Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational0 -> I Rational0 ('Just '('True, l)) 'Nothing Source #

Interval Integer ('Just l) ('Nothing :: Maybe Integer) => Shove Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)) => With Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 ('Just '('False, l)) 'Nothing -> (forall (t :: T Rational0). Known Rational0 ('Just '('False, l)) 'Nothing t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) => With Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 ('Just '('True, l)) 'Nothing -> (forall (t :: T Rational0). Known Rational0 ('Just '('True, l)) 'Nothing t => Proxy t -> b) -> b Source #

Interval Integer ('Just l) ('Nothing :: Maybe Integer) => With Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

with :: I Integer0 ('Just l) 'Nothing -> (forall (t :: T Integer0). Known Integer0 ('Just l) 'Nothing t => Proxy t -> b) -> b Source #

(Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)), l < (0 / 1)) => Zero Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational0 ('Just '('False, l)) 'Nothing Source #

(Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)), l <= (0 / 1)) => Zero Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational0 ('Just '('True, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), l <= P 0) => Zero Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

zero :: I Integer0 ('Just l) 'Nothing Source #

(Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)), KnownCtx Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)) t) => Known Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('False, l)) 'Nothing t Source #

Methods

known' :: Proxy t -> I Rational0 ('Just '('False, l)) 'Nothing Source #

(Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)), KnownCtx Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) t) => Known Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('True, l)) 'Nothing t Source #

Methods

known' :: Proxy t -> I Rational0 ('Just '('True, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), KnownCtx Integer ('Just l) ('Nothing :: Maybe Integer) t) => Known Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer ('Just l) 'Nothing t Source #

Methods

known' :: Proxy t -> I Integer0 ('Just l) 'Nothing Source #

Interval Rational ('Just '('True, l)) ('Just '('True, r)) => Clamp Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

clamp :: Rational -> I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

Interval Integer ('Just l) ('Just r) => Clamp Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

clamp :: Integer -> I Integer ('Just l) ('Just r) Source #

(Interval Integer ('Just l) ('Just r), l /= r) => Discrete Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

pred' :: I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

succ' :: I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

((0 / 1) < l, r <= (1 / 1), Interval Rational ('Just '(il, l)) ('Just '(ir, r))) => Div Rational ('Just '(il, l) :: L Rational :: Type) ('Just '(ir, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

div :: I Rational ('Just '(il, l)) ('Just '(ir, r)) -> I Rational ('Just '(il, l)) ('Just '(ir, r)) -> I Rational ('Just '(il, l)) ('Just '(ir, r)) Source #

IntervalCtx Rational ('Just '('False, l)) ('Just '('False, r)) => Interval Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('False, l)) ('Just '('False, r)) Source #

type MinI Rational ('Just '('False, l)) ('Just '('False, r)) :: T x :: Type Source #

type MaxI Rational ('Just '('False, l)) ('Just '('False, r)) :: T x :: Type Source #

Methods

inhabitant :: I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

from :: Rational -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

plus' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

mult' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

minus' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

negate' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

recip' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

div' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

IntervalCtx Rational ('Just '('False, l)) ('Just '('True, r)) => Interval Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('False, l)) ('Just '('True, r)) Source #

type MinI Rational ('Just '('False, l)) ('Just '('True, r)) :: T x :: Type Source #

type MaxI Rational ('Just '('False, l)) ('Just '('True, r)) :: T x :: Type Source #

Methods

inhabitant :: I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

from :: Rational -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

plus' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

mult' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

minus' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

negate' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

recip' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

div' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

IntervalCtx Rational ('Just '('True, l)) ('Just '('False, r)) => Interval Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('True, l)) ('Just '('False, r)) Source #

type MinI Rational ('Just '('True, l)) ('Just '('False, r)) :: T x :: Type Source #

type MaxI Rational ('Just '('True, l)) ('Just '('False, r)) :: T x :: Type Source #

Methods

inhabitant :: I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

from :: Rational -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

plus' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

mult' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

minus' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

negate' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

recip' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

div' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

IntervalCtx Rational ('Just '('True, l)) ('Just '('True, r)) => Interval Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('True, l)) ('Just '('True, r)) Source #

type MinI Rational ('Just '('True, l)) ('Just '('True, r)) :: T x :: Type Source #

type MaxI Rational ('Just '('True, l)) ('Just '('True, r)) :: T x :: Type Source #

Methods

inhabitant :: I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

from :: Rational -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

plus' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

mult' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

minus' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

negate' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

recip' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

div' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

IntervalCtx Integer ('Just l) ('Just r) => Interval Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type IntervalCtx Integer ('Just l) ('Just r) Source #

type MinI Integer ('Just l) ('Just r) :: T x :: Type Source #

type MaxI Integer ('Just l) ('Just r) :: T x :: Type Source #

Methods

inhabitant :: I Integer ('Just l) ('Just r) Source #

from :: Integer -> Maybe (I Integer ('Just l) ('Just r)) Source #

plus' :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

mult' :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

minus' :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

negate' :: I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

recip' :: I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

div' :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

(Interval Rational ('Just '(il, l)) ('Just '(ir, r)), (0 / 1) <= l, r <= (1 / 1)) => Mult Rational ('Just '(il, l) :: L Rational :: Type) ('Just '(ir, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

mult :: I Rational ('Just '(il, l)) ('Just '(ir, r)) -> I Rational ('Just '(il, l)) ('Just '(ir, r)) -> I Rational ('Just '(il, l)) ('Just '(ir, r)) Source #

(l == Negate r, Zero Rational ('Just '(i, l)) ('Just '(i, r))) => Negate Rational ('Just '(i, l) :: L Rational :: Type) ('Just '(i, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

negate :: I Rational ('Just '(i, l)) ('Just '(i, r)) -> I Rational ('Just '(i, l)) ('Just '(i, r)) Source #

(Zero Integer ('Just l) ('Just r), l == Negate r) => Negate Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

negate :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) Source #

(l < (1 / 1), (1 / 1) < r, Interval Rational ('Just '('False, l)) ('Just '('False, r))) => One Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

(l < (1 / 1), (1 / 1) <= r, Interval Rational ('Just '('False, l)) ('Just '('True, r))) => One Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

(l <= (1 / 1), (1 / 1) < r, Interval Rational ('Just '('True, l)) ('Just '('False, r))) => One Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

(l <= (1 / 1), (1 / 1) <= r, Interval Rational ('Just '('True, l)) ('Just '('True, r))) => One Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

(Interval Integer ('Just l) ('Just r), l <= P 1, P 1 <= r) => One Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

one :: I Integer ('Just l) ('Just r) Source #

Interval Rational ('Just '('False, l)) ('Just '('False, r)) => Shove Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational -> I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

Interval Rational ('Just '('False, l)) ('Just '('True, r)) => Shove Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational -> I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

Interval Rational ('Just '('True, l)) ('Just '('False, r)) => Shove Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational -> I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

Interval Rational ('Just '('True, l)) ('Just '('True, r)) => Shove Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational -> I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

Interval Integer ('Just l) ('Just r) => Shove Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

shove :: Integer -> I Integer ('Just l) ('Just r) Source #

Interval Rational ('Just '('False, l)) ('Just '('False, r)) => With Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> (forall (t :: T Rational). Known Rational ('Just '('False, l)) ('Just '('False, r)) t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('False, l)) ('Just '('True, r)) => With Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> (forall (t :: T Rational). Known Rational ('Just '('False, l)) ('Just '('True, r)) t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('True, l)) ('Just '('False, r)) => With Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> (forall (t :: T Rational). Known Rational ('Just '('True, l)) ('Just '('False, r)) t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('True, l)) ('Just '('True, r)) => With Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> (forall (t :: T Rational). Known Rational ('Just '('True, l)) ('Just '('True, r)) t => Proxy t -> b) -> b Source #

Interval Integer ('Just l) ('Just r) => With Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

with :: I Integer ('Just l) ('Just r) -> (forall (t :: T Integer). Known Integer ('Just l) ('Just r) t => Proxy t -> b) -> b Source #

(l < (0 / 1), (0 / 1) < r, Interval Rational ('Just '('False, l)) ('Just '('False, r))) => Zero Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

(l < (0 / 1), (0 / 1) <= r, Interval Rational ('Just '('False, l)) ('Just '('True, r))) => Zero Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

(l <= (0 / 1), (0 / 1) < r, Interval Rational ('Just '('True, l)) ('Just '('False, r))) => Zero Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

(l <= (0 / 1), (0 / 1) <= r, Interval Rational ('Just '('True, l)) ('Just '('True, r))) => Zero Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

(Interval Integer ('Just l) ('Just r), l <= P 0, P 0 <= r) => Zero Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

zero :: I Integer ('Just l) ('Just r) Source #

(Interval Rational ('Just '('False, l)) ('Just '('False, r)), KnownCtx Rational ('Just '('False, l)) ('Just '('False, r)) t) => Known Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('False, l)) ('Just '('False, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

(Interval Rational ('Just '('False, l)) ('Just '('True, r)), KnownCtx Rational ('Just '('False, l)) ('Just '('True, r)) t) => Known Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('False, l)) ('Just '('True, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

(Interval Rational ('Just '('True, l)) ('Just '('False, r)), KnownCtx Rational ('Just '('True, l)) ('Just '('False, r)) t) => Known Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('True, l)) ('Just '('False, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

(Interval Rational ('Just '('True, l)) ('Just '('True, r)), KnownCtx Rational ('Just '('True, l)) ('Just '('True, r)) t) => Known Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('True, l)) ('Just '('True, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

(Interval Integer ('Just l) ('Just r), KnownCtx Integer ('Just l) ('Just r) t) => Known Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer ('Just l) ('Just r) t Source #

Methods

known' :: Proxy t -> I Integer ('Just l) ('Just r) Source #

(Interval Rational ('Just '('False, ld)) ('Just '('False, rd)), Interval Rational ('Just '('False, lu)) ('Just '('False, ru)), lu <= ld, rd <= ru) => Up Rational ('Just '('False, ld) :: L Rational :: Type) ('Just '('False, rd) :: R Rational :: Type) ('Just '('False, lu) :: L Rational :: Type) ('Just '('False, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational ('Just '('False, ld)) ('Just '('False, rd)) -> I Rational ('Just '('False, lu)) ('Just '('False, ru)) Source #

(Interval Rational ('Just '('False, ld)) ('Just '(ird, rd)), Interval Rational ('Just '('False, lu)) ('Just '('True, ru)), lu <= ld, rd <= ru) => Up Rational ('Just '('False, ld) :: L Rational :: Type) ('Just '(ird, rd) :: R Rational :: Type) ('Just '('False, lu) :: L Rational :: Type) ('Just '('True, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational ('Just '('False, ld)) ('Just '(ird, rd)) -> I Rational ('Just '('False, lu)) ('Just '('True, ru)) Source #

(Interval Rational ('Just '(ild, ld)) ('Just '('False, rd)), Interval Rational ('Just '('True, lu)) ('Just '('False, ru)), lu <= ld, rd <= ru) => Up Rational ('Just '(ild, ld) :: L Rational :: Type) ('Just '('False, rd) :: R Rational :: Type) ('Just '('True, lu) :: L Rational :: Type) ('Just '('False, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational ('Just '(ild, ld)) ('Just '('False, rd)) -> I Rational ('Just '('True, lu)) ('Just '('False, ru)) Source #

(Interval Rational ('Just '(ild, ld)) ('Just '(ird, rd)), Interval Rational ('Just '('True, lu)) ('Just '('True, ru)), lu <= ld, rd <= ru) => Up Rational ('Just '(ild, ld) :: L Rational :: Type) ('Just '(ird, rd) :: R Rational :: Type) ('Just '('True, lu) :: L Rational :: Type) ('Just '('True, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational ('Just '(ild, ld)) ('Just '(ird, rd)) -> I Rational ('Just '('True, lu)) ('Just '('True, ru)) Source #

(lu <= ld, rd <= ru, Interval Integer ('Just ld) ('Just rd), Interval Integer ('Just lu) ('Just ru)) => Up Integer ('Just ld :: L Integer :: Type) ('Just rd :: R Integer :: Type) ('Just lu :: L Integer :: Type) ('Just ru :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

up :: I Integer ('Just ld) ('Just rd) -> I Integer ('Just lu) ('Just ru) Source #

type L Int16 Source # 
Instance details

Defined in I.Internal

type L Int16 = Integer
type L Int32 Source # 
Instance details

Defined in I.Internal

type L Int32 = Integer
type L Int64 Source # 
Instance details

Defined in I.Internal

type L Int64 = Integer
type L Int8 Source # 
Instance details

Defined in I.Internal

type L Int8 = Integer
type L Rational Source #
  • 'Nothing means unbounded.
  • ''Just ('True, t) means up to t, inclusive.
  • ''Just ('False, t) means up to t, exclusive.
Instance details

Defined in I.Internal

type L Word16 Source # 
Instance details

Defined in I.Internal

type L Word32 Source # 
Instance details

Defined in I.Internal

type L Word64 Source # 
Instance details

Defined in I.Internal

type L Word8 Source # 
Instance details

Defined in I.Internal

type L Word8 = Natural
type L Integer Source #
  • 'Nothing means unbounded.
  • 'Just t means up to t, inclusive.
Instance details

Defined in I.Internal

type L Natural Source # 
Instance details

Defined in I.Internal

type L Int Source # 
Instance details

Defined in I.Internal

type L Int = Integer
type L Word Source # 
Instance details

Defined in I.Internal

type L Word = Natural
type L CChar Source # 
Instance details

Defined in I.Internal

type L CChar = L Int8 :: k
type L CClock Source # 
Instance details

Defined in I.Internal

type L CClock = L Int64 :: k
type L CInt Source # 
Instance details

Defined in I.Internal

type L CInt = L Int32 :: k
type L CIntMax Source # 
Instance details

Defined in I.Internal

type L CIntMax = L Int64 :: k
type L CIntPtr Source # 
Instance details

Defined in I.Internal

type L CIntPtr = L Int64 :: k
type L CLLong Source # 
Instance details

Defined in I.Internal

type L CLLong = L Int64 :: k
type L CLong Source # 
Instance details

Defined in I.Internal

type L CLong = L Int64 :: k
type L CPtrdiff Source # 
Instance details

Defined in I.Internal

type L CPtrdiff = L Int64 :: k
type L CSChar Source # 
Instance details

Defined in I.Internal

type L CSChar = L Int8 :: k
type L CSUSeconds Source # 
Instance details

Defined in I.Internal

type L CSUSeconds = L Int64 :: k
type L CShort Source # 
Instance details

Defined in I.Internal

type L CShort = L Int16 :: k
type L CSize Source # 
Instance details

Defined in I.Internal

type L CSize = L Word64 :: k
type L CTime Source # 
Instance details

Defined in I.Internal

type L CTime = L Int64 :: k
type L CUChar Source # 
Instance details

Defined in I.Internal

type L CUChar = L Word8 :: k
type L CUInt Source # 
Instance details

Defined in I.Internal

type L CUInt = L Word32 :: k
type L CUIntMax Source # 
Instance details

Defined in I.Internal

type L CUIntMax = L Word64 :: k
type L CUIntPtr Source # 
Instance details

Defined in I.Internal

type L CUIntPtr = L Word64 :: k
type L CULLong Source # 
Instance details

Defined in I.Internal

type L CULLong = L Word64 :: k
type L CULong Source # 
Instance details

Defined in I.Internal

type L CULong = L Word64 :: k
type L CUSeconds Source # 
Instance details

Defined in I.Internal

type L CUSeconds = L Word32 :: k
type L CUShort Source # 
Instance details

Defined in I.Internal

type L CUShort = L Word16 :: k
type L CWchar Source # 
Instance details

Defined in I.Internal

type L CWchar = L Int32 :: k
type IntervalCtx CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

type IntervalCtx CChar (l :: L CChar :: Type) (r :: R CChar :: Type) = (KnownInteger l, KnownInteger r, MinT CChar <= l, l <= r, r <= MaxT CChar)
type IntervalCtx CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

type IntervalCtx CInt (l :: L CInt :: Type) (r :: R CInt :: Type) = (KnownInteger l, KnownInteger r, MinT CInt <= l, l <= r, r <= MaxT CInt)
type IntervalCtx CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

type IntervalCtx CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

type IntervalCtx CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

type IntervalCtx CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) = (KnownInteger l, KnownInteger r, MinT CLLong <= l, l <= r, r <= MaxT CLLong)
type IntervalCtx CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

type IntervalCtx CLong (l :: L CLong :: Type) (r :: R CLong :: Type) = (KnownInteger l, KnownInteger r, MinT CLong <= l, l <= r, r <= MaxT CLong)
type IntervalCtx CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

type IntervalCtx CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

type IntervalCtx CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) = (KnownInteger l, KnownInteger r, MinT CSChar <= l, l <= r, r <= MaxT CSChar)
type IntervalCtx CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

type IntervalCtx CShort (l :: L CShort :: Type) (r :: R CShort :: Type) = (KnownInteger l, KnownInteger r, MinT CShort <= l, l <= r, r <= MaxT CShort)
type IntervalCtx CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

type IntervalCtx CSize (l :: L CSize :: Type) (r :: R CSize :: Type) = (KnownNat l, KnownNat r, MinT CSize <= l, l <= r, r <= MaxT CSize)
type IntervalCtx CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

type IntervalCtx CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) = (KnownNat l, KnownNat r, MinT CUChar <= l, l <= r, r <= MaxT CUChar)
type IntervalCtx CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

type IntervalCtx CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) = (KnownNat l, KnownNat r, MinT CUInt <= l, l <= r, r <= MaxT CUInt)
type IntervalCtx CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

type IntervalCtx CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) = (KnownNat l, KnownNat r, MinT CUIntMax <= l, l <= r, r <= MaxT CUIntMax)
type IntervalCtx CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

type IntervalCtx CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) = (KnownNat l, KnownNat r, MinT CUIntPtr <= l, l <= r, r <= MaxT CUIntPtr)
type IntervalCtx CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

type IntervalCtx CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) = (KnownNat l, KnownNat r, MinT CULLong <= l, l <= r, r <= MaxT CULLong)
type IntervalCtx CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

type IntervalCtx CULong (l :: L CULong :: Type) (r :: R CULong :: Type) = (KnownNat l, KnownNat r, MinT CULong <= l, l <= r, r <= MaxT CULong)
type IntervalCtx CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

type IntervalCtx CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) = (KnownNat l, KnownNat r, MinT CUShort <= l, l <= r, r <= MaxT CUShort)
type IntervalCtx CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

type IntervalCtx CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) = (KnownInteger l, KnownInteger r, MinT CWchar <= l, l <= r, r <= MaxT CWchar)
type IntervalCtx Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

type IntervalCtx Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) = (KnownInteger l, KnownInteger r, MinT Int16 <= l, l <= r, r <= MaxT Int16)
type IntervalCtx Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

type IntervalCtx Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) = (KnownInteger l, KnownInteger r, MinT Int32 <= l, l <= r, r <= MaxT Int32)
type IntervalCtx Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

type IntervalCtx Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) = (KnownInteger l, KnownInteger r, MinT Int64 <= l, l <= r, r <= MaxT Int64)
type IntervalCtx Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

type IntervalCtx Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) = (KnownInteger l, KnownInteger r, MinT Int8 <= l, l <= r, r <= MaxT Int8)
type IntervalCtx Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

type IntervalCtx Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) = (KnownNat l, KnownNat r, MinT Word16 <= l, l <= r, r <= MaxT Word16)
type IntervalCtx Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

type IntervalCtx Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) = (KnownNat l, KnownNat r, MinT Word32 <= l, l <= r, r <= MaxT Word32)
type IntervalCtx Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

type IntervalCtx Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) = (KnownNat l, KnownNat r, MinT Word64 <= l, l <= r, r <= MaxT Word64)
type IntervalCtx Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

type IntervalCtx Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) = (KnownNat l, KnownNat r, MinT Word8 <= l, l <= r, r <= MaxT Word8)
type IntervalCtx Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

type IntervalCtx Int (l :: L Int :: Type) (r :: R Int :: Type) = (KnownInteger l, KnownInteger r, MinT Int <= l, l <= r, r <= MaxT Int)
type IntervalCtx Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

type IntervalCtx Word (l :: L Word :: Type) (r :: R Word :: Type) = (KnownNat l, KnownNat r, MinT Word <= l, l <= r, r <= MaxT Word)
type MaxI CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

type MaxI CChar (l :: L CChar :: Type) (r :: R CChar :: Type) = r
type MaxI CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

type MaxI CInt (l :: L CInt :: Type) (r :: R CInt :: Type) = r
type MaxI CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

type MaxI CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) = r
type MaxI CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

type MaxI CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) = r
type MaxI CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

type MaxI CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) = r
type MaxI CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

type MaxI CLong (l :: L CLong :: Type) (r :: R CLong :: Type) = r
type MaxI CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

type MaxI CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) = r
type MaxI CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

type MaxI CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) = r
type MaxI CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

type MaxI CShort (l :: L CShort :: Type) (r :: R CShort :: Type) = r
type MaxI CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

type MaxI CSize (l :: L CSize :: Type) (r :: R CSize :: Type) = r
type MaxI CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

type MaxI CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) = r
type MaxI CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

type MaxI CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) = r
type MaxI CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

type MaxI CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) = r
type MaxI CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

type MaxI CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) = r
type MaxI CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

type MaxI CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) = r
type MaxI CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

type MaxI CULong (l :: L CULong :: Type) (r :: R CULong :: Type) = r
type MaxI CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

type MaxI CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) = r
type MaxI CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

type MaxI CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) = r
type MaxI Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

type MaxI Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) = r
type MaxI Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

type MaxI Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) = r
type MaxI Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

type MaxI Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) = r
type MaxI Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

type MaxI Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) = r
type MaxI Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

type MaxI Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) = r
type MaxI Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

type MaxI Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) = r
type MaxI Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

type MaxI Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) = r
type MaxI Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

type MaxI Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) = r
type MaxI Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

type MaxI Int (l :: L Int :: Type) (r :: R Int :: Type) = r
type MaxI Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

type MaxI Word (l :: L Word :: Type) (r :: R Word :: Type) = r
type MinI CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

type MinI CChar (l :: L CChar :: Type) (r :: R CChar :: Type) = l
type MinI CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

type MinI CInt (l :: L CInt :: Type) (r :: R CInt :: Type) = l
type MinI CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

type MinI CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) = l
type MinI CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

type MinI CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) = l
type MinI CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

type MinI CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) = l
type MinI CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

type MinI CLong (l :: L CLong :: Type) (r :: R CLong :: Type) = l
type MinI CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

type MinI CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) = l
type MinI CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

type MinI CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) = l
type MinI CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

type MinI CShort (l :: L CShort :: Type) (r :: R CShort :: Type) = l
type MinI CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

type MinI CSize (l :: L CSize :: Type) (r :: R CSize :: Type) = l
type MinI CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

type MinI CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) = l
type MinI CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

type MinI CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) = l
type MinI CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

type MinI CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) = l
type MinI CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

type MinI CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) = l
type MinI CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

type MinI CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) = l
type MinI CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

type MinI CULong (l :: L CULong :: Type) (r :: R CULong :: Type) = l
type MinI CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

type MinI CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) = l
type MinI CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

type MinI CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) = l
type MinI Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

type MinI Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) = l
type MinI Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

type MinI Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) = l
type MinI Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

type MinI Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) = l
type MinI Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

type MinI Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) = l
type MinI Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

type MinI Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) = l
type MinI Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

type MinI Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) = l
type MinI Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

type MinI Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) = l
type MinI Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

type MinI Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) = l
type MinI Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

type MinI Int (l :: L Int :: Type) (r :: R Int :: Type) = l
type MinI Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

type MinI Word (l :: L Word :: Type) (r :: R Word :: Type) = l
type KnownCtx CChar (l :: L CChar :: Type) (r :: R CChar :: Type) (t :: T CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

type KnownCtx CChar (l :: L CChar :: Type) (r :: R CChar :: Type) (t :: T CChar :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CInt (l :: L CInt :: Type) (r :: R CInt :: Type) (t :: T CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

type KnownCtx CInt (l :: L CInt :: Type) (r :: R CInt :: Type) (t :: T CInt :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) (t :: T CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

type KnownCtx CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) (t :: T CIntMax :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) (t :: T CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

type KnownCtx CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) (t :: T CIntPtr :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) (t :: T CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

type KnownCtx CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) (t :: T CLLong :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CLong (l :: L CLong :: Type) (r :: R CLong :: Type) (t :: T CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

type KnownCtx CLong (l :: L CLong :: Type) (r :: R CLong :: Type) (t :: T CLong :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) (t :: T CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

type KnownCtx CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) (t :: T CPtrdiff :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) (t :: T CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

type KnownCtx CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) (t :: T CSChar :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CShort (l :: L CShort :: Type) (r :: R CShort :: Type) (t :: T CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

type KnownCtx CShort (l :: L CShort :: Type) (r :: R CShort :: Type) (t :: T CShort :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CSize (l :: L CSize :: Type) (r :: R CSize :: Type) (t :: T CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

type KnownCtx CSize (l :: L CSize :: Type) (r :: R CSize :: Type) (t :: T CSize :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) (t :: T CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

type KnownCtx CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) (t :: T CUChar :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) (t :: T CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

type KnownCtx CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) (t :: T CUInt :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) (t :: T CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

type KnownCtx CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) (t :: T CUIntMax :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) (t :: T CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

type KnownCtx CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) (t :: T CUIntPtr :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) (t :: T CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

type KnownCtx CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) (t :: T CULLong :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CULong (l :: L CULong :: Type) (r :: R CULong :: Type) (t :: T CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

type KnownCtx CULong (l :: L CULong :: Type) (r :: R CULong :: Type) (t :: T CULong :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) (t :: T CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

type KnownCtx CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) (t :: T CUShort :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) (t :: T CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

type KnownCtx CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) (t :: T CWchar :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) (t :: T Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

type KnownCtx Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) (t :: T Int16 :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) (t :: T Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

type KnownCtx Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) (t :: T Int32 :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) (t :: T Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

type KnownCtx Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) (t :: T Int64 :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) (t :: T Int8 :: Type) Source # 
Instance details

Defined in I.Int8

type KnownCtx Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) (t :: T Int8 :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) (t :: T Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

type KnownCtx Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) (t :: T Word16 :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) (t :: T Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

type KnownCtx Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) (t :: T Word32 :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) (t :: T Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

type KnownCtx Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) (t :: T Word64 :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) (t :: T Word8 :: Type) Source # 
Instance details

Defined in I.Word8

type KnownCtx Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) (t :: T Word8 :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Int (l :: L Int :: Type) (r :: R Int :: Type) (t :: T Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

type KnownCtx Int (l :: L Int :: Type) (r :: R Int :: Type) (t :: T Int :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Word (l :: L Word :: Type) (r :: R Word :: Type) (t :: T Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

type KnownCtx Word (l :: L Word :: Type) (r :: R Word :: Type) (t :: T Word :: Type) = (KnownNat t, l <= t, t <= r)
type IntervalCtx Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

type MaxI Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

type MaxI Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Natural l ('Nothing :: Maybe Natural))) ':<>: 'Text "\8217") :: T Natural :: Type
type MinI Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

type MinI Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) = l
type KnownCtx Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

type KnownCtx Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) (t :: T Natural :: Type) = (KnownNat t, l <= t)
type IntervalCtx Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

type IntervalCtx Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) = (KnownNat l, KnownNat r, MinT Natural <= l, l <= r)
type MaxI Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

type MaxI Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) = r
type MinI Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

type MinI Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) = l
type KnownCtx Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

type KnownCtx Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) (t :: T Natural :: Type) = (KnownNat t, l <= t, t <= r)
type IntervalCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

type MaxI Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MaxI Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

type MaxI Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer))) ':<>: 'Text "\8217") :: T Integer :: Type
type MinI Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MinI Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

type MinI Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer))) ':<>: 'Text "\8217") :: T Integer :: Type
type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

type IntervalCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

type MaxI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MaxI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) = r
type MaxI Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

type MaxI Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) = r
type MinI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MinI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MinI Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

type MinI Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Integer ('Nothing :: Maybe Integer) ('Just r))) ':<>: 'Text "\8217") :: T Integer :: Type
type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, t < r)
type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, t <= r)
type KnownCtx Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

type KnownCtx Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) = (KnownInteger t, t <= r)
type IntervalCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

type MaxI Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MaxI Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MaxI Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

type MaxI Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Integer ('Just l) ('Nothing :: Maybe Integer))) ':<>: 'Text "\8217") :: T Integer :: Type
type MinI Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MinI Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) = l
type MinI Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

type MinI Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) = l
type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) = (KnownRational t, l < t)
type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) = (KnownRational t, l <= t)
type KnownCtx Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

type KnownCtx Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) = (KnownInteger t, l <= t)
type IntervalCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) = (KnownRational l, KnownRational r, l < r)
type IntervalCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) = (KnownRational l, KnownRational r, l < r)
type IntervalCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) = (KnownRational l, KnownRational r, l < r)
type IntervalCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) = (KnownRational l, KnownRational r, l <= r)
type IntervalCtx Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

type IntervalCtx Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) = (KnownInteger l, KnownInteger r, l <= r)
type MaxI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('False, l)) ('Just '('False, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MaxI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) = r
type MaxI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('True, l)) ('Just '('False, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MaxI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) = r
type MaxI Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

type MaxI Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) = r
type MinI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('False, l)) ('Just '('False, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MinI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('False, l)) ('Just '('True, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MinI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) = l
type MinI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) = l
type MinI Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

type MinI Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) = l
type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, l < t, t < r)
type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, l < t, t <= r)
type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, l <= t, t < r)
type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, l <= t, t <= r)
type KnownCtx Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

type KnownCtx Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) = (KnownInteger t, l <= t, t <= r)

type family MinL (x :: Type) :: L x Source #

Minimum left bound for x. All the values of type x are at least as MinL x says, as required by wrap.

Instances

Instances details
type MinL CChar Source # 
Instance details

Defined in I.Autogen.CChar

type MinL CInt Source # 
Instance details

Defined in I.Autogen.CInt

type MinL CIntMax Source # 
Instance details

Defined in I.Autogen.CIntMax

type MinL CIntPtr Source # 
Instance details

Defined in I.Autogen.CIntPtr

type MinL CLLong Source # 
Instance details

Defined in I.Autogen.CLLong

type MinL CLong Source # 
Instance details

Defined in I.Autogen.CLong

type MinL CPtrdiff Source # 
Instance details

Defined in I.Autogen.CPtrdiff

type MinL CSChar Source # 
Instance details

Defined in I.Autogen.CSChar

type MinL CShort Source # 
Instance details

Defined in I.Autogen.CShort

type MinL CSize Source # 
Instance details

Defined in I.Autogen.CSize

type MinL CUChar Source # 
Instance details

Defined in I.Autogen.CUChar

type MinL CUInt Source # 
Instance details

Defined in I.Autogen.CUInt

type MinL CUIntMax Source # 
Instance details

Defined in I.Autogen.CUIntMax

type MinL CUIntPtr Source # 
Instance details

Defined in I.Autogen.CUIntPtr

type MinL CULLong Source # 
Instance details

Defined in I.Autogen.CULLong

type MinL CULong Source # 
Instance details

Defined in I.Autogen.CULong

type MinL CUShort Source # 
Instance details

Defined in I.Autogen.CUShort

type MinL CWchar Source # 
Instance details

Defined in I.Autogen.CWchar

type MinL Int16 Source # 
Instance details

Defined in I.Autogen.Int16

type MinL Int32 Source # 
Instance details

Defined in I.Autogen.Int32

type MinL Int64 Source # 
Instance details

Defined in I.Autogen.Int64

type MinL Int8 Source # 
Instance details

Defined in I.Int8

type MinL Rational Source # 
Instance details

Defined in I.Rational

type MinL Word16 Source # 
Instance details

Defined in I.Autogen.Word16

type MinL Word32 Source # 
Instance details

Defined in I.Autogen.Word32

type MinL Word64 Source # 
Instance details

Defined in I.Autogen.Word64

type MinL Word8 Source # 
Instance details

Defined in I.Word8

type MinL Integer Source # 
Instance details

Defined in I.Integer

type MinL Natural Source # 
Instance details

Defined in I.Natural

type MinL Int Source # 
Instance details

Defined in I.Autogen.Int

type MinL Int = MinT Int
type MinL Word Source # 
Instance details

Defined in I.Autogen.Word

type family R (x :: Type) :: k Source #

The kind of r in I x l r.

Instances

Instances details
Interval CChar l r => Clamp CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

clamp :: CChar -> I CChar l r Source #

Interval CInt l r => Clamp CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

clamp :: CInt -> I CInt l r Source #

Interval CIntMax l r => Clamp CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

clamp :: CIntMax -> I CIntMax l r Source #

Interval CIntPtr l r => Clamp CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

clamp :: CIntPtr -> I CIntPtr l r Source #

Interval CLLong l r => Clamp CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

clamp :: CLLong -> I CLLong l r Source #

Interval CLong l r => Clamp CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

clamp :: CLong -> I CLong l r Source #

Interval CPtrdiff l r => Clamp CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

clamp :: CPtrdiff -> I CPtrdiff l r Source #

Interval CSChar l r => Clamp CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

clamp :: CSChar -> I CSChar l r Source #

Interval CShort l r => Clamp CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

clamp :: CShort -> I CShort l r Source #

Interval CSize l r => Clamp CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

clamp :: CSize -> I CSize l r Source #

Interval CUChar l r => Clamp CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

clamp :: CUChar -> I CUChar l r Source #

Interval CUInt l r => Clamp CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

clamp :: CUInt -> I CUInt l r Source #

Interval CUIntMax l r => Clamp CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

clamp :: CUIntMax -> I CUIntMax l r Source #

Interval CUIntPtr l r => Clamp CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

clamp :: CUIntPtr -> I CUIntPtr l r Source #

Interval CULLong l r => Clamp CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

clamp :: CULLong -> I CULLong l r Source #

Interval CULong l r => Clamp CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

clamp :: CULong -> I CULong l r Source #

Interval CUShort l r => Clamp CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

clamp :: CUShort -> I CUShort l r Source #

Interval CWchar l r => Clamp CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

clamp :: CWchar -> I CWchar l r Source #

Interval Int16 l r => Clamp Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

clamp :: Int16 -> I Int16 l r Source #

Interval Int32 l r => Clamp Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

clamp :: Int32 -> I Int32 l r Source #

Interval Int64 l r => Clamp Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

clamp :: Int64 -> I Int64 l r Source #

Interval Int8 l r => Clamp Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

clamp :: Int8 -> I Int8 l r Source #

Interval Word16 l r => Clamp Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

clamp :: Word16 -> I Word16 l r Source #

Interval Word32 l r => Clamp Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

clamp :: Word32 -> I Word32 l r Source #

Interval Word64 l r => Clamp Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

clamp :: Word64 -> I Word64 l r Source #

Interval Word8 l r => Clamp Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

clamp :: Word8 -> I Word8 l r Source #

Interval Int l r => Clamp Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

clamp :: Int -> I Int l r Source #

Interval Word l r => Clamp Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

clamp :: Word -> I Word l r Source #

(Interval CChar l r, l /= r) => Discrete CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

pred' :: I CChar l r -> Maybe (I CChar l r) Source #

succ' :: I CChar l r -> Maybe (I CChar l r) Source #

(Interval CInt l r, l /= r) => Discrete CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

pred' :: I CInt l r -> Maybe (I CInt l r) Source #

succ' :: I CInt l r -> Maybe (I CInt l r) Source #

(Interval CIntMax l r, l /= r) => Discrete CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

pred' :: I CIntMax l r -> Maybe (I CIntMax l r) Source #

succ' :: I CIntMax l r -> Maybe (I CIntMax l r) Source #

(Interval CIntPtr l r, l /= r) => Discrete CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

pred' :: I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

succ' :: I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

(Interval CLLong l r, l /= r) => Discrete CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

pred' :: I CLLong l r -> Maybe (I CLLong l r) Source #

succ' :: I CLLong l r -> Maybe (I CLLong l r) Source #

(Interval CLong l r, l /= r) => Discrete CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

pred' :: I CLong l r -> Maybe (I CLong l r) Source #

succ' :: I CLong l r -> Maybe (I CLong l r) Source #

(Interval CPtrdiff l r, l /= r) => Discrete CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

pred' :: I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

succ' :: I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

(Interval CSChar l r, l /= r) => Discrete CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

pred' :: I CSChar l r -> Maybe (I CSChar l r) Source #

succ' :: I CSChar l r -> Maybe (I CSChar l r) Source #

(Interval CShort l r, l /= r) => Discrete CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

pred' :: I CShort l r -> Maybe (I CShort l r) Source #

succ' :: I CShort l r -> Maybe (I CShort l r) Source #

(Interval CSize l r, l /= r) => Discrete CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

pred' :: I CSize l r -> Maybe (I CSize l r) Source #

succ' :: I CSize l r -> Maybe (I CSize l r) Source #

(Interval CUChar l r, l /= r) => Discrete CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

pred' :: I CUChar l r -> Maybe (I CUChar l r) Source #

succ' :: I CUChar l r -> Maybe (I CUChar l r) Source #

(Interval CUInt l r, l /= r) => Discrete CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

pred' :: I CUInt l r -> Maybe (I CUInt l r) Source #

succ' :: I CUInt l r -> Maybe (I CUInt l r) Source #

(Interval CUIntMax l r, l /= r) => Discrete CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

pred' :: I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

succ' :: I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

(Interval CUIntPtr l r, l /= r) => Discrete CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

pred' :: I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

succ' :: I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

(Interval CULLong l r, l /= r) => Discrete CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

pred' :: I CULLong l r -> Maybe (I CULLong l r) Source #

succ' :: I CULLong l r -> Maybe (I CULLong l r) Source #

(Interval CULong l r, l /= r) => Discrete CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

pred' :: I CULong l r -> Maybe (I CULong l r) Source #

succ' :: I CULong l r -> Maybe (I CULong l r) Source #

(Interval CUShort l r, l /= r) => Discrete CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

pred' :: I CUShort l r -> Maybe (I CUShort l r) Source #

succ' :: I CUShort l r -> Maybe (I CUShort l r) Source #

(Interval CWchar l r, l /= r) => Discrete CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

pred' :: I CWchar l r -> Maybe (I CWchar l r) Source #

succ' :: I CWchar l r -> Maybe (I CWchar l r) Source #

(Interval Int16 l r, l /= r) => Discrete Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

pred' :: I Int16 l r -> Maybe (I Int16 l r) Source #

succ' :: I Int16 l r -> Maybe (I Int16 l r) Source #

(Interval Int32 l r, l /= r) => Discrete Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

pred' :: I Int32 l r -> Maybe (I Int32 l r) Source #

succ' :: I Int32 l r -> Maybe (I Int32 l r) Source #

(Interval Int64 l r, l /= r) => Discrete Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

pred' :: I Int64 l r -> Maybe (I Int64 l r) Source #

succ' :: I Int64 l r -> Maybe (I Int64 l r) Source #

(Interval Int8 l r, l /= r) => Discrete Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

pred' :: I Int8 l r -> Maybe (I Int8 l r) Source #

succ' :: I Int8 l r -> Maybe (I Int8 l r) Source #

(Interval Word16 l r, l /= r) => Discrete Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

pred' :: I Word16 l r -> Maybe (I Word16 l r) Source #

succ' :: I Word16 l r -> Maybe (I Word16 l r) Source #

(Interval Word32 l r, l /= r) => Discrete Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

pred' :: I Word32 l r -> Maybe (I Word32 l r) Source #

succ' :: I Word32 l r -> Maybe (I Word32 l r) Source #

(Interval Word64 l r, l /= r) => Discrete Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

pred' :: I Word64 l r -> Maybe (I Word64 l r) Source #

succ' :: I Word64 l r -> Maybe (I Word64 l r) Source #

(Interval Word8 l r, l /= r) => Discrete Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

pred' :: I Word8 l r -> Maybe (I Word8 l r) Source #

succ' :: I Word8 l r -> Maybe (I Word8 l r) Source #

(Interval Int l r, l /= r) => Discrete Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

pred' :: I Int l r -> Maybe (I Int l r) Source #

succ' :: I Int l r -> Maybe (I Int l r) Source #

(Interval Word l r, l /= r) => Discrete Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

pred' :: I Word l r -> Maybe (I Word l r) Source #

succ' :: I Word l r -> Maybe (I Word l r) Source #

IntervalCtx CChar l r => Interval CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Associated Types

type IntervalCtx CChar l r Source #

type MinI CChar l r :: T x :: Type Source #

type MaxI CChar l r :: T x :: Type Source #

Methods

inhabitant :: I CChar l r Source #

from :: CChar -> Maybe (I CChar l r) Source #

plus' :: I CChar l r -> I CChar l r -> Maybe (I CChar l r) Source #

mult' :: I CChar l r -> I CChar l r -> Maybe (I CChar l r) Source #

minus' :: I CChar l r -> I CChar l r -> Maybe (I CChar l r) Source #

negate' :: I CChar l r -> Maybe (I CChar l r) Source #

recip' :: I CChar l r -> Maybe (I CChar l r) Source #

div' :: I CChar l r -> I CChar l r -> Maybe (I CChar l r) Source #

IntervalCtx CInt l r => Interval CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Associated Types

type IntervalCtx CInt l r Source #

type MinI CInt l r :: T x :: Type Source #

type MaxI CInt l r :: T x :: Type Source #

Methods

inhabitant :: I CInt l r Source #

from :: CInt -> Maybe (I CInt l r) Source #

plus' :: I CInt l r -> I CInt l r -> Maybe (I CInt l r) Source #

mult' :: I CInt l r -> I CInt l r -> Maybe (I CInt l r) Source #

minus' :: I CInt l r -> I CInt l r -> Maybe (I CInt l r) Source #

negate' :: I CInt l r -> Maybe (I CInt l r) Source #

recip' :: I CInt l r -> Maybe (I CInt l r) Source #

div' :: I CInt l r -> I CInt l r -> Maybe (I CInt l r) Source #

IntervalCtx CIntMax l r => Interval CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Associated Types

type IntervalCtx CIntMax l r Source #

type MinI CIntMax l r :: T x :: Type Source #

type MaxI CIntMax l r :: T x :: Type Source #

Methods

inhabitant :: I CIntMax l r Source #

from :: CIntMax -> Maybe (I CIntMax l r) Source #

plus' :: I CIntMax l r -> I CIntMax l r -> Maybe (I CIntMax l r) Source #

mult' :: I CIntMax l r -> I CIntMax l r -> Maybe (I CIntMax l r) Source #

minus' :: I CIntMax l r -> I CIntMax l r -> Maybe (I CIntMax l r) Source #

negate' :: I CIntMax l r -> Maybe (I CIntMax l r) Source #

recip' :: I CIntMax l r -> Maybe (I CIntMax l r) Source #

div' :: I CIntMax l r -> I CIntMax l r -> Maybe (I CIntMax l r) Source #

IntervalCtx CIntPtr l r => Interval CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Associated Types

type IntervalCtx CIntPtr l r Source #

type MinI CIntPtr l r :: T x :: Type Source #

type MaxI CIntPtr l r :: T x :: Type Source #

Methods

inhabitant :: I CIntPtr l r Source #

from :: CIntPtr -> Maybe (I CIntPtr l r) Source #

plus' :: I CIntPtr l r -> I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

mult' :: I CIntPtr l r -> I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

minus' :: I CIntPtr l r -> I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

negate' :: I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

recip' :: I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

div' :: I CIntPtr l r -> I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

IntervalCtx CLLong l r => Interval CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Associated Types

type IntervalCtx CLLong l r Source #

type MinI CLLong l r :: T x :: Type Source #

type MaxI CLLong l r :: T x :: Type Source #

Methods

inhabitant :: I CLLong l r Source #

from :: CLLong -> Maybe (I CLLong l r) Source #

plus' :: I CLLong l r -> I CLLong l r -> Maybe (I CLLong l r) Source #

mult' :: I CLLong l r -> I CLLong l r -> Maybe (I CLLong l r) Source #

minus' :: I CLLong l r -> I CLLong l r -> Maybe (I CLLong l r) Source #

negate' :: I CLLong l r -> Maybe (I CLLong l r) Source #

recip' :: I CLLong l r -> Maybe (I CLLong l r) Source #

div' :: I CLLong l r -> I CLLong l r -> Maybe (I CLLong l r) Source #

IntervalCtx CLong l r => Interval CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Associated Types

type IntervalCtx CLong l r Source #

type MinI CLong l r :: T x :: Type Source #

type MaxI CLong l r :: T x :: Type Source #

Methods

inhabitant :: I CLong l r Source #

from :: CLong -> Maybe (I CLong l r) Source #

plus' :: I CLong l r -> I CLong l r -> Maybe (I CLong l r) Source #

mult' :: I CLong l r -> I CLong l r -> Maybe (I CLong l r) Source #

minus' :: I CLong l r -> I CLong l r -> Maybe (I CLong l r) Source #

negate' :: I CLong l r -> Maybe (I CLong l r) Source #

recip' :: I CLong l r -> Maybe (I CLong l r) Source #

div' :: I CLong l r -> I CLong l r -> Maybe (I CLong l r) Source #

IntervalCtx CPtrdiff l r => Interval CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Associated Types

type IntervalCtx CPtrdiff l r Source #

type MinI CPtrdiff l r :: T x :: Type Source #

type MaxI CPtrdiff l r :: T x :: Type Source #

Methods

inhabitant :: I CPtrdiff l r Source #

from :: CPtrdiff -> Maybe (I CPtrdiff l r) Source #

plus' :: I CPtrdiff l r -> I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

mult' :: I CPtrdiff l r -> I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

minus' :: I CPtrdiff l r -> I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

negate' :: I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

recip' :: I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

div' :: I CPtrdiff l r -> I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

IntervalCtx CSChar l r => Interval CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Associated Types

type IntervalCtx CSChar l r Source #

type MinI CSChar l r :: T x :: Type Source #

type MaxI CSChar l r :: T x :: Type Source #

Methods

inhabitant :: I CSChar l r Source #

from :: CSChar -> Maybe (I CSChar l r) Source #

plus' :: I CSChar l r -> I CSChar l r -> Maybe (I CSChar l r) Source #

mult' :: I CSChar l r -> I CSChar l r -> Maybe (I CSChar l r) Source #

minus' :: I CSChar l r -> I CSChar l r -> Maybe (I CSChar l r) Source #

negate' :: I CSChar l r -> Maybe (I CSChar l r) Source #

recip' :: I CSChar l r -> Maybe (I CSChar l r) Source #

div' :: I CSChar l r -> I CSChar l r -> Maybe (I CSChar l r) Source #

IntervalCtx CShort l r => Interval CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Associated Types

type IntervalCtx CShort l r Source #

type MinI CShort l r :: T x :: Type Source #

type MaxI CShort l r :: T x :: Type Source #

Methods

inhabitant :: I CShort l r Source #

from :: CShort -> Maybe (I CShort l r) Source #

plus' :: I CShort l r -> I CShort l r -> Maybe (I CShort l r) Source #

mult' :: I CShort l r -> I CShort l r -> Maybe (I CShort l r) Source #

minus' :: I CShort l r -> I CShort l r -> Maybe (I CShort l r) Source #

negate' :: I CShort l r -> Maybe (I CShort l r) Source #

recip' :: I CShort l r -> Maybe (I CShort l r) Source #

div' :: I CShort l r -> I CShort l r -> Maybe (I CShort l r) Source #

IntervalCtx CSize l r => Interval CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Associated Types

type IntervalCtx CSize l r Source #

type MinI CSize l r :: T x :: Type Source #

type MaxI CSize l r :: T x :: Type Source #

Methods

inhabitant :: I CSize l r Source #

from :: CSize -> Maybe (I CSize l r) Source #

plus' :: I CSize l r -> I CSize l r -> Maybe (I CSize l r) Source #

mult' :: I CSize l r -> I CSize l r -> Maybe (I CSize l r) Source #

minus' :: I CSize l r -> I CSize l r -> Maybe (I CSize l r) Source #

negate' :: I CSize l r -> Maybe (I CSize l r) Source #

recip' :: I CSize l r -> Maybe (I CSize l r) Source #

div' :: I CSize l r -> I CSize l r -> Maybe (I CSize l r) Source #

IntervalCtx CUChar l r => Interval CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Associated Types

type IntervalCtx CUChar l r Source #

type MinI CUChar l r :: T x :: Type Source #

type MaxI CUChar l r :: T x :: Type Source #

Methods

inhabitant :: I CUChar l r Source #

from :: CUChar -> Maybe (I CUChar l r) Source #

plus' :: I CUChar l r -> I CUChar l r -> Maybe (I CUChar l r) Source #

mult' :: I CUChar l r -> I CUChar l r -> Maybe (I CUChar l r) Source #

minus' :: I CUChar l r -> I CUChar l r -> Maybe (I CUChar l r) Source #

negate' :: I CUChar l r -> Maybe (I CUChar l r) Source #

recip' :: I CUChar l r -> Maybe (I CUChar l r) Source #

div' :: I CUChar l r -> I CUChar l r -> Maybe (I CUChar l r) Source #

IntervalCtx CUInt l r => Interval CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Associated Types

type IntervalCtx CUInt l r Source #

type MinI CUInt l r :: T x :: Type Source #

type MaxI CUInt l r :: T x :: Type Source #

Methods

inhabitant :: I CUInt l r Source #

from :: CUInt -> Maybe (I CUInt l r) Source #

plus' :: I CUInt l r -> I CUInt l r -> Maybe (I CUInt l r) Source #

mult' :: I CUInt l r -> I CUInt l r -> Maybe (I CUInt l r) Source #

minus' :: I CUInt l r -> I CUInt l r -> Maybe (I CUInt l r) Source #

negate' :: I CUInt l r -> Maybe (I CUInt l r) Source #

recip' :: I CUInt l r -> Maybe (I CUInt l r) Source #

div' :: I CUInt l r -> I CUInt l r -> Maybe (I CUInt l r) Source #

IntervalCtx CUIntMax l r => Interval CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Associated Types

type IntervalCtx CUIntMax l r Source #

type MinI CUIntMax l r :: T x :: Type Source #

type MaxI CUIntMax l r :: T x :: Type Source #

Methods

inhabitant :: I CUIntMax l r Source #

from :: CUIntMax -> Maybe (I CUIntMax l r) Source #

plus' :: I CUIntMax l r -> I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

mult' :: I CUIntMax l r -> I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

minus' :: I CUIntMax l r -> I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

negate' :: I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

recip' :: I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

div' :: I CUIntMax l r -> I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

IntervalCtx CUIntPtr l r => Interval CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Associated Types

type IntervalCtx CUIntPtr l r Source #

type MinI CUIntPtr l r :: T x :: Type Source #

type MaxI CUIntPtr l r :: T x :: Type Source #

Methods

inhabitant :: I CUIntPtr l r Source #

from :: CUIntPtr -> Maybe (I CUIntPtr l r) Source #

plus' :: I CUIntPtr l r -> I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

mult' :: I CUIntPtr l r -> I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

minus' :: I CUIntPtr l r -> I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

negate' :: I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

recip' :: I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

div' :: I CUIntPtr l r -> I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

IntervalCtx CULLong l r => Interval CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Associated Types

type IntervalCtx CULLong l r Source #

type MinI CULLong l r :: T x :: Type Source #

type MaxI CULLong l r :: T x :: Type Source #

Methods

inhabitant :: I CULLong l r Source #

from :: CULLong -> Maybe (I CULLong l r) Source #

plus' :: I CULLong l r -> I CULLong l r -> Maybe (I CULLong l r) Source #

mult' :: I CULLong l r -> I CULLong l r -> Maybe (I CULLong l r) Source #

minus' :: I CULLong l r -> I CULLong l r -> Maybe (I CULLong l r) Source #

negate' :: I CULLong l r -> Maybe (I CULLong l r) Source #

recip' :: I CULLong l r -> Maybe (I CULLong l r) Source #

div' :: I CULLong l r -> I CULLong l r -> Maybe (I CULLong l r) Source #

IntervalCtx CULong l r => Interval CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Associated Types

type IntervalCtx CULong l r Source #

type MinI CULong l r :: T x :: Type Source #

type MaxI CULong l r :: T x :: Type Source #

Methods

inhabitant :: I CULong l r Source #

from :: CULong -> Maybe (I CULong l r) Source #

plus' :: I CULong l r -> I CULong l r -> Maybe (I CULong l r) Source #

mult' :: I CULong l r -> I CULong l r -> Maybe (I CULong l r) Source #

minus' :: I CULong l r -> I CULong l r -> Maybe (I CULong l r) Source #

negate' :: I CULong l r -> Maybe (I CULong l r) Source #

recip' :: I CULong l r -> Maybe (I CULong l r) Source #

div' :: I CULong l r -> I CULong l r -> Maybe (I CULong l r) Source #

IntervalCtx CUShort l r => Interval CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Associated Types

type IntervalCtx CUShort l r Source #

type MinI CUShort l r :: T x :: Type Source #

type MaxI CUShort l r :: T x :: Type Source #

Methods

inhabitant :: I CUShort l r Source #

from :: CUShort -> Maybe (I CUShort l r) Source #

plus' :: I CUShort l r -> I CUShort l r -> Maybe (I CUShort l r) Source #

mult' :: I CUShort l r -> I CUShort l r -> Maybe (I CUShort l r) Source #

minus' :: I CUShort l r -> I CUShort l r -> Maybe (I CUShort l r) Source #

negate' :: I CUShort l r -> Maybe (I CUShort l r) Source #

recip' :: I CUShort l r -> Maybe (I CUShort l r) Source #

div' :: I CUShort l r -> I CUShort l r -> Maybe (I CUShort l r) Source #

IntervalCtx CWchar l r => Interval CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Associated Types

type IntervalCtx CWchar l r Source #

type MinI CWchar l r :: T x :: Type Source #

type MaxI CWchar l r :: T x :: Type Source #

Methods

inhabitant :: I CWchar l r Source #

from :: CWchar -> Maybe (I CWchar l r) Source #

plus' :: I CWchar l r -> I CWchar l r -> Maybe (I CWchar l r) Source #

mult' :: I CWchar l r -> I CWchar l r -> Maybe (I CWchar l r) Source #

minus' :: I CWchar l r -> I CWchar l r -> Maybe (I CWchar l r) Source #

negate' :: I CWchar l r -> Maybe (I CWchar l r) Source #

recip' :: I CWchar l r -> Maybe (I CWchar l r) Source #

div' :: I CWchar l r -> I CWchar l r -> Maybe (I CWchar l r) Source #

IntervalCtx Int16 l r => Interval Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Associated Types

type IntervalCtx Int16 l r Source #

type MinI Int16 l r :: T x :: Type Source #

type MaxI Int16 l r :: T x :: Type Source #

Methods

inhabitant :: I Int16 l r Source #

from :: Int16 -> Maybe (I Int16 l r) Source #

plus' :: I Int16 l r -> I Int16 l r -> Maybe (I Int16 l r) Source #

mult' :: I Int16 l r -> I Int16 l r -> Maybe (I Int16 l r) Source #

minus' :: I Int16 l r -> I Int16 l r -> Maybe (I Int16 l r) Source #

negate' :: I Int16 l r -> Maybe (I Int16 l r) Source #

recip' :: I Int16 l r -> Maybe (I Int16 l r) Source #

div' :: I Int16 l r -> I Int16 l r -> Maybe (I Int16 l r) Source #

IntervalCtx Int32 l r => Interval Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Associated Types

type IntervalCtx Int32 l r Source #

type MinI Int32 l r :: T x :: Type Source #

type MaxI Int32 l r :: T x :: Type Source #

Methods

inhabitant :: I Int32 l r Source #

from :: Int32 -> Maybe (I Int32 l r) Source #

plus' :: I Int32 l r -> I Int32 l r -> Maybe (I Int32 l r) Source #

mult' :: I Int32 l r -> I Int32 l r -> Maybe (I Int32 l r) Source #

minus' :: I Int32 l r -> I Int32 l r -> Maybe (I Int32 l r) Source #

negate' :: I Int32 l r -> Maybe (I Int32 l r) Source #

recip' :: I Int32 l r -> Maybe (I Int32 l r) Source #

div' :: I Int32 l r -> I Int32 l r -> Maybe (I Int32 l r) Source #

IntervalCtx Int64 l r => Interval Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Associated Types

type IntervalCtx Int64 l r Source #

type MinI Int64 l r :: T x :: Type Source #

type MaxI Int64 l r :: T x :: Type Source #

Methods

inhabitant :: I Int64 l r Source #

from :: Int64 -> Maybe (I Int64 l r) Source #

plus' :: I Int64 l r -> I Int64 l r -> Maybe (I Int64 l r) Source #

mult' :: I Int64 l r -> I Int64 l r -> Maybe (I Int64 l r) Source #

minus' :: I Int64 l r -> I Int64 l r -> Maybe (I Int64 l r) Source #

negate' :: I Int64 l r -> Maybe (I Int64 l r) Source #

recip' :: I Int64 l r -> Maybe (I Int64 l r) Source #

div' :: I Int64 l r -> I Int64 l r -> Maybe (I Int64 l r) Source #

IntervalCtx Int8 l r => Interval Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Associated Types

type IntervalCtx Int8 l r Source #

type MinI Int8 l r :: T x :: Type Source #

type MaxI Int8 l r :: T x :: Type Source #

Methods

inhabitant :: I Int8 l r Source #

from :: Int8 -> Maybe (I Int8 l r) Source #

plus' :: I Int8 l r -> I Int8 l r -> Maybe (I Int8 l r) Source #

mult' :: I Int8 l r -> I Int8 l r -> Maybe (I Int8 l r) Source #

minus' :: I Int8 l r -> I Int8 l r -> Maybe (I Int8 l r) Source #

negate' :: I Int8 l r -> Maybe (I Int8 l r) Source #

recip' :: I Int8 l r -> Maybe (I Int8 l r) Source #

div' :: I Int8 l r -> I Int8 l r -> Maybe (I Int8 l r) Source #

IntervalCtx Word16 l r => Interval Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Associated Types

type IntervalCtx Word16 l r Source #

type MinI Word16 l r :: T x :: Type Source #

type MaxI Word16 l r :: T x :: Type Source #

Methods

inhabitant :: I Word16 l r Source #

from :: Word16 -> Maybe (I Word16 l r) Source #

plus' :: I Word16 l r -> I Word16 l r -> Maybe (I Word16 l r) Source #

mult' :: I Word16 l r -> I Word16 l r -> Maybe (I Word16 l r) Source #

minus' :: I Word16 l r -> I Word16 l r -> Maybe (I Word16 l r) Source #

negate' :: I Word16 l r -> Maybe (I Word16 l r) Source #

recip' :: I Word16 l r -> Maybe (I Word16 l r) Source #

div' :: I Word16 l r -> I Word16 l r -> Maybe (I Word16 l r) Source #

IntervalCtx Word32 l r => Interval Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Associated Types

type IntervalCtx Word32 l r Source #

type MinI Word32 l r :: T x :: Type Source #

type MaxI Word32 l r :: T x :: Type Source #

Methods

inhabitant :: I Word32 l r Source #

from :: Word32 -> Maybe (I Word32 l r) Source #

plus' :: I Word32 l r -> I Word32 l r -> Maybe (I Word32 l r) Source #

mult' :: I Word32 l r -> I Word32 l r -> Maybe (I Word32 l r) Source #

minus' :: I Word32 l r -> I Word32 l r -> Maybe (I Word32 l r) Source #

negate' :: I Word32 l r -> Maybe (I Word32 l r) Source #

recip' :: I Word32 l r -> Maybe (I Word32 l r) Source #

div' :: I Word32 l r -> I Word32 l r -> Maybe (I Word32 l r) Source #

IntervalCtx Word64 l r => Interval Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Associated Types

type IntervalCtx Word64 l r Source #

type MinI Word64 l r :: T x :: Type Source #

type MaxI Word64 l r :: T x :: Type Source #

Methods

inhabitant :: I Word64 l r Source #

from :: Word64 -> Maybe (I Word64 l r) Source #

plus' :: I Word64 l r -> I Word64 l r -> Maybe (I Word64 l r) Source #

mult' :: I Word64 l r -> I Word64 l r -> Maybe (I Word64 l r) Source #

minus' :: I Word64 l r -> I Word64 l r -> Maybe (I Word64 l r) Source #

negate' :: I Word64 l r -> Maybe (I Word64 l r) Source #

recip' :: I Word64 l r -> Maybe (I Word64 l r) Source #

div' :: I Word64 l r -> I Word64 l r -> Maybe (I Word64 l r) Source #

IntervalCtx Word8 l r => Interval Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Associated Types

type IntervalCtx Word8 l r Source #

type MinI Word8 l r :: T x :: Type Source #

type MaxI Word8 l r :: T x :: Type Source #

Methods

inhabitant :: I Word8 l r Source #

from :: Word8 -> Maybe (I Word8 l r) Source #

plus' :: I Word8 l r -> I Word8 l r -> Maybe (I Word8 l r) Source #

mult' :: I Word8 l r -> I Word8 l r -> Maybe (I Word8 l r) Source #

minus' :: I Word8 l r -> I Word8 l r -> Maybe (I Word8 l r) Source #

negate' :: I Word8 l r -> Maybe (I Word8 l r) Source #

recip' :: I Word8 l r -> Maybe (I Word8 l r) Source #

div' :: I Word8 l r -> I Word8 l r -> Maybe (I Word8 l r) Source #

IntervalCtx Int l r => Interval Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Associated Types

type IntervalCtx Int l r Source #

type MinI Int l r :: T x :: Type Source #

type MaxI Int l r :: T x :: Type Source #

Methods

inhabitant :: I Int l r Source #

from :: Int -> Maybe (I Int l r) Source #

plus' :: I Int l r -> I Int l r -> Maybe (I Int l r) Source #

mult' :: I Int l r -> I Int l r -> Maybe (I Int l r) Source #

minus' :: I Int l r -> I Int l r -> Maybe (I Int l r) Source #

negate' :: I Int l r -> Maybe (I Int l r) Source #

recip' :: I Int l r -> Maybe (I Int l r) Source #

div' :: I Int l r -> I Int l r -> Maybe (I Int l r) Source #

IntervalCtx Word l r => Interval Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Associated Types

type IntervalCtx Word l r Source #

type MinI Word l r :: T x :: Type Source #

type MaxI Word l r :: T x :: Type Source #

Methods

inhabitant :: I Word l r Source #

from :: Word -> Maybe (I Word l r) Source #

plus' :: I Word l r -> I Word l r -> Maybe (I Word l r) Source #

mult' :: I Word l r -> I Word l r -> Maybe (I Word l r) Source #

minus' :: I Word l r -> I Word l r -> Maybe (I Word l r) Source #

negate' :: I Word l r -> Maybe (I Word l r) Source #

recip' :: I Word l r -> Maybe (I Word l r) Source #

div' :: I Word l r -> I Word l r -> Maybe (I Word l r) Source #

(Zero CChar l r, l == Negate r) => Negate CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

negate :: I CChar l r -> I CChar l r Source #

(Zero CInt l r, l == Negate r) => Negate CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

negate :: I CInt l r -> I CInt l r Source #

(Zero CIntMax l r, l == Negate r) => Negate CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

negate :: I CIntMax l r -> I CIntMax l r Source #

(Zero CIntPtr l r, l == Negate r) => Negate CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

negate :: I CIntPtr l r -> I CIntPtr l r Source #

(Zero CLLong l r, l == Negate r) => Negate CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

negate :: I CLLong l r -> I CLLong l r Source #

(Zero CLong l r, l == Negate r) => Negate CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

negate :: I CLong l r -> I CLong l r Source #

(Zero CPtrdiff l r, l == Negate r) => Negate CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

negate :: I CPtrdiff l r -> I CPtrdiff l r Source #

(Zero CSChar l r, l == Negate r) => Negate CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

negate :: I CSChar l r -> I CSChar l r Source #

(Zero CShort l r, l == Negate r) => Negate CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

negate :: I CShort l r -> I CShort l r Source #

(Zero CWchar l r, l == Negate r) => Negate CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

negate :: I CWchar l r -> I CWchar l r Source #

(Zero Int16 l r, l == Negate r) => Negate Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

negate :: I Int16 l r -> I Int16 l r Source #

(Zero Int32 l r, l == Negate r) => Negate Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

negate :: I Int32 l r -> I Int32 l r Source #

(Zero Int64 l r, l == Negate r) => Negate Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

negate :: I Int64 l r -> I Int64 l r Source #

(Zero Int8 l r, l == Negate r) => Negate Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

negate :: I Int8 l r -> I Int8 l r Source #

(Zero Int l r, l == Negate r) => Negate Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

negate :: I Int l r -> I Int l r Source #

(Interval CChar l r, l <= P 1, P 1 <= r) => One CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

one :: I CChar l r Source #

(Interval CInt l r, l <= P 1, P 1 <= r) => One CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

one :: I CInt l r Source #

(Interval CIntMax l r, l <= P 1, P 1 <= r) => One CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

one :: I CIntMax l r Source #

(Interval CIntPtr l r, l <= P 1, P 1 <= r) => One CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

one :: I CIntPtr l r Source #

(Interval CLLong l r, l <= P 1, P 1 <= r) => One CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

one :: I CLLong l r Source #

(Interval CLong l r, l <= P 1, P 1 <= r) => One CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

one :: I CLong l r Source #

(Interval CPtrdiff l r, l <= P 1, P 1 <= r) => One CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

one :: I CPtrdiff l r Source #

(Interval CSChar l r, l <= P 1, P 1 <= r) => One CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

one :: I CSChar l r Source #

(Interval CShort l r, l <= P 1, P 1 <= r) => One CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

one :: I CShort l r Source #

(Interval CSize l r, l <= 1, 1 <= r) => One CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

one :: I CSize l r Source #

(Interval CUChar l r, l <= 1, 1 <= r) => One CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

one :: I CUChar l r Source #

(Interval CUInt l r, l <= 1, 1 <= r) => One CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

one :: I CUInt l r Source #

(Interval CUIntMax l r, l <= 1, 1 <= r) => One CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

one :: I CUIntMax l r Source #

(Interval CUIntPtr l r, l <= 1, 1 <= r) => One CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

one :: I CUIntPtr l r Source #

(Interval CULLong l r, l <= 1, 1 <= r) => One CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

one :: I CULLong l r Source #

(Interval CULong l r, l <= 1, 1 <= r) => One CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

one :: I CULong l r Source #

(Interval CUShort l r, l <= 1, 1 <= r) => One CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

one :: I CUShort l r Source #

(Interval CWchar l r, l <= P 1, P 1 <= r) => One CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

one :: I CWchar l r Source #

(Interval Int16 l r, l <= P 1, P 1 <= r) => One Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

one :: I Int16 l r Source #

(Interval Int32 l r, l <= P 1, P 1 <= r) => One Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

one :: I Int32 l r Source #

(Interval Int64 l r, l <= P 1, P 1 <= r) => One Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

one :: I Int64 l r Source #

(Interval Int8 l r, l <= P 1, P 1 <= r) => One Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

one :: I Int8 l r Source #

(Interval Word16 l r, l <= 1, 1 <= r) => One Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

one :: I Word16 l r Source #

(Interval Word32 l r, l <= 1, 1 <= r) => One Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

one :: I Word32 l r Source #

(Interval Word64 l r, l <= 1, 1 <= r) => One Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

one :: I Word64 l r Source #

(Interval Word8 l r, l <= 1, 1 <= r) => One Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

one :: I Word8 l r Source #

(Interval Int l r, l <= P 1, P 1 <= r) => One Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

one :: I Int l r Source #

(Interval Word l r, l <= 1, 1 <= r) => One Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

one :: I Word l r Source #

Interval CChar l r => Shove CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

shove :: CChar -> I CChar l r Source #

Interval CInt l r => Shove CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

shove :: CInt -> I CInt l r Source #

Interval CIntMax l r => Shove CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

shove :: CIntMax -> I CIntMax l r Source #

Interval CIntPtr l r => Shove CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

shove :: CIntPtr -> I CIntPtr l r Source #

Interval CLLong l r => Shove CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

shove :: CLLong -> I CLLong l r Source #

Interval CLong l r => Shove CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

shove :: CLong -> I CLong l r Source #

Interval CPtrdiff l r => Shove CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

shove :: CPtrdiff -> I CPtrdiff l r Source #

Interval CSChar l r => Shove CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

shove :: CSChar -> I CSChar l r Source #

Interval CShort l r => Shove CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

shove :: CShort -> I CShort l r Source #

Interval CSize l r => Shove CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

shove :: CSize -> I CSize l r Source #

Interval CUChar l r => Shove CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

shove :: CUChar -> I CUChar l r Source #

Interval CUInt l r => Shove CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

shove :: CUInt -> I CUInt l r Source #

Interval CUIntMax l r => Shove CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

shove :: CUIntMax -> I CUIntMax l r Source #

Interval CUIntPtr l r => Shove CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

shove :: CUIntPtr -> I CUIntPtr l r Source #

Interval CULLong l r => Shove CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

shove :: CULLong -> I CULLong l r Source #

Interval CULong l r => Shove CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

shove :: CULong -> I CULong l r Source #

Interval CUShort l r => Shove CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

shove :: CUShort -> I CUShort l r Source #

Interval CWchar l r => Shove CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

shove :: CWchar -> I CWchar l r Source #

Interval Int16 l r => Shove Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

shove :: Int16 -> I Int16 l r Source #

Interval Int32 l r => Shove Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

shove :: Int32 -> I Int32 l r Source #

Interval Int64 l r => Shove Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

shove :: Int64 -> I Int64 l r Source #

Interval Int8 l r => Shove Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

shove :: Int8 -> I Int8 l r Source #

Interval Word16 l r => Shove Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

shove :: Word16 -> I Word16 l r Source #

Interval Word32 l r => Shove Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

shove :: Word32 -> I Word32 l r Source #

Interval Word64 l r => Shove Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

shove :: Word64 -> I Word64 l r Source #

Interval Word8 l r => Shove Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

shove :: Word8 -> I Word8 l r Source #

Interval Int l r => Shove Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

shove :: Int -> I Int l r Source #

Interval Word l r => Shove Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

shove :: Word -> I Word l r Source #

Interval CChar l r => With CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

with :: I CChar l r -> (forall (t :: T CChar). Known CChar l r t => Proxy t -> b) -> b Source #

Interval CInt l r => With CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

with :: I CInt l r -> (forall (t :: T CInt). Known CInt l r t => Proxy t -> b) -> b Source #

Interval CIntMax l r => With CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

with :: I CIntMax l r -> (forall (t :: T CIntMax). Known CIntMax l r t => Proxy t -> b) -> b Source #

Interval CIntPtr l r => With CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

with :: I CIntPtr l r -> (forall (t :: T CIntPtr). Known CIntPtr l r t => Proxy t -> b) -> b Source #

Interval CLLong l r => With CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

with :: I CLLong l r -> (forall (t :: T CLLong). Known CLLong l r t => Proxy t -> b) -> b Source #

Interval CLong l r => With CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

with :: I CLong l r -> (forall (t :: T CLong). Known CLong l r t => Proxy t -> b) -> b Source #

Interval CPtrdiff l r => With CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

with :: I CPtrdiff l r -> (forall (t :: T CPtrdiff). Known CPtrdiff l r t => Proxy t -> b) -> b Source #

Interval CSChar l r => With CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

with :: I CSChar l r -> (forall (t :: T CSChar). Known CSChar l r t => Proxy t -> b) -> b Source #

Interval CShort l r => With CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

with :: I CShort l r -> (forall (t :: T CShort). Known CShort l r t => Proxy t -> b) -> b Source #

Interval CSize l r => With CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

with :: I CSize l r -> (forall (t :: T CSize). Known CSize l r t => Proxy t -> b) -> b Source #

Interval CUChar l r => With CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

with :: I CUChar l r -> (forall (t :: T CUChar). Known CUChar l r t => Proxy t -> b) -> b Source #

Interval CUInt l r => With CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

with :: I CUInt l r -> (forall (t :: T CUInt). Known CUInt l r t => Proxy t -> b) -> b Source #

Interval CUIntMax l r => With CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

with :: I CUIntMax l r -> (forall (t :: T CUIntMax). Known CUIntMax l r t => Proxy t -> b) -> b Source #

Interval CUIntPtr l r => With CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

with :: I CUIntPtr l r -> (forall (t :: T CUIntPtr). Known CUIntPtr l r t => Proxy t -> b) -> b Source #

Interval CULLong l r => With CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

with :: I CULLong l r -> (forall (t :: T CULLong). Known CULLong l r t => Proxy t -> b) -> b Source #

Interval CULong l r => With CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

with :: I CULong l r -> (forall (t :: T CULong). Known CULong l r t => Proxy t -> b) -> b Source #

Interval CUShort l r => With CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

with :: I CUShort l r -> (forall (t :: T CUShort). Known CUShort l r t => Proxy t -> b) -> b Source #

Interval CWchar l r => With CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

with :: I CWchar l r -> (forall (t :: T CWchar). Known CWchar l r t => Proxy t -> b) -> b Source #

Interval Int16 l r => With Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

with :: I Int16 l r -> (forall (t :: T Int16). Known Int16 l r t => Proxy t -> b) -> b Source #

Interval Int32 l r => With Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

with :: I Int32 l r -> (forall (t :: T Int32). Known Int32 l r t => Proxy t -> b) -> b Source #

Interval Int64 l r => With Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

with :: I Int64 l r -> (forall (t :: T Int64). Known Int64 l r t => Proxy t -> b) -> b Source #

Interval Int8 l r => With Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

with :: I Int8 l r -> (forall (t :: T Int8). Known Int8 l r t => Proxy t -> b) -> b Source #

Interval Word16 l r => With Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

with :: I Word16 l r -> (forall (t :: T Word16). Known Word16 l r t => Proxy t -> b) -> b Source #

Interval Word32 l r => With Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

with :: I Word32 l r -> (forall (t :: T Word32). Known Word32 l r t => Proxy t -> b) -> b Source #

Interval Word64 l r => With Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

with :: I Word64 l r -> (forall (t :: T Word64). Known Word64 l r t => Proxy t -> b) -> b Source #

Interval Word8 l r => With Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

with :: I Word8 l r -> (forall (t :: T Word8). Known Word8 l r t => Proxy t -> b) -> b Source #

Interval Int l r => With Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

with :: I Int l r -> (forall (t :: T Int). Known Int l r t => Proxy t -> b) -> b Source #

Interval Word l r => With Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

with :: I Word l r -> (forall (t :: T Word). Known Word l r t => Proxy t -> b) -> b Source #

(Interval CChar l r, l <= P 0, P 0 <= r) => Zero CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

zero :: I CChar l r Source #

(Interval CInt l r, l <= P 0, P 0 <= r) => Zero CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

zero :: I CInt l r Source #

(Interval CIntMax l r, l <= P 0, P 0 <= r) => Zero CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

zero :: I CIntMax l r Source #

(Interval CIntPtr l r, l <= P 0, P 0 <= r) => Zero CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

zero :: I CIntPtr l r Source #

(Interval CLLong l r, l <= P 0, P 0 <= r) => Zero CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

zero :: I CLLong l r Source #

(Interval CLong l r, l <= P 0, P 0 <= r) => Zero CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

zero :: I CLong l r Source #

(Interval CPtrdiff l r, l <= P 0, P 0 <= r) => Zero CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

zero :: I CPtrdiff l r Source #

(Interval CSChar l r, l <= P 0, P 0 <= r) => Zero CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

zero :: I CSChar l r Source #

(Interval CShort l r, l <= P 0, P 0 <= r) => Zero CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

zero :: I CShort l r Source #

Interval CSize 0 r => Zero CSize 0 (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

zero :: I CSize 0 r Source #

Interval CUChar 0 r => Zero CUChar 0 (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

zero :: I CUChar 0 r Source #

Interval CUInt 0 r => Zero CUInt 0 (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

zero :: I CUInt 0 r Source #

Interval CUIntMax 0 r => Zero CUIntMax 0 (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

zero :: I CUIntMax 0 r Source #

Interval CUIntPtr 0 r => Zero CUIntPtr 0 (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

zero :: I CUIntPtr 0 r Source #

Interval CULLong 0 r => Zero CULLong 0 (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

zero :: I CULLong 0 r Source #

Interval CULong 0 r => Zero CULong 0 (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

zero :: I CULong 0 r Source #

Interval CUShort 0 r => Zero CUShort 0 (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

zero :: I CUShort 0 r Source #

(Interval CWchar l r, l <= P 0, P 0 <= r) => Zero CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

zero :: I CWchar l r Source #

(Interval Int16 l r, l <= P 0, P 0 <= r) => Zero Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

zero :: I Int16 l r Source #

(Interval Int32 l r, l <= P 0, P 0 <= r) => Zero Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

zero :: I Int32 l r Source #

(Interval Int64 l r, l <= P 0, P 0 <= r) => Zero Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

zero :: I Int64 l r Source #

(Interval Int8 l r, l <= P 0, P 0 <= r) => Zero Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

zero :: I Int8 l r Source #

Interval Word16 0 r => Zero Word16 0 (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

zero :: I Word16 0 r Source #

Interval Word32 0 r => Zero Word32 0 (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

zero :: I Word32 0 r Source #

Interval Word64 0 r => Zero Word64 0 (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

zero :: I Word64 0 r Source #

Interval Word8 0 r => Zero Word8 0 (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

zero :: I Word8 0 r Source #

Interval Natural 0 r => Zero Natural 0 (r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

zero :: I Natural 0 r Source #

(Interval Int l r, l <= P 0, P 0 <= r) => Zero Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

zero :: I Int l r Source #

Interval Word 0 r => Zero Word 0 (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

zero :: I Word 0 r Source #

(Interval CChar l r, KnownCtx CChar l r t) => Known CChar (l :: L CChar :: Type) (r :: R CChar :: Type) (t :: T CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Associated Types

type KnownCtx CChar l r t Source #

Methods

known' :: Proxy t -> I CChar l r Source #

(Interval CInt l r, KnownCtx CInt l r t) => Known CInt (l :: L CInt :: Type) (r :: R CInt :: Type) (t :: T CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Associated Types

type KnownCtx CInt l r t Source #

Methods

known' :: Proxy t -> I CInt l r Source #

(Interval CIntMax l r, KnownCtx CIntMax l r t) => Known CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) (t :: T CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Associated Types

type KnownCtx CIntMax l r t Source #

Methods

known' :: Proxy t -> I CIntMax l r Source #

(Interval CIntPtr l r, KnownCtx CIntPtr l r t) => Known CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) (t :: T CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Associated Types

type KnownCtx CIntPtr l r t Source #

Methods

known' :: Proxy t -> I CIntPtr l r Source #

(Interval CLLong l r, KnownCtx CLLong l r t) => Known CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) (t :: T CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Associated Types

type KnownCtx CLLong l r t Source #

Methods

known' :: Proxy t -> I CLLong l r Source #

(Interval CLong l r, KnownCtx CLong l r t) => Known CLong (l :: L CLong :: Type) (r :: R CLong :: Type) (t :: T CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Associated Types

type KnownCtx CLong l r t Source #

Methods

known' :: Proxy t -> I CLong l r Source #

(Interval CPtrdiff l r, KnownCtx CPtrdiff l r t) => Known CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) (t :: T CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Associated Types

type KnownCtx CPtrdiff l r t Source #

Methods

known' :: Proxy t -> I CPtrdiff l r Source #

(Interval CSChar l r, KnownCtx CSChar l r t) => Known CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) (t :: T CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Associated Types

type KnownCtx CSChar l r t Source #

Methods

known' :: Proxy t -> I CSChar l r Source #

(Interval CShort l r, KnownCtx CShort l r t) => Known CShort (l :: L CShort :: Type) (r :: R CShort :: Type) (t :: T CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Associated Types

type KnownCtx CShort l r t Source #

Methods

known' :: Proxy t -> I CShort l r Source #

(Interval CSize l r, KnownCtx CSize l r t) => Known CSize (l :: L CSize :: Type) (r :: R CSize :: Type) (t :: T CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Associated Types

type KnownCtx CSize l r t Source #

Methods

known' :: Proxy t -> I CSize l r Source #

(Interval CUChar l r, KnownCtx CUChar l r t) => Known CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) (t :: T CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Associated Types

type KnownCtx CUChar l r t Source #

Methods

known' :: Proxy t -> I CUChar l r Source #

(Interval CUInt l r, KnownCtx CUInt l r t) => Known CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) (t :: T CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Associated Types

type KnownCtx CUInt l r t Source #

Methods

known' :: Proxy t -> I CUInt l r Source #

(Interval CUIntMax l r, KnownCtx CUIntMax l r t) => Known CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) (t :: T CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Associated Types

type KnownCtx CUIntMax l r t Source #

Methods

known' :: Proxy t -> I CUIntMax l r Source #

(Interval CUIntPtr l r, KnownCtx CUIntPtr l r t) => Known CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) (t :: T CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Associated Types

type KnownCtx CUIntPtr l r t Source #

Methods

known' :: Proxy t -> I CUIntPtr l r Source #

(Interval CULLong l r, KnownCtx CULLong l r t) => Known CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) (t :: T CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Associated Types

type KnownCtx CULLong l r t Source #

Methods

known' :: Proxy t -> I CULLong l r Source #

(Interval CULong l r, KnownCtx CULong l r t) => Known CULong (l :: L CULong :: Type) (r :: R CULong :: Type) (t :: T CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Associated Types

type KnownCtx CULong l r t Source #

Methods

known' :: Proxy t -> I CULong l r Source #

(Interval CUShort l r, KnownCtx CUShort l r t) => Known CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) (t :: T CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Associated Types

type KnownCtx CUShort l r t Source #

Methods

known' :: Proxy t -> I CUShort l r Source #

(Interval CWchar l r, KnownCtx CWchar l r t) => Known CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) (t :: T CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Associated Types

type KnownCtx CWchar l r t Source #

Methods

known' :: Proxy t -> I CWchar l r Source #

(Interval Int16 l r, KnownCtx Int16 l r t) => Known Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) (t :: T Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Associated Types

type KnownCtx Int16 l r t Source #

Methods

known' :: Proxy t -> I Int16 l r Source #

(Interval Int32 l r, KnownCtx Int32 l r t) => Known Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) (t :: T Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Associated Types

type KnownCtx Int32 l r t Source #

Methods

known' :: Proxy t -> I Int32 l r Source #

(Interval Int64 l r, KnownCtx Int64 l r t) => Known Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) (t :: T Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Associated Types

type KnownCtx Int64 l r t Source #

Methods

known' :: Proxy t -> I Int64 l r Source #

(Interval Int8 l r, KnownCtx Int8 l r t) => Known Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) (t :: T Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Associated Types

type KnownCtx Int8 l r t Source #

Methods

known' :: Proxy t -> I Int8 l r Source #

(Interval Word16 l r, KnownCtx Word16 l r t) => Known Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) (t :: T Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Associated Types

type KnownCtx Word16 l r t Source #

Methods

known' :: Proxy t -> I Word16 l r Source #

(Interval Word32 l r, KnownCtx Word32 l r t) => Known Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) (t :: T Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Associated Types

type KnownCtx Word32 l r t Source #

Methods

known' :: Proxy t -> I Word32 l r Source #

(Interval Word64 l r, KnownCtx Word64 l r t) => Known Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) (t :: T Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Associated Types

type KnownCtx Word64 l r t Source #

Methods

known' :: Proxy t -> I Word64 l r Source #

(Interval Word8 l r, KnownCtx Word8 l r t) => Known Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) (t :: T Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Associated Types

type KnownCtx Word8 l r t Source #

Methods

known' :: Proxy t -> I Word8 l r Source #

(Interval Int l r, KnownCtx Int l r t) => Known Int (l :: L Int :: Type) (r :: R Int :: Type) (t :: T Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Associated Types

type KnownCtx Int l r t Source #

Methods

known' :: Proxy t -> I Int l r Source #

(Interval Word l r, KnownCtx Word l r t) => Known Word (l :: L Word :: Type) (r :: R Word :: Type) (t :: T Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Associated Types

type KnownCtx Word l r t Source #

Methods

known' :: Proxy t -> I Word l r Source #

(Interval CChar ld rd, Interval CChar lu ru, lu <= ld, rd <= ru) => Up CChar (ld :: L CChar :: Type) (rd :: R CChar :: Type) (lu :: L CChar :: Type) (ru :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

up :: I CChar ld rd -> I CChar lu ru Source #

(Interval CInt ld rd, Interval CInt lu ru, lu <= ld, rd <= ru) => Up CInt (ld :: L CInt :: Type) (rd :: R CInt :: Type) (lu :: L CInt :: Type) (ru :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

up :: I CInt ld rd -> I CInt lu ru Source #

(Interval CIntMax ld rd, Interval CIntMax lu ru, lu <= ld, rd <= ru) => Up CIntMax (ld :: L CIntMax :: Type) (rd :: R CIntMax :: Type) (lu :: L CIntMax :: Type) (ru :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

up :: I CIntMax ld rd -> I CIntMax lu ru Source #

(Interval CIntPtr ld rd, Interval CIntPtr lu ru, lu <= ld, rd <= ru) => Up CIntPtr (ld :: L CIntPtr :: Type) (rd :: R CIntPtr :: Type) (lu :: L CIntPtr :: Type) (ru :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

up :: I CIntPtr ld rd -> I CIntPtr lu ru Source #

(Interval CLLong ld rd, Interval CLLong lu ru, lu <= ld, rd <= ru) => Up CLLong (ld :: L CLLong :: Type) (rd :: R CLLong :: Type) (lu :: L CLLong :: Type) (ru :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

up :: I CLLong ld rd -> I CLLong lu ru Source #

(Interval CLong ld rd, Interval CLong lu ru, lu <= ld, rd <= ru) => Up CLong (ld :: L CLong :: Type) (rd :: R CLong :: Type) (lu :: L CLong :: Type) (ru :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

up :: I CLong ld rd -> I CLong lu ru Source #

(Interval CPtrdiff ld rd, Interval CPtrdiff lu ru, lu <= ld, rd <= ru) => Up CPtrdiff (ld :: L CPtrdiff :: Type) (rd :: R CPtrdiff :: Type) (lu :: L CPtrdiff :: Type) (ru :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

up :: I CPtrdiff ld rd -> I CPtrdiff lu ru Source #

(Interval CSChar ld rd, Interval CSChar lu ru, lu <= ld, rd <= ru) => Up CSChar (ld :: L CSChar :: Type) (rd :: R CSChar :: Type) (lu :: L CSChar :: Type) (ru :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

up :: I CSChar ld rd -> I CSChar lu ru Source #

(Interval CShort ld rd, Interval CShort lu ru, lu <= ld, rd <= ru) => Up CShort (ld :: L CShort :: Type) (rd :: R CShort :: Type) (lu :: L CShort :: Type) (ru :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

up :: I CShort ld rd -> I CShort lu ru Source #

(Interval CSize ld rd, Interval CSize lu ru, lu <= ld, rd <= ru) => Up CSize (ld :: L CSize :: Type) (rd :: R CSize :: Type) (lu :: L CSize :: Type) (ru :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

up :: I CSize ld rd -> I CSize lu ru Source #

(Interval CUChar ld rd, Interval CUChar lu ru, lu <= ld, rd <= ru) => Up CUChar (ld :: L CUChar :: Type) (rd :: R CUChar :: Type) (lu :: L CUChar :: Type) (ru :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

up :: I CUChar ld rd -> I CUChar lu ru Source #

(Interval CUInt ld rd, Interval CUInt lu ru, lu <= ld, rd <= ru) => Up CUInt (ld :: L CUInt :: Type) (rd :: R CUInt :: Type) (lu :: L CUInt :: Type) (ru :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

up :: I CUInt ld rd -> I CUInt lu ru Source #

(Interval CUIntMax ld rd, Interval CUIntMax lu ru, lu <= ld, rd <= ru) => Up CUIntMax (ld :: L CUIntMax :: Type) (rd :: R CUIntMax :: Type) (lu :: L CUIntMax :: Type) (ru :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

up :: I CUIntMax ld rd -> I CUIntMax lu ru Source #

(Interval CUIntPtr ld rd, Interval CUIntPtr lu ru, lu <= ld, rd <= ru) => Up CUIntPtr (ld :: L CUIntPtr :: Type) (rd :: R CUIntPtr :: Type) (lu :: L CUIntPtr :: Type) (ru :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

up :: I CUIntPtr ld rd -> I CUIntPtr lu ru Source #

(Interval CULLong ld rd, Interval CULLong lu ru, lu <= ld, rd <= ru) => Up CULLong (ld :: L CULLong :: Type) (rd :: R CULLong :: Type) (lu :: L CULLong :: Type) (ru :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

up :: I CULLong ld rd -> I CULLong lu ru Source #

(Interval CULong ld rd, Interval CULong lu ru, lu <= ld, rd <= ru) => Up CULong (ld :: L CULong :: Type) (rd :: R CULong :: Type) (lu :: L CULong :: Type) (ru :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

up :: I CULong ld rd -> I CULong lu ru Source #

(Interval CUShort ld rd, Interval CUShort lu ru, lu <= ld, rd <= ru) => Up CUShort (ld :: L CUShort :: Type) (rd :: R CUShort :: Type) (lu :: L CUShort :: Type) (ru :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

up :: I CUShort ld rd -> I CUShort lu ru Source #

(Interval CWchar ld rd, Interval CWchar lu ru, lu <= ld, rd <= ru) => Up CWchar (ld :: L CWchar :: Type) (rd :: R CWchar :: Type) (lu :: L CWchar :: Type) (ru :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

up :: I CWchar ld rd -> I CWchar lu ru Source #

(Interval Int16 ld rd, Interval Int16 lu ru, lu <= ld, rd <= ru) => Up Int16 (ld :: L Int16 :: Type) (rd :: R Int16 :: Type) (lu :: L Int16 :: Type) (ru :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

up :: I Int16 ld rd -> I Int16 lu ru Source #

(Interval Int32 ld rd, Interval Int32 lu ru, lu <= ld, rd <= ru) => Up Int32 (ld :: L Int32 :: Type) (rd :: R Int32 :: Type) (lu :: L Int32 :: Type) (ru :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

up :: I Int32 ld rd -> I Int32 lu ru Source #

(Interval Int64 ld rd, Interval Int64 lu ru, lu <= ld, rd <= ru) => Up Int64 (ld :: L Int64 :: Type) (rd :: R Int64 :: Type) (lu :: L Int64 :: Type) (ru :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

up :: I Int64 ld rd -> I Int64 lu ru Source #

(Interval Int8 ld rd, Interval Int8 lu ru, lu <= ld, rd <= ru) => Up Int8 (ld :: L Int8 :: Type) (rd :: R Int8 :: Type) (lu :: L Int8 :: Type) (ru :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

up :: I Int8 ld rd -> I Int8 lu ru Source #

(Interval Word16 ld rd, Interval Word16 lu ru, lu <= ld, rd <= ru) => Up Word16 (ld :: L Word16 :: Type) (rd :: R Word16 :: Type) (lu :: L Word16 :: Type) (ru :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

up :: I Word16 ld rd -> I Word16 lu ru Source #

(Interval Word32 ld rd, Interval Word32 lu ru, lu <= ld, rd <= ru) => Up Word32 (ld :: L Word32 :: Type) (rd :: R Word32 :: Type) (lu :: L Word32 :: Type) (ru :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

up :: I Word32 ld rd -> I Word32 lu ru Source #

(Interval Word64 ld rd, Interval Word64 lu ru, lu <= ld, rd <= ru) => Up Word64 (ld :: L Word64 :: Type) (rd :: R Word64 :: Type) (lu :: L Word64 :: Type) (ru :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

up :: I Word64 ld rd -> I Word64 lu ru Source #

(Interval Word8 ld rd, Interval Word8 lu ru, lu <= ld, rd <= ru) => Up Word8 (ld :: L Word8 :: Type) (rd :: R Word8 :: Type) (lu :: L Word8 :: Type) (ru :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

up :: I Word8 ld rd -> I Word8 lu ru Source #

(Interval Int ld rd, Interval Int lu ru, lu <= ld, rd <= ru) => Up Int (ld :: L Int :: Type) (rd :: R Int :: Type) (lu :: L Int :: Type) (ru :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

up :: I Int ld rd -> I Int lu ru Source #

(Interval Word ld rd, Interval Word lu ru, lu <= ld, rd <= ru) => Up Word (ld :: L Word :: Type) (rd :: R Word :: Type) (lu :: L Word :: Type) (ru :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

up :: I Word ld rd -> I Word lu ru Source #

(lu <= ld, Interval Natural ld yrd, Interval Natural lu ('Nothing :: Maybe Natural)) => Up Natural (ld :: L Natural :: Type) (yrd :: R Natural :: Type) (lu :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Methods

up :: I Natural ld yrd -> I Natural lu 'Nothing Source #

(Interval Rational yld yrd, Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational))) => Up Rational (yld :: L Rational :: Type) (yrd :: R Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 yld yrd -> I Rational0 'Nothing 'Nothing Source #

(Interval Integer yld yrd, Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer)) => Up Integer (yld :: L Integer :: Type) (yrd :: R Integer :: Type) ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

up :: I Integer0 yld yrd -> I Integer0 'Nothing 'Nothing Source #

Interval Natural l ('Nothing :: Maybe Natural) => Clamp Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Interval Natural l ('Nothing :: Maybe Natural) => Discrete Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

IntervalCtx Natural l ('Nothing :: Maybe Natural) => Interval Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Associated Types

type IntervalCtx Natural l 'Nothing Source #

type MinI Natural l 'Nothing :: T x :: Type Source #

type MaxI Natural l 'Nothing :: T x :: Type Source #

Interval Natural l ('Nothing :: Maybe Natural) => Mult Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

(Interval Natural l ('Nothing :: Maybe Natural), l <= 1) => One Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Methods

one :: I Natural l 'Nothing Source #

Interval Natural l ('Nothing :: Maybe Natural) => Plus Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Interval Natural l ('Nothing :: Maybe Natural) => Shove Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Discrete Integer l ('Nothing :: Maybe Integer) => Succ Integer (l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Discrete Natural l ('Nothing :: Maybe Natural) => Succ Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Interval Natural l ('Nothing :: Maybe Natural) => With Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Methods

with :: I Natural l 'Nothing -> (forall (t :: T Natural). Known Natural l 'Nothing t => Proxy t -> b) -> b Source #

(Interval Natural l ('Nothing :: Maybe Natural), KnownCtx Natural l ('Nothing :: Maybe Natural) t) => Known Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

Associated Types

type KnownCtx Natural l 'Nothing t Source #

Methods

known' :: Proxy t -> I Natural l 'Nothing Source #

Interval Natural l ('Just r) => Clamp Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

clamp :: Natural -> I Natural l ('Just r) Source #

(Interval Natural l ('Just r), l /= r) => Discrete Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

pred' :: I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

succ' :: I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

IntervalCtx Natural l ('Just r) => Interval Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Associated Types

type IntervalCtx Natural l ('Just r) Source #

type MinI Natural l ('Just r) :: T x :: Type Source #

type MaxI Natural l ('Just r) :: T x :: Type Source #

Methods

inhabitant :: I Natural l ('Just r) Source #

from :: Natural -> Maybe (I Natural l ('Just r)) Source #

plus' :: I Natural l ('Just r) -> I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

mult' :: I Natural l ('Just r) -> I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

minus' :: I Natural l ('Just r) -> I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

negate' :: I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

recip' :: I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

div' :: I Natural l ('Just r) -> I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

(Interval Natural l ('Just r), l <= 1, 1 <= r) => One Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

one :: I Natural l ('Just r) Source #

Interval Natural l ('Just r) => Shove Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

shove :: Natural -> I Natural l ('Just r) Source #

Interval Natural l ('Just r) => With Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

with :: I Natural l ('Just r) -> (forall (t :: T Natural). Known Natural l ('Just r) t => Proxy t -> b) -> b Source #

(Interval Natural l ('Just r), KnownCtx Natural l ('Just r) t) => Known Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

Associated Types

type KnownCtx Natural l ('Just r) t Source #

Methods

known' :: Proxy t -> I Natural l ('Just r) Source #

(lu <= ld, rd <= ru, Interval Natural ld ('Just rd), Interval Natural lu ('Just ru)) => Up Natural (ld :: L Natural :: Type) ('Just rd :: R Natural :: Type) (lu :: L Natural :: Type) ('Just ru :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

up :: I Natural ld ('Just rd) -> I Natural lu ('Just ru) Source #

(Interval Rational yld ('Just '('False, rd)), Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, ru)), ru <= rd) => Up Rational (yld :: L Rational :: Type) ('Just '('False, rd) :: R Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 yld ('Just '('False, rd)) -> I Rational0 'Nothing ('Just '('False, ru)) Source #

(Interval Rational yld ('Just '(ird, rd)), Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, ru)), ru <= rd) => Up Rational (yld :: L Rational :: Type) ('Just '(ird, rd) :: R Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 yld ('Just '(ird, rd)) -> I Rational0 'Nothing ('Just '('True, ru)) Source #

(rd <= ru, Interval Integer yld ('Just rd), Interval Integer ('Nothing :: Maybe Integer) ('Just ru)) => Up Integer (yld :: L Integer :: Type) ('Just rd :: R Integer :: Type) ('Nothing :: Maybe Integer) ('Just ru :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

up :: I Integer0 yld ('Just rd) -> I Integer0 'Nothing ('Just ru) Source #

Discrete Integer ('Nothing :: Maybe Integer) r => Pred Integer ('Nothing :: Maybe Integer) (r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) => Clamp Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) => Clamp Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Discrete Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Minus Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Minus Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Mult Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Mult Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Negate Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Negate Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

One Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

One Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Plus Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Plus Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Shove Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) => Shove Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

With Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 'Nothing 'Nothing -> (forall (t :: T Rational0). Known Rational0 'Nothing 'Nothing t => Proxy t -> b) -> b Source #

With Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

with :: I Integer0 'Nothing 'Nothing -> (forall (t :: T Integer0). Known Integer0 'Nothing 'Nothing t => Proxy t -> b) -> b Source #

Zero Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Zero Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) t => Known Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational 'Nothing 'Nothing t Source #

KnownCtx Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) t => Known Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer 'Nothing 'Nothing t Source #

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) => Clamp Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

clamp :: Rational0 -> I Rational0 'Nothing ('Just '('True, r)) Source #

Interval Integer ('Nothing :: Maybe Integer) ('Just r) => Clamp Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Interval Integer ('Nothing :: Maybe Integer) ('Just r) => Discrete Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

IntervalCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)) => Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational 'Nothing ('Just '('False, r)) Source #

type MinI Rational 'Nothing ('Just '('False, r)) :: T x :: Type Source #

type MaxI Rational 'Nothing ('Just '('False, r)) :: T x :: Type Source #

IntervalCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) => Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational 'Nothing ('Just '('True, r)) Source #

type MinI Rational 'Nothing ('Just '('True, r)) :: T x :: Type Source #

type MaxI Rational 'Nothing ('Just '('True, r)) :: T x :: Type Source #

IntervalCtx Integer ('Nothing :: Maybe Integer) ('Just r) => Interval Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type IntervalCtx Integer 'Nothing ('Just r) Source #

type MinI Integer 'Nothing ('Just r) :: T x :: Type Source #

type MaxI Integer 'Nothing ('Just r) :: T x :: Type Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)), (1 / 1) < r) => One Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational0 'Nothing ('Just '('False, r)) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)), (1 / 1) <= r) => One Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational0 'Nothing ('Just '('True, r)) Source #

(Interval Integer ('Nothing :: Maybe Integer) ('Just r), P 1 <= r) => One Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

one :: I Integer0 'Nothing ('Just r) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '(ir, r)), r <= (0 / 1)) => Plus Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '(ir, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

plus :: I Rational0 'Nothing ('Just '(ir, r)) -> I Rational0 'Nothing ('Just '(ir, r)) -> I Rational0 'Nothing ('Just '(ir, r)) Source #

(Interval Integer ('Nothing :: Maybe Integer) ('Just r), r <= P 0) => Plus Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

plus :: I Integer0 'Nothing ('Just r) -> I Integer0 'Nothing ('Just r) -> I Integer0 'Nothing ('Just r) Source #

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)) => Shove Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational0 -> I Rational0 'Nothing ('Just '('False, r)) Source #

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) => Shove Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational0 -> I Rational0 'Nothing ('Just '('True, r)) Source #

Interval Integer ('Nothing :: Maybe Integer) ('Just r) => Shove Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)) => With Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 'Nothing ('Just '('False, r)) -> (forall (t :: T Rational0). Known Rational0 'Nothing ('Just '('False, r)) t => Proxy t -> b) -> b Source #

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) => With Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 'Nothing ('Just '('True, r)) -> (forall (t :: T Rational0). Known Rational0 'Nothing ('Just '('True, r)) t => Proxy t -> b) -> b Source #

Interval Integer ('Nothing :: Maybe Integer) ('Just r) => With Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

with :: I Integer0 'Nothing ('Just r) -> (forall (t :: T Integer0). Known Integer0 'Nothing ('Just r) t => Proxy t -> b) -> b Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)), (0 / 1) < r) => Zero Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational0 'Nothing ('Just '('False, r)) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)), (0 / 1) <= r) => Zero Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational0 'Nothing ('Just '('True, r)) Source #

(Interval Integer ('Nothing :: Maybe Integer) ('Just r), P 0 <= r) => Zero Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

zero :: I Integer0 'Nothing ('Just r) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)), KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)) t) => Known Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational 'Nothing ('Just '('False, r)) t Source #

Methods

known' :: Proxy t -> I Rational0 'Nothing ('Just '('False, r)) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)), KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) t) => Known Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational 'Nothing ('Just '('True, r)) t Source #

Methods

known' :: Proxy t -> I Rational0 'Nothing ('Just '('True, r)) Source #

(Interval Integer ('Nothing :: Maybe Integer) ('Just r), KnownCtx Integer ('Nothing :: Maybe Integer) ('Just r) t) => Known Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer 'Nothing ('Just r) t Source #

Methods

known' :: Proxy t -> I Integer0 'Nothing ('Just r) Source #

(Interval Rational ('Just '('False, ld)) yrd, Interval Rational ('Just '('False, lu)) ('Nothing :: Maybe (Bool, Rational)), lu <= ld) => Up Rational ('Just '('False, ld) :: L Rational :: Type) (yrd :: R Rational :: Type) ('Just '('False, lu) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 ('Just '('False, ld)) yrd -> I Rational0 ('Just '('False, lu)) 'Nothing Source #

(Interval Rational ('Just '(ild, ld)) yrd, Interval Rational ('Just '('True, lu)) ('Nothing :: Maybe (Bool, Rational)), lu <= ld) => Up Rational ('Just '(ild, ld) :: L Rational :: Type) (yrd :: R Rational :: Type) ('Just '('True, lu) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 ('Just '(ild, ld)) yrd -> I Rational0 ('Just '('True, lu)) 'Nothing Source #

(lu <= ld, Interval Integer ('Just ld) yrd, Interval Integer ('Just lu) ('Nothing :: Maybe Integer)) => Up Integer ('Just ld :: L Integer :: Type) (yrd :: R Integer :: Type) ('Just lu :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

up :: I Integer0 ('Just ld) yrd -> I Integer0 ('Just lu) 'Nothing Source #

Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) => Clamp Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

clamp :: Rational0 -> I Rational0 ('Just '('True, l)) 'Nothing Source #

Interval Integer ('Just l) ('Nothing :: Maybe Integer) => Clamp Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Interval Integer ('Just l) ('Nothing :: Maybe Integer) => Discrete Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

IntervalCtx Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)) => Interval Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('False, l)) 'Nothing Source #

type MinI Rational ('Just '('False, l)) 'Nothing :: T x :: Type Source #

type MaxI Rational ('Just '('False, l)) 'Nothing :: T x :: Type Source #

IntervalCtx Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) => Interval Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('True, l)) 'Nothing Source #

type MinI Rational ('Just '('True, l)) 'Nothing :: T x :: Type Source #

type MaxI Rational ('Just '('True, l)) 'Nothing :: T x :: Type Source #

IntervalCtx Integer ('Just l) ('Nothing :: Maybe Integer) => Interval Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Associated Types

type IntervalCtx Integer ('Just l) 'Nothing Source #

type MinI Integer ('Just l) 'Nothing :: T x :: Type Source #

type MaxI Integer ('Just l) 'Nothing :: T x :: Type Source #

(Interval Rational ('Just '(il, l)) ('Nothing :: Maybe (Bool, Rational)), (1 / 1) <= l) => Mult Rational ('Just '(il, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

mult :: I Rational0 ('Just '(il, l)) 'Nothing -> I Rational0 ('Just '(il, l)) 'Nothing -> I Rational0 ('Just '(il, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), P 0 <= l) => Mult Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

mult :: I Integer0 ('Just l) 'Nothing -> I Integer0 ('Just l) 'Nothing -> I Integer0 ('Just l) 'Nothing Source #

(Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)), l < (1 / 1)) => One Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational0 ('Just '('False, l)) 'Nothing Source #

(Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)), l <= (1 / 1)) => One Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational0 ('Just '('True, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), l <= P 1) => One Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

one :: I Integer0 ('Just l) 'Nothing Source #

(Interval Rational ('Just '(il, l)) ('Nothing :: Maybe (Bool, Rational)), (0 / 1) <= l) => Plus Rational ('Just '(il, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

plus :: I Rational0 ('Just '(il, l)) 'Nothing -> I Rational0 ('Just '(il, l)) 'Nothing -> I Rational0 ('Just '(il, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), P 0 <= l) => Plus Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

plus :: I Integer0 ('Just l) 'Nothing -> I Integer0 ('Just l) 'Nothing -> I Integer0 ('Just l) 'Nothing Source #

Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)) => Shove Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational0 -> I Rational0 ('Just '('False, l)) 'Nothing Source #

Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) => Shove Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational0 -> I Rational0 ('Just '('True, l)) 'Nothing Source #

Interval Integer ('Just l) ('Nothing :: Maybe Integer) => Shove Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)) => With Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 ('Just '('False, l)) 'Nothing -> (forall (t :: T Rational0). Known Rational0 ('Just '('False, l)) 'Nothing t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) => With Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 ('Just '('True, l)) 'Nothing -> (forall (t :: T Rational0). Known Rational0 ('Just '('True, l)) 'Nothing t => Proxy t -> b) -> b Source #

Interval Integer ('Just l) ('Nothing :: Maybe Integer) => With Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

with :: I Integer0 ('Just l) 'Nothing -> (forall (t :: T Integer0). Known Integer0 ('Just l) 'Nothing t => Proxy t -> b) -> b Source #

(Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)), l < (0 / 1)) => Zero Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational0 ('Just '('False, l)) 'Nothing Source #

(Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)), l <= (0 / 1)) => Zero Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational0 ('Just '('True, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), l <= P 0) => Zero Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

zero :: I Integer0 ('Just l) 'Nothing Source #

(Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)), KnownCtx Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)) t) => Known Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('False, l)) 'Nothing t Source #

Methods

known' :: Proxy t -> I Rational0 ('Just '('False, l)) 'Nothing Source #

(Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)), KnownCtx Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) t) => Known Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('True, l)) 'Nothing t Source #

Methods

known' :: Proxy t -> I Rational0 ('Just '('True, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), KnownCtx Integer ('Just l) ('Nothing :: Maybe Integer) t) => Known Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer ('Just l) 'Nothing t Source #

Methods

known' :: Proxy t -> I Integer0 ('Just l) 'Nothing Source #

Interval Rational ('Just '('True, l)) ('Just '('True, r)) => Clamp Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

clamp :: Rational -> I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

Interval Integer ('Just l) ('Just r) => Clamp Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

clamp :: Integer -> I Integer ('Just l) ('Just r) Source #

(Interval Integer ('Just l) ('Just r), l /= r) => Discrete Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

pred' :: I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

succ' :: I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

((0 / 1) < l, r <= (1 / 1), Interval Rational ('Just '(il, l)) ('Just '(ir, r))) => Div Rational ('Just '(il, l) :: L Rational :: Type) ('Just '(ir, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

div :: I Rational ('Just '(il, l)) ('Just '(ir, r)) -> I Rational ('Just '(il, l)) ('Just '(ir, r)) -> I Rational ('Just '(il, l)) ('Just '(ir, r)) Source #

IntervalCtx Rational ('Just '('False, l)) ('Just '('False, r)) => Interval Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('False, l)) ('Just '('False, r)) Source #

type MinI Rational ('Just '('False, l)) ('Just '('False, r)) :: T x :: Type Source #

type MaxI Rational ('Just '('False, l)) ('Just '('False, r)) :: T x :: Type Source #

Methods

inhabitant :: I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

from :: Rational -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

plus' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

mult' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

minus' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

negate' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

recip' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

div' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

IntervalCtx Rational ('Just '('False, l)) ('Just '('True, r)) => Interval Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('False, l)) ('Just '('True, r)) Source #

type MinI Rational ('Just '('False, l)) ('Just '('True, r)) :: T x :: Type Source #

type MaxI Rational ('Just '('False, l)) ('Just '('True, r)) :: T x :: Type Source #

Methods

inhabitant :: I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

from :: Rational -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

plus' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

mult' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

minus' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

negate' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

recip' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

div' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

IntervalCtx Rational ('Just '('True, l)) ('Just '('False, r)) => Interval Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('True, l)) ('Just '('False, r)) Source #

type MinI Rational ('Just '('True, l)) ('Just '('False, r)) :: T x :: Type Source #

type MaxI Rational ('Just '('True, l)) ('Just '('False, r)) :: T x :: Type Source #

Methods

inhabitant :: I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

from :: Rational -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

plus' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

mult' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

minus' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

negate' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

recip' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

div' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

IntervalCtx Rational ('Just '('True, l)) ('Just '('True, r)) => Interval Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('True, l)) ('Just '('True, r)) Source #

type MinI Rational ('Just '('True, l)) ('Just '('True, r)) :: T x :: Type Source #

type MaxI Rational ('Just '('True, l)) ('Just '('True, r)) :: T x :: Type Source #

Methods

inhabitant :: I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

from :: Rational -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

plus' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

mult' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

minus' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

negate' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

recip' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

div' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

IntervalCtx Integer ('Just l) ('Just r) => Interval Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type IntervalCtx Integer ('Just l) ('Just r) Source #

type MinI Integer ('Just l) ('Just r) :: T x :: Type Source #

type MaxI Integer ('Just l) ('Just r) :: T x :: Type Source #

Methods

inhabitant :: I Integer ('Just l) ('Just r) Source #

from :: Integer -> Maybe (I Integer ('Just l) ('Just r)) Source #

plus' :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

mult' :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

minus' :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

negate' :: I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

recip' :: I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

div' :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

(Interval Rational ('Just '(il, l)) ('Just '(ir, r)), (0 / 1) <= l, r <= (1 / 1)) => Mult Rational ('Just '(il, l) :: L Rational :: Type) ('Just '(ir, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

mult :: I Rational ('Just '(il, l)) ('Just '(ir, r)) -> I Rational ('Just '(il, l)) ('Just '(ir, r)) -> I Rational ('Just '(il, l)) ('Just '(ir, r)) Source #

(l == Negate r, Zero Rational ('Just '(i, l)) ('Just '(i, r))) => Negate Rational ('Just '(i, l) :: L Rational :: Type) ('Just '(i, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

negate :: I Rational ('Just '(i, l)) ('Just '(i, r)) -> I Rational ('Just '(i, l)) ('Just '(i, r)) Source #

(Zero Integer ('Just l) ('Just r), l == Negate r) => Negate Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

negate :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) Source #

(l < (1 / 1), (1 / 1) < r, Interval Rational ('Just '('False, l)) ('Just '('False, r))) => One Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

(l < (1 / 1), (1 / 1) <= r, Interval Rational ('Just '('False, l)) ('Just '('True, r))) => One Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

(l <= (1 / 1), (1 / 1) < r, Interval Rational ('Just '('True, l)) ('Just '('False, r))) => One Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

(l <= (1 / 1), (1 / 1) <= r, Interval Rational ('Just '('True, l)) ('Just '('True, r))) => One Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

(Interval Integer ('Just l) ('Just r), l <= P 1, P 1 <= r) => One Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

one :: I Integer ('Just l) ('Just r) Source #

Interval Rational ('Just '('False, l)) ('Just '('False, r)) => Shove Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational -> I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

Interval Rational ('Just '('False, l)) ('Just '('True, r)) => Shove Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational -> I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

Interval Rational ('Just '('True, l)) ('Just '('False, r)) => Shove Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational -> I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

Interval Rational ('Just '('True, l)) ('Just '('True, r)) => Shove Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational -> I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

Interval Integer ('Just l) ('Just r) => Shove Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

shove :: Integer -> I Integer ('Just l) ('Just r) Source #

Interval Rational ('Just '('False, l)) ('Just '('False, r)) => With Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> (forall (t :: T Rational). Known Rational ('Just '('False, l)) ('Just '('False, r)) t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('False, l)) ('Just '('True, r)) => With Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> (forall (t :: T Rational). Known Rational ('Just '('False, l)) ('Just '('True, r)) t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('True, l)) ('Just '('False, r)) => With Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> (forall (t :: T Rational). Known Rational ('Just '('True, l)) ('Just '('False, r)) t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('True, l)) ('Just '('True, r)) => With Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> (forall (t :: T Rational). Known Rational ('Just '('True, l)) ('Just '('True, r)) t => Proxy t -> b) -> b Source #

Interval Integer ('Just l) ('Just r) => With Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

with :: I Integer ('Just l) ('Just r) -> (forall (t :: T Integer). Known Integer ('Just l) ('Just r) t => Proxy t -> b) -> b Source #

(l < (0 / 1), (0 / 1) < r, Interval Rational ('Just '('False, l)) ('Just '('False, r))) => Zero Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

(l < (0 / 1), (0 / 1) <= r, Interval Rational ('Just '('False, l)) ('Just '('True, r))) => Zero Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

(l <= (0 / 1), (0 / 1) < r, Interval Rational ('Just '('True, l)) ('Just '('False, r))) => Zero Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

(l <= (0 / 1), (0 / 1) <= r, Interval Rational ('Just '('True, l)) ('Just '('True, r))) => Zero Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

(Interval Integer ('Just l) ('Just r), l <= P 0, P 0 <= r) => Zero Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

zero :: I Integer ('Just l) ('Just r) Source #

(Interval Rational ('Just '('False, l)) ('Just '('False, r)), KnownCtx Rational ('Just '('False, l)) ('Just '('False, r)) t) => Known Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('False, l)) ('Just '('False, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

(Interval Rational ('Just '('False, l)) ('Just '('True, r)), KnownCtx Rational ('Just '('False, l)) ('Just '('True, r)) t) => Known Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('False, l)) ('Just '('True, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

(Interval Rational ('Just '('True, l)) ('Just '('False, r)), KnownCtx Rational ('Just '('True, l)) ('Just '('False, r)) t) => Known Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('True, l)) ('Just '('False, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

(Interval Rational ('Just '('True, l)) ('Just '('True, r)), KnownCtx Rational ('Just '('True, l)) ('Just '('True, r)) t) => Known Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('True, l)) ('Just '('True, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

(Interval Integer ('Just l) ('Just r), KnownCtx Integer ('Just l) ('Just r) t) => Known Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer ('Just l) ('Just r) t Source #

Methods

known' :: Proxy t -> I Integer ('Just l) ('Just r) Source #

(Interval Rational ('Just '('False, ld)) ('Just '('False, rd)), Interval Rational ('Just '('False, lu)) ('Just '('False, ru)), lu <= ld, rd <= ru) => Up Rational ('Just '('False, ld) :: L Rational :: Type) ('Just '('False, rd) :: R Rational :: Type) ('Just '('False, lu) :: L Rational :: Type) ('Just '('False, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational ('Just '('False, ld)) ('Just '('False, rd)) -> I Rational ('Just '('False, lu)) ('Just '('False, ru)) Source #

(Interval Rational ('Just '('False, ld)) ('Just '(ird, rd)), Interval Rational ('Just '('False, lu)) ('Just '('True, ru)), lu <= ld, rd <= ru) => Up Rational ('Just '('False, ld) :: L Rational :: Type) ('Just '(ird, rd) :: R Rational :: Type) ('Just '('False, lu) :: L Rational :: Type) ('Just '('True, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational ('Just '('False, ld)) ('Just '(ird, rd)) -> I Rational ('Just '('False, lu)) ('Just '('True, ru)) Source #

(Interval Rational ('Just '(ild, ld)) ('Just '('False, rd)), Interval Rational ('Just '('True, lu)) ('Just '('False, ru)), lu <= ld, rd <= ru) => Up Rational ('Just '(ild, ld) :: L Rational :: Type) ('Just '('False, rd) :: R Rational :: Type) ('Just '('True, lu) :: L Rational :: Type) ('Just '('False, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational ('Just '(ild, ld)) ('Just '('False, rd)) -> I Rational ('Just '('True, lu)) ('Just '('False, ru)) Source #

(Interval Rational ('Just '(ild, ld)) ('Just '(ird, rd)), Interval Rational ('Just '('True, lu)) ('Just '('True, ru)), lu <= ld, rd <= ru) => Up Rational ('Just '(ild, ld) :: L Rational :: Type) ('Just '(ird, rd) :: R Rational :: Type) ('Just '('True, lu) :: L Rational :: Type) ('Just '('True, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational ('Just '(ild, ld)) ('Just '(ird, rd)) -> I Rational ('Just '('True, lu)) ('Just '('True, ru)) Source #

(lu <= ld, rd <= ru, Interval Integer ('Just ld) ('Just rd), Interval Integer ('Just lu) ('Just ru)) => Up Integer ('Just ld :: L Integer :: Type) ('Just rd :: R Integer :: Type) ('Just lu :: L Integer :: Type) ('Just ru :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

up :: I Integer ('Just ld) ('Just rd) -> I Integer ('Just lu) ('Just ru) Source #

type R Int16 Source # 
Instance details

Defined in I.Internal

type R Int16 = Integer
type R Int32 Source # 
Instance details

Defined in I.Internal

type R Int32 = Integer
type R Int64 Source # 
Instance details

Defined in I.Internal

type R Int64 = Integer
type R Int8 Source # 
Instance details

Defined in I.Internal

type R Int8 = Integer
type R Rational Source #
  • 'Nothing means unbounded.
  • ''Just ('True, t) means up to t, inclusive.
  • ''Just ('False, t) means up to t, exclusive.
Instance details

Defined in I.Internal

type R Word16 Source # 
Instance details

Defined in I.Internal

type R Word32 Source # 
Instance details

Defined in I.Internal

type R Word64 Source # 
Instance details

Defined in I.Internal

type R Word8 Source # 
Instance details

Defined in I.Internal

type R Word8 = Natural
type R Integer Source #
  • 'Nothing means unbounded.
  • 'Just t means up to t, inclusive.
Instance details

Defined in I.Internal

type R Natural Source #

'Nothing means unbounded.

Instance details

Defined in I.Internal

type R Int Source # 
Instance details

Defined in I.Internal

type R Int = Integer
type R Word Source # 
Instance details

Defined in I.Internal

type R Word = Natural
type R CChar Source # 
Instance details

Defined in I.Internal

type R CChar = R Int8 :: k
type R CClock Source # 
Instance details

Defined in I.Internal

type R CClock = R Int64 :: k
type R CInt Source # 
Instance details

Defined in I.Internal

type R CInt = R Int32 :: k
type R CIntMax Source # 
Instance details

Defined in I.Internal

type R CIntMax = R Int64 :: k
type R CIntPtr Source # 
Instance details

Defined in I.Internal

type R CIntPtr = R Int64 :: k
type R CLLong Source # 
Instance details

Defined in I.Internal

type R CLLong = R Int64 :: k
type R CLong Source # 
Instance details

Defined in I.Internal

type R CLong = R Int64 :: k
type R CPtrdiff Source # 
Instance details

Defined in I.Internal

type R CPtrdiff = R Int64 :: k
type R CSChar Source # 
Instance details

Defined in I.Internal

type R CSChar = R Int8 :: k
type R CSUSeconds Source # 
Instance details

Defined in I.Internal

type R CSUSeconds = R Int64 :: k
type R CShort Source # 
Instance details

Defined in I.Internal

type R CShort = R Int16 :: k
type R CSize Source # 
Instance details

Defined in I.Internal

type R CSize = R Word64 :: k
type R CTime Source # 
Instance details

Defined in I.Internal

type R CTime = R Int64 :: k
type R CUChar Source # 
Instance details

Defined in I.Internal

type R CUChar = R Word8 :: k
type R CUInt Source # 
Instance details

Defined in I.Internal

type R CUInt = R Word32 :: k
type R CUIntMax Source # 
Instance details

Defined in I.Internal

type R CUIntMax = R Word64 :: k
type R CUIntPtr Source # 
Instance details

Defined in I.Internal

type R CUIntPtr = R Word64 :: k
type R CULLong Source # 
Instance details

Defined in I.Internal

type R CULLong = R Word64 :: k
type R CULong Source # 
Instance details

Defined in I.Internal

type R CULong = R Word64 :: k
type R CUSeconds Source # 
Instance details

Defined in I.Internal

type R CUSeconds = R Word32 :: k
type R CUShort Source # 
Instance details

Defined in I.Internal

type R CUShort = R Word16 :: k
type R CWchar Source # 
Instance details

Defined in I.Internal

type R CWchar = R Int32 :: k
type IntervalCtx CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

type IntervalCtx CChar (l :: L CChar :: Type) (r :: R CChar :: Type) = (KnownInteger l, KnownInteger r, MinT CChar <= l, l <= r, r <= MaxT CChar)
type IntervalCtx CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

type IntervalCtx CInt (l :: L CInt :: Type) (r :: R CInt :: Type) = (KnownInteger l, KnownInteger r, MinT CInt <= l, l <= r, r <= MaxT CInt)
type IntervalCtx CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

type IntervalCtx CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

type IntervalCtx CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

type IntervalCtx CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) = (KnownInteger l, KnownInteger r, MinT CLLong <= l, l <= r, r <= MaxT CLLong)
type IntervalCtx CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

type IntervalCtx CLong (l :: L CLong :: Type) (r :: R CLong :: Type) = (KnownInteger l, KnownInteger r, MinT CLong <= l, l <= r, r <= MaxT CLong)
type IntervalCtx CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

type IntervalCtx CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

type IntervalCtx CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) = (KnownInteger l, KnownInteger r, MinT CSChar <= l, l <= r, r <= MaxT CSChar)
type IntervalCtx CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

type IntervalCtx CShort (l :: L CShort :: Type) (r :: R CShort :: Type) = (KnownInteger l, KnownInteger r, MinT CShort <= l, l <= r, r <= MaxT CShort)
type IntervalCtx CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

type IntervalCtx CSize (l :: L CSize :: Type) (r :: R CSize :: Type) = (KnownNat l, KnownNat r, MinT CSize <= l, l <= r, r <= MaxT CSize)
type IntervalCtx CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

type IntervalCtx CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) = (KnownNat l, KnownNat r, MinT CUChar <= l, l <= r, r <= MaxT CUChar)
type IntervalCtx CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

type IntervalCtx CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) = (KnownNat l, KnownNat r, MinT CUInt <= l, l <= r, r <= MaxT CUInt)
type IntervalCtx CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

type IntervalCtx CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) = (KnownNat l, KnownNat r, MinT CUIntMax <= l, l <= r, r <= MaxT CUIntMax)
type IntervalCtx CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

type IntervalCtx CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) = (KnownNat l, KnownNat r, MinT CUIntPtr <= l, l <= r, r <= MaxT CUIntPtr)
type IntervalCtx CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

type IntervalCtx CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) = (KnownNat l, KnownNat r, MinT CULLong <= l, l <= r, r <= MaxT CULLong)
type IntervalCtx CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

type IntervalCtx CULong (l :: L CULong :: Type) (r :: R CULong :: Type) = (KnownNat l, KnownNat r, MinT CULong <= l, l <= r, r <= MaxT CULong)
type IntervalCtx CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

type IntervalCtx CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) = (KnownNat l, KnownNat r, MinT CUShort <= l, l <= r, r <= MaxT CUShort)
type IntervalCtx CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

type IntervalCtx CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) = (KnownInteger l, KnownInteger r, MinT CWchar <= l, l <= r, r <= MaxT CWchar)
type IntervalCtx Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

type IntervalCtx Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) = (KnownInteger l, KnownInteger r, MinT Int16 <= l, l <= r, r <= MaxT Int16)
type IntervalCtx Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

type IntervalCtx Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) = (KnownInteger l, KnownInteger r, MinT Int32 <= l, l <= r, r <= MaxT Int32)
type IntervalCtx Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

type IntervalCtx Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) = (KnownInteger l, KnownInteger r, MinT Int64 <= l, l <= r, r <= MaxT Int64)
type IntervalCtx Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

type IntervalCtx Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) = (KnownInteger l, KnownInteger r, MinT Int8 <= l, l <= r, r <= MaxT Int8)
type IntervalCtx Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

type IntervalCtx Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) = (KnownNat l, KnownNat r, MinT Word16 <= l, l <= r, r <= MaxT Word16)
type IntervalCtx Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

type IntervalCtx Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) = (KnownNat l, KnownNat r, MinT Word32 <= l, l <= r, r <= MaxT Word32)
type IntervalCtx Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

type IntervalCtx Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) = (KnownNat l, KnownNat r, MinT Word64 <= l, l <= r, r <= MaxT Word64)
type IntervalCtx Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

type IntervalCtx Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) = (KnownNat l, KnownNat r, MinT Word8 <= l, l <= r, r <= MaxT Word8)
type IntervalCtx Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

type IntervalCtx Int (l :: L Int :: Type) (r :: R Int :: Type) = (KnownInteger l, KnownInteger r, MinT Int <= l, l <= r, r <= MaxT Int)
type IntervalCtx Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

type IntervalCtx Word (l :: L Word :: Type) (r :: R Word :: Type) = (KnownNat l, KnownNat r, MinT Word <= l, l <= r, r <= MaxT Word)
type MaxI CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

type MaxI CChar (l :: L CChar :: Type) (r :: R CChar :: Type) = r
type MaxI CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

type MaxI CInt (l :: L CInt :: Type) (r :: R CInt :: Type) = r
type MaxI CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

type MaxI CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) = r
type MaxI CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

type MaxI CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) = r
type MaxI CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

type MaxI CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) = r
type MaxI CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

type MaxI CLong (l :: L CLong :: Type) (r :: R CLong :: Type) = r
type MaxI CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

type MaxI CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) = r
type MaxI CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

type MaxI CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) = r
type MaxI CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

type MaxI CShort (l :: L CShort :: Type) (r :: R CShort :: Type) = r
type MaxI CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

type MaxI CSize (l :: L CSize :: Type) (r :: R CSize :: Type) = r
type MaxI CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

type MaxI CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) = r
type MaxI CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

type MaxI CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) = r
type MaxI CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

type MaxI CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) = r
type MaxI CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

type MaxI CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) = r
type MaxI CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

type MaxI CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) = r
type MaxI CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

type MaxI CULong (l :: L CULong :: Type) (r :: R CULong :: Type) = r
type MaxI CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

type MaxI CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) = r
type MaxI CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

type MaxI CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) = r
type MaxI Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

type MaxI Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) = r
type MaxI Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

type MaxI Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) = r
type MaxI Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

type MaxI Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) = r
type MaxI Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

type MaxI Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) = r
type MaxI Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

type MaxI Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) = r
type MaxI Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

type MaxI Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) = r
type MaxI Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

type MaxI Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) = r
type MaxI Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

type MaxI Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) = r
type MaxI Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

type MaxI Int (l :: L Int :: Type) (r :: R Int :: Type) = r
type MaxI Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

type MaxI Word (l :: L Word :: Type) (r :: R Word :: Type) = r
type MinI CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

type MinI CChar (l :: L CChar :: Type) (r :: R CChar :: Type) = l
type MinI CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

type MinI CInt (l :: L CInt :: Type) (r :: R CInt :: Type) = l
type MinI CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

type MinI CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) = l
type MinI CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

type MinI CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) = l
type MinI CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

type MinI CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) = l
type MinI CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

type MinI CLong (l :: L CLong :: Type) (r :: R CLong :: Type) = l
type MinI CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

type MinI CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) = l
type MinI CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

type MinI CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) = l
type MinI CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

type MinI CShort (l :: L CShort :: Type) (r :: R CShort :: Type) = l
type MinI CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

type MinI CSize (l :: L CSize :: Type) (r :: R CSize :: Type) = l
type MinI CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

type MinI CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) = l
type MinI CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

type MinI CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) = l
type MinI CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

type MinI CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) = l
type MinI CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

type MinI CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) = l
type MinI CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

type MinI CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) = l
type MinI CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

type MinI CULong (l :: L CULong :: Type) (r :: R CULong :: Type) = l
type MinI CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

type MinI CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) = l
type MinI CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

type MinI CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) = l
type MinI Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

type MinI Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) = l
type MinI Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

type MinI Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) = l
type MinI Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

type MinI Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) = l
type MinI Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

type MinI Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) = l
type MinI Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

type MinI Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) = l
type MinI Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

type MinI Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) = l
type MinI Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

type MinI Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) = l
type MinI Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

type MinI Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) = l
type MinI Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

type MinI Int (l :: L Int :: Type) (r :: R Int :: Type) = l
type MinI Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

type MinI Word (l :: L Word :: Type) (r :: R Word :: Type) = l
type KnownCtx CChar (l :: L CChar :: Type) (r :: R CChar :: Type) (t :: T CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

type KnownCtx CChar (l :: L CChar :: Type) (r :: R CChar :: Type) (t :: T CChar :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CInt (l :: L CInt :: Type) (r :: R CInt :: Type) (t :: T CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

type KnownCtx CInt (l :: L CInt :: Type) (r :: R CInt :: Type) (t :: T CInt :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) (t :: T CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

type KnownCtx CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) (t :: T CIntMax :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) (t :: T CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

type KnownCtx CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) (t :: T CIntPtr :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) (t :: T CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

type KnownCtx CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) (t :: T CLLong :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CLong (l :: L CLong :: Type) (r :: R CLong :: Type) (t :: T CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

type KnownCtx CLong (l :: L CLong :: Type) (r :: R CLong :: Type) (t :: T CLong :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) (t :: T CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

type KnownCtx CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) (t :: T CPtrdiff :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) (t :: T CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

type KnownCtx CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) (t :: T CSChar :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CShort (l :: L CShort :: Type) (r :: R CShort :: Type) (t :: T CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

type KnownCtx CShort (l :: L CShort :: Type) (r :: R CShort :: Type) (t :: T CShort :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx CSize (l :: L CSize :: Type) (r :: R CSize :: Type) (t :: T CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

type KnownCtx CSize (l :: L CSize :: Type) (r :: R CSize :: Type) (t :: T CSize :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) (t :: T CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

type KnownCtx CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) (t :: T CUChar :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) (t :: T CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

type KnownCtx CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) (t :: T CUInt :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) (t :: T CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

type KnownCtx CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) (t :: T CUIntMax :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) (t :: T CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

type KnownCtx CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) (t :: T CUIntPtr :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) (t :: T CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

type KnownCtx CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) (t :: T CULLong :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CULong (l :: L CULong :: Type) (r :: R CULong :: Type) (t :: T CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

type KnownCtx CULong (l :: L CULong :: Type) (r :: R CULong :: Type) (t :: T CULong :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) (t :: T CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

type KnownCtx CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) (t :: T CUShort :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) (t :: T CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

type KnownCtx CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) (t :: T CWchar :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) (t :: T Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

type KnownCtx Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) (t :: T Int16 :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) (t :: T Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

type KnownCtx Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) (t :: T Int32 :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) (t :: T Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

type KnownCtx Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) (t :: T Int64 :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) (t :: T Int8 :: Type) Source # 
Instance details

Defined in I.Int8

type KnownCtx Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) (t :: T Int8 :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) (t :: T Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

type KnownCtx Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) (t :: T Word16 :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) (t :: T Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

type KnownCtx Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) (t :: T Word32 :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) (t :: T Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

type KnownCtx Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) (t :: T Word64 :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) (t :: T Word8 :: Type) Source # 
Instance details

Defined in I.Word8

type KnownCtx Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) (t :: T Word8 :: Type) = (KnownNat t, l <= t, t <= r)
type KnownCtx Int (l :: L Int :: Type) (r :: R Int :: Type) (t :: T Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

type KnownCtx Int (l :: L Int :: Type) (r :: R Int :: Type) (t :: T Int :: Type) = (KnownInteger t, l <= t, t <= r)
type KnownCtx Word (l :: L Word :: Type) (r :: R Word :: Type) (t :: T Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

type KnownCtx Word (l :: L Word :: Type) (r :: R Word :: Type) (t :: T Word :: Type) = (KnownNat t, l <= t, t <= r)
type IntervalCtx Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

type MaxI Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

type MaxI Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Natural l ('Nothing :: Maybe Natural))) ':<>: 'Text "\8217") :: T Natural :: Type
type MinI Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

type MinI Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) = l
type KnownCtx Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

type KnownCtx Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) (t :: T Natural :: Type) = (KnownNat t, l <= t)
type IntervalCtx Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

type IntervalCtx Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) = (KnownNat l, KnownNat r, MinT Natural <= l, l <= r)
type MaxI Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

type MaxI Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) = r
type MinI Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

type MinI Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) = l
type KnownCtx Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

type KnownCtx Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) (t :: T Natural :: Type) = (KnownNat t, l <= t, t <= r)
type IntervalCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

type MaxI Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MaxI Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

type MaxI Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer))) ':<>: 'Text "\8217") :: T Integer :: Type
type MinI Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MinI Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

type MinI Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer))) ':<>: 'Text "\8217") :: T Integer :: Type
type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

type IntervalCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

type MaxI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MaxI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) = r
type MaxI Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

type MaxI Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) = r
type MinI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MinI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MinI Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

type MinI Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Integer ('Nothing :: Maybe Integer) ('Just r))) ':<>: 'Text "\8217") :: T Integer :: Type
type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, t < r)
type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, t <= r)
type KnownCtx Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

type KnownCtx Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) = (KnownInteger t, t <= r)
type IntervalCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

type MaxI Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MaxI Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MaxI Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

type MaxI Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Integer ('Just l) ('Nothing :: Maybe Integer))) ':<>: 'Text "\8217") :: T Integer :: Type
type MinI Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MinI Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) = l
type MinI Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

type MinI Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) = l
type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) = (KnownRational t, l < t)
type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) = (KnownRational t, l <= t)
type KnownCtx Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

type KnownCtx Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) = (KnownInteger t, l <= t)
type IntervalCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) = (KnownRational l, KnownRational r, l < r)
type IntervalCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) = (KnownRational l, KnownRational r, l < r)
type IntervalCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) = (KnownRational l, KnownRational r, l < r)
type IntervalCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type IntervalCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) = (KnownRational l, KnownRational r, l <= r)
type IntervalCtx Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

type IntervalCtx Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) = (KnownInteger l, KnownInteger r, l <= r)
type MaxI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('False, l)) ('Just '('False, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MaxI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) = r
type MaxI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('True, l)) ('Just '('False, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MaxI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MaxI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) = r
type MaxI Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

type MaxI Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) = r
type MinI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('False, l)) ('Just '('False, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MinI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval Rational ('Just '('False, l)) ('Just '('True, r)))) ':<>: 'Text "\8217") :: T Rational :: Type
type MinI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) = l
type MinI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

type MinI Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) = l
type MinI Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

type MinI Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) = l
type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, l < t, t < r)
type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, l < t, t <= r)
type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, l <= t, t < r)
type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

type KnownCtx Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) = (KnownRational t, l <= t, t <= r)
type KnownCtx Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

type KnownCtx Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) = (KnownInteger t, l <= t, t <= r)

type family MaxR (x :: Type) :: R x Source #

Maximum right bound for x. All the values of type x are at most as MaxR x says, as required by wrap.

Instances

Instances details
type MaxR CChar Source # 
Instance details

Defined in I.Autogen.CChar

type MaxR CInt Source # 
Instance details

Defined in I.Autogen.CInt

type MaxR CIntMax Source # 
Instance details

Defined in I.Autogen.CIntMax

type MaxR CIntPtr Source # 
Instance details

Defined in I.Autogen.CIntPtr

type MaxR CLLong Source # 
Instance details

Defined in I.Autogen.CLLong

type MaxR CLong Source # 
Instance details

Defined in I.Autogen.CLong

type MaxR CPtrdiff Source # 
Instance details

Defined in I.Autogen.CPtrdiff

type MaxR CSChar Source # 
Instance details

Defined in I.Autogen.CSChar

type MaxR CShort Source # 
Instance details

Defined in I.Autogen.CShort

type MaxR CSize Source # 
Instance details

Defined in I.Autogen.CSize

type MaxR CUChar Source # 
Instance details

Defined in I.Autogen.CUChar

type MaxR CUInt Source # 
Instance details

Defined in I.Autogen.CUInt

type MaxR CUIntMax Source # 
Instance details

Defined in I.Autogen.CUIntMax

type MaxR CUIntPtr Source # 
Instance details

Defined in I.Autogen.CUIntPtr

type MaxR CULLong Source # 
Instance details

Defined in I.Autogen.CULLong

type MaxR CULong Source # 
Instance details

Defined in I.Autogen.CULong

type MaxR CUShort Source # 
Instance details

Defined in I.Autogen.CUShort

type MaxR CWchar Source # 
Instance details

Defined in I.Autogen.CWchar

type MaxR Int16 Source # 
Instance details

Defined in I.Autogen.Int16

type MaxR Int32 Source # 
Instance details

Defined in I.Autogen.Int32

type MaxR Int64 Source # 
Instance details

Defined in I.Autogen.Int64

type MaxR Int8 Source # 
Instance details

Defined in I.Int8

type MaxR Rational Source # 
Instance details

Defined in I.Rational

type MaxR Word16 Source # 
Instance details

Defined in I.Autogen.Word16

type MaxR Word32 Source # 
Instance details

Defined in I.Autogen.Word32

type MaxR Word64 Source # 
Instance details

Defined in I.Autogen.Word64

type MaxR Word8 Source # 
Instance details

Defined in I.Word8

type MaxR Integer Source # 
Instance details

Defined in I.Integer

type MaxR Natural Source # 
Instance details

Defined in I.Natural

type MaxR Int Source # 
Instance details

Defined in I.Autogen.Int

type MaxR Int = MaxT Int
type MaxR Word Source # 
Instance details

Defined in I.Autogen.Word

class IntervalCtx x l r => Interval (x :: Type) (l :: L x) (r :: R x) where Source #

For I x l r to be a valid interval type, Interval x l r needs to be satisfied. All Intervals are non-empty.

NB: When defining Interval instances, instead of mentioning any necessary constraints in the instance context, mention them them in IntervalCtx. By doing so, when an instance of Interval x l r is satisfied, IntervalCtx x l r is satisfied as well. If you don't do this, with won't behave as you would expect.

Minimal complete definition

inhabitant, from

Associated Types

type IntervalCtx x l r :: Constraint Source #

Constraints to be satisfied for I x l r to be a valid non-empty interval type.

type IntervalCtx x l r = ()

type MinI x l r :: T x Source #

Minimum value of type x contained in the interval I x l r, if any. If I x l r is unbounded on the left end, then it's ok to leave MinI x l r undefined. If defined, it should mean the same as l.

type MinI x l r = TypeError (('Text "MinI not defined in instance \8216" ':<>: 'ShowType (Interval x l r)) ':<>: 'Text "\8217")

type MaxI x l r :: T x Source #

Maximum value of type x contained in the interval I x l r, if any. If I x l r is unbounded on the right end, then it's ok to leave MaxI x l r undefined. If defined, it should mean the same as r.

type MaxI x l r = TypeError (('Text "MaxI not defined in instance \8216" ':<>: 'ShowType (Interval x l r)) ':<>: 'Text "\8217")

Methods

inhabitant :: I x l r Source #

Proof that there is at least one element in the I x l r interval.

No guarantees are made about the value of inhabitant other than the fact that it is known to inhabit the interval. The only exception to this are intervals that contain a single inhabitant, in which case inhabitant will produce it. See single.

from :: x -> Maybe (I x l r) Source #

Wrap the x value in the interval I x l r, if it fits.

  • Consider using wrap if the interval includes all values of type x.
  • Consider using known if you have type-level knowledge about the value of x.
  • Consider using unsafe if you know that the x is within the interval.
Identity law
forall (x :: Type).
  such that isJust (from x).
    fmap unwrap (from x)  ==  Just x

plus' :: I x l r -> I x l r -> Maybe (I x l r) Source #

plus' a b adds a and b.

Nothing if the result would be out of the interval. See plus, too.

mult' :: I x l r -> I x l r -> Maybe (I x l r) Source #

mult' a b multiplies a times b.

Nothing if the result would be out of the interval. See mult, too.

minus' :: I x l r -> I x l r -> Maybe (I x l r) Source #

minus' a b substracts b from a.

Nothing if the result would be out of the interval. See minus, too.

negate' :: I x l r -> Maybe (I x l r) Source #

negate' a is the additive inverse of a.

Nothing if the result would be out of the interval. See negate, too.

recip' :: I x l r -> Maybe (I x l r) Source #

recip' a is the multiplicative inverse of a.

Nothing if the result would be out of the interval.

div' :: I x l r -> I x l r -> Maybe (I x l r) Source #

div' a b divides a by b.

Nothing if the result would be out of the interval. See div too.

Instances

Instances details
IntervalCtx CChar l r => Interval CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Associated Types

type IntervalCtx CChar l r Source #

type MinI CChar l r :: T x :: Type Source #

type MaxI CChar l r :: T x :: Type Source #

Methods

inhabitant :: I CChar l r Source #

from :: CChar -> Maybe (I CChar l r) Source #

plus' :: I CChar l r -> I CChar l r -> Maybe (I CChar l r) Source #

mult' :: I CChar l r -> I CChar l r -> Maybe (I CChar l r) Source #

minus' :: I CChar l r -> I CChar l r -> Maybe (I CChar l r) Source #

negate' :: I CChar l r -> Maybe (I CChar l r) Source #

recip' :: I CChar l r -> Maybe (I CChar l r) Source #

div' :: I CChar l r -> I CChar l r -> Maybe (I CChar l r) Source #

IntervalCtx CInt l r => Interval CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Associated Types

type IntervalCtx CInt l r Source #

type MinI CInt l r :: T x :: Type Source #

type MaxI CInt l r :: T x :: Type Source #

Methods

inhabitant :: I CInt l r Source #

from :: CInt -> Maybe (I CInt l r) Source #

plus' :: I CInt l r -> I CInt l r -> Maybe (I CInt l r) Source #

mult' :: I CInt l r -> I CInt l r -> Maybe (I CInt l r) Source #

minus' :: I CInt l r -> I CInt l r -> Maybe (I CInt l r) Source #

negate' :: I CInt l r -> Maybe (I CInt l r) Source #

recip' :: I CInt l r -> Maybe (I CInt l r) Source #

div' :: I CInt l r -> I CInt l r -> Maybe (I CInt l r) Source #

IntervalCtx CIntMax l r => Interval CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Associated Types

type IntervalCtx CIntMax l r Source #

type MinI CIntMax l r :: T x :: Type Source #

type MaxI CIntMax l r :: T x :: Type Source #

Methods

inhabitant :: I CIntMax l r Source #

from :: CIntMax -> Maybe (I CIntMax l r) Source #

plus' :: I CIntMax l r -> I CIntMax l r -> Maybe (I CIntMax l r) Source #

mult' :: I CIntMax l r -> I CIntMax l r -> Maybe (I CIntMax l r) Source #

minus' :: I CIntMax l r -> I CIntMax l r -> Maybe (I CIntMax l r) Source #

negate' :: I CIntMax l r -> Maybe (I CIntMax l r) Source #

recip' :: I CIntMax l r -> Maybe (I CIntMax l r) Source #

div' :: I CIntMax l r -> I CIntMax l r -> Maybe (I CIntMax l r) Source #

IntervalCtx CIntPtr l r => Interval CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Associated Types

type IntervalCtx CIntPtr l r Source #

type MinI CIntPtr l r :: T x :: Type Source #

type MaxI CIntPtr l r :: T x :: Type Source #

Methods

inhabitant :: I CIntPtr l r Source #

from :: CIntPtr -> Maybe (I CIntPtr l r) Source #

plus' :: I CIntPtr l r -> I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

mult' :: I CIntPtr l r -> I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

minus' :: I CIntPtr l r -> I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

negate' :: I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

recip' :: I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

div' :: I CIntPtr l r -> I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

IntervalCtx CLLong l r => Interval CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Associated Types

type IntervalCtx CLLong l r Source #

type MinI CLLong l r :: T x :: Type Source #

type MaxI CLLong l r :: T x :: Type Source #

Methods

inhabitant :: I CLLong l r Source #

from :: CLLong -> Maybe (I CLLong l r) Source #

plus' :: I CLLong l r -> I CLLong l r -> Maybe (I CLLong l r) Source #

mult' :: I CLLong l r -> I CLLong l r -> Maybe (I CLLong l r) Source #

minus' :: I CLLong l r -> I CLLong l r -> Maybe (I CLLong l r) Source #

negate' :: I CLLong l r -> Maybe (I CLLong l r) Source #

recip' :: I CLLong l r -> Maybe (I CLLong l r) Source #

div' :: I CLLong l r -> I CLLong l r -> Maybe (I CLLong l r) Source #

IntervalCtx CLong l r => Interval CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Associated Types

type IntervalCtx CLong l r Source #

type MinI CLong l r :: T x :: Type Source #

type MaxI CLong l r :: T x :: Type Source #

Methods

inhabitant :: I CLong l r Source #

from :: CLong -> Maybe (I CLong l r) Source #

plus' :: I CLong l r -> I CLong l r -> Maybe (I CLong l r) Source #

mult' :: I CLong l r -> I CLong l r -> Maybe (I CLong l r) Source #

minus' :: I CLong l r -> I CLong l r -> Maybe (I CLong l r) Source #

negate' :: I CLong l r -> Maybe (I CLong l r) Source #

recip' :: I CLong l r -> Maybe (I CLong l r) Source #

div' :: I CLong l r -> I CLong l r -> Maybe (I CLong l r) Source #

IntervalCtx CPtrdiff l r => Interval CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Associated Types

type IntervalCtx CPtrdiff l r Source #

type MinI CPtrdiff l r :: T x :: Type Source #

type MaxI CPtrdiff l r :: T x :: Type Source #

Methods

inhabitant :: I CPtrdiff l r Source #

from :: CPtrdiff -> Maybe (I CPtrdiff l r) Source #

plus' :: I CPtrdiff l r -> I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

mult' :: I CPtrdiff l r -> I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

minus' :: I CPtrdiff l r -> I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

negate' :: I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

recip' :: I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

div' :: I CPtrdiff l r -> I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

IntervalCtx CSChar l r => Interval CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Associated Types

type IntervalCtx CSChar l r Source #

type MinI CSChar l r :: T x :: Type Source #

type MaxI CSChar l r :: T x :: Type Source #

Methods

inhabitant :: I CSChar l r Source #

from :: CSChar -> Maybe (I CSChar l r) Source #

plus' :: I CSChar l r -> I CSChar l r -> Maybe (I CSChar l r) Source #

mult' :: I CSChar l r -> I CSChar l r -> Maybe (I CSChar l r) Source #

minus' :: I CSChar l r -> I CSChar l r -> Maybe (I CSChar l r) Source #

negate' :: I CSChar l r -> Maybe (I CSChar l r) Source #

recip' :: I CSChar l r -> Maybe (I CSChar l r) Source #

div' :: I CSChar l r -> I CSChar l r -> Maybe (I CSChar l r) Source #

IntervalCtx CShort l r => Interval CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Associated Types

type IntervalCtx CShort l r Source #

type MinI CShort l r :: T x :: Type Source #

type MaxI CShort l r :: T x :: Type Source #

Methods

inhabitant :: I CShort l r Source #

from :: CShort -> Maybe (I CShort l r) Source #

plus' :: I CShort l r -> I CShort l r -> Maybe (I CShort l r) Source #

mult' :: I CShort l r -> I CShort l r -> Maybe (I CShort l r) Source #

minus' :: I CShort l r -> I CShort l r -> Maybe (I CShort l r) Source #

negate' :: I CShort l r -> Maybe (I CShort l r) Source #

recip' :: I CShort l r -> Maybe (I CShort l r) Source #

div' :: I CShort l r -> I CShort l r -> Maybe (I CShort l r) Source #

IntervalCtx CSize l r => Interval CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Associated Types

type IntervalCtx CSize l r Source #

type MinI CSize l r :: T x :: Type Source #

type MaxI CSize l r :: T x :: Type Source #

Methods

inhabitant :: I CSize l r Source #

from :: CSize -> Maybe (I CSize l r) Source #

plus' :: I CSize l r -> I CSize l r -> Maybe (I CSize l r) Source #

mult' :: I CSize l r -> I CSize l r -> Maybe (I CSize l r) Source #

minus' :: I CSize l r -> I CSize l r -> Maybe (I CSize l r) Source #

negate' :: I CSize l r -> Maybe (I CSize l r) Source #

recip' :: I CSize l r -> Maybe (I CSize l r) Source #

div' :: I CSize l r -> I CSize l r -> Maybe (I CSize l r) Source #

IntervalCtx CUChar l r => Interval CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Associated Types

type IntervalCtx CUChar l r Source #

type MinI CUChar l r :: T x :: Type Source #

type MaxI CUChar l r :: T x :: Type Source #

Methods

inhabitant :: I CUChar l r Source #

from :: CUChar -> Maybe (I CUChar l r) Source #

plus' :: I CUChar l r -> I CUChar l r -> Maybe (I CUChar l r) Source #

mult' :: I CUChar l r -> I CUChar l r -> Maybe (I CUChar l r) Source #

minus' :: I CUChar l r -> I CUChar l r -> Maybe (I CUChar l r) Source #

negate' :: I CUChar l r -> Maybe (I CUChar l r) Source #

recip' :: I CUChar l r -> Maybe (I CUChar l r) Source #

div' :: I CUChar l r -> I CUChar l r -> Maybe (I CUChar l r) Source #

IntervalCtx CUInt l r => Interval CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Associated Types

type IntervalCtx CUInt l r Source #

type MinI CUInt l r :: T x :: Type Source #

type MaxI CUInt l r :: T x :: Type Source #

Methods

inhabitant :: I CUInt l r Source #

from :: CUInt -> Maybe (I CUInt l r) Source #

plus' :: I CUInt l r -> I CUInt l r -> Maybe (I CUInt l r) Source #

mult' :: I CUInt l r -> I CUInt l r -> Maybe (I CUInt l r) Source #

minus' :: I CUInt l r -> I CUInt l r -> Maybe (I CUInt l r) Source #

negate' :: I CUInt l r -> Maybe (I CUInt l r) Source #

recip' :: I CUInt l r -> Maybe (I CUInt l r) Source #

div' :: I CUInt l r -> I CUInt l r -> Maybe (I CUInt l r) Source #

IntervalCtx CUIntMax l r => Interval CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Associated Types

type IntervalCtx CUIntMax l r Source #

type MinI CUIntMax l r :: T x :: Type Source #

type MaxI CUIntMax l r :: T x :: Type Source #

Methods

inhabitant :: I CUIntMax l r Source #

from :: CUIntMax -> Maybe (I CUIntMax l r) Source #

plus' :: I CUIntMax l r -> I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

mult' :: I CUIntMax l r -> I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

minus' :: I CUIntMax l r -> I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

negate' :: I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

recip' :: I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

div' :: I CUIntMax l r -> I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

IntervalCtx CUIntPtr l r => Interval CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Associated Types

type IntervalCtx CUIntPtr l r Source #

type MinI CUIntPtr l r :: T x :: Type Source #

type MaxI CUIntPtr l r :: T x :: Type Source #

Methods

inhabitant :: I CUIntPtr l r Source #

from :: CUIntPtr -> Maybe (I CUIntPtr l r) Source #

plus' :: I CUIntPtr l r -> I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

mult' :: I CUIntPtr l r -> I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

minus' :: I CUIntPtr l r -> I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

negate' :: I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

recip' :: I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

div' :: I CUIntPtr l r -> I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

IntervalCtx CULLong l r => Interval CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Associated Types

type IntervalCtx CULLong l r Source #

type MinI CULLong l r :: T x :: Type Source #

type MaxI CULLong l r :: T x :: Type Source #

Methods

inhabitant :: I CULLong l r Source #

from :: CULLong -> Maybe (I CULLong l r) Source #

plus' :: I CULLong l r -> I CULLong l r -> Maybe (I CULLong l r) Source #

mult' :: I CULLong l r -> I CULLong l r -> Maybe (I CULLong l r) Source #

minus' :: I CULLong l r -> I CULLong l r -> Maybe (I CULLong l r) Source #

negate' :: I CULLong l r -> Maybe (I CULLong l r) Source #

recip' :: I CULLong l r -> Maybe (I CULLong l r) Source #

div' :: I CULLong l r -> I CULLong l r -> Maybe (I CULLong l r) Source #

IntervalCtx CULong l r => Interval CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Associated Types

type IntervalCtx CULong l r Source #

type MinI CULong l r :: T x :: Type Source #

type MaxI CULong l r :: T x :: Type Source #

Methods

inhabitant :: I CULong l r Source #

from :: CULong -> Maybe (I CULong l r) Source #

plus' :: I CULong l r -> I CULong l r -> Maybe (I CULong l r) Source #

mult' :: I CULong l r -> I CULong l r -> Maybe (I CULong l r) Source #

minus' :: I CULong l r -> I CULong l r -> Maybe (I CULong l r) Source #

negate' :: I CULong l r -> Maybe (I CULong l r) Source #

recip' :: I CULong l r -> Maybe (I CULong l r) Source #

div' :: I CULong l r -> I CULong l r -> Maybe (I CULong l r) Source #

IntervalCtx CUShort l r => Interval CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Associated Types

type IntervalCtx CUShort l r Source #

type MinI CUShort l r :: T x :: Type Source #

type MaxI CUShort l r :: T x :: Type Source #

Methods

inhabitant :: I CUShort l r Source #

from :: CUShort -> Maybe (I CUShort l r) Source #

plus' :: I CUShort l r -> I CUShort l r -> Maybe (I CUShort l r) Source #

mult' :: I CUShort l r -> I CUShort l r -> Maybe (I CUShort l r) Source #

minus' :: I CUShort l r -> I CUShort l r -> Maybe (I CUShort l r) Source #

negate' :: I CUShort l r -> Maybe (I CUShort l r) Source #

recip' :: I CUShort l r -> Maybe (I CUShort l r) Source #

div' :: I CUShort l r -> I CUShort l r -> Maybe (I CUShort l r) Source #

IntervalCtx CWchar l r => Interval CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Associated Types

type IntervalCtx CWchar l r Source #

type MinI CWchar l r :: T x :: Type Source #

type MaxI CWchar l r :: T x :: Type Source #

Methods

inhabitant :: I CWchar l r Source #

from :: CWchar -> Maybe (I CWchar l r) Source #

plus' :: I CWchar l r -> I CWchar l r -> Maybe (I CWchar l r) Source #

mult' :: I CWchar l r -> I CWchar l r -> Maybe (I CWchar l r) Source #

minus' :: I CWchar l r -> I CWchar l r -> Maybe (I CWchar l r) Source #

negate' :: I CWchar l r -> Maybe (I CWchar l r) Source #

recip' :: I CWchar l r -> Maybe (I CWchar l r) Source #

div' :: I CWchar l r -> I CWchar l r -> Maybe (I CWchar l r) Source #

IntervalCtx Int16 l r => Interval Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Associated Types

type IntervalCtx Int16 l r Source #

type MinI Int16 l r :: T x :: Type Source #

type MaxI Int16 l r :: T x :: Type Source #

Methods

inhabitant :: I Int16 l r Source #

from :: Int16 -> Maybe (I Int16 l r) Source #

plus' :: I Int16 l r -> I Int16 l r -> Maybe (I Int16 l r) Source #

mult' :: I Int16 l r -> I Int16 l r -> Maybe (I Int16 l r) Source #

minus' :: I Int16 l r -> I Int16 l r -> Maybe (I Int16 l r) Source #

negate' :: I Int16 l r -> Maybe (I Int16 l r) Source #

recip' :: I Int16 l r -> Maybe (I Int16 l r) Source #

div' :: I Int16 l r -> I Int16 l r -> Maybe (I Int16 l r) Source #

IntervalCtx Int32 l r => Interval Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Associated Types

type IntervalCtx Int32 l r Source #

type MinI Int32 l r :: T x :: Type Source #

type MaxI Int32 l r :: T x :: Type Source #

Methods

inhabitant :: I Int32 l r Source #

from :: Int32 -> Maybe (I Int32 l r) Source #

plus' :: I Int32 l r -> I Int32 l r -> Maybe (I Int32 l r) Source #

mult' :: I Int32 l r -> I Int32 l r -> Maybe (I Int32 l r) Source #

minus' :: I Int32 l r -> I Int32 l r -> Maybe (I Int32 l r) Source #

negate' :: I Int32 l r -> Maybe (I Int32 l r) Source #

recip' :: I Int32 l r -> Maybe (I Int32 l r) Source #

div' :: I Int32 l r -> I Int32 l r -> Maybe (I Int32 l r) Source #

IntervalCtx Int64 l r => Interval Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Associated Types

type IntervalCtx Int64 l r Source #

type MinI Int64 l r :: T x :: Type Source #

type MaxI Int64 l r :: T x :: Type Source #

Methods

inhabitant :: I Int64 l r Source #

from :: Int64 -> Maybe (I Int64 l r) Source #

plus' :: I Int64 l r -> I Int64 l r -> Maybe (I Int64 l r) Source #

mult' :: I Int64 l r -> I Int64 l r -> Maybe (I Int64 l r) Source #

minus' :: I Int64 l r -> I Int64 l r -> Maybe (I Int64 l r) Source #

negate' :: I Int64 l r -> Maybe (I Int64 l r) Source #

recip' :: I Int64 l r -> Maybe (I Int64 l r) Source #

div' :: I Int64 l r -> I Int64 l r -> Maybe (I Int64 l r) Source #

IntervalCtx Int8 l r => Interval Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Associated Types

type IntervalCtx Int8 l r Source #

type MinI Int8 l r :: T x :: Type Source #

type MaxI Int8 l r :: T x :: Type Source #

Methods

inhabitant :: I Int8 l r Source #

from :: Int8 -> Maybe (I Int8 l r) Source #

plus' :: I Int8 l r -> I Int8 l r -> Maybe (I Int8 l r) Source #

mult' :: I Int8 l r -> I Int8 l r -> Maybe (I Int8 l r) Source #

minus' :: I Int8 l r -> I Int8 l r -> Maybe (I Int8 l r) Source #

negate' :: I Int8 l r -> Maybe (I Int8 l r) Source #

recip' :: I Int8 l r -> Maybe (I Int8 l r) Source #

div' :: I Int8 l r -> I Int8 l r -> Maybe (I Int8 l r) Source #

IntervalCtx Word16 l r => Interval Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Associated Types

type IntervalCtx Word16 l r Source #

type MinI Word16 l r :: T x :: Type Source #

type MaxI Word16 l r :: T x :: Type Source #

Methods

inhabitant :: I Word16 l r Source #

from :: Word16 -> Maybe (I Word16 l r) Source #

plus' :: I Word16 l r -> I Word16 l r -> Maybe (I Word16 l r) Source #

mult' :: I Word16 l r -> I Word16 l r -> Maybe (I Word16 l r) Source #

minus' :: I Word16 l r -> I Word16 l r -> Maybe (I Word16 l r) Source #

negate' :: I Word16 l r -> Maybe (I Word16 l r) Source #

recip' :: I Word16 l r -> Maybe (I Word16 l r) Source #

div' :: I Word16 l r -> I Word16 l r -> Maybe (I Word16 l r) Source #

IntervalCtx Word32 l r => Interval Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Associated Types

type IntervalCtx Word32 l r Source #

type MinI Word32 l r :: T x :: Type Source #

type MaxI Word32 l r :: T x :: Type Source #

Methods

inhabitant :: I Word32 l r Source #

from :: Word32 -> Maybe (I Word32 l r) Source #

plus' :: I Word32 l r -> I Word32 l r -> Maybe (I Word32 l r) Source #

mult' :: I Word32 l r -> I Word32 l r -> Maybe (I Word32 l r) Source #

minus' :: I Word32 l r -> I Word32 l r -> Maybe (I Word32 l r) Source #

negate' :: I Word32 l r -> Maybe (I Word32 l r) Source #

recip' :: I Word32 l r -> Maybe (I Word32 l r) Source #

div' :: I Word32 l r -> I Word32 l r -> Maybe (I Word32 l r) Source #

IntervalCtx Word64 l r => Interval Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Associated Types

type IntervalCtx Word64 l r Source #

type MinI Word64 l r :: T x :: Type Source #

type MaxI Word64 l r :: T x :: Type Source #

Methods

inhabitant :: I Word64 l r Source #

from :: Word64 -> Maybe (I Word64 l r) Source #

plus' :: I Word64 l r -> I Word64 l r -> Maybe (I Word64 l r) Source #

mult' :: I Word64 l r -> I Word64 l r -> Maybe (I Word64 l r) Source #

minus' :: I Word64 l r -> I Word64 l r -> Maybe (I Word64 l r) Source #

negate' :: I Word64 l r -> Maybe (I Word64 l r) Source #

recip' :: I Word64 l r -> Maybe (I Word64 l r) Source #

div' :: I Word64 l r -> I Word64 l r -> Maybe (I Word64 l r) Source #

IntervalCtx Word8 l r => Interval Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Associated Types

type IntervalCtx Word8 l r Source #

type MinI Word8 l r :: T x :: Type Source #

type MaxI Word8 l r :: T x :: Type Source #

Methods

inhabitant :: I Word8 l r Source #

from :: Word8 -> Maybe (I Word8 l r) Source #

plus' :: I Word8 l r -> I Word8 l r -> Maybe (I Word8 l r) Source #

mult' :: I Word8 l r -> I Word8 l r -> Maybe (I Word8 l r) Source #

minus' :: I Word8 l r -> I Word8 l r -> Maybe (I Word8 l r) Source #

negate' :: I Word8 l r -> Maybe (I Word8 l r) Source #

recip' :: I Word8 l r -> Maybe (I Word8 l r) Source #

div' :: I Word8 l r -> I Word8 l r -> Maybe (I Word8 l r) Source #

IntervalCtx Int l r => Interval Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Associated Types

type IntervalCtx Int l r Source #

type MinI Int l r :: T x :: Type Source #

type MaxI Int l r :: T x :: Type Source #

Methods

inhabitant :: I Int l r Source #

from :: Int -> Maybe (I Int l r) Source #

plus' :: I Int l r -> I Int l r -> Maybe (I Int l r) Source #

mult' :: I Int l r -> I Int l r -> Maybe (I Int l r) Source #

minus' :: I Int l r -> I Int l r -> Maybe (I Int l r) Source #

negate' :: I Int l r -> Maybe (I Int l r) Source #

recip' :: I Int l r -> Maybe (I Int l r) Source #

div' :: I Int l r -> I Int l r -> Maybe (I Int l r) Source #

IntervalCtx Word l r => Interval Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Associated Types

type IntervalCtx Word l r Source #

type MinI Word l r :: T x :: Type Source #

type MaxI Word l r :: T x :: Type Source #

Methods

inhabitant :: I Word l r Source #

from :: Word -> Maybe (I Word l r) Source #

plus' :: I Word l r -> I Word l r -> Maybe (I Word l r) Source #

mult' :: I Word l r -> I Word l r -> Maybe (I Word l r) Source #

minus' :: I Word l r -> I Word l r -> Maybe (I Word l r) Source #

negate' :: I Word l r -> Maybe (I Word l r) Source #

recip' :: I Word l r -> Maybe (I Word l r) Source #

div' :: I Word l r -> I Word l r -> Maybe (I Word l r) Source #

IntervalCtx Natural l ('Nothing :: Maybe Natural) => Interval Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Associated Types

type IntervalCtx Natural l 'Nothing Source #

type MinI Natural l 'Nothing :: T x :: Type Source #

type MaxI Natural l 'Nothing :: T x :: Type Source #

IntervalCtx Natural l ('Just r) => Interval Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Associated Types

type IntervalCtx Natural l ('Just r) Source #

type MinI Natural l ('Just r) :: T x :: Type Source #

type MaxI Natural l ('Just r) :: T x :: Type Source #

Methods

inhabitant :: I Natural l ('Just r) Source #

from :: Natural -> Maybe (I Natural l ('Just r)) Source #

plus' :: I Natural l ('Just r) -> I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

mult' :: I Natural l ('Just r) -> I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

minus' :: I Natural l ('Just r) -> I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

negate' :: I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

recip' :: I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

div' :: I Natural l ('Just r) -> I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

IntervalCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)) => Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational 'Nothing ('Just '('False, r)) Source #

type MinI Rational 'Nothing ('Just '('False, r)) :: T x :: Type Source #

type MaxI Rational 'Nothing ('Just '('False, r)) :: T x :: Type Source #

IntervalCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) => Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational 'Nothing ('Just '('True, r)) Source #

type MinI Rational 'Nothing ('Just '('True, r)) :: T x :: Type Source #

type MaxI Rational 'Nothing ('Just '('True, r)) :: T x :: Type Source #

IntervalCtx Integer ('Nothing :: Maybe Integer) ('Just r) => Interval Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type IntervalCtx Integer 'Nothing ('Just r) Source #

type MinI Integer 'Nothing ('Just r) :: T x :: Type Source #

type MaxI Integer 'Nothing ('Just r) :: T x :: Type Source #

IntervalCtx Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)) => Interval Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('False, l)) 'Nothing Source #

type MinI Rational ('Just '('False, l)) 'Nothing :: T x :: Type Source #

type MaxI Rational ('Just '('False, l)) 'Nothing :: T x :: Type Source #

IntervalCtx Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) => Interval Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('True, l)) 'Nothing Source #

type MinI Rational ('Just '('True, l)) 'Nothing :: T x :: Type Source #

type MaxI Rational ('Just '('True, l)) 'Nothing :: T x :: Type Source #

IntervalCtx Integer ('Just l) ('Nothing :: Maybe Integer) => Interval Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Associated Types

type IntervalCtx Integer ('Just l) 'Nothing Source #

type MinI Integer ('Just l) 'Nothing :: T x :: Type Source #

type MaxI Integer ('Just l) 'Nothing :: T x :: Type Source #

IntervalCtx Rational ('Just '('False, l)) ('Just '('False, r)) => Interval Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('False, l)) ('Just '('False, r)) Source #

type MinI Rational ('Just '('False, l)) ('Just '('False, r)) :: T x :: Type Source #

type MaxI Rational ('Just '('False, l)) ('Just '('False, r)) :: T x :: Type Source #

Methods

inhabitant :: I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

from :: Rational -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

plus' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

mult' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

minus' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

negate' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

recip' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

div' :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> I Rational ('Just '('False, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('False, r))) Source #

IntervalCtx Rational ('Just '('False, l)) ('Just '('True, r)) => Interval Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('False, l)) ('Just '('True, r)) Source #

type MinI Rational ('Just '('False, l)) ('Just '('True, r)) :: T x :: Type Source #

type MaxI Rational ('Just '('False, l)) ('Just '('True, r)) :: T x :: Type Source #

Methods

inhabitant :: I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

from :: Rational -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

plus' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

mult' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

minus' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

negate' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

recip' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

div' :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> I Rational ('Just '('False, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('False, l)) ('Just '('True, r))) Source #

IntervalCtx Rational ('Just '('True, l)) ('Just '('False, r)) => Interval Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('True, l)) ('Just '('False, r)) Source #

type MinI Rational ('Just '('True, l)) ('Just '('False, r)) :: T x :: Type Source #

type MaxI Rational ('Just '('True, l)) ('Just '('False, r)) :: T x :: Type Source #

Methods

inhabitant :: I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

from :: Rational -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

plus' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

mult' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

minus' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

negate' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

recip' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

div' :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> I Rational ('Just '('True, l)) ('Just '('False, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('False, r))) Source #

IntervalCtx Rational ('Just '('True, l)) ('Just '('True, r)) => Interval Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type IntervalCtx Rational ('Just '('True, l)) ('Just '('True, r)) Source #

type MinI Rational ('Just '('True, l)) ('Just '('True, r)) :: T x :: Type Source #

type MaxI Rational ('Just '('True, l)) ('Just '('True, r)) :: T x :: Type Source #

Methods

inhabitant :: I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

from :: Rational -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

plus' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

mult' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

minus' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

negate' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

recip' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

div' :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> I Rational ('Just '('True, l)) ('Just '('True, r)) -> Maybe (I Rational ('Just '('True, l)) ('Just '('True, r))) Source #

IntervalCtx Integer ('Just l) ('Just r) => Interval Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type IntervalCtx Integer ('Just l) ('Just r) Source #

type MinI Integer ('Just l) ('Just r) :: T x :: Type Source #

type MaxI Integer ('Just l) ('Just r) :: T x :: Type Source #

Methods

inhabitant :: I Integer ('Just l) ('Just r) Source #

from :: Integer -> Maybe (I Integer ('Just l) ('Just r)) Source #

plus' :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

mult' :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

minus' :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

negate' :: I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

recip' :: I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

div' :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

unwrap :: forall x l r. I x l r -> x Source #

Obtain the x that is wrapped in the I x l r.

Identity law
wrap . unwrap == id
unwrap . wrap == id

wrap :: Interval x (MinL x) (MaxR x) => x -> I x (MinL x) (MaxR x) Source #

Wrap the given x in the interval I x (MinL x) (MaxR x).

This function always succeeds because the interval known to fit all the values of type x.

Identity law
wrap . unwrap == id
unwrap . wrap == id

If the interval is not as big as x:

  • Consider using from.
  • Consider using known if you have type-level knowledge about the value of x.
  • Consider using unsafe if you know that the x is within the interval.

unsafe :: forall x l r. (HasCallStack, Interval x l r) => x -> I x l r Source #

unsafe allows you to wrap an x in an I x l r, failing with error if the x is outside the interval.

WARNING: This function calls from, which means that you can't use it to implement from. You will have to use unsafest in that case. Your code will loop indefinitely otherwise.

class Interval x l r => Clamp (x :: Type) (l :: L x) (r :: R x) where Source #

Intervals that support clamping.

Minimal complete definition

Nothing

Methods

clamp :: x -> I x l r Source #

Wrap x in I x l r, making sure that x is within the interval ends by clamping it to MinI x l r if less than l, or to MaxI x l r if more than r, if necessary.

default clamp :: (Known x l r (MinI x l r), Known x l r (MaxI x l r), Ord x) => x -> I x l r Source #

Instances

Instances details
Interval CChar l r => Clamp CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

clamp :: CChar -> I CChar l r Source #

Interval CInt l r => Clamp CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

clamp :: CInt -> I CInt l r Source #

Interval CIntMax l r => Clamp CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

clamp :: CIntMax -> I CIntMax l r Source #

Interval CIntPtr l r => Clamp CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

clamp :: CIntPtr -> I CIntPtr l r Source #

Interval CLLong l r => Clamp CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

clamp :: CLLong -> I CLLong l r Source #

Interval CLong l r => Clamp CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

clamp :: CLong -> I CLong l r Source #

Interval CPtrdiff l r => Clamp CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

clamp :: CPtrdiff -> I CPtrdiff l r Source #

Interval CSChar l r => Clamp CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

clamp :: CSChar -> I CSChar l r Source #

Interval CShort l r => Clamp CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

clamp :: CShort -> I CShort l r Source #

Interval CSize l r => Clamp CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

clamp :: CSize -> I CSize l r Source #

Interval CUChar l r => Clamp CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

clamp :: CUChar -> I CUChar l r Source #

Interval CUInt l r => Clamp CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

clamp :: CUInt -> I CUInt l r Source #

Interval CUIntMax l r => Clamp CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

clamp :: CUIntMax -> I CUIntMax l r Source #

Interval CUIntPtr l r => Clamp CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

clamp :: CUIntPtr -> I CUIntPtr l r Source #

Interval CULLong l r => Clamp CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

clamp :: CULLong -> I CULLong l r Source #

Interval CULong l r => Clamp CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

clamp :: CULong -> I CULong l r Source #

Interval CUShort l r => Clamp CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

clamp :: CUShort -> I CUShort l r Source #

Interval CWchar l r => Clamp CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

clamp :: CWchar -> I CWchar l r Source #

Interval Int16 l r => Clamp Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

clamp :: Int16 -> I Int16 l r Source #

Interval Int32 l r => Clamp Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

clamp :: Int32 -> I Int32 l r Source #

Interval Int64 l r => Clamp Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

clamp :: Int64 -> I Int64 l r Source #

Interval Int8 l r => Clamp Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

clamp :: Int8 -> I Int8 l r Source #

Interval Word16 l r => Clamp Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

clamp :: Word16 -> I Word16 l r Source #

Interval Word32 l r => Clamp Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

clamp :: Word32 -> I Word32 l r Source #

Interval Word64 l r => Clamp Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

clamp :: Word64 -> I Word64 l r Source #

Interval Word8 l r => Clamp Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

clamp :: Word8 -> I Word8 l r Source #

Interval Int l r => Clamp Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

clamp :: Int -> I Int l r Source #

Interval Word l r => Clamp Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

clamp :: Word -> I Word l r Source #

Interval Natural l ('Nothing :: Maybe Natural) => Clamp Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Interval Natural l ('Just r) => Clamp Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

clamp :: Natural -> I Natural l ('Just r) Source #

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) => Clamp Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) => Clamp Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) => Clamp Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

clamp :: Rational0 -> I Rational0 'Nothing ('Just '('True, r)) Source #

Interval Integer ('Nothing :: Maybe Integer) ('Just r) => Clamp Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) => Clamp Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

clamp :: Rational0 -> I Rational0 ('Just '('True, l)) 'Nothing Source #

Interval Integer ('Just l) ('Nothing :: Maybe Integer) => Clamp Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Just '('True, l)) ('Just '('True, r)) => Clamp Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

clamp :: Rational -> I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

Interval Integer ('Just l) ('Just r) => Clamp Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

clamp :: Integer -> I Integer ('Just l) ('Just r) Source #

class (Interval x ld rd, Interval x lu ru) => Up (x :: Type) (ld :: L x) (rd :: R x) (lu :: L x) (ru :: R x) where Source #

Intervals that can be upcasted to a larger Interval type.

Minimal complete definition

Nothing

Methods

up :: I x ld rd -> I x lu ru Source #

Proof that I x ld rd can be upcasted into I x lu ru.

Identity law
forall (a :: I x ld rd).
  (Up x ld rd lu ru) =>
    unwrap a == unwrap (up a :: I x lu ru)

default up :: HasCallStack => I x ld rd -> I x lu ru Source #

Instances

Instances details
(Interval CChar ld rd, Interval CChar lu ru, lu <= ld, rd <= ru) => Up CChar (ld :: L CChar :: Type) (rd :: R CChar :: Type) (lu :: L CChar :: Type) (ru :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

up :: I CChar ld rd -> I CChar lu ru Source #

(Interval CInt ld rd, Interval CInt lu ru, lu <= ld, rd <= ru) => Up CInt (ld :: L CInt :: Type) (rd :: R CInt :: Type) (lu :: L CInt :: Type) (ru :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

up :: I CInt ld rd -> I CInt lu ru Source #

(Interval CIntMax ld rd, Interval CIntMax lu ru, lu <= ld, rd <= ru) => Up CIntMax (ld :: L CIntMax :: Type) (rd :: R CIntMax :: Type) (lu :: L CIntMax :: Type) (ru :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

up :: I CIntMax ld rd -> I CIntMax lu ru Source #

(Interval CIntPtr ld rd, Interval CIntPtr lu ru, lu <= ld, rd <= ru) => Up CIntPtr (ld :: L CIntPtr :: Type) (rd :: R CIntPtr :: Type) (lu :: L CIntPtr :: Type) (ru :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

up :: I CIntPtr ld rd -> I CIntPtr lu ru Source #

(Interval CLLong ld rd, Interval CLLong lu ru, lu <= ld, rd <= ru) => Up CLLong (ld :: L CLLong :: Type) (rd :: R CLLong :: Type) (lu :: L CLLong :: Type) (ru :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

up :: I CLLong ld rd -> I CLLong lu ru Source #

(Interval CLong ld rd, Interval CLong lu ru, lu <= ld, rd <= ru) => Up CLong (ld :: L CLong :: Type) (rd :: R CLong :: Type) (lu :: L CLong :: Type) (ru :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

up :: I CLong ld rd -> I CLong lu ru Source #

(Interval CPtrdiff ld rd, Interval CPtrdiff lu ru, lu <= ld, rd <= ru) => Up CPtrdiff (ld :: L CPtrdiff :: Type) (rd :: R CPtrdiff :: Type) (lu :: L CPtrdiff :: Type) (ru :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

up :: I CPtrdiff ld rd -> I CPtrdiff lu ru Source #

(Interval CSChar ld rd, Interval CSChar lu ru, lu <= ld, rd <= ru) => Up CSChar (ld :: L CSChar :: Type) (rd :: R CSChar :: Type) (lu :: L CSChar :: Type) (ru :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

up :: I CSChar ld rd -> I CSChar lu ru Source #

(Interval CShort ld rd, Interval CShort lu ru, lu <= ld, rd <= ru) => Up CShort (ld :: L CShort :: Type) (rd :: R CShort :: Type) (lu :: L CShort :: Type) (ru :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

up :: I CShort ld rd -> I CShort lu ru Source #

(Interval CSize ld rd, Interval CSize lu ru, lu <= ld, rd <= ru) => Up CSize (ld :: L CSize :: Type) (rd :: R CSize :: Type) (lu :: L CSize :: Type) (ru :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

up :: I CSize ld rd -> I CSize lu ru Source #

(Interval CUChar ld rd, Interval CUChar lu ru, lu <= ld, rd <= ru) => Up CUChar (ld :: L CUChar :: Type) (rd :: R CUChar :: Type) (lu :: L CUChar :: Type) (ru :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

up :: I CUChar ld rd -> I CUChar lu ru Source #

(Interval CUInt ld rd, Interval CUInt lu ru, lu <= ld, rd <= ru) => Up CUInt (ld :: L CUInt :: Type) (rd :: R CUInt :: Type) (lu :: L CUInt :: Type) (ru :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

up :: I CUInt ld rd -> I CUInt lu ru Source #

(Interval CUIntMax ld rd, Interval CUIntMax lu ru, lu <= ld, rd <= ru) => Up CUIntMax (ld :: L CUIntMax :: Type) (rd :: R CUIntMax :: Type) (lu :: L CUIntMax :: Type) (ru :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

up :: I CUIntMax ld rd -> I CUIntMax lu ru Source #

(Interval CUIntPtr ld rd, Interval CUIntPtr lu ru, lu <= ld, rd <= ru) => Up CUIntPtr (ld :: L CUIntPtr :: Type) (rd :: R CUIntPtr :: Type) (lu :: L CUIntPtr :: Type) (ru :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

up :: I CUIntPtr ld rd -> I CUIntPtr lu ru Source #

(Interval CULLong ld rd, Interval CULLong lu ru, lu <= ld, rd <= ru) => Up CULLong (ld :: L CULLong :: Type) (rd :: R CULLong :: Type) (lu :: L CULLong :: Type) (ru :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

up :: I CULLong ld rd -> I CULLong lu ru Source #

(Interval CULong ld rd, Interval CULong lu ru, lu <= ld, rd <= ru) => Up CULong (ld :: L CULong :: Type) (rd :: R CULong :: Type) (lu :: L CULong :: Type) (ru :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

up :: I CULong ld rd -> I CULong lu ru Source #

(Interval CUShort ld rd, Interval CUShort lu ru, lu <= ld, rd <= ru) => Up CUShort (ld :: L CUShort :: Type) (rd :: R CUShort :: Type) (lu :: L CUShort :: Type) (ru :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

up :: I CUShort ld rd -> I CUShort lu ru Source #

(Interval CWchar ld rd, Interval CWchar lu ru, lu <= ld, rd <= ru) => Up CWchar (ld :: L CWchar :: Type) (rd :: R CWchar :: Type) (lu :: L CWchar :: Type) (ru :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

up :: I CWchar ld rd -> I CWchar lu ru Source #

(Interval Int16 ld rd, Interval Int16 lu ru, lu <= ld, rd <= ru) => Up Int16 (ld :: L Int16 :: Type) (rd :: R Int16 :: Type) (lu :: L Int16 :: Type) (ru :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

up :: I Int16 ld rd -> I Int16 lu ru Source #

(Interval Int32 ld rd, Interval Int32 lu ru, lu <= ld, rd <= ru) => Up Int32 (ld :: L Int32 :: Type) (rd :: R Int32 :: Type) (lu :: L Int32 :: Type) (ru :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

up :: I Int32 ld rd -> I Int32 lu ru Source #

(Interval Int64 ld rd, Interval Int64 lu ru, lu <= ld, rd <= ru) => Up Int64 (ld :: L Int64 :: Type) (rd :: R Int64 :: Type) (lu :: L Int64 :: Type) (ru :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

up :: I Int64 ld rd -> I Int64 lu ru Source #

(Interval Int8 ld rd, Interval Int8 lu ru, lu <= ld, rd <= ru) => Up Int8 (ld :: L Int8 :: Type) (rd :: R Int8 :: Type) (lu :: L Int8 :: Type) (ru :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

up :: I Int8 ld rd -> I Int8 lu ru Source #

(Interval Word16 ld rd, Interval Word16 lu ru, lu <= ld, rd <= ru) => Up Word16 (ld :: L Word16 :: Type) (rd :: R Word16 :: Type) (lu :: L Word16 :: Type) (ru :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

up :: I Word16 ld rd -> I Word16 lu ru Source #

(Interval Word32 ld rd, Interval Word32 lu ru, lu <= ld, rd <= ru) => Up Word32 (ld :: L Word32 :: Type) (rd :: R Word32 :: Type) (lu :: L Word32 :: Type) (ru :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

up :: I Word32 ld rd -> I Word32 lu ru Source #

(Interval Word64 ld rd, Interval Word64 lu ru, lu <= ld, rd <= ru) => Up Word64 (ld :: L Word64 :: Type) (rd :: R Word64 :: Type) (lu :: L Word64 :: Type) (ru :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

up :: I Word64 ld rd -> I Word64 lu ru Source #

(Interval Word8 ld rd, Interval Word8 lu ru, lu <= ld, rd <= ru) => Up Word8 (ld :: L Word8 :: Type) (rd :: R Word8 :: Type) (lu :: L Word8 :: Type) (ru :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

up :: I Word8 ld rd -> I Word8 lu ru Source #

(Interval Int ld rd, Interval Int lu ru, lu <= ld, rd <= ru) => Up Int (ld :: L Int :: Type) (rd :: R Int :: Type) (lu :: L Int :: Type) (ru :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

up :: I Int ld rd -> I Int lu ru Source #

(Interval Word ld rd, Interval Word lu ru, lu <= ld, rd <= ru) => Up Word (ld :: L Word :: Type) (rd :: R Word :: Type) (lu :: L Word :: Type) (ru :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

up :: I Word ld rd -> I Word lu ru Source #

Interval x l r => Up x (l :: L x :: Type) (r :: R x :: Type) (l :: L x :: Type) (r :: R x :: Type) Source #

Identity. This instance is INCOHERENT, but that's OK because all implementations of up should give the same result, and this instance is as fast as possible. So, it doesn't matter whether this instance or another one is picked.

Instance details

Defined in I.Internal

Methods

up :: I x l r -> I x l r Source #

(lu <= ld, Interval Natural ld yrd, Interval Natural lu ('Nothing :: Maybe Natural)) => Up Natural (ld :: L Natural :: Type) (yrd :: R Natural :: Type) (lu :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Methods

up :: I Natural ld yrd -> I Natural lu 'Nothing Source #

(Interval Rational yld yrd, Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational))) => Up Rational (yld :: L Rational :: Type) (yrd :: R Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 yld yrd -> I Rational0 'Nothing 'Nothing Source #

(Interval Integer yld yrd, Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer)) => Up Integer (yld :: L Integer :: Type) (yrd :: R Integer :: Type) ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

up :: I Integer0 yld yrd -> I Integer0 'Nothing 'Nothing Source #

(lu <= ld, rd <= ru, Interval Natural ld ('Just rd), Interval Natural lu ('Just ru)) => Up Natural (ld :: L Natural :: Type) ('Just rd :: R Natural :: Type) (lu :: L Natural :: Type) ('Just ru :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

up :: I Natural ld ('Just rd) -> I Natural lu ('Just ru) Source #

(Interval Rational yld ('Just '('False, rd)), Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, ru)), ru <= rd) => Up Rational (yld :: L Rational :: Type) ('Just '('False, rd) :: R Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 yld ('Just '('False, rd)) -> I Rational0 'Nothing ('Just '('False, ru)) Source #

(Interval Rational yld ('Just '(ird, rd)), Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, ru)), ru <= rd) => Up Rational (yld :: L Rational :: Type) ('Just '(ird, rd) :: R Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 yld ('Just '(ird, rd)) -> I Rational0 'Nothing ('Just '('True, ru)) Source #

(rd <= ru, Interval Integer yld ('Just rd), Interval Integer ('Nothing :: Maybe Integer) ('Just ru)) => Up Integer (yld :: L Integer :: Type) ('Just rd :: R Integer :: Type) ('Nothing :: Maybe Integer) ('Just ru :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

up :: I Integer0 yld ('Just rd) -> I Integer0 'Nothing ('Just ru) Source #

(Interval Rational ('Just '('False, ld)) yrd, Interval Rational ('Just '('False, lu)) ('Nothing :: Maybe (Bool, Rational)), lu <= ld) => Up Rational ('Just '('False, ld) :: L Rational :: Type) (yrd :: R Rational :: Type) ('Just '('False, lu) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 ('Just '('False, ld)) yrd -> I Rational0 ('Just '('False, lu)) 'Nothing Source #

(Interval Rational ('Just '(ild, ld)) yrd, Interval Rational ('Just '('True, lu)) ('Nothing :: Maybe (Bool, Rational)), lu <= ld) => Up Rational ('Just '(ild, ld) :: L Rational :: Type) (yrd :: R Rational :: Type) ('Just '('True, lu) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational0 ('Just '(ild, ld)) yrd -> I Rational0 ('Just '('True, lu)) 'Nothing Source #

(lu <= ld, Interval Integer ('Just ld) yrd, Interval Integer ('Just lu) ('Nothing :: Maybe Integer)) => Up Integer ('Just ld :: L Integer :: Type) (yrd :: R Integer :: Type) ('Just lu :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

up :: I Integer0 ('Just ld) yrd -> I Integer0 ('Just lu) 'Nothing Source #

(Interval Rational ('Just '('False, ld)) ('Just '('False, rd)), Interval Rational ('Just '('False, lu)) ('Just '('False, ru)), lu <= ld, rd <= ru) => Up Rational ('Just '('False, ld) :: L Rational :: Type) ('Just '('False, rd) :: R Rational :: Type) ('Just '('False, lu) :: L Rational :: Type) ('Just '('False, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational ('Just '('False, ld)) ('Just '('False, rd)) -> I Rational ('Just '('False, lu)) ('Just '('False, ru)) Source #

(Interval Rational ('Just '('False, ld)) ('Just '(ird, rd)), Interval Rational ('Just '('False, lu)) ('Just '('True, ru)), lu <= ld, rd <= ru) => Up Rational ('Just '('False, ld) :: L Rational :: Type) ('Just '(ird, rd) :: R Rational :: Type) ('Just '('False, lu) :: L Rational :: Type) ('Just '('True, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational ('Just '('False, ld)) ('Just '(ird, rd)) -> I Rational ('Just '('False, lu)) ('Just '('True, ru)) Source #

(Interval Rational ('Just '(ild, ld)) ('Just '('False, rd)), Interval Rational ('Just '('True, lu)) ('Just '('False, ru)), lu <= ld, rd <= ru) => Up Rational ('Just '(ild, ld) :: L Rational :: Type) ('Just '('False, rd) :: R Rational :: Type) ('Just '('True, lu) :: L Rational :: Type) ('Just '('False, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational ('Just '(ild, ld)) ('Just '('False, rd)) -> I Rational ('Just '('True, lu)) ('Just '('False, ru)) Source #

(Interval Rational ('Just '(ild, ld)) ('Just '(ird, rd)), Interval Rational ('Just '('True, lu)) ('Just '('True, ru)), lu <= ld, rd <= ru) => Up Rational ('Just '(ild, ld) :: L Rational :: Type) ('Just '(ird, rd) :: R Rational :: Type) ('Just '('True, lu) :: L Rational :: Type) ('Just '('True, ru) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

up :: I Rational ('Just '(ild, ld)) ('Just '(ird, rd)) -> I Rational ('Just '('True, lu)) ('Just '('True, ru)) Source #

(lu <= ld, rd <= ru, Interval Integer ('Just ld) ('Just rd), Interval Integer ('Just lu) ('Just ru)) => Up Integer ('Just ld :: L Integer :: Type) ('Just rd :: R Integer :: Type) ('Just lu :: L Integer :: Type) ('Just ru :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

up :: I Integer ('Just ld) ('Just rd) -> I Integer ('Just lu) ('Just ru) Source #

down :: forall x lu ru ld rd. Interval x ld rd => I x lu ru -> Maybe (I x ld rd) Source #

Downcast I x lu ru into I x ld rd if wrapped x value fits in I x ld rd.

class Interval x l r => Discrete (x :: Type) (l :: L x) (r :: R x) where Source #

Intervals that contain discrete elements.

Methods

pred' :: I x l r -> Maybe (I x l r) Source #

Predecessor. That is, the previous discrete value in the interval.

Nothing if the result would be out of the interval. See pred too.

succ' :: I x l r -> Maybe (I x l r) Source #

Successor. That is, the next discrete value in the interval.

Nothing if the result would be out of the interval. See succ too.

Instances

Instances details
(Interval CChar l r, l /= r) => Discrete CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

pred' :: I CChar l r -> Maybe (I CChar l r) Source #

succ' :: I CChar l r -> Maybe (I CChar l r) Source #

(Interval CInt l r, l /= r) => Discrete CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

pred' :: I CInt l r -> Maybe (I CInt l r) Source #

succ' :: I CInt l r -> Maybe (I CInt l r) Source #

(Interval CIntMax l r, l /= r) => Discrete CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

pred' :: I CIntMax l r -> Maybe (I CIntMax l r) Source #

succ' :: I CIntMax l r -> Maybe (I CIntMax l r) Source #

(Interval CIntPtr l r, l /= r) => Discrete CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

pred' :: I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

succ' :: I CIntPtr l r -> Maybe (I CIntPtr l r) Source #

(Interval CLLong l r, l /= r) => Discrete CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

pred' :: I CLLong l r -> Maybe (I CLLong l r) Source #

succ' :: I CLLong l r -> Maybe (I CLLong l r) Source #

(Interval CLong l r, l /= r) => Discrete CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

pred' :: I CLong l r -> Maybe (I CLong l r) Source #

succ' :: I CLong l r -> Maybe (I CLong l r) Source #

(Interval CPtrdiff l r, l /= r) => Discrete CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

pred' :: I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

succ' :: I CPtrdiff l r -> Maybe (I CPtrdiff l r) Source #

(Interval CSChar l r, l /= r) => Discrete CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

pred' :: I CSChar l r -> Maybe (I CSChar l r) Source #

succ' :: I CSChar l r -> Maybe (I CSChar l r) Source #

(Interval CShort l r, l /= r) => Discrete CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

pred' :: I CShort l r -> Maybe (I CShort l r) Source #

succ' :: I CShort l r -> Maybe (I CShort l r) Source #

(Interval CSize l r, l /= r) => Discrete CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

pred' :: I CSize l r -> Maybe (I CSize l r) Source #

succ' :: I CSize l r -> Maybe (I CSize l r) Source #

(Interval CUChar l r, l /= r) => Discrete CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

pred' :: I CUChar l r -> Maybe (I CUChar l r) Source #

succ' :: I CUChar l r -> Maybe (I CUChar l r) Source #

(Interval CUInt l r, l /= r) => Discrete CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

pred' :: I CUInt l r -> Maybe (I CUInt l r) Source #

succ' :: I CUInt l r -> Maybe (I CUInt l r) Source #

(Interval CUIntMax l r, l /= r) => Discrete CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

pred' :: I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

succ' :: I CUIntMax l r -> Maybe (I CUIntMax l r) Source #

(Interval CUIntPtr l r, l /= r) => Discrete CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

pred' :: I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

succ' :: I CUIntPtr l r -> Maybe (I CUIntPtr l r) Source #

(Interval CULLong l r, l /= r) => Discrete CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

pred' :: I CULLong l r -> Maybe (I CULLong l r) Source #

succ' :: I CULLong l r -> Maybe (I CULLong l r) Source #

(Interval CULong l r, l /= r) => Discrete CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

pred' :: I CULong l r -> Maybe (I CULong l r) Source #

succ' :: I CULong l r -> Maybe (I CULong l r) Source #

(Interval CUShort l r, l /= r) => Discrete CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

pred' :: I CUShort l r -> Maybe (I CUShort l r) Source #

succ' :: I CUShort l r -> Maybe (I CUShort l r) Source #

(Interval CWchar l r, l /= r) => Discrete CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

pred' :: I CWchar l r -> Maybe (I CWchar l r) Source #

succ' :: I CWchar l r -> Maybe (I CWchar l r) Source #

(Interval Int16 l r, l /= r) => Discrete Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

pred' :: I Int16 l r -> Maybe (I Int16 l r) Source #

succ' :: I Int16 l r -> Maybe (I Int16 l r) Source #

(Interval Int32 l r, l /= r) => Discrete Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

pred' :: I Int32 l r -> Maybe (I Int32 l r) Source #

succ' :: I Int32 l r -> Maybe (I Int32 l r) Source #

(Interval Int64 l r, l /= r) => Discrete Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

pred' :: I Int64 l r -> Maybe (I Int64 l r) Source #

succ' :: I Int64 l r -> Maybe (I Int64 l r) Source #

(Interval Int8 l r, l /= r) => Discrete Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

pred' :: I Int8 l r -> Maybe (I Int8 l r) Source #

succ' :: I Int8 l r -> Maybe (I Int8 l r) Source #

(Interval Word16 l r, l /= r) => Discrete Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

pred' :: I Word16 l r -> Maybe (I Word16 l r) Source #

succ' :: I Word16 l r -> Maybe (I Word16 l r) Source #

(Interval Word32 l r, l /= r) => Discrete Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

pred' :: I Word32 l r -> Maybe (I Word32 l r) Source #

succ' :: I Word32 l r -> Maybe (I Word32 l r) Source #

(Interval Word64 l r, l /= r) => Discrete Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

pred' :: I Word64 l r -> Maybe (I Word64 l r) Source #

succ' :: I Word64 l r -> Maybe (I Word64 l r) Source #

(Interval Word8 l r, l /= r) => Discrete Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

pred' :: I Word8 l r -> Maybe (I Word8 l r) Source #

succ' :: I Word8 l r -> Maybe (I Word8 l r) Source #

(Interval Int l r, l /= r) => Discrete Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

pred' :: I Int l r -> Maybe (I Int l r) Source #

succ' :: I Int l r -> Maybe (I Int l r) Source #

(Interval Word l r, l /= r) => Discrete Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

pred' :: I Word l r -> Maybe (I Word l r) Source #

succ' :: I Word l r -> Maybe (I Word l r) Source #

Interval Natural l ('Nothing :: Maybe Natural) => Discrete Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

(Interval Natural l ('Just r), l /= r) => Discrete Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

pred' :: I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

succ' :: I Natural l ('Just r) -> Maybe (I Natural l ('Just r)) Source #

Discrete Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Interval Integer ('Nothing :: Maybe Integer) ('Just r) => Discrete Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Interval Integer ('Just l) ('Nothing :: Maybe Integer) => Discrete Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

(Interval Integer ('Just l) ('Just r), l /= r) => Discrete Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

pred' :: I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

succ' :: I Integer ('Just l) ('Just r) -> Maybe (I Integer ('Just l) ('Just r)) Source #

class Discrete x l r => Succ (x :: Type) (l :: L x) (r :: R x) where Source #

Discrete Intervals where obtaining the successor is knonwn to be a closed operation.

Methods

succ :: I x l r -> I x l r Source #

succ a is the next discrete value in the interval, the successor.

Correspondence with succ'
forall (a :: I x l r).
  (Succ x l r) =>
    succ' a  ==  Just (succ a)

Instances

Instances details
Discrete Integer l ('Nothing :: Maybe Integer) => Succ Integer (l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Discrete Natural l ('Nothing :: Maybe Natural) => Succ Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

class Discrete x l r => Pred (x :: Type) (l :: L x) (r :: R x) where Source #

Discrete Intervals where obtaining the predecessor is knonwn to be a closed operation.

Methods

pred :: I x l r -> I x l r Source #

pred a is the previous discrete value in the interval, the predecessor.

Correspondence with pred'
forall (a :: I x l r).
  (Pred x l r) =>
    pred' a  ==  Just (pred a)

Instances

Instances details
Discrete Integer ('Nothing :: Maybe Integer) r => Pred Integer ('Nothing :: Maybe Integer) (r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

class Interval x l r => One (x :: Type) (l :: L x) (r :: R x) where Source #

Intervals known to be inhabited by the number one.

Methods

one :: I x l r Source #

One.

Instances

Instances details
(Interval CChar l r, l <= P 1, P 1 <= r) => One CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

one :: I CChar l r Source #

(Interval CInt l r, l <= P 1, P 1 <= r) => One CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

one :: I CInt l r Source #

(Interval CIntMax l r, l <= P 1, P 1 <= r) => One CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

one :: I CIntMax l r Source #

(Interval CIntPtr l r, l <= P 1, P 1 <= r) => One CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

one :: I CIntPtr l r Source #

(Interval CLLong l r, l <= P 1, P 1 <= r) => One CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

one :: I CLLong l r Source #

(Interval CLong l r, l <= P 1, P 1 <= r) => One CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

one :: I CLong l r Source #

(Interval CPtrdiff l r, l <= P 1, P 1 <= r) => One CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

one :: I CPtrdiff l r Source #

(Interval CSChar l r, l <= P 1, P 1 <= r) => One CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

one :: I CSChar l r Source #

(Interval CShort l r, l <= P 1, P 1 <= r) => One CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

one :: I CShort l r Source #

(Interval CSize l r, l <= 1, 1 <= r) => One CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

one :: I CSize l r Source #

(Interval CUChar l r, l <= 1, 1 <= r) => One CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

one :: I CUChar l r Source #

(Interval CUInt l r, l <= 1, 1 <= r) => One CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

one :: I CUInt l r Source #

(Interval CUIntMax l r, l <= 1, 1 <= r) => One CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

one :: I CUIntMax l r Source #

(Interval CUIntPtr l r, l <= 1, 1 <= r) => One CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

one :: I CUIntPtr l r Source #

(Interval CULLong l r, l <= 1, 1 <= r) => One CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

one :: I CULLong l r Source #

(Interval CULong l r, l <= 1, 1 <= r) => One CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

one :: I CULong l r Source #

(Interval CUShort l r, l <= 1, 1 <= r) => One CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

one :: I CUShort l r Source #

(Interval CWchar l r, l <= P 1, P 1 <= r) => One CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

one :: I CWchar l r Source #

(Interval Int16 l r, l <= P 1, P 1 <= r) => One Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

one :: I Int16 l r Source #

(Interval Int32 l r, l <= P 1, P 1 <= r) => One Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

one :: I Int32 l r Source #

(Interval Int64 l r, l <= P 1, P 1 <= r) => One Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

one :: I Int64 l r Source #

(Interval Int8 l r, l <= P 1, P 1 <= r) => One Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

one :: I Int8 l r Source #

(Interval Word16 l r, l <= 1, 1 <= r) => One Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

one :: I Word16 l r Source #

(Interval Word32 l r, l <= 1, 1 <= r) => One Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

one :: I Word32 l r Source #

(Interval Word64 l r, l <= 1, 1 <= r) => One Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

one :: I Word64 l r Source #

(Interval Word8 l r, l <= 1, 1 <= r) => One Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

one :: I Word8 l r Source #

(Interval Int l r, l <= P 1, P 1 <= r) => One Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

one :: I Int l r Source #

(Interval Word l r, l <= 1, 1 <= r) => One Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

one :: I Word l r Source #

(Interval Natural l ('Nothing :: Maybe Natural), l <= 1) => One Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Methods

one :: I Natural l 'Nothing Source #

(Interval Natural l ('Just r), l <= 1, 1 <= r) => One Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

one :: I Natural l ('Just r) Source #

One Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

One Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)), (1 / 1) < r) => One Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational0 'Nothing ('Just '('False, r)) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)), (1 / 1) <= r) => One Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational0 'Nothing ('Just '('True, r)) Source #

(Interval Integer ('Nothing :: Maybe Integer) ('Just r), P 1 <= r) => One Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

one :: I Integer0 'Nothing ('Just r) Source #

(Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)), l < (1 / 1)) => One Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational0 ('Just '('False, l)) 'Nothing Source #

(Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)), l <= (1 / 1)) => One Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational0 ('Just '('True, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), l <= P 1) => One Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

one :: I Integer0 ('Just l) 'Nothing Source #

(l < (1 / 1), (1 / 1) < r, Interval Rational ('Just '('False, l)) ('Just '('False, r))) => One Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

(l < (1 / 1), (1 / 1) <= r, Interval Rational ('Just '('False, l)) ('Just '('True, r))) => One Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

(l <= (1 / 1), (1 / 1) < r, Interval Rational ('Just '('True, l)) ('Just '('False, r))) => One Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

(l <= (1 / 1), (1 / 1) <= r, Interval Rational ('Just '('True, l)) ('Just '('True, r))) => One Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

one :: I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

(Interval Integer ('Just l) ('Just r), l <= P 1, P 1 <= r) => One Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

one :: I Integer ('Just l) ('Just r) Source #

class Interval x l r => Zero (x :: Type) (l :: L x) (r :: R x) where Source #

Intervals known to be inhabited by the number zero.

Methods

zero :: I x l r Source #

Zero.

Instances

Instances details
(Interval CChar l r, l <= P 0, P 0 <= r) => Zero CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

zero :: I CChar l r Source #

(Interval CInt l r, l <= P 0, P 0 <= r) => Zero CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

zero :: I CInt l r Source #

(Interval CIntMax l r, l <= P 0, P 0 <= r) => Zero CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

zero :: I CIntMax l r Source #

(Interval CIntPtr l r, l <= P 0, P 0 <= r) => Zero CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

zero :: I CIntPtr l r Source #

(Interval CLLong l r, l <= P 0, P 0 <= r) => Zero CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

zero :: I CLLong l r Source #

(Interval CLong l r, l <= P 0, P 0 <= r) => Zero CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

zero :: I CLong l r Source #

(Interval CPtrdiff l r, l <= P 0, P 0 <= r) => Zero CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

zero :: I CPtrdiff l r Source #

(Interval CSChar l r, l <= P 0, P 0 <= r) => Zero CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

zero :: I CSChar l r Source #

(Interval CShort l r, l <= P 0, P 0 <= r) => Zero CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

zero :: I CShort l r Source #

Interval CSize 0 r => Zero CSize 0 (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

zero :: I CSize 0 r Source #

Interval CUChar 0 r => Zero CUChar 0 (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

zero :: I CUChar 0 r Source #

Interval CUInt 0 r => Zero CUInt 0 (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

zero :: I CUInt 0 r Source #

Interval CUIntMax 0 r => Zero CUIntMax 0 (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

zero :: I CUIntMax 0 r Source #

Interval CUIntPtr 0 r => Zero CUIntPtr 0 (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

zero :: I CUIntPtr 0 r Source #

Interval CULLong 0 r => Zero CULLong 0 (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

zero :: I CULLong 0 r Source #

Interval CULong 0 r => Zero CULong 0 (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

zero :: I CULong 0 r Source #

Interval CUShort 0 r => Zero CUShort 0 (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

zero :: I CUShort 0 r Source #

(Interval CWchar l r, l <= P 0, P 0 <= r) => Zero CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

zero :: I CWchar l r Source #

(Interval Int16 l r, l <= P 0, P 0 <= r) => Zero Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

zero :: I Int16 l r Source #

(Interval Int32 l r, l <= P 0, P 0 <= r) => Zero Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

zero :: I Int32 l r Source #

(Interval Int64 l r, l <= P 0, P 0 <= r) => Zero Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

zero :: I Int64 l r Source #

(Interval Int8 l r, l <= P 0, P 0 <= r) => Zero Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

zero :: I Int8 l r Source #

Interval Word16 0 r => Zero Word16 0 (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

zero :: I Word16 0 r Source #

Interval Word32 0 r => Zero Word32 0 (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

zero :: I Word32 0 r Source #

Interval Word64 0 r => Zero Word64 0 (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

zero :: I Word64 0 r Source #

Interval Word8 0 r => Zero Word8 0 (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

zero :: I Word8 0 r Source #

Interval Natural 0 r => Zero Natural 0 (r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

zero :: I Natural 0 r Source #

(Interval Int l r, l <= P 0, P 0 <= r) => Zero Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

zero :: I Int l r Source #

Interval Word 0 r => Zero Word 0 (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

zero :: I Word 0 r Source #

Zero Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Zero Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)), (0 / 1) < r) => Zero Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational0 'Nothing ('Just '('False, r)) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)), (0 / 1) <= r) => Zero Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational0 'Nothing ('Just '('True, r)) Source #

(Interval Integer ('Nothing :: Maybe Integer) ('Just r), P 0 <= r) => Zero Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

zero :: I Integer0 'Nothing ('Just r) Source #

(Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)), l < (0 / 1)) => Zero Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational0 ('Just '('False, l)) 'Nothing Source #

(Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)), l <= (0 / 1)) => Zero Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational0 ('Just '('True, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), l <= P 0) => Zero Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

zero :: I Integer0 ('Just l) 'Nothing Source #

(l < (0 / 1), (0 / 1) < r, Interval Rational ('Just '('False, l)) ('Just '('False, r))) => Zero Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

(l < (0 / 1), (0 / 1) <= r, Interval Rational ('Just '('False, l)) ('Just '('True, r))) => Zero Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

(l <= (0 / 1), (0 / 1) < r, Interval Rational ('Just '('True, l)) ('Just '('False, r))) => Zero Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

(l <= (0 / 1), (0 / 1) <= r, Interval Rational ('Just '('True, l)) ('Just '('True, r))) => Zero Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

zero :: I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

(Interval Integer ('Just l) ('Just r), l <= P 0, P 0 <= r) => Zero Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

zero :: I Integer ('Just l) ('Just r) Source #

class Zero x l r => Negate (x :: Type) (l :: L x) (r :: R x) where Source #

Intervals where negation is known to be a closed operation.

Methods

negate :: I x l r -> I x l r Source #

Additive inverse, if it fits in the interval.

Identity law
forall (a :: I x l r).
  (Negate x l r) =>
    a == negate (negate a)
Correspondence with negate'
forall (a :: I x l r) (b :: I x l r).
  (Minus x l r) =>
    negate' a b  ==  Just (negate a b)

Instances

Instances details
(Zero CChar l r, l == Negate r) => Negate CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

negate :: I CChar l r -> I CChar l r Source #

(Zero CInt l r, l == Negate r) => Negate CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

negate :: I CInt l r -> I CInt l r Source #

(Zero CIntMax l r, l == Negate r) => Negate CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

negate :: I CIntMax l r -> I CIntMax l r Source #

(Zero CIntPtr l r, l == Negate r) => Negate CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

negate :: I CIntPtr l r -> I CIntPtr l r Source #

(Zero CLLong l r, l == Negate r) => Negate CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

negate :: I CLLong l r -> I CLLong l r Source #

(Zero CLong l r, l == Negate r) => Negate CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

negate :: I CLong l r -> I CLong l r Source #

(Zero CPtrdiff l r, l == Negate r) => Negate CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

negate :: I CPtrdiff l r -> I CPtrdiff l r Source #

(Zero CSChar l r, l == Negate r) => Negate CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

negate :: I CSChar l r -> I CSChar l r Source #

(Zero CShort l r, l == Negate r) => Negate CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

negate :: I CShort l r -> I CShort l r Source #

(Zero CWchar l r, l == Negate r) => Negate CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

negate :: I CWchar l r -> I CWchar l r Source #

(Zero Int16 l r, l == Negate r) => Negate Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

negate :: I Int16 l r -> I Int16 l r Source #

(Zero Int32 l r, l == Negate r) => Negate Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

negate :: I Int32 l r -> I Int32 l r Source #

(Zero Int64 l r, l == Negate r) => Negate Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

negate :: I Int64 l r -> I Int64 l r Source #

(Zero Int8 l r, l == Negate r) => Negate Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

negate :: I Int8 l r -> I Int8 l r Source #

(Zero Int l r, l == Negate r) => Negate Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

negate :: I Int l r -> I Int l r Source #

Negate Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Negate Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

(l == Negate r, Zero Rational ('Just '(i, l)) ('Just '(i, r))) => Negate Rational ('Just '(i, l) :: L Rational :: Type) ('Just '(i, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

negate :: I Rational ('Just '(i, l)) ('Just '(i, r)) -> I Rational ('Just '(i, l)) ('Just '(i, r)) Source #

(Zero Integer ('Just l) ('Just r), l == Negate r) => Negate Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

negate :: I Integer ('Just l) ('Just r) -> I Integer ('Just l) ('Just r) Source #

class Interval x l r => Plus (x :: Type) (l :: L x) (r :: R x) where Source #

Intervals where addition is known to be a closed operation.

Methods

plus :: I x l r -> I x l r -> I x l r Source #

plus a b adds a and b.

Correspondence with plus'
forall (a :: I x l r) (b :: I x l r).
  (Plus x l r) =>
    plus' a b  ==  Just (plus a b)

Instances

Instances details
Interval Natural l ('Nothing :: Maybe Natural) => Plus Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Plus Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Plus Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '(ir, r)), r <= (0 / 1)) => Plus Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '(ir, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

plus :: I Rational0 'Nothing ('Just '(ir, r)) -> I Rational0 'Nothing ('Just '(ir, r)) -> I Rational0 'Nothing ('Just '(ir, r)) Source #

(Interval Integer ('Nothing :: Maybe Integer) ('Just r), r <= P 0) => Plus Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

plus :: I Integer0 'Nothing ('Just r) -> I Integer0 'Nothing ('Just r) -> I Integer0 'Nothing ('Just r) Source #

(Interval Rational ('Just '(il, l)) ('Nothing :: Maybe (Bool, Rational)), (0 / 1) <= l) => Plus Rational ('Just '(il, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

plus :: I Rational0 ('Just '(il, l)) 'Nothing -> I Rational0 ('Just '(il, l)) 'Nothing -> I Rational0 ('Just '(il, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), P 0 <= l) => Plus Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

plus :: I Integer0 ('Just l) 'Nothing -> I Integer0 ('Just l) 'Nothing -> I Integer0 ('Just l) 'Nothing Source #

class Interval x l r => Mult (x :: Type) (l :: L x) (r :: R x) where Source #

Intervals where multiplication is known to be a closed operation.

Methods

mult :: I x l r -> I x l r -> I x l r Source #

mult a b multiplies a times b.

Correspondence with mult'
forall (a :: I x l r) (b :: I x l r).
  (Mult x l r) =>
    mult' a b  ==  Just (mult a b)

Instances

Instances details
Interval Natural l ('Nothing :: Maybe Natural) => Mult Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Mult Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Mult Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

(Interval Rational ('Just '(il, l)) ('Nothing :: Maybe (Bool, Rational)), (1 / 1) <= l) => Mult Rational ('Just '(il, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

mult :: I Rational0 ('Just '(il, l)) 'Nothing -> I Rational0 ('Just '(il, l)) 'Nothing -> I Rational0 ('Just '(il, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), P 0 <= l) => Mult Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

mult :: I Integer0 ('Just l) 'Nothing -> I Integer0 ('Just l) 'Nothing -> I Integer0 ('Just l) 'Nothing Source #

(Interval Rational ('Just '(il, l)) ('Just '(ir, r)), (0 / 1) <= l, r <= (1 / 1)) => Mult Rational ('Just '(il, l) :: L Rational :: Type) ('Just '(ir, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

mult :: I Rational ('Just '(il, l)) ('Just '(ir, r)) -> I Rational ('Just '(il, l)) ('Just '(ir, r)) -> I Rational ('Just '(il, l)) ('Just '(ir, r)) Source #

class Zero x l r => Minus (x :: Type) (l :: L x) (r :: R x) where Source #

Intervals where subtraction is known to be a closed operation.

Methods

minus :: I x l r -> I x l r -> I x l r Source #

minus a b substracts b from a

Correspondence with minus'
forall (a :: I x l r) (b :: I x l r).
  (Minus x l r) =>
    minus' a b  ==  Just (minus a b)

Instances

Instances details
Minus Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Minus Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

class Interval x l r => Div (x :: Type) (l :: L x) (r :: R x) where Source #

Intervals where division is known to be a closed operation.

Methods

div :: I x l r -> I x l r -> I x l r Source #

div a b divides a by b.

Correspondence with div'
forall (a :: I x l r) (b :: I x l r).
  (Div x l r) =>
    div' a b  ==  Just (div a b)

Instances

Instances details
((0 / 1) < l, r <= (1 / 1), Interval Rational ('Just '(il, l)) ('Just '(ir, r))) => Div Rational ('Just '(il, l) :: L Rational :: Type) ('Just '(ir, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

div :: I Rational ('Just '(il, l)) ('Just '(ir, r)) -> I Rational ('Just '(il, l)) ('Just '(ir, r)) -> I Rational ('Just '(il, l)) ('Just '(ir, r)) Source #

Known

class (Interval x l r, KnownCtx x l r t) => Known (x :: Type) (l :: L x) (r :: R x) (t :: T x) where Source #

Proof that t is known to be within l and r in I x l r.

NB: When defining Known instances, instead of mentioning any necessary constraints in the instance context, mention them them in KnownCtx. By doing so, when an instance of Known x l r is satisfied, KnownCtx x l r is satisfied as well. If you don't do this, with won't behave as you would expect.

Associated Types

type KnownCtx x l r t :: Constraint Source #

Constraints to be satisfied by t if it is known to be within the I x l r interval.

type KnownCtx x l r t = ()

Methods

known' :: Proxy t -> I x l r Source #

Obtain a term-level representation of t as I x l r.

Also consider using known, an alternative version of this function designed to be used with -XTypeApplications.

Instances

Instances details
(Interval CChar l r, KnownCtx CChar l r t) => Known CChar (l :: L CChar :: Type) (r :: R CChar :: Type) (t :: T CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Associated Types

type KnownCtx CChar l r t Source #

Methods

known' :: Proxy t -> I CChar l r Source #

(Interval CInt l r, KnownCtx CInt l r t) => Known CInt (l :: L CInt :: Type) (r :: R CInt :: Type) (t :: T CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Associated Types

type KnownCtx CInt l r t Source #

Methods

known' :: Proxy t -> I CInt l r Source #

(Interval CIntMax l r, KnownCtx CIntMax l r t) => Known CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) (t :: T CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Associated Types

type KnownCtx CIntMax l r t Source #

Methods

known' :: Proxy t -> I CIntMax l r Source #

(Interval CIntPtr l r, KnownCtx CIntPtr l r t) => Known CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) (t :: T CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Associated Types

type KnownCtx CIntPtr l r t Source #

Methods

known' :: Proxy t -> I CIntPtr l r Source #

(Interval CLLong l r, KnownCtx CLLong l r t) => Known CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) (t :: T CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Associated Types

type KnownCtx CLLong l r t Source #

Methods

known' :: Proxy t -> I CLLong l r Source #

(Interval CLong l r, KnownCtx CLong l r t) => Known CLong (l :: L CLong :: Type) (r :: R CLong :: Type) (t :: T CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Associated Types

type KnownCtx CLong l r t Source #

Methods

known' :: Proxy t -> I CLong l r Source #

(Interval CPtrdiff l r, KnownCtx CPtrdiff l r t) => Known CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) (t :: T CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Associated Types

type KnownCtx CPtrdiff l r t Source #

Methods

known' :: Proxy t -> I CPtrdiff l r Source #

(Interval CSChar l r, KnownCtx CSChar l r t) => Known CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) (t :: T CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Associated Types

type KnownCtx CSChar l r t Source #

Methods

known' :: Proxy t -> I CSChar l r Source #

(Interval CShort l r, KnownCtx CShort l r t) => Known CShort (l :: L CShort :: Type) (r :: R CShort :: Type) (t :: T CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Associated Types

type KnownCtx CShort l r t Source #

Methods

known' :: Proxy t -> I CShort l r Source #

(Interval CSize l r, KnownCtx CSize l r t) => Known CSize (l :: L CSize :: Type) (r :: R CSize :: Type) (t :: T CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Associated Types

type KnownCtx CSize l r t Source #

Methods

known' :: Proxy t -> I CSize l r Source #

(Interval CUChar l r, KnownCtx CUChar l r t) => Known CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) (t :: T CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Associated Types

type KnownCtx CUChar l r t Source #

Methods

known' :: Proxy t -> I CUChar l r Source #

(Interval CUInt l r, KnownCtx CUInt l r t) => Known CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) (t :: T CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Associated Types

type KnownCtx CUInt l r t Source #

Methods

known' :: Proxy t -> I CUInt l r Source #

(Interval CUIntMax l r, KnownCtx CUIntMax l r t) => Known CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) (t :: T CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Associated Types

type KnownCtx CUIntMax l r t Source #

Methods

known' :: Proxy t -> I CUIntMax l r Source #

(Interval CUIntPtr l r, KnownCtx CUIntPtr l r t) => Known CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) (t :: T CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Associated Types

type KnownCtx CUIntPtr l r t Source #

Methods

known' :: Proxy t -> I CUIntPtr l r Source #

(Interval CULLong l r, KnownCtx CULLong l r t) => Known CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) (t :: T CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Associated Types

type KnownCtx CULLong l r t Source #

Methods

known' :: Proxy t -> I CULLong l r Source #

(Interval CULong l r, KnownCtx CULong l r t) => Known CULong (l :: L CULong :: Type) (r :: R CULong :: Type) (t :: T CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Associated Types

type KnownCtx CULong l r t Source #

Methods

known' :: Proxy t -> I CULong l r Source #

(Interval CUShort l r, KnownCtx CUShort l r t) => Known CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) (t :: T CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Associated Types

type KnownCtx CUShort l r t Source #

Methods

known' :: Proxy t -> I CUShort l r Source #

(Interval CWchar l r, KnownCtx CWchar l r t) => Known CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) (t :: T CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Associated Types

type KnownCtx CWchar l r t Source #

Methods

known' :: Proxy t -> I CWchar l r Source #

(Interval Int16 l r, KnownCtx Int16 l r t) => Known Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) (t :: T Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Associated Types

type KnownCtx Int16 l r t Source #

Methods

known' :: Proxy t -> I Int16 l r Source #

(Interval Int32 l r, KnownCtx Int32 l r t) => Known Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) (t :: T Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Associated Types

type KnownCtx Int32 l r t Source #

Methods

known' :: Proxy t -> I Int32 l r Source #

(Interval Int64 l r, KnownCtx Int64 l r t) => Known Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) (t :: T Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Associated Types

type KnownCtx Int64 l r t Source #

Methods

known' :: Proxy t -> I Int64 l r Source #

(Interval Int8 l r, KnownCtx Int8 l r t) => Known Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) (t :: T Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Associated Types

type KnownCtx Int8 l r t Source #

Methods

known' :: Proxy t -> I Int8 l r Source #

(Interval Word16 l r, KnownCtx Word16 l r t) => Known Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) (t :: T Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Associated Types

type KnownCtx Word16 l r t Source #

Methods

known' :: Proxy t -> I Word16 l r Source #

(Interval Word32 l r, KnownCtx Word32 l r t) => Known Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) (t :: T Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Associated Types

type KnownCtx Word32 l r t Source #

Methods

known' :: Proxy t -> I Word32 l r Source #

(Interval Word64 l r, KnownCtx Word64 l r t) => Known Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) (t :: T Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Associated Types

type KnownCtx Word64 l r t Source #

Methods

known' :: Proxy t -> I Word64 l r Source #

(Interval Word8 l r, KnownCtx Word8 l r t) => Known Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) (t :: T Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Associated Types

type KnownCtx Word8 l r t Source #

Methods

known' :: Proxy t -> I Word8 l r Source #

(Interval Int l r, KnownCtx Int l r t) => Known Int (l :: L Int :: Type) (r :: R Int :: Type) (t :: T Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Associated Types

type KnownCtx Int l r t Source #

Methods

known' :: Proxy t -> I Int l r Source #

(Interval Word l r, KnownCtx Word l r t) => Known Word (l :: L Word :: Type) (r :: R Word :: Type) (t :: T Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Associated Types

type KnownCtx Word l r t Source #

Methods

known' :: Proxy t -> I Word l r Source #

(Interval Natural l ('Nothing :: Maybe Natural), KnownCtx Natural l ('Nothing :: Maybe Natural) t) => Known Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

Associated Types

type KnownCtx Natural l 'Nothing t Source #

Methods

known' :: Proxy t -> I Natural l 'Nothing Source #

(Interval Natural l ('Just r), KnownCtx Natural l ('Just r) t) => Known Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) (t :: T Natural :: Type) Source # 
Instance details

Defined in I.Natural

Associated Types

type KnownCtx Natural l ('Just r) t Source #

Methods

known' :: Proxy t -> I Natural l ('Just r) Source #

KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) t => Known Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational 'Nothing 'Nothing t Source #

KnownCtx Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) t => Known Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer 'Nothing 'Nothing t Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)), KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)) t) => Known Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational 'Nothing ('Just '('False, r)) t Source #

Methods

known' :: Proxy t -> I Rational0 'Nothing ('Just '('False, r)) Source #

(Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)), KnownCtx Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) t) => Known Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational 'Nothing ('Just '('True, r)) t Source #

Methods

known' :: Proxy t -> I Rational0 'Nothing ('Just '('True, r)) Source #

(Interval Integer ('Nothing :: Maybe Integer) ('Just r), KnownCtx Integer ('Nothing :: Maybe Integer) ('Just r) t) => Known Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer 'Nothing ('Just r) t Source #

Methods

known' :: Proxy t -> I Integer0 'Nothing ('Just r) Source #

(Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)), KnownCtx Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)) t) => Known Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('False, l)) 'Nothing t Source #

Methods

known' :: Proxy t -> I Rational0 ('Just '('False, l)) 'Nothing Source #

(Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)), KnownCtx Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) t) => Known Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('True, l)) 'Nothing t Source #

Methods

known' :: Proxy t -> I Rational0 ('Just '('True, l)) 'Nothing Source #

(Interval Integer ('Just l) ('Nothing :: Maybe Integer), KnownCtx Integer ('Just l) ('Nothing :: Maybe Integer) t) => Known Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer ('Just l) 'Nothing t Source #

Methods

known' :: Proxy t -> I Integer0 ('Just l) 'Nothing Source #

(Interval Rational ('Just '('False, l)) ('Just '('False, r)), KnownCtx Rational ('Just '('False, l)) ('Just '('False, r)) t) => Known Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('False, l)) ('Just '('False, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

(Interval Rational ('Just '('False, l)) ('Just '('True, r)), KnownCtx Rational ('Just '('False, l)) ('Just '('True, r)) t) => Known Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('False, l)) ('Just '('True, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

(Interval Rational ('Just '('True, l)) ('Just '('False, r)), KnownCtx Rational ('Just '('True, l)) ('Just '('False, r)) t) => Known Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('True, l)) ('Just '('False, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

(Interval Rational ('Just '('True, l)) ('Just '('True, r)), KnownCtx Rational ('Just '('True, l)) ('Just '('True, r)) t) => Known Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) (t :: T Rational :: Type) Source # 
Instance details

Defined in I.Rational

Associated Types

type KnownCtx Rational ('Just '('True, l)) ('Just '('True, r)) t Source #

Methods

known' :: Proxy t -> I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

(Interval Integer ('Just l) ('Just r), KnownCtx Integer ('Just l) ('Just r) t) => Known Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) (t :: T Integer :: Type) Source # 
Instance details

Defined in I.Integer

Associated Types

type KnownCtx Integer ('Just l) ('Just r) t Source #

Methods

known' :: Proxy t -> I Integer ('Just l) ('Just r) Source #

known :: forall {x} t l r. Known x l r t => I x l r Source #

Alternative version of known', designed to be used with -XTypeApplications. It works only when x can be inferred by other means.

> :type known
known :: forall {x :: Type} (t :: T x) (l :: L x) (r :: R x). Known x l r t => I x l r

> :type known @55 :: Known Word8 l r 55 => I Word8 l r
known @55 :: Known Word8 l r 55 => I Word8 l r

> :type known @55 @33 :: Known Word8 33 r 55 => I Word8 33 r
known @55 @33 :: Known Word8 33 r 55 => I Word8 33 r

> :type known @55 @33 @77 :: I Word8 33 77
known @55 @33 @77 :: I Word8 33 77 :: I Word8 33 77

> known @55 @33 @77 :: I Word8 33 77
55

class Interval x l r => With (x :: Type) (l :: L x) (r :: R x) where Source #

Proof that I x l r contains a value of type x whose type-level representation t :: T x satisfies a Known x l r t.

Methods

with :: I x l r -> (forall (t :: T x). Known x l r t => Proxy t -> b) -> b Source #

Bring to scope the type-level representation of x as t :: T x, together with the constraints that prove that t is Known to be in the interval I x l r.

Identity law
x  ==  with x known'

Instances

Instances details
Interval CChar l r => With CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

with :: I CChar l r -> (forall (t :: T CChar). Known CChar l r t => Proxy t -> b) -> b Source #

Interval CInt l r => With CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

with :: I CInt l r -> (forall (t :: T CInt). Known CInt l r t => Proxy t -> b) -> b Source #

Interval CIntMax l r => With CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

with :: I CIntMax l r -> (forall (t :: T CIntMax). Known CIntMax l r t => Proxy t -> b) -> b Source #

Interval CIntPtr l r => With CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

with :: I CIntPtr l r -> (forall (t :: T CIntPtr). Known CIntPtr l r t => Proxy t -> b) -> b Source #

Interval CLLong l r => With CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

with :: I CLLong l r -> (forall (t :: T CLLong). Known CLLong l r t => Proxy t -> b) -> b Source #

Interval CLong l r => With CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

with :: I CLong l r -> (forall (t :: T CLong). Known CLong l r t => Proxy t -> b) -> b Source #

Interval CPtrdiff l r => With CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

with :: I CPtrdiff l r -> (forall (t :: T CPtrdiff). Known CPtrdiff l r t => Proxy t -> b) -> b Source #

Interval CSChar l r => With CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

with :: I CSChar l r -> (forall (t :: T CSChar). Known CSChar l r t => Proxy t -> b) -> b Source #

Interval CShort l r => With CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

with :: I CShort l r -> (forall (t :: T CShort). Known CShort l r t => Proxy t -> b) -> b Source #

Interval CSize l r => With CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

with :: I CSize l r -> (forall (t :: T CSize). Known CSize l r t => Proxy t -> b) -> b Source #

Interval CUChar l r => With CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

with :: I CUChar l r -> (forall (t :: T CUChar). Known CUChar l r t => Proxy t -> b) -> b Source #

Interval CUInt l r => With CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

with :: I CUInt l r -> (forall (t :: T CUInt). Known CUInt l r t => Proxy t -> b) -> b Source #

Interval CUIntMax l r => With CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

with :: I CUIntMax l r -> (forall (t :: T CUIntMax). Known CUIntMax l r t => Proxy t -> b) -> b Source #

Interval CUIntPtr l r => With CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

with :: I CUIntPtr l r -> (forall (t :: T CUIntPtr). Known CUIntPtr l r t => Proxy t -> b) -> b Source #

Interval CULLong l r => With CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

with :: I CULLong l r -> (forall (t :: T CULLong). Known CULLong l r t => Proxy t -> b) -> b Source #

Interval CULong l r => With CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

with :: I CULong l r -> (forall (t :: T CULong). Known CULong l r t => Proxy t -> b) -> b Source #

Interval CUShort l r => With CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

with :: I CUShort l r -> (forall (t :: T CUShort). Known CUShort l r t => Proxy t -> b) -> b Source #

Interval CWchar l r => With CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

with :: I CWchar l r -> (forall (t :: T CWchar). Known CWchar l r t => Proxy t -> b) -> b Source #

Interval Int16 l r => With Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

with :: I Int16 l r -> (forall (t :: T Int16). Known Int16 l r t => Proxy t -> b) -> b Source #

Interval Int32 l r => With Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

with :: I Int32 l r -> (forall (t :: T Int32). Known Int32 l r t => Proxy t -> b) -> b Source #

Interval Int64 l r => With Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

with :: I Int64 l r -> (forall (t :: T Int64). Known Int64 l r t => Proxy t -> b) -> b Source #

Interval Int8 l r => With Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

with :: I Int8 l r -> (forall (t :: T Int8). Known Int8 l r t => Proxy t -> b) -> b Source #

Interval Word16 l r => With Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

with :: I Word16 l r -> (forall (t :: T Word16). Known Word16 l r t => Proxy t -> b) -> b Source #

Interval Word32 l r => With Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

with :: I Word32 l r -> (forall (t :: T Word32). Known Word32 l r t => Proxy t -> b) -> b Source #

Interval Word64 l r => With Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

with :: I Word64 l r -> (forall (t :: T Word64). Known Word64 l r t => Proxy t -> b) -> b Source #

Interval Word8 l r => With Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

with :: I Word8 l r -> (forall (t :: T Word8). Known Word8 l r t => Proxy t -> b) -> b Source #

Interval Int l r => With Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

with :: I Int l r -> (forall (t :: T Int). Known Int l r t => Proxy t -> b) -> b Source #

Interval Word l r => With Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

with :: I Word l r -> (forall (t :: T Word). Known Word l r t => Proxy t -> b) -> b Source #

Interval Natural l ('Nothing :: Maybe Natural) => With Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Methods

with :: I Natural l 'Nothing -> (forall (t :: T Natural). Known Natural l 'Nothing t => Proxy t -> b) -> b Source #

Interval Natural l ('Just r) => With Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

with :: I Natural l ('Just r) -> (forall (t :: T Natural). Known Natural l ('Just r) t => Proxy t -> b) -> b Source #

With Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 'Nothing 'Nothing -> (forall (t :: T Rational0). Known Rational0 'Nothing 'Nothing t => Proxy t -> b) -> b Source #

With Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

with :: I Integer0 'Nothing 'Nothing -> (forall (t :: T Integer0). Known Integer0 'Nothing 'Nothing t => Proxy t -> b) -> b Source #

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)) => With Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 'Nothing ('Just '('False, r)) -> (forall (t :: T Rational0). Known Rational0 'Nothing ('Just '('False, r)) t => Proxy t -> b) -> b Source #

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) => With Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 'Nothing ('Just '('True, r)) -> (forall (t :: T Rational0). Known Rational0 'Nothing ('Just '('True, r)) t => Proxy t -> b) -> b Source #

Interval Integer ('Nothing :: Maybe Integer) ('Just r) => With Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

with :: I Integer0 'Nothing ('Just r) -> (forall (t :: T Integer0). Known Integer0 'Nothing ('Just r) t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)) => With Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 ('Just '('False, l)) 'Nothing -> (forall (t :: T Rational0). Known Rational0 ('Just '('False, l)) 'Nothing t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) => With Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational0 ('Just '('True, l)) 'Nothing -> (forall (t :: T Rational0). Known Rational0 ('Just '('True, l)) 'Nothing t => Proxy t -> b) -> b Source #

Interval Integer ('Just l) ('Nothing :: Maybe Integer) => With Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Methods

with :: I Integer0 ('Just l) 'Nothing -> (forall (t :: T Integer0). Known Integer0 ('Just l) 'Nothing t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('False, l)) ('Just '('False, r)) => With Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational ('Just '('False, l)) ('Just '('False, r)) -> (forall (t :: T Rational). Known Rational ('Just '('False, l)) ('Just '('False, r)) t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('False, l)) ('Just '('True, r)) => With Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational ('Just '('False, l)) ('Just '('True, r)) -> (forall (t :: T Rational). Known Rational ('Just '('False, l)) ('Just '('True, r)) t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('True, l)) ('Just '('False, r)) => With Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational ('Just '('True, l)) ('Just '('False, r)) -> (forall (t :: T Rational). Known Rational ('Just '('True, l)) ('Just '('False, r)) t => Proxy t -> b) -> b Source #

Interval Rational ('Just '('True, l)) ('Just '('True, r)) => With Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

with :: I Rational ('Just '('True, l)) ('Just '('True, r)) -> (forall (t :: T Rational). Known Rational ('Just '('True, l)) ('Just '('True, r)) t => Proxy t -> b) -> b Source #

Interval Integer ('Just l) ('Just r) => With Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

with :: I Integer ('Just l) ('Just r) -> (forall (t :: T Integer). Known Integer ('Just l) ('Just r) t => Proxy t -> b) -> b Source #

min :: forall x l r. Known x l r (MinI x l r) => I x l r Source #

Minimum value in the interval, if MinI x is defined.

max :: forall x l r. Known x l r (MaxI x l r) => I x l r Source #

Maximum value in the interval, if MaxI x is defined.

single :: forall x l r. (MinI x l r ~ MaxI x l r, Known x l r (MinI x l r)) => I x l r Source #

If an Interval contains a single inhabitant, obtain it.

Testing

class Interval x l r => Shove (x :: Type) (l :: L x) (r :: R x) where Source #

Shove an x into an interval I x l r, somehow.

Note: This class is for testing purposes only. For example, if you want to generate random values of type I x l r for testing purposes, all you have to do is generate random values of type x and then shove them into I x l r.

Note: We don't like this too much. If there was a good way to export generators for Hedgehog or QuickCheck without depending on these libraries, we'd probably export that instead.

Methods

shove :: x -> I x l r Source #

No guarantees are made about the x value that ends up in I x l r. In particular, you can't expect id == unwrap . shove, not even for x values for which from == Just. All shove guarantees is a more or less uniform distribution.

Instances

Instances details
Interval CChar l r => Shove CChar (l :: L CChar :: Type) (r :: R CChar :: Type) Source # 
Instance details

Defined in I.Autogen.CChar

Methods

shove :: CChar -> I CChar l r Source #

Interval CInt l r => Shove CInt (l :: L CInt :: Type) (r :: R CInt :: Type) Source # 
Instance details

Defined in I.Autogen.CInt

Methods

shove :: CInt -> I CInt l r Source #

Interval CIntMax l r => Shove CIntMax (l :: L CIntMax :: Type) (r :: R CIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CIntMax

Methods

shove :: CIntMax -> I CIntMax l r Source #

Interval CIntPtr l r => Shove CIntPtr (l :: L CIntPtr :: Type) (r :: R CIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CIntPtr

Methods

shove :: CIntPtr -> I CIntPtr l r Source #

Interval CLLong l r => Shove CLLong (l :: L CLLong :: Type) (r :: R CLLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLLong

Methods

shove :: CLLong -> I CLLong l r Source #

Interval CLong l r => Shove CLong (l :: L CLong :: Type) (r :: R CLong :: Type) Source # 
Instance details

Defined in I.Autogen.CLong

Methods

shove :: CLong -> I CLong l r Source #

Interval CPtrdiff l r => Shove CPtrdiff (l :: L CPtrdiff :: Type) (r :: R CPtrdiff :: Type) Source # 
Instance details

Defined in I.Autogen.CPtrdiff

Methods

shove :: CPtrdiff -> I CPtrdiff l r Source #

Interval CSChar l r => Shove CSChar (l :: L CSChar :: Type) (r :: R CSChar :: Type) Source # 
Instance details

Defined in I.Autogen.CSChar

Methods

shove :: CSChar -> I CSChar l r Source #

Interval CShort l r => Shove CShort (l :: L CShort :: Type) (r :: R CShort :: Type) Source # 
Instance details

Defined in I.Autogen.CShort

Methods

shove :: CShort -> I CShort l r Source #

Interval CSize l r => Shove CSize (l :: L CSize :: Type) (r :: R CSize :: Type) Source # 
Instance details

Defined in I.Autogen.CSize

Methods

shove :: CSize -> I CSize l r Source #

Interval CUChar l r => Shove CUChar (l :: L CUChar :: Type) (r :: R CUChar :: Type) Source # 
Instance details

Defined in I.Autogen.CUChar

Methods

shove :: CUChar -> I CUChar l r Source #

Interval CUInt l r => Shove CUInt (l :: L CUInt :: Type) (r :: R CUInt :: Type) Source # 
Instance details

Defined in I.Autogen.CUInt

Methods

shove :: CUInt -> I CUInt l r Source #

Interval CUIntMax l r => Shove CUIntMax (l :: L CUIntMax :: Type) (r :: R CUIntMax :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntMax

Methods

shove :: CUIntMax -> I CUIntMax l r Source #

Interval CUIntPtr l r => Shove CUIntPtr (l :: L CUIntPtr :: Type) (r :: R CUIntPtr :: Type) Source # 
Instance details

Defined in I.Autogen.CUIntPtr

Methods

shove :: CUIntPtr -> I CUIntPtr l r Source #

Interval CULLong l r => Shove CULLong (l :: L CULLong :: Type) (r :: R CULLong :: Type) Source # 
Instance details

Defined in I.Autogen.CULLong

Methods

shove :: CULLong -> I CULLong l r Source #

Interval CULong l r => Shove CULong (l :: L CULong :: Type) (r :: R CULong :: Type) Source # 
Instance details

Defined in I.Autogen.CULong

Methods

shove :: CULong -> I CULong l r Source #

Interval CUShort l r => Shove CUShort (l :: L CUShort :: Type) (r :: R CUShort :: Type) Source # 
Instance details

Defined in I.Autogen.CUShort

Methods

shove :: CUShort -> I CUShort l r Source #

Interval CWchar l r => Shove CWchar (l :: L CWchar :: Type) (r :: R CWchar :: Type) Source # 
Instance details

Defined in I.Autogen.CWchar

Methods

shove :: CWchar -> I CWchar l r Source #

Interval Int16 l r => Shove Int16 (l :: L Int16 :: Type) (r :: R Int16 :: Type) Source # 
Instance details

Defined in I.Autogen.Int16

Methods

shove :: Int16 -> I Int16 l r Source #

Interval Int32 l r => Shove Int32 (l :: L Int32 :: Type) (r :: R Int32 :: Type) Source # 
Instance details

Defined in I.Autogen.Int32

Methods

shove :: Int32 -> I Int32 l r Source #

Interval Int64 l r => Shove Int64 (l :: L Int64 :: Type) (r :: R Int64 :: Type) Source # 
Instance details

Defined in I.Autogen.Int64

Methods

shove :: Int64 -> I Int64 l r Source #

Interval Int8 l r => Shove Int8 (l :: L Int8 :: Type) (r :: R Int8 :: Type) Source # 
Instance details

Defined in I.Int8

Methods

shove :: Int8 -> I Int8 l r Source #

Interval Word16 l r => Shove Word16 (l :: L Word16 :: Type) (r :: R Word16 :: Type) Source # 
Instance details

Defined in I.Autogen.Word16

Methods

shove :: Word16 -> I Word16 l r Source #

Interval Word32 l r => Shove Word32 (l :: L Word32 :: Type) (r :: R Word32 :: Type) Source # 
Instance details

Defined in I.Autogen.Word32

Methods

shove :: Word32 -> I Word32 l r Source #

Interval Word64 l r => Shove Word64 (l :: L Word64 :: Type) (r :: R Word64 :: Type) Source # 
Instance details

Defined in I.Autogen.Word64

Methods

shove :: Word64 -> I Word64 l r Source #

Interval Word8 l r => Shove Word8 (l :: L Word8 :: Type) (r :: R Word8 :: Type) Source # 
Instance details

Defined in I.Word8

Methods

shove :: Word8 -> I Word8 l r Source #

Interval Int l r => Shove Int (l :: L Int :: Type) (r :: R Int :: Type) Source # 
Instance details

Defined in I.Autogen.Int

Methods

shove :: Int -> I Int l r Source #

Interval Word l r => Shove Word (l :: L Word :: Type) (r :: R Word :: Type) Source # 
Instance details

Defined in I.Autogen.Word

Methods

shove :: Word -> I Word l r Source #

Interval Natural l ('Nothing :: Maybe Natural) => Shove Natural (l :: L Natural :: Type) ('Nothing :: Maybe Natural) Source # 
Instance details

Defined in I.Natural

Interval Natural l ('Just r) => Shove Natural (l :: L Natural :: Type) ('Just r :: R Natural :: Type) Source # 
Instance details

Defined in I.Natural

Methods

shove :: Natural -> I Natural l ('Just r) Source #

Shove Rational ('Nothing :: Maybe (Bool, Rational)) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Interval Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) => Shove Integer ('Nothing :: Maybe Integer) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r)) => Shove Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational0 -> I Rational0 'Nothing ('Just '('False, r)) Source #

Interval Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r)) => Shove Rational ('Nothing :: Maybe (Bool, Rational)) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational0 -> I Rational0 'Nothing ('Just '('True, r)) Source #

Interval Integer ('Nothing :: Maybe Integer) ('Just r) => Shove Integer ('Nothing :: Maybe Integer) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Just '('False, l)) ('Nothing :: Maybe (Bool, Rational)) => Shove Rational ('Just '('False, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational0 -> I Rational0 ('Just '('False, l)) 'Nothing Source #

Interval Rational ('Just '('True, l)) ('Nothing :: Maybe (Bool, Rational)) => Shove Rational ('Just '('True, l) :: L Rational :: Type) ('Nothing :: Maybe (Bool, Rational)) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational0 -> I Rational0 ('Just '('True, l)) 'Nothing Source #

Interval Integer ('Just l) ('Nothing :: Maybe Integer) => Shove Integer ('Just l :: L Integer :: Type) ('Nothing :: Maybe Integer) Source # 
Instance details

Defined in I.Integer

Interval Rational ('Just '('False, l)) ('Just '('False, r)) => Shove Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational -> I Rational ('Just '('False, l)) ('Just '('False, r)) Source #

Interval Rational ('Just '('False, l)) ('Just '('True, r)) => Shove Rational ('Just '('False, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational -> I Rational ('Just '('False, l)) ('Just '('True, r)) Source #

Interval Rational ('Just '('True, l)) ('Just '('False, r)) => Shove Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('False, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational -> I Rational ('Just '('True, l)) ('Just '('False, r)) Source #

Interval Rational ('Just '('True, l)) ('Just '('True, r)) => Shove Rational ('Just '('True, l) :: L Rational :: Type) ('Just '('True, r) :: R Rational :: Type) Source # 
Instance details

Defined in I.Rational

Methods

shove :: Rational -> I Rational ('Just '('True, l)) ('Just '('True, r)) Source #

Interval Integer ('Just l) ('Just r) => Shove Integer ('Just l :: L Integer :: Type) ('Just r :: R Integer :: Type) Source # 
Instance details

Defined in I.Integer

Methods

shove :: Integer -> I Integer ('Just l) ('Just r) Source #

Danger

unsafest :: forall x l r. x -> I x l r Source #

unsafest allows you to wrap an x in an I x l r without checking whether the x is within the interval ends.

WARNING: This function is fast because it doesn't do any work, but also it is very dangerous because it ignores all the safety supposedly given by the I x l r type. Don't use this unless you have proved by other means that the x is within the I x l r interval. Please use from instead, or even unsafe.