{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE Unsafe #-}
#if __GLASGOW_HASKELL__ >= 800
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
#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 :: a :- b
unsafeCoerceConstraint = (Any :- Any) -> a :- b
forall a b. a -> b
unsafeCoerce Any :- Any
forall (a :: Constraint). a :- a
refl
unsafeDerive :: Coercible n o => (o -> n) -> t o :- t n
unsafeDerive :: (o -> n) -> t o :- t n
unsafeDerive o -> n
_ = t o :- t n
forall (a :: Constraint) (b :: Constraint). a :- b
unsafeCoerceConstraint
unsafeUnderive :: Coercible n o => (o -> n) -> t n :- t o
unsafeUnderive :: (o -> n) -> t n :- t o
unsafeUnderive o -> n
_ = t n :- t o
forall (a :: Constraint) (b :: Constraint). a :- b
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 :: (Applicative m => m a) -> m a
unsafeApplicative Applicative m => m a
m = m a
Applicative m => m a
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 :: (Alternative m => m a) -> m a
unsafeAlternative Alternative m => m a
m = m a
Alternative m => m a
m
#endif