Skip to content

Commit

Permalink
Don't auto-complete commands that require God capability outside crea…
Browse files Browse the repository at this point in the history
…tive mode (#1619)

fixes #1572
Fixed auto-completion for non-creative mode
  • Loading branch information
p3rsik authored Nov 13, 2023
1 parent 3592b4e commit aca8049
Showing 1 changed file with 14 additions and 5 deletions.
19 changes: 14 additions & 5 deletions src/Swarm/TUI/Controller.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}

-- |
-- SPDX-License-Identifier: BSD-3-Clause
Expand Down Expand Up @@ -81,7 +82,7 @@ import Swarm.Game.Scenario.Topography.Structure.Recognition.Type (definitions)
import Swarm.Game.ScenarioInfo
import Swarm.Game.State
import Swarm.Game.Step (finishGameTick, gameTick)
import Swarm.Language.Capability (Capability (CDebug, CMake))
import Swarm.Language.Capability (Capability (CDebug, CGod, CMake), constCaps)
import Swarm.Language.Context
import Swarm.Language.Key (KeyCombo, mkKeyCombo)
import Swarm.Language.Module
Expand Down Expand Up @@ -1179,7 +1180,7 @@ handleREPLEventTyping = \case
CharKey '\t' -> do
s <- get
let names = s ^.. gameState . baseRobot . robotContext . defTypes . to assocs . traverse . _1
uiState . uiREPL %= tabComplete names (s ^. gameState . landscape . entityMap)
uiState . uiREPL %= tabComplete (CompletionContext (s ^. gameState . creativeMode)) names (s ^. gameState . landscape . entityMap)
modify validateREPLForm
EscapeKey -> do
formSt <- use $ uiState . uiREPL . replPromptType
Expand All @@ -1205,11 +1206,14 @@ data CompletionType
| EntityName
deriving (Eq)

newtype CompletionContext = CompletionContext {ctxCreativeMode :: Bool}
deriving (Eq)

-- | Try to complete the last word in a partially-entered REPL prompt using
-- reserved words and names in scope (in the case of function names) or
-- entity names (in the case of string literals).
tabComplete :: [Var] -> EntityMap -> REPLState -> REPLState
tabComplete names em theRepl = case theRepl ^. replPromptType of
tabComplete :: CompletionContext -> [Var] -> EntityMap -> REPLState -> REPLState
tabComplete CompletionContext {..} names em theRepl = case theRepl ^. replPromptType of
SearchPrompt _ -> theRepl
CmdPrompt mms
-- Case 1: If completion candidates have already been
Expand Down Expand Up @@ -1254,7 +1258,12 @@ tabComplete names em theRepl = case theRepl ^. replPromptType of
EntityName -> (entityNames, (/= '"'))
FunctionName -> (possibleWords, isIdentChar)

possibleWords = reservedWords ++ names
creativeWords = map (syntax . constInfo) $ filter (\w -> constCaps w == Just CGod) allConst

possibleWords =
names <> case ctxCreativeMode of
True -> reservedWords
False -> filter (`notElem` creativeWords) reservedWords

entityNames = M.keys $ entitiesByName em

Expand Down

0 comments on commit aca8049

Please sign in to comment.