{-# LANGUAGE CPP, DefaultSignatures, PolyKinds, TypeFamilies, TypeOperators #-}
module Data.Semilattice.Lower
( Lower(..)
) where
import Data.Char
import Data.Coerce
import Data.Functor.Const
import Data.Functor.Identity
import Data.HashMap.Lazy as HashMap
import Data.HashSet as HashSet
import Data.Int
import Data.IntMap as IntMap
import Data.IntSet as IntSet
import Data.Map as Map
import Data.Monoid as Monoid
import Data.Proxy
import Data.Semigroup as Semigroup
import Data.Sequence as Seq
import Data.Set as Set
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 Lower s where
  lowerBound :: s
  default lowerBound :: Bounded s => s
  lowerBound = s
forall a. Bounded a => a
minBound
instance Lower ()
instance Lower Bool
instance Lower Ordering
instance Lower Char
instance Lower Int
instance (Lower a, Lower b) => Lower (a, b) where lowerBound :: (a, b)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound)
instance (Lower a, Lower b, Lower c) => Lower (a, b, c) where lowerBound :: (a, b, c)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound, c
forall s. Lower s => s
lowerBound)
instance (Lower a, Lower b, Lower c, Lower d) => Lower (a, b, c, d) where lowerBound :: (a, b, c, d)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound, c
forall s. Lower s => s
lowerBound, d
forall s. Lower s => s
lowerBound)
instance (Lower a, Lower b, Lower c, Lower d, Lower e) => Lower (a, b, c, d, e) where lowerBound :: (a, b, c, d, e)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound, c
forall s. Lower s => s
lowerBound, d
forall s. Lower s => s
lowerBound, e
forall s. Lower s => s
lowerBound)
instance (Lower a, Lower b, Lower c, Lower d, Lower e, Lower f) => Lower (a, b, c, d, e, f) where lowerBound :: (a, b, c, d, e, f)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound, c
forall s. Lower s => s
lowerBound, d
forall s. Lower s => s
lowerBound, e
forall s. Lower s => s
lowerBound, f
forall s. Lower s => s
lowerBound)
instance (Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g) => Lower (a, b, c, d, e, f, g) where lowerBound :: (a, b, c, d, e, f, g)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound, c
forall s. Lower s => s
lowerBound, d
forall s. Lower s => s
lowerBound, e
forall s. Lower s => s
lowerBound, f
forall s. Lower s => s
lowerBound, g
forall s. Lower s => s
lowerBound)
instance (Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h) => Lower (a, b, c, d, e, f, g, h) where lowerBound :: (a, b, c, d, e, f, g, h)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound, c
forall s. Lower s => s
lowerBound, d
forall s. Lower s => s
lowerBound, e
forall s. Lower s => s
lowerBound, f
forall s. Lower s => s
lowerBound, g
forall s. Lower s => s
lowerBound, h
forall s. Lower s => s
lowerBound)
instance (Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i) => Lower (a, b, c, d, e, f, g, h, i) where lowerBound :: (a, b, c, d, e, f, g, h, i)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound, c
forall s. Lower s => s
lowerBound, d
forall s. Lower s => s
lowerBound, e
forall s. Lower s => s
lowerBound, f
forall s. Lower s => s
lowerBound, g
forall s. Lower s => s
lowerBound, h
forall s. Lower s => s
lowerBound, i
forall s. Lower s => s
lowerBound)
instance (Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i, Lower j) => Lower (a, b, c, d, e, f, g, h, i, j) where lowerBound :: (a, b, c, d, e, f, g, h, i, j)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound, c
forall s. Lower s => s
lowerBound, d
forall s. Lower s => s
lowerBound, e
forall s. Lower s => s
lowerBound, f
forall s. Lower s => s
lowerBound, g
forall s. Lower s => s
lowerBound, h
forall s. Lower s => s
lowerBound, i
forall s. Lower s => s
lowerBound, j
forall s. Lower s => s
lowerBound)
instance (Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i, Lower j, Lower k) => Lower (a, b, c, d, e, f, g, h, i, j, k) where lowerBound :: (a, b, c, d, e, f, g, h, i, j, k)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound, c
forall s. Lower s => s
lowerBound, d
forall s. Lower s => s
lowerBound, e
forall s. Lower s => s
lowerBound, f
forall s. Lower s => s
lowerBound, g
forall s. Lower s => s
lowerBound, h
forall s. Lower s => s
lowerBound, i
forall s. Lower s => s
lowerBound, j
forall s. Lower s => s
lowerBound, k
forall s. Lower s => s
lowerBound)
instance (Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i, Lower j, Lower k, Lower l) => Lower (a, b, c, d, e, f, g, h, i, j, k, l) where lowerBound :: (a, b, c, d, e, f, g, h, i, j, k, l)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound, c
forall s. Lower s => s
lowerBound, d
forall s. Lower s => s
lowerBound, e
forall s. Lower s => s
lowerBound, f
forall s. Lower s => s
lowerBound, g
forall s. Lower s => s
lowerBound, h
forall s. Lower s => s
lowerBound, i
forall s. Lower s => s
lowerBound, j
forall s. Lower s => s
lowerBound, k
forall s. Lower s => s
lowerBound, l
forall s. Lower s => s
lowerBound)
instance (Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i, Lower j, Lower k, Lower l, Lower m) => Lower (a, b, c, d, e, f, g, h, i, j, k, l, m) where lowerBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound, c
forall s. Lower s => s
lowerBound, d
forall s. Lower s => s
lowerBound, e
forall s. Lower s => s
lowerBound, f
forall s. Lower s => s
lowerBound, g
forall s. Lower s => s
lowerBound, h
forall s. Lower s => s
lowerBound, i
forall s. Lower s => s
lowerBound, j
forall s. Lower s => s
lowerBound, k
forall s. Lower s => s
lowerBound, l
forall s. Lower s => s
lowerBound, m
forall s. Lower s => s
lowerBound)
instance (Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i, Lower j, Lower k, Lower l, Lower m, Lower n) => Lower (a, b, c, d, e, f, g, h, i, j, k, l, m, n) where lowerBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound, c
forall s. Lower s => s
lowerBound, d
forall s. Lower s => s
lowerBound, e
forall s. Lower s => s
lowerBound, f
forall s. Lower s => s
lowerBound, g
forall s. Lower s => s
lowerBound, h
forall s. Lower s => s
lowerBound, i
forall s. Lower s => s
lowerBound, j
forall s. Lower s => s
lowerBound, k
forall s. Lower s => s
lowerBound, l
forall s. Lower s => s
lowerBound, m
forall s. Lower s => s
lowerBound, n
forall s. Lower s => s
lowerBound)
instance (Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i, Lower j, Lower k, Lower l, Lower m, Lower n, Lower o) => Lower (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) where lowerBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
lowerBound = (a
forall s. Lower s => s
lowerBound, b
forall s. Lower s => s
lowerBound, c
forall s. Lower s => s
lowerBound, d
forall s. Lower s => s
lowerBound, e
forall s. Lower s => s
lowerBound, f
forall s. Lower s => s
lowerBound, g
forall s. Lower s => s
lowerBound, h
forall s. Lower s => s
lowerBound, i
forall s. Lower s => s
lowerBound, j
forall s. Lower s => s
lowerBound, k
forall s. Lower s => s
lowerBound, l
forall s. Lower s => s
lowerBound, m
forall s. Lower s => s
lowerBound, n
forall s. Lower s => s
lowerBound, o
forall s. Lower s => s
lowerBound)
instance Lower b => Lower (a -> b) where lowerBound :: a -> b
lowerBound = b -> a -> b
forall a b. a -> b -> a
const b
forall s. Lower s => s
lowerBound
instance Lower (Maybe a) where lowerBound :: Maybe a
lowerBound = Maybe a
forall a. Maybe a
Nothing
instance Lower [a] where lowerBound :: [a]
lowerBound = []
instance Lower GeneralCategory
instance Lower Int8
instance Lower Int16
instance Lower Int32
instance Lower Int64
instance Lower a => Lower (Const a b) where lowerBound :: Const a b
lowerBound = a -> Const a b
forall {k} a (b :: k). a -> Const a b
Const a
forall s. Lower s => s
lowerBound
instance Lower a => Lower (Identity a) where lowerBound :: Identity a
lowerBound = a -> Identity a
forall a. a -> Identity a
Identity a
forall s. Lower s => s
lowerBound
instance Lower All
instance Lower Any
instance Lower a => Lower (Product a) where lowerBound :: Product a
lowerBound = a -> Product a
forall a. a -> Product a
Product a
forall s. Lower s => s
lowerBound
instance Lower a => Lower (Sum a) where lowerBound :: Sum a
lowerBound = a -> Sum a
forall a. a -> Sum a
Sum a
forall s. Lower s => s
lowerBound
instance Lower a => Lower (Dual a) where lowerBound :: Dual a
lowerBound = a -> Dual a
forall a. a -> Dual a
Dual a
forall s. Lower s => s
lowerBound
instance Lower (Endo a) where lowerBound :: Endo a
lowerBound = (a -> a) -> Endo a
forall a. (a -> a) -> Endo a
Endo a -> a
forall a. a -> a
id
instance Lower (Monoid.First a) where lowerBound :: First a
lowerBound = First a
forall a. Monoid a => a
mempty
instance Lower (Monoid.Last a) where lowerBound :: Last a
lowerBound = Last a
forall a. Monoid a => a
mempty
instance Lower (Proxy a)
instance Lower a => Lower (Semigroup.First a) where lowerBound :: First a
lowerBound = a -> First a
forall a. a -> First a
Semigroup.First a
forall s. Lower s => s
lowerBound
instance Lower a => Lower (Semigroup.Last a) where lowerBound :: Last a
lowerBound = a -> Last a
forall a. a -> Last a
Semigroup.Last a
forall s. Lower s => s
lowerBound
instance Lower a => Lower (Max a) where lowerBound :: Max a
lowerBound = a -> Max a
forall a. a -> Max a
Max a
forall s. Lower s => s
lowerBound
instance Lower a => Lower (Min a) where lowerBound :: Min a
lowerBound = a -> Min a
forall a. a -> Min a
Min a
forall s. Lower s => s
lowerBound
instance Lower a => Lower (WrappedMonoid a) where lowerBound :: WrappedMonoid a
lowerBound = a -> WrappedMonoid a
forall m. m -> WrappedMonoid m
WrapMonoid a
forall s. Lower s => s
lowerBound
instance Coercible a b => Lower (Coercion a b)
instance (a ~ b) => Lower (a :~: b)
#if MIN_VERSION_base(4,10,0)
instance (a ~~ b) => Lower (a :~~: b)
#endif
instance Lower Word8
instance Lower Word16
instance Lower Word32
instance Lower Word64
instance Lower CUIntMax
instance Lower CIntMax
instance Lower CUIntPtr
instance Lower CIntPtr
instance Lower CSigAtomic
instance Lower CWchar
instance Lower CSize
instance Lower CPtrdiff
instance Lower CULLong
instance Lower CLLong
instance Lower CULong
instance Lower CLong
instance Lower CUInt
instance Lower CInt
instance Lower CUShort
instance Lower CShort
instance Lower CUChar
instance Lower CSChar
instance Lower CChar
#if MIN_VERSION_base(4,10,0)
instance Lower CBool
#endif
instance Lower IntPtr
instance Lower WordPtr
instance Lower DecidedStrictness
instance Lower SourceStrictness
instance Lower SourceUnpackedness
instance Lower Associativity
#if !defined(OS_Win32)
instance Lower Fd
instance Lower CRLim
instance Lower CTcflag
instance Lower CUid
instance Lower CNlink
instance Lower CGid
instance Lower CSsize
instance Lower CPid
instance Lower COff
instance Lower CMode
instance Lower CIno
instance Lower CDev
#endif
#if MIN_VERSION_base(4,10,0)
instance Lower CKey
instance Lower CId
instance Lower CFsFilCnt
instance Lower CFsBlkCnt
#ifdef HTYPE_CLOCKID_T
instance Lower CClockId
#endif
instance Lower CBlkCnt
instance Lower CBlkSize
#endif
instance Lower (IntMap a) where lowerBound :: IntMap a
lowerBound = IntMap a
forall a. IntMap a
IntMap.empty
instance Lower IntSet where lowerBound :: IntSet
lowerBound = IntSet
IntSet.empty
instance Lower (Map k a) where lowerBound :: Map k a
lowerBound = Map k a
forall k a. Map k a
Map.empty
instance Lower (Seq a) where lowerBound :: Seq a
lowerBound = Seq a
forall a. Seq a
Seq.empty
instance Lower (Set a) where lowerBound :: Set a
lowerBound = Set a
forall a. Set a
Set.empty
instance Lower (HashMap k a) where lowerBound :: HashMap k a
lowerBound = HashMap k a
forall k a. HashMap k a
HashMap.empty
instance Lower (HashSet a) where lowerBound :: HashSet a
lowerBound = HashSet a
forall a. HashSet a
HashSet.empty