@@ -14,7 +14,6 @@ import Control.Monad.State qualified as State
1414import Data.Foldable qualified as Foldable
1515import Data.List qualified as List
1616import Data.List.Extra (nubOrd )
17- import Data.List.NonEmpty (NonEmpty )
1817import Data.List.NonEmpty qualified as Nel
1918import Data.Map qualified as Map
2019import Data.Set qualified as Set
@@ -85,7 +84,7 @@ import Unison.Codebase.Editor.HandleInput.Reflogs qualified as Reflogs
8584import Unison.Codebase.Editor.HandleInput.ReleaseDraft (handleReleaseDraft )
8685import Unison.Codebase.Editor.HandleInput.Run (handleRun )
8786import Unison.Codebase.Editor.HandleInput.RuntimeUtils qualified as RuntimeUtils
88- import Unison.Codebase.Editor.HandleInput.ShowDefinition (showDefinitions )
87+ import Unison.Codebase.Editor.HandleInput.ShowDefinition (handleShowDefinition )
8988import Unison.Codebase.Editor.HandleInput.TermResolution (resolveMainRef )
9089import Unison.Codebase.Editor.HandleInput.Tests qualified as Tests
9190import Unison.Codebase.Editor.HandleInput.Todo (handleTodo )
@@ -616,7 +615,7 @@ loop e = do
616615 DisplayI outputLoc namesToDisplay -> do
617616 traverse_ (displayI outputLoc) namesToDisplay
618617 ShowDefinitionI outputLoc showDefinitionScope query -> handleShowDefinition outputLoc showDefinitionScope query
619- EditNamespaceI paths -> handleEditNamespace LatestFileLocation paths
618+ EditNamespaceI paths -> handleEditNamespace ( LatestFileLocation AboveFold ) paths
620619 FindShallowI pathArg -> handleLs pathArg
621620 FindI isVerbose fscope ws -> handleFindI isVerbose fscope ws input
622621 StructuredFindI _fscope ws -> handleStructuredFindI ws
@@ -763,25 +762,25 @@ loop e = do
763762 Nothing -> do
764763 Cli. respond DebugFuzzyOptionsNoResolver
765764 DebugFormatI -> do
766- Cli. Env {writeSource, loadSource} <- ask
765+ env <- ask
767766 void $ runMaybeT do
768767 (filePath, _) <- MaybeT Cli. getLatestFile
769768 pf <- lift Cli. getLatestParsedFile
770769 tf <- lift Cli. getLatestTypecheckedFile
771770 names <- lift Cli. currentNames
772771 let buildPPED uf tf =
773772 let names' = (fromMaybe mempty $ (UF. typecheckedToNames <$> tf) <|> (UF. toNames <$> uf)) `Names.shadowing` names
774- in pure (PPED. makePPED (PPE. hqNamer 10 names') (PPE. suffixifyByHashName names'))
773+ in pure (PPED. makePPED (PPE. hqNamer 10 names') (PPE. suffixifyByHashName names'))
775774 let formatWidth = 80
776775 currentPath <- lift $ Cli. getCurrentPath
777776 updates <- MaybeT $ Format. formatFile buildPPED formatWidth currentPath pf tf Nothing
778777 source <-
779- liftIO (loadSource (Text. pack filePath)) >>= \ case
778+ liftIO (env . loadSource (Text. pack filePath)) >>= \ case
780779 Cli. InvalidSourceNameError -> lift $ Cli. returnEarly $ Output. InvalidSourceName filePath
781780 Cli. LoadError -> lift $ Cli. returnEarly $ Output. SourceLoadFailed filePath
782781 Cli. LoadSuccess contents -> pure contents
783782 let updatedSource = Format. applyTextReplacements updates source
784- liftIO $ writeSource (Text. pack filePath) updatedSource
783+ liftIO $ env . writeSource (Text. pack filePath) updatedSource True
785784 DebugDumpNamespacesI -> do
786785 let seen h = State. gets (Set. member h)
787786 set h = State. modify (Set. insert h)
@@ -1264,50 +1263,6 @@ handleDependents hq = do
12641263 Cli. setNumberedArgs . map SA. HashQualified $ types <> terms
12651264 Cli. respond (ListDependents ppe lds types terms)
12661265
1267- -- | Handle a @ShowDefinitionI@ input command, i.e. `view` or `edit`.
1268- handleShowDefinition :: OutputLocation -> ShowDefinitionScope -> NonEmpty (HQ. HashQualified Name ) -> Cli ()
1269- handleShowDefinition outputLoc showDefinitionScope query = do
1270- Cli. Env {codebase} <- ask
1271- hqLength <- Cli. runTransaction Codebase. hashLength
1272- let hasAbsoluteQuery = any (any Name. isAbsolute) query
1273- (names, unbiasedPPED) <- case (hasAbsoluteQuery, showDefinitionScope) of
1274- -- TODO: We should instead print each definition using the names from its project-branch root.
1275- (True , _) -> do
1276- root <- Cli. getCurrentProjectRoot
1277- let root0 = Branch. head root
1278- let names = Names. makeAbsolute $ Branch. toNames root0
1279- let pped = PPED. makePPED (PPE. hqNamer 10 names) (suffixify names)
1280- pure (names, pped)
1281- (_, ShowDefinitionGlobal ) -> do
1282- -- TODO: Maybe rewrite to be properly global
1283- root <- Cli. getCurrentProjectRoot
1284- let root0 = Branch. head root
1285- let names = Names. makeAbsolute $ Branch. toNames root0
1286- let pped = PPED. makePPED (PPE. hqNamer 10 names) (suffixify names)
1287- pure (names, pped)
1288- (_, ShowDefinitionLocal ) -> do
1289- currentNames <- Cli. currentNames
1290- let pped = PPED. makePPED (PPE. hqNamer 10 currentNames) (suffixify currentNames)
1291- pure (currentNames, pped)
1292- let pped = PPED. biasTo (mapMaybe HQ. toName (toList query)) unbiasedPPED
1293- Backend. DefinitionResults terms types misses <- do
1294- let nameSearch = NameSearch. makeNameSearch hqLength names
1295- Cli. runTransaction (Backend. definitionsByName codebase nameSearch includeCycles Names. IncludeSuffixes (toList query))
1296- showDefinitions outputLoc pped terms types misses
1297- where
1298- suffixify =
1299- case outputLoc of
1300- ConsoleLocation -> PPE. suffixifyByHash
1301- FileLocation _ -> PPE. suffixifyByHashName
1302- LatestFileLocation -> PPE. suffixifyByHashName
1303-
1304- -- `view`: don't include cycles; `edit`: include cycles
1305- includeCycles =
1306- case outputLoc of
1307- ConsoleLocation -> Backend. DontIncludeCycles
1308- FileLocation _ -> Backend. IncludeCycles
1309- LatestFileLocation -> Backend. IncludeCycles
1310-
13111266-- todo: compare to `getHQTerms` / `getHQTypes`. Is one universally better?
13121267resolveHQToLabeledDependencies :: HQ. HashQualified Name -> Cli (Set LabeledDependency )
13131268resolveHQToLabeledDependencies = \ case
@@ -1355,17 +1310,17 @@ doDisplay outputLoc names tm = do
13551310 rendered <- DisplayValues. displayTerm pped loadTerm loadTypeOfTerm' evalTerm loadDecl tm
13561311 mayFP <- case outputLoc of
13571312 ConsoleLocation -> pure Nothing
1358- FileLocation path -> Just <$> Directory. canonicalizePath path
1359- LatestFileLocation -> traverse Directory. canonicalizePath $ fmap fst (loopState ^. # latestFile) <|> Just " scratch.u"
1313+ FileLocation path _ -> Just <$> Directory. canonicalizePath path
1314+ LatestFileLocation _ -> traverse Directory. canonicalizePath $ fmap fst (loopState ^. # latestFile) <|> Just " scratch.u"
13601315 whenJust mayFP \ fp -> do
13611316 liftIO $ prependFile fp (Text. pack . P. toPlain 80 $ rendered)
13621317 Cli. respond $ DisplayRendered mayFP rendered
13631318 where
13641319 suffixify =
13651320 case outputLoc of
13661321 ConsoleLocation -> PPE. suffixifyByHash
1367- FileLocation _ -> PPE. suffixifyByHashName
1368- LatestFileLocation -> PPE. suffixifyByHashName
1322+ FileLocation _ _ -> PPE. suffixifyByHashName
1323+ LatestFileLocation _ -> PPE. suffixifyByHashName
13691324
13701325 prependFile :: FilePath -> Text -> IO ()
13711326 prependFile filePath txt = do
@@ -1475,7 +1430,7 @@ doCompile profile native output main = do
14751430 outf
14761431 | native = output
14771432 | otherwise = output <> " .uc"
1478- copts = Runtime. defaultCompileOpts { Runtime. profile = profile }
1433+ copts = Runtime. defaultCompileOpts {Runtime. profile = profile}
14791434 whenJustM
14801435 ( liftIO $
14811436 Runtime. compileTo theRuntime copts codeLookup ppe ref outf
@@ -1661,8 +1616,8 @@ displayI outputLoc hq = do
16611616 suffixify =
16621617 case outputLoc of
16631618 ConsoleLocation -> PPE. suffixifyByHash
1664- FileLocation _ -> PPE. suffixifyByHashName
1665- LatestFileLocation -> PPE. suffixifyByHashName
1619+ FileLocation _ _ -> PPE. suffixifyByHashName
1620+ LatestFileLocation _ -> PPE. suffixifyByHashName
16661621
16671622docsI :: Name -> Cli ()
16681623docsI src = do
0 commit comments