{-# LANGUAGE DeriveTraversable, GeneralizedNewtypeDeriving #-}
-- | 'Lower' and 'Upper' bounds from 'Bounded' instances.
module Data.Semilattice.Bound
( Bound(..)
) where

import Data.Semilattice.Lower
import Data.Semilattice.Upper

-- | A convenience bridging 'Bounded' to 'Lower' and 'Upper'.
newtype Bound a = Bound { Bound a -> a
getBound :: a }
  deriving (Bound a
Bound a -> Bound a -> Bounded (Bound a)
forall a. a -> a -> Bounded a
forall a. Bounded a => Bound a
maxBound :: Bound a
$cmaxBound :: forall a. Bounded a => Bound a
minBound :: Bound a
$cminBound :: forall a. Bounded a => Bound a
Bounded, Int -> Bound a
Bound a -> Int
Bound a -> [Bound a]
Bound a -> Bound a
Bound a -> Bound a -> [Bound a]
Bound a -> Bound a -> Bound a -> [Bound a]
(Bound a -> Bound a)
-> (Bound a -> Bound a)
-> (Int -> Bound a)
-> (Bound a -> Int)
-> (Bound a -> [Bound a])
-> (Bound a -> Bound a -> [Bound a])
-> (Bound a -> Bound a -> [Bound a])
-> (Bound a -> Bound a -> Bound a -> [Bound a])
-> Enum (Bound a)
forall a. Enum a => Int -> Bound a
forall a. Enum a => Bound a -> Int
forall a. Enum a => Bound a -> [Bound a]
forall a. Enum a => Bound a -> Bound a
forall a. Enum a => Bound a -> Bound a -> [Bound a]
forall a. Enum a => Bound a -> Bound a -> Bound a -> [Bound a]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Bound a -> Bound a -> Bound a -> [Bound a]
$cenumFromThenTo :: forall a. Enum a => Bound a -> Bound a -> Bound a -> [Bound a]
enumFromTo :: Bound a -> Bound a -> [Bound a]
$cenumFromTo :: forall a. Enum a => Bound a -> Bound a -> [Bound a]
enumFromThen :: Bound a -> Bound a -> [Bound a]
$cenumFromThen :: forall a. Enum a => Bound a -> Bound a -> [Bound a]
enumFrom :: Bound a -> [Bound a]
$cenumFrom :: forall a. Enum a => Bound a -> [Bound a]
fromEnum :: Bound a -> Int
$cfromEnum :: forall a. Enum a => Bound a -> Int
toEnum :: Int -> Bound a
$ctoEnum :: forall a. Enum a => Int -> Bound a
pred :: Bound a -> Bound a
$cpred :: forall a. Enum a => Bound a -> Bound a
succ :: Bound a -> Bound a
$csucc :: forall a. Enum a => Bound a -> Bound a
Enum, Bound a -> Bound a -> Bool
(Bound a -> Bound a -> Bool)
-> (Bound a -> Bound a -> Bool) -> Eq (Bound a)
forall a. Eq a => Bound a -> Bound a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bound a -> Bound a -> Bool
$c/= :: forall a. Eq a => Bound a -> Bound a -> Bool
== :: Bound a -> Bound a -> Bool
$c== :: forall a. Eq a => Bound a -> Bound a -> Bool
Eq, Bound a -> Bool
(a -> m) -> Bound a -> m
(a -> b -> b) -> b -> Bound a -> b
(forall m. Monoid m => Bound m -> m)
-> (forall m a. Monoid m => (a -> m) -> Bound a -> m)
-> (forall m a. Monoid m => (a -> m) -> Bound a -> m)
-> (forall a b. (a -> b -> b) -> b -> Bound a -> b)
-> (forall a b. (a -> b -> b) -> b -> Bound a -> b)
-> (forall b a. (b -> a -> b) -> b -> Bound a -> b)
-> (forall b a. (b -> a -> b) -> b -> Bound a -> b)
-> (forall a. (a -> a -> a) -> Bound a -> a)
-> (forall a. (a -> a -> a) -> Bound a -> a)
-> (forall a. Bound a -> [a])
-> (forall a. Bound a -> Bool)
-> (forall a. Bound a -> Int)
-> (forall a. Eq a => a -> Bound a -> Bool)
-> (forall a. Ord a => Bound a -> a)
-> (forall a. Ord a => Bound a -> a)
-> (forall a. Num a => Bound a -> a)
-> (forall a. Num a => Bound a -> a)
-> Foldable Bound
forall a. Eq a => a -> Bound a -> Bool
forall a. Num a => Bound a -> a
forall a. Ord a => Bound a -> a
forall m. Monoid m => Bound m -> m
forall a. Bound a -> Bool
forall a. Bound a -> Int
forall a. Bound a -> [a]
forall a. (a -> a -> a) -> Bound a -> a
forall m a. Monoid m => (a -> m) -> Bound a -> m
forall b a. (b -> a -> b) -> b -> Bound a -> b
forall a b. (a -> b -> b) -> b -> Bound a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Bound a -> a
$cproduct :: forall a. Num a => Bound a -> a
sum :: Bound a -> a
$csum :: forall a. Num a => Bound a -> a
minimum :: Bound a -> a
$cminimum :: forall a. Ord a => Bound a -> a
maximum :: Bound a -> a
$cmaximum :: forall a. Ord a => Bound a -> a
elem :: a -> Bound a -> Bool
$celem :: forall a. Eq a => a -> Bound a -> Bool
length :: Bound a -> Int
$clength :: forall a. Bound a -> Int
null :: Bound a -> Bool
$cnull :: forall a. Bound a -> Bool
toList :: Bound a -> [a]
$ctoList :: forall a. Bound a -> [a]
foldl1 :: (a -> a -> a) -> Bound a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Bound a -> a
foldr1 :: (a -> a -> a) -> Bound a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Bound a -> a
foldl' :: (b -> a -> b) -> b -> Bound a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Bound a -> b
foldl :: (b -> a -> b) -> b -> Bound a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Bound a -> b
foldr' :: (a -> b -> b) -> b -> Bound a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Bound a -> b
foldr :: (a -> b -> b) -> b -> Bound a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Bound a -> b
foldMap' :: (a -> m) -> Bound a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Bound a -> m
foldMap :: (a -> m) -> Bound a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Bound a -> m
fold :: Bound m -> m
$cfold :: forall m. Monoid m => Bound m -> m
Foldable, a -> Bound b -> Bound a
(a -> b) -> Bound a -> Bound b
(forall a b. (a -> b) -> Bound a -> Bound b)
-> (forall a b. a -> Bound b -> Bound a) -> Functor Bound
forall a b. a -> Bound b -> Bound a
forall a b. (a -> b) -> Bound a -> Bound b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Bound b -> Bound a
$c<$ :: forall a b. a -> Bound b -> Bound a
fmap :: (a -> b) -> Bound a -> Bound b
$cfmap :: forall a b. (a -> b) -> Bound a -> Bound b
Functor, Integer -> Bound a
Bound a -> Bound a
Bound a -> Bound a -> Bound a
(Bound a -> Bound a -> Bound a)
-> (Bound a -> Bound a -> Bound a)
-> (Bound a -> Bound a -> Bound a)
-> (Bound a -> Bound a)
-> (Bound a -> Bound a)
-> (Bound a -> Bound a)
-> (Integer -> Bound a)
-> Num (Bound a)
forall a. Num a => Integer -> Bound a
forall a. Num a => Bound a -> Bound a
forall a. Num a => Bound a -> Bound a -> Bound a
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Bound a
$cfromInteger :: forall a. Num a => Integer -> Bound a
signum :: Bound a -> Bound a
$csignum :: forall a. Num a => Bound a -> Bound a
abs :: Bound a -> Bound a
$cabs :: forall a. Num a => Bound a -> Bound a
negate :: Bound a -> Bound a
$cnegate :: forall a. Num a => Bound a -> Bound a
* :: Bound a -> Bound a -> Bound a
$c* :: forall a. Num a => Bound a -> Bound a -> Bound a
- :: Bound a -> Bound a -> Bound a
$c- :: forall a. Num a => Bound a -> Bound a -> Bound a
+ :: Bound a -> Bound a -> Bound a
$c+ :: forall a. Num a => Bound a -> Bound a -> Bound a
Num, Eq (Bound a)
Eq (Bound a) =>
(Bound a -> Bound a -> Ordering)
-> (Bound a -> Bound a -> Bool)
-> (Bound a -> Bound a -> Bool)
-> (Bound a -> Bound a -> Bool)
-> (Bound a -> Bound a -> Bool)
-> (Bound a -> Bound a -> Bound a)
-> (Bound a -> Bound a -> Bound a)
-> Ord (Bound a)
Bound a -> Bound a -> Bool
Bound a -> Bound a -> Ordering
Bound a -> Bound a -> Bound a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (Bound a)
forall a. Ord a => Bound a -> Bound a -> Bool
forall a. Ord a => Bound a -> Bound a -> Ordering
forall a. Ord a => Bound a -> Bound a -> Bound a
min :: Bound a -> Bound a -> Bound a
$cmin :: forall a. Ord a => Bound a -> Bound a -> Bound a
max :: Bound a -> Bound a -> Bound a
$cmax :: forall a. Ord a => Bound a -> Bound a -> Bound a
>= :: Bound a -> Bound a -> Bool
$c>= :: forall a. Ord a => Bound a -> Bound a -> Bool
> :: Bound a -> Bound a -> Bool
$c> :: forall a. Ord a => Bound a -> Bound a -> Bool
<= :: Bound a -> Bound a -> Bool
$c<= :: forall a. Ord a => Bound a -> Bound a -> Bool
< :: Bound a -> Bound a -> Bool
$c< :: forall a. Ord a => Bound a -> Bound a -> Bool
compare :: Bound a -> Bound a -> Ordering
$ccompare :: forall a. Ord a => Bound a -> Bound a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (Bound a)
Ord, ReadPrec [Bound a]
ReadPrec (Bound a)
Int -> ReadS (Bound a)
ReadS [Bound a]
(Int -> ReadS (Bound a))
-> ReadS [Bound a]
-> ReadPrec (Bound a)
-> ReadPrec [Bound a]
-> Read (Bound a)
forall a. Read a => ReadPrec [Bound a]
forall a. Read a => ReadPrec (Bound a)
forall a. Read a => Int -> ReadS (Bound a)
forall a. Read a => ReadS [Bound a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Bound a]
$creadListPrec :: forall a. Read a => ReadPrec [Bound a]
readPrec :: ReadPrec (Bound a)
$creadPrec :: forall a. Read a => ReadPrec (Bound a)
readList :: ReadS [Bound a]
$creadList :: forall a. Read a => ReadS [Bound a]
readsPrec :: Int -> ReadS (Bound a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Bound a)
Read, Int -> Bound a -> ShowS
[Bound a] -> ShowS
Bound a -> String
(Int -> Bound a -> ShowS)
-> (Bound a -> String) -> ([Bound a] -> ShowS) -> Show (Bound a)
forall a. Show a => Int -> Bound a -> ShowS
forall a. Show a => [Bound a] -> ShowS
forall a. Show a => Bound a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bound a] -> ShowS
$cshowList :: forall a. Show a => [Bound a] -> ShowS
show :: Bound a -> String
$cshow :: forall a. Show a => Bound a -> String
showsPrec :: Int -> Bound a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Bound a -> ShowS
Show, Functor Bound
Foldable Bound
(Functor Bound, Foldable Bound) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> Bound a -> f (Bound b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Bound (f a) -> f (Bound a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Bound a -> m (Bound b))
-> (forall (m :: * -> *) a. Monad m => Bound (m a) -> m (Bound a))
-> Traversable Bound
(a -> f b) -> Bound a -> f (Bound b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Bound (m a) -> m (Bound a)
forall (f :: * -> *) a. Applicative f => Bound (f a) -> f (Bound a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Bound a -> m (Bound b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Bound a -> f (Bound b)
sequence :: Bound (m a) -> m (Bound a)
$csequence :: forall (m :: * -> *) a. Monad m => Bound (m a) -> m (Bound a)
mapM :: (a -> m b) -> Bound a -> m (Bound b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Bound a -> m (Bound b)
sequenceA :: Bound (f a) -> f (Bound a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Bound (f a) -> f (Bound a)
traverse :: (a -> f b) -> Bound a -> f (Bound b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Bound a -> f (Bound b)
$cp2Traversable :: Foldable Bound
$cp1Traversable :: Functor Bound
Traversable)

instance Bounded a => Lower (Bound a)
instance Bounded a => Upper (Bound a)