{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, UndecidableInstances #-}
module CHR.Data.Substitutable
(
VarUpdatable(..)
, VarExtractable(..)
, ExtrValVarKey
, VarTerm(..)
)
where
import qualified Data.Set as Set
import CHR.Data.VarMp
infixr 6 `varUpd`
infixr 6 `varUpdCyc`
type family ExtrValVarKey vv :: *
class VarUpdatable vv subst where
varUpd :: subst -> vv -> vv
varUpdCyc :: subst -> vv -> (vv, VarMp' (VarLookupKey subst) (VarLookupVal subst))
s `varUpdCyc` x = (s `varUpd` x, emptyVarMp)
{-# INLINE varUpdCyc #-}
instance {-# OVERLAPPABLE #-} VarUpdatable vv subst => VarUpdatable (Maybe vv) subst where
s `varUpd` m = fmap (s `varUpd`) m
s `varUpdCyc` (Just x) = let (x',cm) = s `varUpdCyc` x in (Just x', cm)
s `varUpdCyc` Nothing = (Nothing, emptyVarMp)
instance {-# OVERLAPPABLE #-} (Ord (VarLookupKey subst), VarUpdatable vv subst) => VarUpdatable [vv] subst where
s `varUpd` l = map (s `varUpd`) l
s `varUpdCyc` l = let (l',cms) = unzip $ map (s `varUpdCyc`) l in (l', varmpUnions cms)
class Ord (ExtrValVarKey vv) => VarExtractable vv where
varFree :: vv -> [ExtrValVarKey vv]
varFree = Set.toList . varFreeSet
varFreeSet :: vv -> Set.Set (ExtrValVarKey vv)
varFreeSet = Set.fromList . varFree
type instance ExtrValVarKey (Maybe vv) = ExtrValVarKey vv
instance {-# OVERLAPPABLE #-} (VarExtractable vv, Ord (ExtrValVarKey vv)) => VarExtractable (Maybe vv) where
varFreeSet = maybe Set.empty varFreeSet
type instance ExtrValVarKey [vv] = ExtrValVarKey vv
instance {-# OVERLAPPABLE #-} (VarExtractable vv, Ord (ExtrValVarKey vv)) => VarExtractable [vv] where
varFreeSet = Set.unions . map varFreeSet
class VarTerm vv where
varTermMbKey :: vv -> Maybe (ExtrValVarKey vv)
varTermMkKey :: ExtrValVarKey vv -> vv