{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Safe #-}

module Data.Order.Extended (
    -- * Lattice extensions
    Lifted,
    Lowered,
    Extended (..),
    extended,
    --, retract

    -- * Lattice Extensions
    liftMaybe,
    liftEitherL,
    liftEitherR,
    liftExtended,
) where

import safe Data.Order
import safe Data.Order.Syntax
import safe GHC.Generics
import safe Prelude hiding (Bounded, Eq (..), Ord (..))

type Lifted = Either ()

type Lowered a = Either a ()

-- | Add a bottom and top to a lattice.
--
-- The top is the absorbing element for the join, and the bottom is the absorbing
-- element for the meet.
data Extended a = Bottom | Extended a | Top
    deriving (Extended a -> Extended a -> Bool
(Extended a -> Extended a -> Bool)
-> (Extended a -> Extended a -> Bool) -> Eq (Extended a)
forall a. Eq a => Extended a -> Extended a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Extended a -> Extended a -> Bool
$c/= :: forall a. Eq a => Extended a -> Extended a -> Bool
== :: Extended a -> Extended a -> Bool
$c== :: forall a. Eq a => Extended a -> Extended a -> Bool
Eq, Eq (Extended a)
Eq (Extended a)
-> (Extended a -> Extended a -> Ordering)
-> (Extended a -> Extended a -> Bool)
-> (Extended a -> Extended a -> Bool)
-> (Extended a -> Extended a -> Bool)
-> (Extended a -> Extended a -> Bool)
-> (Extended a -> Extended a -> Extended a)
-> (Extended a -> Extended a -> Extended a)
-> Ord (Extended a)
Extended a -> Extended a -> Bool
Extended a -> Extended a -> Ordering
Extended a -> Extended a -> Extended 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 (Extended a)
forall a. Ord a => Extended a -> Extended a -> Bool
forall a. Ord a => Extended a -> Extended a -> Ordering
forall a. Ord a => Extended a -> Extended a -> Extended a
min :: Extended a -> Extended a -> Extended a
$cmin :: forall a. Ord a => Extended a -> Extended a -> Extended a
max :: Extended a -> Extended a -> Extended a
$cmax :: forall a. Ord a => Extended a -> Extended a -> Extended a
>= :: Extended a -> Extended a -> Bool
$c>= :: forall a. Ord a => Extended a -> Extended a -> Bool
> :: Extended a -> Extended a -> Bool
$c> :: forall a. Ord a => Extended a -> Extended a -> Bool
<= :: Extended a -> Extended a -> Bool
$c<= :: forall a. Ord a => Extended a -> Extended a -> Bool
< :: Extended a -> Extended a -> Bool
$c< :: forall a. Ord a => Extended a -> Extended a -> Bool
compare :: Extended a -> Extended a -> Ordering
$ccompare :: forall a. Ord a => Extended a -> Extended a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (Extended a)
Ord, Int -> Extended a -> ShowS
[Extended a] -> ShowS
Extended a -> String
(Int -> Extended a -> ShowS)
-> (Extended a -> String)
-> ([Extended a] -> ShowS)
-> Show (Extended a)
forall a. Show a => Int -> Extended a -> ShowS
forall a. Show a => [Extended a] -> ShowS
forall a. Show a => Extended a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Extended a] -> ShowS
$cshowList :: forall a. Show a => [Extended a] -> ShowS
show :: Extended a -> String
$cshow :: forall a. Show a => Extended a -> String
showsPrec :: Int -> Extended a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Extended a -> ShowS
Show, (forall x. Extended a -> Rep (Extended a) x)
-> (forall x. Rep (Extended a) x -> Extended a)
-> Generic (Extended a)
forall x. Rep (Extended a) x -> Extended a
forall x. Extended a -> Rep (Extended a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Extended a) x -> Extended a
forall a x. Extended a -> Rep (Extended a) x
$cto :: forall a x. Rep (Extended a) x -> Extended a
$cfrom :: forall a x. Extended a -> Rep (Extended a) x
Generic, a -> Extended b -> Extended a
(a -> b) -> Extended a -> Extended b
(forall a b. (a -> b) -> Extended a -> Extended b)
-> (forall a b. a -> Extended b -> Extended a) -> Functor Extended
forall a b. a -> Extended b -> Extended a
forall a b. (a -> b) -> Extended a -> Extended b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Extended b -> Extended a
$c<$ :: forall a b. a -> Extended b -> Extended a
fmap :: (a -> b) -> Extended a -> Extended b
$cfmap :: forall a b. (a -> b) -> Extended a -> Extended b
Functor, (forall a. Extended a -> Rep1 Extended a)
-> (forall a. Rep1 Extended a -> Extended a) -> Generic1 Extended
forall a. Rep1 Extended a -> Extended a
forall a. Extended a -> Rep1 Extended a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall a. Rep1 Extended a -> Extended a
$cfrom1 :: forall a. Extended a -> Rep1 Extended a
Generic1)

-- | Eliminate an 'Extended'.
extended :: b -> b -> (a -> b) -> Extended a -> b
extended :: b -> b -> (a -> b) -> Extended a -> b
extended b
b b
_ a -> b
_ Extended a
Bottom = b
b
extended b
_ b
t a -> b
_ Extended a
Top = b
t
extended b
_ b
_ a -> b
f (Extended a
x) = a -> b
f a
x

-------------------------------------------------------------------------------
-- Lattice extensions
-------------------------------------------------------------------------------

{-
lifts :: Minimal a => Eq a => (a -> b) -> a -> Lifted b
lifts = liftEitherL (== minimal)

lifted :: Minimal b => (a -> b) -> Lifted a -> b
lifted f = either (const minimal) f

lowered :: Maximal b => (a -> b) -> Lowered a -> b
lowered f = either f (const maximal)

lowers :: Maximal a => Eq a => (a -> b) -> a -> Lowered b
lowers = liftEitherR (== maximal)
-}

liftMaybe :: (a -> Bool) -> (a -> b) -> a -> Maybe b
liftMaybe :: (a -> Bool) -> (a -> b) -> a -> Maybe b
liftMaybe a -> Bool
p a -> b
f = a -> Maybe b
g
  where
    g :: a -> Maybe b
g a
i
        | a -> Bool
p a
i = Maybe b
forall a. Maybe a
Nothing
        | Bool
otherwise = b -> Maybe b
forall a. a -> Maybe a
Just (b -> Maybe b) -> b -> Maybe b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
i

liftEitherL :: (a -> Bool) -> (a -> b) -> a -> Lifted b
liftEitherL :: (a -> Bool) -> (a -> b) -> a -> Lifted b
liftEitherL a -> Bool
p a -> b
f = a -> Lifted b
g
  where
    g :: a -> Lifted b
g a
i
        | a -> Bool
p a
i = () -> Lifted b
forall a b. a -> Either a b
Left ()
        | Bool
otherwise = b -> Lifted b
forall a b. b -> Either a b
Right (b -> Lifted b) -> b -> Lifted b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
i

liftEitherR :: (a -> Bool) -> (a -> b) -> a -> Lowered b
liftEitherR :: (a -> Bool) -> (a -> b) -> a -> Lowered b
liftEitherR a -> Bool
p a -> b
f = a -> Lowered b
g
  where
    g :: a -> Lowered b
g a
i
        | a -> Bool
p a
i = () -> Lowered b
forall a b. b -> Either a b
Right ()
        | Bool
otherwise = b -> Lowered b
forall a b. a -> Either a b
Left (b -> Lowered b) -> b -> Lowered b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
i

liftExtended :: (a -> Bool) -> (a -> Bool) -> (a -> b) -> a -> Extended b
liftExtended :: (a -> Bool) -> (a -> Bool) -> (a -> b) -> a -> Extended b
liftExtended a -> Bool
p a -> Bool
q a -> b
f = a -> Extended b
g
  where
    g :: a -> Extended b
g a
i
        | a -> Bool
p a
i = Extended b
forall a. Extended a
Bottom
        | a -> Bool
q a
i = Extended b
forall a. Extended a
Top
        | Bool
otherwise = b -> Extended b
forall a. a -> Extended a
Extended (b -> Extended b) -> b -> Extended b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
i

---------------------------------------------------------------------
-- Instances
---------------------------------------------------------------------

instance Preorder a => Preorder (Extended a) where
    Extended a
_ <~ :: Extended a -> Extended a -> Bool
<~ Extended a
Top = Bool
True
    Extended a
Top <~ Extended a
_ = Bool
False
    Extended a
Bottom <~ Extended a
_ = Bool
True
    Extended a
_ <~ Extended a
Bottom = Bool
False
    Extended a
x <~ Extended a
y = a
x a -> a -> Bool
forall a. Preorder a => a -> a -> Bool
<~ a
y

{-
instance Universe a => Universe (Extended a) where
    universe = Top : Bottom : map Extended universe
instance Finite a => Finite (Extended a) where
    universeF = Top : Bottom : map Extended universeF
    cardinality = fmap (2 +) (retag (cardinality :: Tagged a Natural))
-}