@@ -19,15 +19,15 @@ import Control.Monad (unless)
1919import Control.Monad.Module
2020import qualified Data.Core as Core
2121import Data.File
22- import Data.Foldable (foldl' , for_ )
22+ import Data.Foldable (for_ )
2323import Data.Function (fix )
2424import Data.Functor (($>) )
2525import qualified Data.IntMap as IntMap
2626import qualified Data.IntSet as IntSet
2727import Data.List.NonEmpty (nonEmpty )
2828import Data.Loc
2929import qualified Data.Map as Map
30- import Data.Maybe (fromJust )
30+ import Data.Maybe (fromJust , fromMaybe )
3131import Data.Name as Name
3232import Data.Scope
3333import qualified Data.Set as Set
@@ -104,7 +104,7 @@ runFile file = traverse run file
104104 where run
105105 = (\ m -> do
106106 (subst, t) <- m
107- modify @ (Heap Name (Term Monotype Meta )) (substAll subst)
107+ modify @ (Heap Name (Term Monotype Meta )) (fmap ( Set. map ( substAll subst)) )
108108 pure (substAll subst <$> t))
109109 . runState (mempty :: Substitution )
110110 . runReader (fileLoc file)
@@ -182,36 +182,15 @@ solve cs = for_ cs solve
182182 case sol of
183183 Just (_ := t1) -> solve (t1 :===: t2)
184184 Nothing | m1 `IntSet.member` mvs t2 -> fail (" Occurs check failure: " <> show m1 <> " :===: " <> show t2)
185- | otherwise -> modify (IntMap. insert m1 t2 . subst (m1 := t2 ))
185+ | otherwise -> modify (IntMap. insert m1 t2 . fmap (substAll ( IntMap. singleton m1 t2) ))
186186 t1 :===: Var m2 -> solve (Var m2 :===: t1)
187187 t1 :===: t2 -> unless (t1 == t2) $ fail (" Type mismatch:\n expected: " <> show t1 <> " \n actual: " <> show t2)
188188
189189 solution m = fmap (m := ) <$> gets (IntMap. lookup m)
190190
191- substAll :: Substitutable t => Substitution -> t -> t
192- substAll s a = foldl' (flip subst) a (map (uncurry (:=) ) (IntMap. toList s))
193-
194191
195192mvs :: Foldable t => t Meta -> IntSet. IntSet
196193mvs = foldMap IntSet. singleton
197194
198- class Substitutable t where
199- subst :: Solution -> t -> t
200-
201- instance Substitutable (Term Monotype Meta ) where
202- subst (i' := t') t = t >>= \ i -> if i == i' then t' else Var i
203-
204- instance Substitutable Constraint where
205- subst s (t1 :===: t2) = subst s t1 :===: subst s t2
206-
207- instance Substitutable Solution where
208- subst s (m := t) = m := subst s t
209-
210- instance Substitutable a => Substitutable (IntMap. IntMap a ) where
211- subst s = IntMap. map (subst s)
212-
213- instance (Ord a , Substitutable a ) => Substitutable (Set. Set a ) where
214- subst s = Set. map (subst s)
215-
216- instance Substitutable v => Substitutable (Map. Map k v ) where
217- subst s = fmap (subst s)
195+ substAll :: Monad t => IntMap. IntMap (t Meta ) -> t Meta -> t Meta
196+ substAll s a = a >>= \ i -> fromMaybe (pure i) (IntMap. lookup i s)
0 commit comments