{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Generics.Simplistic.Unify
(
Subst , substEmpty , substInsert , substLkup , substApply
, UnifyErr(..) , unify , unify_ , unifyWith , minimize
) where
import Data.List (sort)
import qualified Data.Map as M
import Control.Monad.Except
import Control.Monad.State
import Control.Monad.Writer hiding (All)
import Control.Monad.Cont
import Unsafe.Coerce
import Generics.Simplistic.Deep
import Generics.Simplistic.Util
data UnifyErr kappa fam phi :: * where
OccursCheck :: [Exists phi]
-> UnifyErr kappa fam phi
SymbolClash :: Holes kappa fam phi at
-> Holes kappa fam phi at
-> UnifyErr kappa fam phi
type Subst kappa fam phi
= M.Map (Exists phi) (Exists (Holes kappa fam phi))
substEmpty :: Subst kappa fam phi
substEmpty = M.empty
substLkup :: (Ord (Exists phi))
=> Subst kappa fam phi
-> phi at
-> Maybe (Holes kappa fam phi at)
substLkup sigma var =
case M.lookup (Exists var) sigma of
Nothing -> Nothing
Just (Exists t) -> Just $ unsafeCoerce t
substApply :: (Ord (Exists phi))
=> Subst kappa fam phi
-> Holes kappa fam phi at
-> Holes kappa fam phi at
substApply sigma = holesJoin
. holesMap (\v -> maybe (Hole v) id $ substLkup sigma v)
substInsert :: (Ord (Exists phi))
=> Subst kappa fam phi
-> phi at
-> Holes kappa fam phi at
-> Subst kappa fam phi
substInsert sigma v x = M.insert (Exists v) (Exists x) sigma
type UnifyM kappa fam phi
= StateT (Subst kappa fam phi) (Except (UnifyErr kappa fam phi))
unify_ :: (All Eq kappa , Ord (Exists phi) , EqHO phi)
=> Holes kappa fam phi at
-> Holes kappa fam phi at
-> Maybe (Subst kappa fam phi)
unify_ a = either (const Nothing) Just
. runExcept . unify a
unify :: (All Eq kappa , Ord (Exists phi) , EqHO phi)
=> Holes kappa fam phi at
-> Holes kappa fam phi at
-> Except (UnifyErr kappa fam phi)
(Subst kappa fam phi)
unify = unifyWith substEmpty
unifyWith :: (All Eq kappa , Ord (Exists phi) , EqHO phi)
=> Subst kappa fam phi
-> Holes kappa fam phi at
-> Holes kappa fam phi at
-> Except (UnifyErr kappa fam phi)
(Subst kappa fam phi)
unifyWith sigma x y = execStateT (unifyM x y) sigma
unifyM :: forall kappa fam phi at
. (All Eq kappa , EqHO phi , Ord (Exists phi))
=> Holes kappa fam phi at
-> Holes kappa fam phi at
-> UnifyM kappa fam phi ()
unifyM x y = do
_ <- getEquivs x y
s <- get
case minimize s of
Left vs -> throwError (OccursCheck vs)
Right s' -> put s'
where
getEquivs :: Holes kappa fam phi b
-> Holes kappa fam phi b
-> UnifyM kappa fam phi ()
getEquivs p q = void $ holesMapM (uncurry' getEq) (lgg p q)
getEq :: Holes kappa fam phi b
-> Holes kappa fam phi b
-> UnifyM kappa fam phi (Holes kappa fam phi b)
getEq p (Hole var) = record_eq var p >> return p
getEq p@(Hole var) q = record_eq var q >> return p
getEq p q | eqHO p q = return p
| otherwise = throwError (SymbolClash p q)
record_eq :: phi b -> Holes kappa fam phi b -> UnifyM kappa fam phi ()
record_eq var q = do
sigma <- get
case substLkup sigma var of
Nothing -> when (not $ eqHO q (Hole var))
$ modify (\s -> substInsert s var q)
Just q' -> unless (eqHO q' q)
$ void $ getEquivs q q'
minimize :: forall kappa fam phi . (Ord (Exists phi))
=> Subst kappa fam phi
-> Either [Exists phi] (Subst kappa fam phi)
minimize sigma =
let sigma' = breakCycles inj proj $ removeIds proj sigma
in whileM sigma' [] $ \s _
-> M.fromList <$> (mapM (secondF (exMapM (go sigma'))) (M.toList s))
where
inj :: Exists phi -> Exists (Holes kappa fam phi)
inj = exMap Hole
proj :: Exists (Holes kappa fam phi) -> Maybe (Exists phi)
proj (Exists (Hole phi)) = Just $ Exists phi
proj _ = Nothing
secondF :: (Functor m) => (a -> m b) -> (x , a) -> m (x , b)
secondF f (x , a) = (x,) <$> f a
go :: Subst kappa fam phi
-> Holes kappa fam phi at
-> Writer [Exists phi] (Holes kappa fam phi at)
go ss = holesRefineHolesM $ \var -> do
case substLkup ss var of
Nothing -> return (Hole var)
Just r -> tell [Exists var]
>> return r
mnub :: (Ord a) => [a] -> [a]
mnub [] = []
mnub [x] = [x]
mnub (x:y:ys)
| x == y = mnub (y:ys)
| otherwise = x : mnub (y:ys)
whileM :: (Ord (Exists phi))
=> a -> [Exists phi] -> (a -> [Exists phi] -> Writer [Exists phi] a)
-> Either [Exists phi] a
whileM a xs f = do
let (x' , xs') = runWriter (f a xs)
if null xs'
then return x'
else if (mnub (sort xs') == mnub (sort xs))
then Left xs'
else whileM x' xs' f
removeIds :: forall a b
. (Ord a) => (b -> Maybe a) -> M.Map a b -> M.Map a b
removeIds proj = M.filterWithKey (\a b -> not $ Just a == proj b)
breakCycles :: forall a b
. (Ord a) => (a -> b) -> (b -> Maybe a) -> M.Map a b -> M.Map a b
breakCycles inj proj m0
= let (flattenedCycles , m') = runState (dropCycles m0) M.empty
in M.union flattenedCycles m'
where
dropCycles :: M.Map a b -> State (M.Map a b) (M.Map a b)
dropCycles m = case findCycle m of
Nothing -> return m
Just (a , cyc) -> do
modify (M.union cyc)
dropCycles (M.delete a (m M.\\ cyc))
cycleFor :: a -> M.Map a b -> Maybe (M.Map a b)
cycleFor a0 m = M.lookup a0 m >>= proj >>= go M.empty
where
go :: M.Map a b -> a -> Maybe (M.Map a b)
go aux a'
| a' == a0 || a' `M.member` aux = return aux
| otherwise = M.lookup a' m >>= proj >>= go (M.insert a' (inj a0) aux)
findCycle :: M.Map a b -> Maybe (a , M.Map a b)
findCycle m = (`runCont` id) $ callCC $
\exit -> (>> return Nothing) . flip mapM_ (M.keys m) $
\a -> case cycleFor a m of
Nothing -> return ()
Just r -> exit $ Just (a , r)