Skip to content

Commit

Permalink
Migrate ScopeState to record dot syntax
Browse files Browse the repository at this point in the history
  • Loading branch information
fwcd committed Aug 6, 2024
1 parent 3976f54 commit c130887
Showing 1 changed file with 13 additions and 13 deletions.
26 changes: 13 additions & 13 deletions src/Curry/LanguageServer/Utils/Lookup.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, ViewPatterns #-}
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, NoFieldSelectors, OverloadedRecordDot, ViewPatterns #-}
-- | Position lookup in the AST.
module Curry.LanguageServer.Utils.Lookup
( findQualIdentAtPos
Expand Down Expand Up @@ -50,10 +50,10 @@ findTypeAtPos ast pos = elementAt pos $ typedSpanInfos ast

-- | Finds all accessible identifiers at the given position, using the innermost shadowed one.
findScopeAtPos :: CS.Module a -> J.Position -> Scope a
findScopeAtPos ast pos = sstMatchingEnv $ execState (collectScope ast) $ ScopeState
{ sstCurrentEnv = [M.empty]
, sstMatchingEnv = M.empty
, sstPosition = pos
findScopeAtPos ast pos = (.matchingEnv) $ execState (collectScope ast) $ ScopeState
{ currentEnv = [M.empty]
, matchingEnv = M.empty
, position = pos
}

withSpanInfo :: CSPI.HasSpanInfo a => a -> (a, CSPI.SpanInfo)
Expand All @@ -73,31 +73,31 @@ flattenScopes = foldr M.union M.empty

-- | Stores nested scopes and a cursor position. The head of the list is always the innermost collectScope.
data ScopeState a = ScopeState
{ sstCurrentEnv :: [Scope a]
, sstMatchingEnv :: Scope a
, sstPosition :: J.Position
{ currentEnv :: [Scope a]
, matchingEnv :: Scope a
, position :: J.Position
}

type ScopeM a = State (ScopeState a)

beginScope :: ScopeM a ()
beginScope = modify $ \s -> s { sstCurrentEnv = M.empty : sstCurrentEnv s }
beginScope = modify $ \s -> s { currentEnv = M.empty : s.currentEnv }

endScope :: ScopeM a ()
endScope = modify $ \s -> s { sstCurrentEnv = let e = tail $ sstCurrentEnv s in if null e then error "Cannot end top-level scope!" else e }
endScope = modify $ \s -> s { currentEnv = let e = tail s.currentEnv in if null e then error "Cannot end top-level scope!" else e }

withScope :: ScopeM a () -> ScopeM a ()
withScope x = beginScope >> x >> endScope

bind :: CI.Ident -> Maybe a -> ScopeM a ()
bind i t = do
modify $ \s -> s { sstCurrentEnv = bindInScopes i t $ sstCurrentEnv s }
modify $ \s -> s { currentEnv = bindInScopes i t s.currentEnv }

updateEnvs :: CSPI.HasSpanInfo e => e -> ScopeM a ()
updateEnvs (CSPI.getSpanInfo -> spi) = do
pos <- gets sstPosition
pos <- gets (.position)
when (spi `containsPos` pos) $
modify $ \s -> s { sstMatchingEnv = M.union (flattenScopes $ sstCurrentEnv s) $ sstMatchingEnv s }
modify $ \s -> s { matchingEnv = M.union (flattenScopes s.currentEnv) s.matchingEnv }

class CollectScope e a where
collectScope :: e -> ScopeM a ()
Expand Down

0 comments on commit c130887

Please sign in to comment.