#if __GLASGOW_HASKELL__ >= 800
#endif
module Data.Constraint.Unsafe
( Coercible
, unsafeCoerceConstraint
, unsafeDerive
, unsafeUnderive
, unsafeApplicative
, unsafeAlternative
) where
import Control.Applicative
import Control.Monad
import Data.Coerce
import Data.Constraint
import Unsafe.Coerce
unsafeCoerceConstraint :: a :- b
unsafeCoerceConstraint = unsafeCoerce refl
unsafeDerive :: Coercible n o => (o -> n) -> t o :- t n
unsafeDerive _ = unsafeCoerceConstraint
unsafeUnderive :: Coercible n o => (o -> n) -> t n :- t o
unsafeUnderive _ = unsafeCoerceConstraint
unsafeApplicative :: forall m a. Monad m => (Applicative m => m a) -> m a
#if __GLASGOW_HASKELL__ < 710
unsafeApplicative m = m \\ trans (unsafeCoerceConstraint :: Applicative (WrappedMonad m) :- Applicative m) ins
#else
unsafeApplicative m = m
#endif
unsafeAlternative :: forall m a. MonadPlus m => (Alternative m => m a) -> m a
#if __GLASGOW_HASKELL__ < 710
unsafeAlternative m = m \\ trans (unsafeCoerceConstraint :: Alternative (WrappedMonad m) :- Alternative m) ins
#else
unsafeAlternative m = m
#endif