{-# LANGUAGE CPP #-}
module Control.Super.Plugin.Constraint
(
GivenCt, WantedCt, DerivedCt
, mkDerivedTypeEqCt
, mkDerivedTypeEqCtOfTypes
, mkDerivedClassCt
, isClassConstraint
, isAnyClassConstraint
, constraintClassType
, constraintClassTyArgs
, constraintClassTyCon
, constraintPredicateType
, constraintTopTyCons
, constraintTopTcVars
, constraintLocation
, constraintSourceLocation
, sortConstraintsByLine
, constraintTyVars
) where
import Data.List ( sortBy )
import qualified Data.Set as Set
import TcRnTypes
( Ct(..), CtLoc(..), CtEvidence(..)
, mkNonCanonical )
import Class ( Class(..) )
import Type
( Type, TyVar
, mkTyVarTy, mkAppTys, mkTyConTy
, getClassPredTys_maybe
)
import TyCon ( TyCon )
import Control.Super.Plugin.Collection.Set ( Set )
import qualified Control.Super.Plugin.Collection.Set as S
import Control.Super.Plugin.Wrapper
( mkEqualityCtType, constraintSourceLocation )
import Control.Super.Plugin.Utils
( collectTopTyCons
, collectTopTcVars
, collectTyVars )
type GivenCt = Ct
type DerivedCt = Ct
type WantedCt = Ct
mkDerivedTypeEqCtOfTypes :: Ct -> Type -> Type -> Ct
mkDerivedTypeEqCtOfTypes ct ta tb = mkNonCanonical CtDerived
{ ctev_pred = mkEqualityCtType ta tb
, ctev_loc = constraintLocation ct }
mkDerivedTypeEqCt :: Ct -> TyVar -> Type -> Ct
mkDerivedTypeEqCt ct tv = mkDerivedTypeEqCtOfTypes ct (mkTyVarTy tv)
mkDerivedClassCt :: CtLoc -> Class -> [Type] -> Ct
mkDerivedClassCt loc cls ts = mkNonCanonical CtDerived
{ ctev_pred = mkAppTys (mkTyConTy $ classTyCon cls) ts
, ctev_loc = loc }
isClassConstraint :: Class -> Ct -> Bool
isClassConstraint wantedClass ct =
case constraintClassType ct of
Just (cls, _args) -> cls == wantedClass
_ -> False
isAnyClassConstraint :: [Class] -> Ct -> Bool
isAnyClassConstraint clss ct = or $ fmap (($ ct) . isClassConstraint) clss
constraintClassType :: Ct -> Maybe (Class, [Type])
constraintClassType ct = case ct of
CDictCan {} -> Just (cc_class ct, cc_tyargs ct)
CNonCanonical evdnc -> getClassPredTys_maybe $ ctev_pred evdnc
_ -> Nothing
constraintClassTyArgs :: Ct -> Maybe [Type]
constraintClassTyArgs = fmap snd . constraintClassType
constraintClassTyCon :: Ct -> Maybe TyCon
constraintClassTyCon = fmap (classTyCon . fst) . constraintClassType
constraintTopTyCons :: Ct -> Set TyCon
constraintTopTyCons ct = maybe S.empty collectTopTyCons $ constraintClassTyArgs ct
constraintTopTcVars :: Ct -> Set.Set TyVar
constraintTopTcVars ct = maybe Set.empty collectTopTcVars $ constraintClassTyArgs ct
constraintLocation :: Ct -> CtLoc
constraintLocation ct = ctev_loc $ cc_ev ct
constraintPredicateType :: Ct -> Type
constraintPredicateType ct = ctev_pred $ cc_ev ct
constraintTyVars :: Ct -> Set.Set TyVar
constraintTyVars = collectTyVars . ctev_pred . cc_ev
sortConstraintsByLine :: [Ct] -> [Ct]
sortConstraintsByLine = sortBy cmpLine
where
cmpLine :: Ct -> Ct -> Ordering
cmpLine ct1 ct2 = compare (constraintSourceLocation ct1) (constraintSourceLocation ct2)