module Data.Comp.Multi.Strategy.Classification
(
DynCase(..)
, KDynCase(..)
, dynProj
, caseE
) where
import Data.Comp.Multi ( (:+:), E, K, runE, caseH, (:&:), remA, Cxt(..) )
import Data.Type.Equality ( (:~:)(..), gcastWith )
class DynCase f a where
dyncase :: f b -> Maybe (b :~: a)
class KDynCase f a where
kdyncase :: forall (e :: * -> *) b. DynCase e a => f e b -> Maybe (b :~: a)
instance KDynCase f a where
kdyncase = const Nothing
instance (KDynCase f l, KDynCase g l) => KDynCase (f :+: g) l where
kdyncase = caseH kdyncase kdyncase
instance DynCase (K a) b where
dyncase _ = Nothing
instance (KDynCase f l, DynCase a l) => DynCase (Cxt h f a) l where
dyncase (Term x) = kdyncase x
dyncase (Hole x) = dyncase x
instance (KDynCase f l) => KDynCase (f :&: a) l where
kdyncase = kdyncase . remA
dynProj :: forall f l l'. (DynCase f l) => f l' -> Maybe (f l)
dynProj x = case (dyncase x :: Maybe (l' :~: l)) of
Just p -> Just (gcastWith p x)
Nothing -> Nothing
caseE :: (DynCase f a) => E f -> Maybe (f a)
caseE = runE dynProj