@@ -26,8 +26,11 @@ module Ide.Plugin.Tactic.Judgements
2626 , mkFirstJudgement
2727 , hypothesisFromBindings
2828 , isTopLevel
29+ , hyNamesInScope
30+ , hyByName
2931 ) where
3032
33+ import Control.Arrow
3134import Control.Lens hiding (Context )
3235import Data.Bool
3336import Data.Char
@@ -48,20 +51,20 @@ import Type
4851
4952------------------------------------------------------------------------------
5053-- | Given a 'SrcSpan' and a 'Bindings', create a hypothesis.
51- hypothesisFromBindings :: RealSrcSpan -> Bindings -> Map OccName ( HyInfo CType )
54+ hypothesisFromBindings :: RealSrcSpan -> Bindings -> Hypothesis CType
5255hypothesisFromBindings span bs = buildHypothesis $ getLocalScope bs span
5356
5457
5558------------------------------------------------------------------------------
5659-- | Convert a @Set Id@ into a hypothesis.
57- buildHypothesis :: [(Name , Maybe Type )] -> Map OccName ( HyInfo CType )
60+ buildHypothesis :: [(Name , Maybe Type )] -> Hypothesis CType
5861buildHypothesis
59- = M. fromList
62+ = Hypothesis
6063 . mapMaybe go
6164 where
6265 go (occName -> occ, t)
6366 | Just ty <- t
64- , isAlpha . head . occNameString $ occ = Just (occ, HyInfo UserPrv $ CType ty)
67+ , isAlpha . head . occNameString $ occ = Just $ HyInfo occ UserPrv $ CType ty
6568 | otherwise = Nothing
6669
6770
@@ -96,8 +99,8 @@ introducing
9699 -> Judgement' a
97100 -> Judgement' a
98101introducing f ns =
99- field @ " _jHypothesis" <>~ M. fromList ( zip [0 .. ] ns <&>
100- \ (pos, (name, ty)) -> (name, HyInfo (f pos) ty) )
102+ field @ " _jHypothesis" <>~ ( Hypothesis $ zip [0 .. ] ns <&>
103+ \ (pos, (name, ty)) -> HyInfo name (f pos) ty)
101104
102105
103106------------------------------------------------------------------------------
@@ -149,7 +152,7 @@ filterAncestry
149152 -> Judgement
150153 -> Judgement
151154filterAncestry ancestry reason jdg =
152- disallowing reason (M. keys $ M. filterWithKey go $ jHypothesis jdg) jdg
155+ disallowing reason (M. keys $ M. filterWithKey go $ hyByName $ jHypothesis jdg) jdg
153156 where
154157 go name _
155158 = not
@@ -172,7 +175,7 @@ findPositionVal :: Judgement' a -> OccName -> Int -> Maybe OccName
172175findPositionVal jdg defn pos = listToMaybe $ do
173176 -- It's important to inspect the entire hypothesis here, as we need to trace
174177 -- ancstry through potentially disallowed terms in the hypothesis.
175- (name, hi) <- M. toList $ M. map (overProvenance expandDisallowed) $ jEntireHypothesis jdg
178+ (name, hi) <- M. toList $ M. map (overProvenance expandDisallowed) $ hyByName $ jEntireHypothesis jdg
176179 case hi_provenance hi of
177180 TopLevelArgPrv defn' pos'
178181 | defn == defn'
@@ -188,7 +191,7 @@ findPositionVal jdg defn pos = listToMaybe $ do
188191-- 'filterSameTypeFromOtherPositions'.
189192findDconPositionVals :: Judgement' a -> DataCon -> Int -> [OccName ]
190193findDconPositionVals jdg dcon pos = do
191- (name, hi) <- M. toList $ jHypothesis jdg
194+ (name, hi) <- M. toList $ hyByName $ jHypothesis jdg
192195 case hi_provenance hi of
193196 PatternMatchPrv pv
194197 | pv_datacon pv == Uniquely dcon
@@ -203,14 +206,15 @@ findDconPositionVals jdg dcon pos = do
203206-- other term which might match.
204207filterSameTypeFromOtherPositions :: DataCon -> Int -> Judgement -> Judgement
205208filterSameTypeFromOtherPositions dcon pos jdg =
206- let hy = jHypothesis
209+ let hy = hyByName
210+ . jHypothesis
207211 $ filterAncestry
208212 (findDconPositionVals jdg dcon pos)
209213 (WrongBranch pos)
210214 jdg
211215 tys = S. fromList $ hi_type <$> M. elems hy
212216 to_remove =
213- M. filter (flip S. member tys . hi_type) (jHypothesis jdg)
217+ M. filter (flip S. member tys . hi_type) (hyByName $ jHypothesis jdg)
214218 M. \\ hy
215219 in disallowing Shadowed (M. keys to_remove) jdg
216220
@@ -267,8 +271,8 @@ introducingPat scrutinee dc ns jdg
267271-- them from 'jHypothesis', but not from 'jEntireHypothesis'.
268272disallowing :: DisallowReason -> [OccName ] -> Judgement' a -> Judgement' a
269273disallowing reason (S. fromList -> ns) =
270- field @ " _jHypothesis" %~ (M. mapWithKey $ \ name hi ->
271- case S. member name ns of
274+ field @ " _jHypothesis" %~ (\ z -> Hypothesis . flip fmap (unHypothesis z) $ \ hi ->
275+ case S. member (hi_name hi) ns of
272276 True -> overProvenance (DisallowedPrv reason) hi
273277 False -> hi
274278 )
@@ -277,20 +281,28 @@ disallowing reason (S.fromList -> ns) =
277281------------------------------------------------------------------------------
278282-- | The hypothesis, consisting of local terms and the ambient environment
279283-- (impors and class methods.) Hides disallowed values.
280- jHypothesis :: Judgement' a -> Map OccName (HyInfo a )
281- jHypothesis = M. filter (not . isDisallowed . hi_provenance) . jEntireHypothesis
284+ jHypothesis :: Judgement' a -> Hypothesis a
285+ jHypothesis
286+ = Hypothesis
287+ . filter (not . isDisallowed . hi_provenance)
288+ . unHypothesis
289+ . jEntireHypothesis
282290
283291
284292------------------------------------------------------------------------------
285293-- | The whole hypothesis, including things disallowed.
286- jEntireHypothesis :: Judgement' a -> Map OccName ( HyInfo a )
294+ jEntireHypothesis :: Judgement' a -> Hypothesis a
287295jEntireHypothesis = _jHypothesis
288296
289297
290298------------------------------------------------------------------------------
291299-- | Just the local hypothesis.
292- jLocalHypothesis :: Judgement' a -> Map OccName (HyInfo a )
293- jLocalHypothesis = M. filter (isLocalHypothesis . hi_provenance) . jHypothesis
300+ jLocalHypothesis :: Judgement' a -> Hypothesis a
301+ jLocalHypothesis
302+ = Hypothesis
303+ . filter (isLocalHypothesis . hi_provenance)
304+ . unHypothesis
305+ . jHypothesis
294306
295307
296308------------------------------------------------------------------------------
@@ -304,10 +316,30 @@ unsetIsTopHole :: Judgement' a -> Judgement' a
304316unsetIsTopHole = field @ " _jIsTopHole" .~ False
305317
306318
319+ ------------------------------------------------------------------------------
320+ -- | What names are currently in scope in the hypothesis?
321+ hyNamesInScope :: Hypothesis a -> Set OccName
322+ hyNamesInScope = M. keysSet . hyByName
323+
324+
325+ ------------------------------------------------------------------------------
326+ -- | Fold a hypothesis into a single mapping from name to info. This
327+ -- unavoidably will cause duplicate names (things like methods) to shadow one
328+ -- another.
329+ hyByName :: Hypothesis a -> Map OccName (HyInfo a )
330+ hyByName
331+ = M. fromList
332+ . fmap (hi_name &&& id )
333+ . unHypothesis
334+
335+
307336------------------------------------------------------------------------------
308337-- | Only the hypothesis members which are pattern vals
309338jPatHypothesis :: Judgement' a -> Map OccName PatVal
310- jPatHypothesis = M. mapMaybe (getPatVal . hi_provenance) . jHypothesis
339+ jPatHypothesis
340+ = M. mapMaybe (getPatVal . hi_provenance)
341+ . hyByName
342+ . jHypothesis
311343
312344
313345getPatVal :: Provenance -> Maybe PatVal
@@ -326,7 +358,7 @@ substJdg subst = fmap $ coerce . substTy subst . coerce
326358
327359
328360mkFirstJudgement
329- :: M. Map OccName ( HyInfo CType )
361+ :: Hypothesis CType
330362 -> Bool -- ^ are we in the top level rhs hole?
331363 -> Type
332364 -> Judgement' CType
0 commit comments