#if __GLASGOW_HASKELL__ < 709
#else
#endif
module Algebra.Lattice.Dropped (
Dropped(..)
, retractDropped
) 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 Dropped a = Top
| Drop a
deriving ( Eq, Ord, Show, Read, Data, Typeable, Generic, Functor, Foldable, Traversable
#if __GLASGOW_HASKELL__ >= 706
, Generic1
#endif
)
instance Applicative Dropped where
pure = return
(<*>) = ap
instance Monad Dropped where
return = Drop
Top >>= _ = Top
Drop x >>= f = f x
instance NFData a => NFData (Dropped a) where
rnf Top = ()
rnf (Drop a) = rnf a
instance Hashable a => Hashable (Dropped a)
instance JoinSemiLattice a => JoinSemiLattice (Dropped a) where
Top \/ _ = Top
_ \/ Top = Top
Drop x \/ Drop y = Drop (x \/ y)
instance MeetSemiLattice a => MeetSemiLattice (Dropped a) where
Top /\ drop_y = drop_y
drop_x /\ Top = drop_x
Drop x /\ Drop y = Drop (x /\ y)
instance Lattice a => Lattice (Dropped a) where
instance BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Dropped a) where
bottom = Drop bottom
instance MeetSemiLattice a => BoundedMeetSemiLattice (Dropped a) where
top = Top
instance BoundedLattice a => BoundedLattice (Dropped a) where
retractDropped :: BoundedMeetSemiLattice a => Dropped a -> a
retractDropped Top = top
retractDropped (Drop x) = x