module Data.Void (Void, absurd, vacuous, vacuousM) where
import Data.Semigroup (Semigroup(..))
import Data.Ix
#ifdef LANGUAGE_DeriveDataTypeable
import Data.Data
#endif
#ifdef __GLASGOW_HASKELL__
import Unsafe.Coerce
#else
import Control.Monad (liftM)
#endif
#if __GLASGOW_HASKELL__ < 700
data Void = Void !Void
#else
newtype Void = Void Void
#endif
deriving
( Eq, Ord, Show, Read
#ifdef LANGUAGE_DeriveDataTypeable
, Data, Typeable
#endif
)
absurd :: Void -> a
absurd a = a `seq` spin a where
spin (Void b) = spin b
vacuous :: Functor f => f Void -> f a
#ifdef __GLASGOW_HASKELL__
vacuous = unsafeCoerce
#else
vacuous = fmap absurd
#endif
vacuousM :: Monad m => m Void -> m a
#ifdef __GLASGOW_HASKELL__
vacuousM = unsafeCoerce
#else
vacuousM = liftM absurd
#endif
instance Semigroup Void where
a <> _ = a
times1p _ a = a
instance Ix Void where
range _ = []
index _ = absurd
inRange _ = absurd
rangeSize _ = 0