Skip to content

Commit

Permalink
Rename nameMap -> userNames
Browse files Browse the repository at this point in the history
  • Loading branch information
croyzor committed Dec 3, 2024
1 parent ed36c04 commit 4e06428
Show file tree
Hide file tree
Showing 6 changed files with 17 additions and 17 deletions.
6 changes: 3 additions & 3 deletions brat/Brat/Checker/Monad.hs
Original file line number Diff line number Diff line change
Expand Up @@ -269,12 +269,12 @@ handler (Req s k) ctx g
M.lookup tycon tbl
handler (k args) ctx g

NameMeta end name -> let names = nameMap (store ctx) in
NameMeta end name -> let names = userNames (store ctx) in
case M.lookup end names of
Just oldName -> error $ "Trying to name end (" ++ show end ++ ")\nas " ++ show name ++ " but it's already called " ++ oldName
Nothing -> let st = store ctx in
handler (k ()) (ctx { store = st { nameMap = M.insert end name (nameMap st) } }) g
AskNames -> handler (k (nameMap (store ctx))) ctx g
handler (k ()) (ctx { store = st { userNames = M.insert end name (userNames st) } }) g
AskNames -> handler (k (userNames (store ctx))) ctx g

type Checking = Free CheckingSig

Expand Down
6 changes: 3 additions & 3 deletions brat/Brat/Checker/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -95,9 +95,9 @@ instance Show EndType where
show (EndType Braty (Right ty)) = show ty

data Store = Store
{ typeMap :: M.Map End EndType
, valueMap :: M.Map End (Val Z)
, nameMap :: M.Map End String
{ typeMap :: M.Map End EndType
, valueMap :: M.Map End (Val Z)
, userNames :: M.Map End String
}

instance Show Store where
Expand Down
8 changes: 4 additions & 4 deletions brat/Brat/Compiler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ import Brat.Elaborator
import Brat.Error
import Brat.Load
import Brat.Naming (root, split)
import Brat.Syntax.Common (NameMap)
import Brat.Syntax.Common (UserNameMap)
import Brat.Syntax.Value (ShowWithMetas(..))

import Control.Exception (evaluate)
Expand All @@ -30,7 +30,7 @@ printDeclsHoles libDirs file = do
print decls
putStrLn ""
putStrLn "Holes:"
mapM_ (putStrLn . showWithMetas (nameMap store)) holes
mapM_ (putStrLn . showWithMetas (userNames store)) holes

-- Print an 80 column banner as the header and footer of some IO action's output
banner :: String -> IO a -> IO a
Expand Down Expand Up @@ -66,7 +66,7 @@ writeDot libDirs file out = do
isMain _ = False
-}

data CompilingHoles = CompilingHoles NameMap [TypedHole]
data CompilingHoles = CompilingHoles UserNameMap [TypedHole]

instance Show CompilingHoles where
show (CompilingHoles nm hs) = unlines $
Expand All @@ -80,7 +80,7 @@ compileFile libDirs file = do
case holes of
[] -> Right <$> evaluate -- turns 'error' into IO 'die'
(compile defs newRoot outerGraph venv)
hs -> pure $ Left (CompilingHoles (nameMap defs) hs)
hs -> pure $ Left (CompilingHoles (userNames defs) hs)

compileAndPrintFile :: [FilePath] -> String -> IO ()
compileAndPrintFile libDirs file = compileFile libDirs file >>= \case
Expand Down
4 changes: 2 additions & 2 deletions brat/Brat/Syntax/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ module Brat.Syntax.Common (PortName,
pattern Star,
Precedence(..),
showSig,
NameMap
UserNameMap
) where

import Brat.FC
Expand Down Expand Up @@ -174,7 +174,7 @@ deriving instance Eq io => Eq (CType' io)
instance Semigroup (CType' (PortName, ty)) where
(ss :-> ts) <> (us :-> vs) = (ss <> us) :-> (ts <> vs)

type NameMap = M.Map End String
type UserNameMap = M.Map End String

data Import
= Import { importName :: WC QualName
Expand Down
4 changes: 2 additions & 2 deletions brat/lsp/Brat/LSP/Holes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,10 +2,10 @@ module Brat.LSP.Holes where

import Brat.Checker.Types (TypedHole(..), HoleData(..))
import Brat.FC (FC)
import Brat.Syntax.Common (NameMap)
import Brat.Syntax.Common (UserNameMap)
import Brat.Syntax.Value (ShowWithMetas(..))

holeInfo :: NameMap -> TypedHole -> (FC, String)
holeInfo :: UserNameMap -> TypedHole -> (FC, String)
holeInfo m h@(TypedHole _ HoleData { .. }) = (fc,
unlines (showWithMetas m h : maybe [] (delim:) suggestions)
)
Expand Down
6 changes: 3 additions & 3 deletions brat/lsp/Driver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ import Brat.LSP.Find
import Brat.LSP.Holes
import Brat.LSP.State
import qualified Brat.Naming as Name
import Brat.Syntax.Common (NameMap)
import Brat.Syntax.Common (UserNameMap)

main :: IO Int
main = do
Expand Down Expand Up @@ -81,7 +81,7 @@ convPos (Pos l c) = Position (fromIntegral (max 0 (l - 1))) (fromIntegral (max 0
allGood :: NormalizedUri -> LspM () ()
allGood fileUri = publishDiagnostics 0 fileUri Nothing (partitionBySource [])

logHoles :: NameMap -> [TypedHole] -> NormalizedUri -> LspM () ()
logHoles :: UserNameMap -> [TypedHole] -> NormalizedUri -> LspM () ()
logHoles nm hs fileUri = publishDiagnostics (length hs) fileUri Nothing (partitionBySource (logHole <$> hs))
where
logHole :: TypedHole -> Diagnostic
Expand Down Expand Up @@ -120,7 +120,7 @@ loadVFile state _ msg = do
old <- liftIO $ takeMVar state
liftIO $ putMVar state (updateState (snd <$> newDecls, holes) old)
allGood fileName
logHoles (nameMap store) holes fileName
logHoles (userNames store) holes fileName
Left (SrcErr _ err) -> allGood fileName *> sendError fileName err
Nothing -> do
liftIO $ debugM "loadVFile" $ "Couldn't find " ++ show fileName ++ " in VFS"
Expand Down

0 comments on commit 4e06428

Please sign in to comment.