Skip to content

Commit

Permalink
Use Set for reservedWords instead of list
Browse files Browse the repository at this point in the history
  • Loading branch information
byorgey committed May 21, 2024
1 parent 271c19c commit eab417d
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 12 deletions.
17 changes: 10 additions & 7 deletions src/swarm-lang/Swarm/Language/Parser/Lex.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,8 @@ import Control.Monad (void)
import Data.Char (isUpper)
import Data.Containers.ListUtils (nubOrd)
import Data.Sequence qualified as Seq
import Data.Set (Set)
import Data.Set qualified as S
import Data.Text (Text)
import Data.Text qualified as T
import Swarm.Language.Parser.Core
Expand Down Expand Up @@ -162,12 +164,13 @@ keywords :: [Text]
keywords = T.words "let in def end true false forall require requirements"

-- | List of reserved words that cannot be used as variable names.
reservedWords :: [Text]
reservedWords :: Set Text
reservedWords =
map (syntax . constInfo) (filter isUserFunc allConst)
++ map directionSyntax allDirs
++ primitiveTypeNames
++ keywords
S.fromList $
map (syntax . constInfo) (filter isUserFunc allConst)
++ map directionSyntax allDirs
++ primitiveTypeNames
++ keywords

-- | Parse a reserved word, given a string recognizer (which can
-- /e.g./ be case sensitive or not), making sure it is not a prefix
Expand All @@ -194,10 +197,10 @@ locIdentifier idTy = uncurry LV <$> parseLocG ((lexeme . try) (p >>= check) <?>
where
p = (:) <$> (letterChar <|> char '_') <*> many (alphaNumChar <|> char '_' <|> char '\'')
check (into @Text -> t)
| t `elem` reservedWords || T.toLower t `elem` reservedWords =
| t `S.member` reservedWords || T.toLower t `S.member` reservedWords =
failT ["Reserved word", squote t, "cannot be used as a variable name"]
| IDTyVar <- idTy
, T.toTitle t `elem` reservedWords =
, T.toTitle t `S.member` reservedWords =
failT ["Reserved type name", squote t, "cannot be used as a type variable name; perhaps you meant", squote (T.toTitle t) <> "?"]
| IDTyVar <- idTy
, isUpper (T.head t) =
Expand Down
11 changes: 6 additions & 5 deletions src/swarm-tui/Swarm/TUI/Controller.hs
Original file line number Diff line number Diff line change
Expand Up @@ -60,6 +60,7 @@ import Data.List.NonEmpty (NonEmpty (..))
import Data.List.NonEmpty qualified as NE
import Data.Map qualified as M
import Data.Maybe (fromMaybe, isJust, isNothing, mapMaybe)
import Data.Set qualified as S
import Data.String (fromString)
import Data.Text qualified as T
import Data.Text.IO qualified as T
Expand Down Expand Up @@ -347,9 +348,9 @@ handleMainEvent ev = do
then -- ignore repeated keypresses
continueWithoutRedraw
else -- hide for two seconds
do
uiState . uiGameplay . uiHideRobotsUntil .= t + TimeSpec 2 0
invalidateCacheEntry WorldCache
do
uiState . uiGameplay . uiHideRobotsUntil .= t + TimeSpec 2 0
invalidateCacheEntry WorldCache
-- debug focused robot
MetaChar 'd' | isPaused && hasDebug -> do
debug <- uiState . uiGameplay . uiShowDebug Lens.<%= not
Expand Down Expand Up @@ -1264,8 +1265,8 @@ tabComplete CompletionContext {..} names em theRepl = case theRepl ^. replPrompt

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

entityNames = M.keys $ entitiesByName em

Expand Down

0 comments on commit eab417d

Please sign in to comment.