#if __GLASGOW_HASKELL__ < 709
#else
#endif
module Algebra.Lattice.Lifted (
Lifted(..)
, retractLifted
) where
import Prelude ()
import Prelude.Compat
import Algebra.Lattice
import Control.DeepSeq
import Control.Monad
import Data.Data
import Data.Hashable
import GHC.Generics
data Lifted a = Lift a
| Bottom
deriving ( Eq, Ord, Show, Read, Data, Typeable, Generic, Functor, Foldable, Traversable
#if __GLASGOW_HASKELL__ >= 706
, Generic1
#endif
)
instance Applicative Lifted where
pure = return
(<*>) = ap
instance Monad Lifted where
return = Lift
Bottom >>= _ = Bottom
Lift x >>= f = f x
instance NFData a => NFData (Lifted a) where
rnf Bottom = ()
rnf (Lift a) = rnf a
instance Hashable a => Hashable (Lifted a)
instance JoinSemiLattice a => JoinSemiLattice (Lifted a) where
Lift x \/ Lift y = Lift (x \/ y)
Bottom \/ lift_y = lift_y
lift_x \/ Bottom = lift_x
instance MeetSemiLattice a => MeetSemiLattice (Lifted a) where
Lift x /\ Lift y = Lift (x /\ y)
Bottom /\ _ = Bottom
_ /\ Bottom = Bottom
instance Lattice a => Lattice (Lifted a) where
instance JoinSemiLattice a => BoundedJoinSemiLattice (Lifted a) where
bottom = Bottom
instance BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Lifted a) where
top = Lift top
instance BoundedLattice a => BoundedLattice (Lifted a) where
retractLifted :: BoundedJoinSemiLattice a => Lifted a -> a
retractLifted Bottom = bottom
retractLifted (Lift x) = x