{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Control.Super.Plugin.Wrapper
(
fromLeft, fromRight
,
TypeVarSubst
, mkTypeVarSubst
, splitKindFunTys
, mkEqualityCtType
, constraintSourceLocation
, UnitId
, baseUnitId
, moduleUnitId
, isImportedFrom
, mkTcCoercion
, produceTupleEvidence, isTupleTyCon
, lookupInstEnv
, uniqSetToList
) where
import Data.Either ( isLeft )
import Control.Monad ( mapM )
import qualified Type as T
import qualified TyCon as TC
import qualified Kind as K
import qualified Module as M
import qualified Coercion as C
import qualified Outputable as O
import qualified InstEnv as IE
import qualified Class
import qualified RdrName as RdrN
import qualified TcType as TcT
import qualified TcRnTypes as TcRnT
import qualified TcEvidence as TcEv
import qualified TcPluginM
import qualified SrcLoc
import qualified UniqSet
fromLeft :: Either a b -> a
fromLeft (Left a) = a
fromLeft (Right _) = error "fromLeft: Applied to 'Right'"
fromRight :: Either a b -> b
fromRight (Left _) = error "fromRight: Applied to 'Left'"
fromRight (Right b) = b
#if MIN_VERSION_GLASGOW_HASKELL(8,0,0,0)
type TypeVarSubst = T.TCvSubst
#elif MIN_VERSION_GLASGOW_HASKELL(7,10,1,0)
type TypeVarSubst = T.TvSubst
#endif
mkTypeVarSubst :: [(T.TyVar, T.Type)] -> TypeVarSubst
#if MIN_VERSION_GLASGOW_HASKELL(8,0,0,0)
mkTypeVarSubst = T.mkTvSubstPrs
#elif MIN_VERSION_GLASGOW_HASKELL(7,10,1,0)
mkTypeVarSubst = T.mkTopTvSubst
#endif
splitKindFunTys :: K.Kind -> ([K.Kind], K.Kind)
#if MIN_VERSION_GLASGOW_HASKELL(8,0,0,0)
splitKindFunTys = T.splitFunTys
#elif MIN_VERSION_GLASGOW_HASKELL(7,10,1,0)
splitKindFunTys = K.splitKindFunTys
#endif
mkEqualityCtType :: T.Type -> T.Type -> T.Type
#if MIN_VERSION_GLASGOW_HASKELL(8,0,0,0)
mkEqualityCtType = T.mkPrimEqPred
#elif MIN_VERSION_GLASGOW_HASKELL(7,10,1,0)
mkEqualityCtType = TcT.mkTcEqPred
#endif
constraintSourceLocation :: TcRnT.Ct -> SrcLoc.SrcSpan
#if MIN_VERSION_GLASGOW_HASKELL(7,10,2,0)
constraintSourceLocation = SrcLoc.RealSrcSpan . TcRnT.tcl_loc . TcRnT.ctl_env . TcRnT.ctev_loc . TcRnT.cc_ev
#else
constraintSourceLocation = TcRnT.tcl_loc . TcRnT.ctl_env . TcRnT.ctev_loc . TcRnT.cc_ev
#endif
#if MIN_VERSION_GLASGOW_HASKELL(8,0,0,0)
type UnitId = M.UnitId
#elif MIN_VERSION_GLASGOW_HASKELL(7,10,1,0)
type UnitId = M.PackageKey
#endif
baseUnitId :: UnitId
#if MIN_VERSION_GLASGOW_HASKELL(8,0,0,0)
baseUnitId = M.baseUnitId
#elif MIN_VERSION_GLASGOW_HASKELL(7,10,1,0)
baseUnitId = M.basePackageKey
#endif
moduleUnitId :: M.Module -> UnitId
#if MIN_VERSION_GLASGOW_HASKELL(8,0,0,0)
moduleUnitId = M.moduleUnitId
#elif MIN_VERSION_GLASGOW_HASKELL(7,10,1,0)
moduleUnitId = M.modulePackageKey
#endif
isImportedFrom :: RdrN.GlobalRdrElt -> M.Module -> Bool
#if MIN_VERSION_GLASGOW_HASKELL(8,0,0,0)
isImportedFrom rdrElt mdl = if not (RdrN.gre_lcl rdrElt)
then any (M.moduleName mdl ==) (RdrN.importSpecModule <$> RdrN.gre_imp rdrElt)
else False
#elif MIN_VERSION_GLASGOW_HASKELL(7,10,1,0)
isImportedFrom rdrElt mdl = case RdrN.gre_prov rdrElt of
RdrN.LocalDef -> False
RdrN.Imported [] -> False
RdrN.Imported impSpecs -> M.moduleName mdl == RdrN.importSpecModule (last impSpecs)
#endif
mkTcCoercion :: C.Coercion -> TcEv.TcCoercion
#if MIN_VERSION_GLASGOW_HASKELL(8,0,0,0)
mkTcCoercion = id
#elif MIN_VERSION_GLASGOW_HASKELL(7,10,1,0)
mkTcCoercion = TcEv.TcCoercion
#endif
produceTupleEvidence :: T.Type
-> TC.TyCon -> [T.Type]
-> (T.Type -> TcPluginM.TcPluginM (Either O.SDoc TcEv.EvTerm))
-> TcPluginM.TcPluginM (Either O.SDoc TcEv.EvTerm)
#if MIN_VERSION_GLASGOW_HASKELL(8,0,0,0)
produceTupleEvidence ct _tc _tcArgs _cont = return $ Left $
O.text "Production of tuple evidence not necessary anymore! How did we get here?"
O.$$ O.ppr ct
#elif MIN_VERSION_GLASGOW_HASKELL(7,10,1,0)
produceTupleEvidence ct _tc tcArgs cont = do
tupleEvs <- mapM cont tcArgs
return $ if any isLeft tupleEvs
then Left
$ O.text "Can't find evidence for this tuple constraint:"
O.$$ O.ppr ct
O.$$ O.text "Reason:"
O.$$ O.vcat (fromLeft <$> filter isLeft tupleEvs)
else Right $ TcEv.EvTupleMk $ fmap fromRight tupleEvs
#endif
isTupleTyCon :: TC.TyCon -> Bool
#if MIN_VERSION_GLASGOW_HASKELL(8,0,0,0)
isTupleTyCon _tc = False
#elif MIN_VERSION_GLASGOW_HASKELL(7,10,1,0)
isTupleTyCon = TC.isTupleTyCon
#endif
lookupInstEnv :: IE.InstEnvs -> Class.Class -> [T.Type] -> IE.ClsInstLookupResult
#if MIN_VERSION_GLASGOW_HASKELL(8,0,0,0)
lookupInstEnv instEnv cls tys = IE.lookupInstEnv False instEnv cls tys
#elif MIN_VERSION_GLASGOW_HASKELL(7,10,1,0)
lookupInstEnv instEnv cls tys = IE.lookupInstEnv instEnv cls tys
#endif
uniqSetToList :: UniqSet.UniqSet a -> [a]
#if MIN_VERSION_GLASGOW_HASKELL(8,2,0,0)
uniqSetToList = UniqSet.nonDetEltsUniqSet
#elif MIN_VERSION_GLASGOW_HASKELL(7,10,0,0)
uniqSetToList = UniqSet.uniqSetToList
#endif