{-# LANGUAGE CPP, DefaultSignatures, PolyKinds, TypeFamilies, TypeOperators #-}
module Data.Semilattice.Upper
( Upper(..)
) where
import Data.Char
import Data.Coerce
import Data.Functor.Const
import Data.Functor.Identity
import Data.Int
import Data.Monoid as Monoid
import Data.Proxy
import Data.Semigroup as Semigroup
import Data.Type.Coercion
import Data.Type.Equality
import Data.Word
import Foreign.C.Types
import Foreign.Ptr
import GHC.Generics
#if !defined(OS_Win32)
import System.Posix.Types
#endif
class Upper s where
upperBound :: s
default upperBound :: Bounded s => s
upperBound = s
forall a. Bounded a => a
maxBound
instance Upper ()
instance Upper Bool
instance Upper Ordering
instance Upper Char
instance Upper Int
instance (Upper a, Upper b) => Upper (a, b) where upperBound :: (a, b)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound)
instance (Upper a, Upper b, Upper c) => Upper (a, b, c) where upperBound :: (a, b, c)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound, c
forall s. Upper s => s
upperBound)
instance (Upper a, Upper b, Upper c, Upper d) => Upper (a, b, c, d) where upperBound :: (a, b, c, d)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound, c
forall s. Upper s => s
upperBound, d
forall s. Upper s => s
upperBound)
instance (Upper a, Upper b, Upper c, Upper d, Upper e) => Upper (a, b, c, d, e) where upperBound :: (a, b, c, d, e)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound, c
forall s. Upper s => s
upperBound, d
forall s. Upper s => s
upperBound, e
forall s. Upper s => s
upperBound)
instance (Upper a, Upper b, Upper c, Upper d, Upper e, Upper f) => Upper (a, b, c, d, e, f) where upperBound :: (a, b, c, d, e, f)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound, c
forall s. Upper s => s
upperBound, d
forall s. Upper s => s
upperBound, e
forall s. Upper s => s
upperBound, f
forall s. Upper s => s
upperBound)
instance (Upper a, Upper b, Upper c, Upper d, Upper e, Upper f, Upper g) => Upper (a, b, c, d, e, f, g) where upperBound :: (a, b, c, d, e, f, g)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound, c
forall s. Upper s => s
upperBound, d
forall s. Upper s => s
upperBound, e
forall s. Upper s => s
upperBound, f
forall s. Upper s => s
upperBound, g
forall s. Upper s => s
upperBound)
instance (Upper a, Upper b, Upper c, Upper d, Upper e, Upper f, Upper g, Upper h) => Upper (a, b, c, d, e, f, g, h) where upperBound :: (a, b, c, d, e, f, g, h)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound, c
forall s. Upper s => s
upperBound, d
forall s. Upper s => s
upperBound, e
forall s. Upper s => s
upperBound, f
forall s. Upper s => s
upperBound, g
forall s. Upper s => s
upperBound, h
forall s. Upper s => s
upperBound)
instance (Upper a, Upper b, Upper c, Upper d, Upper e, Upper f, Upper g, Upper h, Upper i) => Upper (a, b, c, d, e, f, g, h, i) where upperBound :: (a, b, c, d, e, f, g, h, i)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound, c
forall s. Upper s => s
upperBound, d
forall s. Upper s => s
upperBound, e
forall s. Upper s => s
upperBound, f
forall s. Upper s => s
upperBound, g
forall s. Upper s => s
upperBound, h
forall s. Upper s => s
upperBound, i
forall s. Upper s => s
upperBound)
instance (Upper a, Upper b, Upper c, Upper d, Upper e, Upper f, Upper g, Upper h, Upper i, Upper j) => Upper (a, b, c, d, e, f, g, h, i, j) where upperBound :: (a, b, c, d, e, f, g, h, i, j)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound, c
forall s. Upper s => s
upperBound, d
forall s. Upper s => s
upperBound, e
forall s. Upper s => s
upperBound, f
forall s. Upper s => s
upperBound, g
forall s. Upper s => s
upperBound, h
forall s. Upper s => s
upperBound, i
forall s. Upper s => s
upperBound, j
forall s. Upper s => s
upperBound)
instance (Upper a, Upper b, Upper c, Upper d, Upper e, Upper f, Upper g, Upper h, Upper i, Upper j, Upper k) => Upper (a, b, c, d, e, f, g, h, i, j, k) where upperBound :: (a, b, c, d, e, f, g, h, i, j, k)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound, c
forall s. Upper s => s
upperBound, d
forall s. Upper s => s
upperBound, e
forall s. Upper s => s
upperBound, f
forall s. Upper s => s
upperBound, g
forall s. Upper s => s
upperBound, h
forall s. Upper s => s
upperBound, i
forall s. Upper s => s
upperBound, j
forall s. Upper s => s
upperBound, k
forall s. Upper s => s
upperBound)
instance (Upper a, Upper b, Upper c, Upper d, Upper e, Upper f, Upper g, Upper h, Upper i, Upper j, Upper k, Upper l) => Upper (a, b, c, d, e, f, g, h, i, j, k, l) where upperBound :: (a, b, c, d, e, f, g, h, i, j, k, l)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound, c
forall s. Upper s => s
upperBound, d
forall s. Upper s => s
upperBound, e
forall s. Upper s => s
upperBound, f
forall s. Upper s => s
upperBound, g
forall s. Upper s => s
upperBound, h
forall s. Upper s => s
upperBound, i
forall s. Upper s => s
upperBound, j
forall s. Upper s => s
upperBound, k
forall s. Upper s => s
upperBound, l
forall s. Upper s => s
upperBound)
instance (Upper a, Upper b, Upper c, Upper d, Upper e, Upper f, Upper g, Upper h, Upper i, Upper j, Upper k, Upper l, Upper m) => Upper (a, b, c, d, e, f, g, h, i, j, k, l, m) where upperBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound, c
forall s. Upper s => s
upperBound, d
forall s. Upper s => s
upperBound, e
forall s. Upper s => s
upperBound, f
forall s. Upper s => s
upperBound, g
forall s. Upper s => s
upperBound, h
forall s. Upper s => s
upperBound, i
forall s. Upper s => s
upperBound, j
forall s. Upper s => s
upperBound, k
forall s. Upper s => s
upperBound, l
forall s. Upper s => s
upperBound, m
forall s. Upper s => s
upperBound)
instance (Upper a, Upper b, Upper c, Upper d, Upper e, Upper f, Upper g, Upper h, Upper i, Upper j, Upper k, Upper l, Upper m, Upper n) => Upper (a, b, c, d, e, f, g, h, i, j, k, l, m, n) where upperBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound, c
forall s. Upper s => s
upperBound, d
forall s. Upper s => s
upperBound, e
forall s. Upper s => s
upperBound, f
forall s. Upper s => s
upperBound, g
forall s. Upper s => s
upperBound, h
forall s. Upper s => s
upperBound, i
forall s. Upper s => s
upperBound, j
forall s. Upper s => s
upperBound, k
forall s. Upper s => s
upperBound, l
forall s. Upper s => s
upperBound, m
forall s. Upper s => s
upperBound, n
forall s. Upper s => s
upperBound)
instance (Upper a, Upper b, Upper c, Upper d, Upper e, Upper f, Upper g, Upper h, Upper i, Upper j, Upper k, Upper l, Upper m, Upper n, Upper o) => Upper (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) where upperBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
upperBound = (a
forall s. Upper s => s
upperBound, b
forall s. Upper s => s
upperBound, c
forall s. Upper s => s
upperBound, d
forall s. Upper s => s
upperBound, e
forall s. Upper s => s
upperBound, f
forall s. Upper s => s
upperBound, g
forall s. Upper s => s
upperBound, h
forall s. Upper s => s
upperBound, i
forall s. Upper s => s
upperBound, j
forall s. Upper s => s
upperBound, k
forall s. Upper s => s
upperBound, l
forall s. Upper s => s
upperBound, m
forall s. Upper s => s
upperBound, n
forall s. Upper s => s
upperBound, o
forall s. Upper s => s
upperBound)
instance Upper b => Upper (a -> b) where upperBound :: a -> b
upperBound = b -> a -> b
forall a b. a -> b -> a
const b
forall s. Upper s => s
upperBound
instance Upper GeneralCategory
instance Upper Int8
instance Upper Int16
instance Upper Int32
instance Upper Int64
instance Upper a => Upper (Const a b) where upperBound :: Const a b
upperBound = a -> Const a b
forall {k} a (b :: k). a -> Const a b
Const a
forall s. Upper s => s
upperBound
instance Upper a => Upper (Identity a) where upperBound :: Identity a
upperBound = a -> Identity a
forall a. a -> Identity a
Identity a
forall s. Upper s => s
upperBound
instance Upper All
instance Upper Any
instance Upper a => Upper (Product a) where upperBound :: Product a
upperBound = a -> Product a
forall a. a -> Product a
Product a
forall s. Upper s => s
upperBound
instance Upper a => Upper (Sum a) where upperBound :: Sum a
upperBound = a -> Sum a
forall a. a -> Sum a
Sum a
forall s. Upper s => s
upperBound
instance Upper a => Upper (Dual a) where upperBound :: Dual a
upperBound = a -> Dual a
forall a. a -> Dual a
Dual a
forall s. Upper s => s
upperBound
instance Upper (Proxy a)
instance Upper a => Upper (Semigroup.First a) where upperBound :: First a
upperBound = a -> First a
forall a. a -> First a
Semigroup.First a
forall s. Upper s => s
upperBound
instance Upper a => Upper (Semigroup.Last a) where upperBound :: Last a
upperBound = a -> Last a
forall a. a -> Last a
Semigroup.Last a
forall s. Upper s => s
upperBound
instance Upper a => Upper (Max a) where upperBound :: Max a
upperBound = a -> Max a
forall a. a -> Max a
Max a
forall s. Upper s => s
upperBound
instance Upper a => Upper (Min a) where upperBound :: Min a
upperBound = a -> Min a
forall a. a -> Min a
Min a
forall s. Upper s => s
upperBound
instance Upper a => Upper (WrappedMonoid a) where upperBound :: WrappedMonoid a
upperBound = a -> WrappedMonoid a
forall m. m -> WrappedMonoid m
WrapMonoid a
forall s. Upper s => s
upperBound
instance Coercible a b => Upper (Coercion a b)
instance (a ~ b) => Upper (a :~: b)
#if MIN_VERSION_base(4,10,0)
instance (a ~~ b) => Upper (a :~~: b)
#endif
instance Upper Word8
instance Upper Word16
instance Upper Word32
instance Upper Word64
instance Upper CUIntMax
instance Upper CIntMax
instance Upper CUIntPtr
instance Upper CIntPtr
instance Upper CSigAtomic
instance Upper CWchar
instance Upper CSize
instance Upper CPtrdiff
instance Upper CULLong
instance Upper CLLong
instance Upper CULong
instance Upper CLong
instance Upper CUInt
instance Upper CInt
instance Upper CUShort
instance Upper CShort
instance Upper CUChar
instance Upper CSChar
instance Upper CChar
#if MIN_VERSION_base(4,10,0)
instance Upper CBool
#endif
instance Upper IntPtr
instance Upper WordPtr
instance Upper DecidedStrictness
instance Upper SourceStrictness
instance Upper SourceUnpackedness
instance Upper Associativity
#if !defined(OS_Win32)
instance Upper Fd
instance Upper CRLim
instance Upper CTcflag
instance Upper CUid
instance Upper CNlink
instance Upper CGid
instance Upper CSsize
instance Upper CPid
instance Upper COff
instance Upper CMode
instance Upper CIno
instance Upper CDev
#endif
#if MIN_VERSION_base(4,10,0)
instance Upper CKey
instance Upper CId
instance Upper CFsFilCnt
instance Upper CFsBlkCnt
#ifdef HTYPE_CLOCKID_T
instance Upper CClockId
#endif
instance Upper CBlkCnt
instance Upper CBlkSize
#endif