remove compile.native.{fetch,genlibs} commands

existing ucm commands can be used instead, i.e. `gen-racket-libs.md`
This commit is contained in:
Arya Irani 2024-03-08 13:11:49 -05:00
parent 8df8744d1b
commit b7530a56ac
7 changed files with 46 additions and 216 deletions

View File

@ -1,10 +1,7 @@
{-# HLINT ignore "Use tuple-section" #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
module Unison.Codebase.Editor.HandleInput
( loop,
)
where
module Unison.Codebase.Editor.HandleInput (loop) where
-- TODO: Don't import backend
@ -19,7 +16,6 @@ import Data.List.Extra (nubOrd)
import Data.List.NonEmpty (NonEmpty)
import Data.List.NonEmpty qualified as Nel
import Data.Map qualified as Map
import Data.Sequence qualified as Seq
import Data.Set qualified as Set
import Data.Set.NonEmpty (NESet)
import Data.Set.NonEmpty qualified as NESet
@ -27,8 +23,6 @@ import Data.Text qualified as Text
import Data.These (These (..))
import Data.Time (UTCTime)
import Data.Tuple.Extra (uncurry3)
import System.Directory (XdgDirectory (..), createDirectoryIfMissing, doesFileExist, getXdgDirectory)
import System.FilePath ((</>))
import Text.Megaparsec qualified as Megaparsec
import U.Codebase.Branch.Diff qualified as V2Branch.Diff
import U.Codebase.Causal qualified as V2Causal
@ -47,7 +41,6 @@ import Unison.Cli.MonadUtils qualified as Cli
import Unison.Cli.NamesUtils qualified as Cli
import Unison.Cli.PrettyPrintUtils qualified as Cli
import Unison.Cli.ProjectUtils qualified as ProjectUtils
import Unison.Cli.TypeCheck (typecheckTerm)
import Unison.Codebase (Codebase)
import Unison.Codebase qualified as Codebase
import Unison.Codebase.Branch (Branch (..), Branch0 (..))
@ -89,7 +82,7 @@ import Unison.Codebase.Editor.HandleInput.ReleaseDraft (handleReleaseDraft)
import Unison.Codebase.Editor.HandleInput.Run (handleRun)
import Unison.Codebase.Editor.HandleInput.RuntimeUtils qualified as RuntimeUtils
import Unison.Codebase.Editor.HandleInput.ShowDefinition (showDefinitions)
import Unison.Codebase.Editor.HandleInput.TermResolution (resolveMainRef, resolveTermRef)
import Unison.Codebase.Editor.HandleInput.TermResolution (resolveMainRef)
import Unison.Codebase.Editor.HandleInput.Tests qualified as Tests
import Unison.Codebase.Editor.HandleInput.UI (openUI)
import Unison.Codebase.Editor.HandleInput.Update (doSlurpAdds, handleUpdate)
@ -100,7 +93,6 @@ import Unison.Codebase.Editor.Input qualified as Input
import Unison.Codebase.Editor.Output
import Unison.Codebase.Editor.Output qualified as Output
import Unison.Codebase.Editor.Output.DumpNamespace qualified as Output.DN
import Unison.Codebase.Editor.RemoteRepo (ReadRemoteNamespace (..))
import Unison.Codebase.Editor.RemoteRepo qualified as RemoteRepo
import Unison.Codebase.Editor.Slurp qualified as Slurp
import Unison.Codebase.Editor.SlurpResult qualified as SlurpResult
@ -116,13 +108,11 @@ import Unison.Codebase.Path.Parse qualified as Path
import Unison.Codebase.Runtime qualified as Runtime
import Unison.Codebase.ShortCausalHash qualified as SCH
import Unison.Codebase.SqliteCodebase.Conversions qualified as Conversions
import Unison.Codebase.SyncMode qualified as SyncMode
import Unison.Codebase.TermEdit (TermEdit (..))
import Unison.Codebase.TermEdit qualified as TermEdit
import Unison.Codebase.TermEdit.Typing qualified as TermEdit
import Unison.Codebase.TypeEdit (TypeEdit)
import Unison.Codebase.TypeEdit qualified as TypeEdit
import Unison.Codebase.Verbosity qualified as Verbosity
import Unison.CommandLine.BranchRelativePath (BranchRelativePath)
import Unison.CommandLine.Completion qualified as Completion
import Unison.CommandLine.DisplayValues qualified as DisplayValues
@ -154,13 +144,12 @@ import Unison.PrettyPrintEnv.Names qualified as PPE
import Unison.PrettyPrintEnvDecl qualified as PPE hiding (biasTo, empty)
import Unison.PrettyPrintEnvDecl qualified as PPED
import Unison.PrettyPrintEnvDecl.Names qualified as PPED
import Unison.Project (ProjectAndBranch (..), ProjectBranchNameOrLatestRelease (..))
import Unison.Project (ProjectAndBranch (..))
import Unison.Project.Util (projectContextFromPath)
import Unison.Reference (Reference, TermReference)
import Unison.Reference qualified as Reference
import Unison.Referent (Referent)
import Unison.Referent qualified as Referent
import Unison.Result qualified as Result
import Unison.Runtime.IOSource qualified as IOSource
import Unison.Server.Backend (ShallowListEntry (..))
import Unison.Server.Backend qualified as Backend
@ -175,19 +164,17 @@ import Unison.Share.Codeserver qualified as Codeserver
import Unison.ShortHash qualified as SH
import Unison.Sqlite qualified as Sqlite
import Unison.Symbol (Symbol)
import Unison.Syntax.HashQualified qualified as HQ (parseTextWith, toText, unsafeParseText)
import Unison.Syntax.HashQualified qualified as HQ (parseTextWith, toText)
import Unison.Syntax.Lexer qualified as L
import Unison.Syntax.Lexer qualified as Lexer
import Unison.Syntax.Name qualified as Name (toText, toVar, unsafeParseVar)
import Unison.Syntax.NameSegment qualified as NameSegment (toEscapedText)
import Unison.Syntax.Parser qualified as Parser
import Unison.Syntax.TermPrinter qualified as TP
import Unison.Term (Term)
import Unison.Term qualified as Term
import Unison.Type (Type)
import Unison.Type qualified as Type
import Unison.Type.Names qualified as Type
import Unison.Typechecker qualified as Typechecker
import Unison.UnisonFile (TypecheckedUnisonFile)
import Unison.UnisonFile qualified as UF
import Unison.UnisonFile.Names qualified as UF
@ -205,7 +192,6 @@ import Unison.Var (Var)
import Unison.Var qualified as Var
import Unison.WatchKind qualified as WK
import UnliftIO.Directory qualified as Directory
import Witch (unsafeFrom)
------------------------------------------------------------------------------------------------------------------------
-- Main loop
@ -975,10 +961,6 @@ loop e = do
CompileSchemeI output main ->
doCompile True (Text.unpack output) main
ExecuteSchemeI main args -> handleRun True main args
GenSchemeLibsI mdir ->
doGenerateSchemeBoot True Nothing mdir
FetchSchemeCompilerI name branch ->
doFetchCompiler name branch
IOTestI main -> Tests.handleIOTest main
IOTestAllI -> Tests.handleAllIOTests
-- UpdateBuiltinsI -> do
@ -1329,11 +1311,6 @@ inputDescription input =
ExecuteSchemeI nm args ->
pure $ "run.native " <> Text.unwords (nm : fmap Text.pack args)
CompileSchemeI fi nm -> pure ("compile.native " <> HQ.toText nm <> " " <> fi)
GenSchemeLibsI mdir ->
pure $
"compile.native.genlibs" <> Text.pack (maybe "" (" " ++) mdir)
FetchSchemeCompilerI name branch ->
pure ("compile.native.fetch" <> Text.pack name <> " " <> Text.pack branch)
CreateAuthorI id name -> pure ("create.author " <> NameSegment.toEscapedText id <> " " <> name)
RemoveTermReplacementI src p0 -> do
p <- opatch p0
@ -1915,96 +1892,6 @@ searchBranchScored names0 score queries =
pair qn =
(\score -> (Just score, result)) <$> score qn (Name.toText name)
compilerPath :: Path.Path'
compilerPath = Path.Path' {Path.unPath' = Left abs}
where
segs = ["unison", "internal"]
rootPath = Path.Path {Path.toSeq = Seq.fromList segs}
abs = Path.Absolute {Path.unabsolute = rootPath}
doFetchCompiler :: String -> String -> Cli ()
doFetchCompiler username branch =
doPullRemoteBranch sourceTarget SyncMode.Complete Input.PullWithoutHistory Verbosity.Silent
where
-- fetching info
prj =
These
(unsafeFrom @Text $ "@" <> Text.pack username <> "/internal")
(ProjectBranchNameOrLatestRelease'Name . unsafeFrom @Text $ Text.pack branch)
sourceTarget =
PullSourceTarget2
(ReadShare'ProjectBranch prj)
(This compilerPath)
getCacheDir :: Cli String
getCacheDir = liftIO $ getXdgDirectory XdgCache "unisonlanguage"
getSchemeGenLibDir :: Cli String
getSchemeGenLibDir =
Cli.getConfig "SchemeLibs.Generated" >>= \case
Just dir -> pure dir
Nothing -> (</> "scheme-libs") <$> getCacheDir
doGenerateSchemeBoot ::
Bool -> Maybe PPE.PrettyPrintEnv -> Maybe String -> Cli ()
doGenerateSchemeBoot force mppe mdir = do
ppe <- maybe (PPED.suffixifiedPPE <$> Cli.currentPrettyPrintEnvDecl) pure mppe
dir <- maybe getSchemeGenLibDir pure mdir
let bootf = dir </> "unison" </> "boot-generated.ss"
swrapf = dir </> "unison" </> "simple-wrappers.ss"
binf = dir </> "unison" </> "builtin-generated.ss"
cwrapf = dir </> "unison" </> "compound-wrappers.ss"
dinfof = dir </> "unison" </> "data-info.ss"
dirTm = Term.text a (Text.pack dir)
liftIO $ createDirectoryIfMissing True dir
saveData <- Term.ref a <$> resolveTermRef sdName
saveBase <- Term.ref a <$> resolveTermRef sbName
saveWrap <- Term.ref a <$> resolveTermRef swName
gen ppe saveData dinfof dirTm dinfoName
gen ppe saveBase bootf dirTm bootName
gen ppe saveWrap swrapf dirTm simpleWrapName
gen ppe saveBase binf dirTm builtinName
gen ppe saveWrap cwrapf dirTm compoundWrapName
where
a = External
sbName = HQ.unsafeParseText ".unison.internal.compiler.scheme.saveBaseFile"
swName = HQ.unsafeParseText ".unison.internal.compiler.scheme.saveWrapperFile"
sdName = HQ.unsafeParseText ".unison.internal.compiler.scheme.saveDataInfoFile"
dinfoName = HQ.unsafeParseText ".unison.internal.compiler.scheme.dataInfos"
bootName = HQ.unsafeParseText ".unison.internal.compiler.scheme.bootSpec"
builtinName = HQ.unsafeParseText ".unison.internal.compiler.scheme.builtinSpec"
simpleWrapName =
HQ.unsafeParseText ".unison.internal.compiler.scheme.simpleWrapperSpec"
compoundWrapName =
HQ.unsafeParseText ".unison.internal.compiler.scheme.compoundWrapperSpec"
gen ppe save file dir nm =
liftIO (doesFileExist file) >>= \b -> when (not b || force) do
spec <- Term.ref a <$> resolveTermRef nm
let make = Term.apps' save [dir, spec]
typecheckAndEval ppe make
typecheckAndEval :: PPE.PrettyPrintEnv -> Term Symbol Ann -> Cli ()
typecheckAndEval ppe tm = do
Cli.Env {codebase, runtime} <- ask
let mty = Runtime.mainType runtime
Cli.runTransaction (typecheckTerm codebase (Term.delay a tm)) >>= \case
-- Type checking succeeded
Result.Result _ (Just ty)
| Typechecker.fitsScheme ty mty ->
() <$ RuntimeUtils.evalUnisonTerm False ppe False tm
| otherwise ->
Cli.returnEarly $ BadMainFunction "run" rendered ty ppe [mty]
Result.Result notes Nothing -> do
currentPath <- Cli.getCurrentPath
let tes = [err | Result.TypeError err <- toList notes]
Cli.returnEarly (TypeErrors currentPath rendered ppe tes)
where
a = External
rendered = Text.pack (P.toPlainUnbroken $ TP.pretty ppe tm)
doCompile :: Bool -> String -> HQ.HashQualified Name -> Cli ()
doCompile native output main = do
Cli.Env {codebase, runtime, nativeRuntime} <- ask

View File

@ -185,10 +185,6 @@ data Input
ExecuteSchemeI Text [String]
| -- compile to a scheme file
CompileSchemeI Text (HQ.HashQualified Name)
| -- generate scheme libraries, optional target directory
GenSchemeLibsI (Maybe String)
| -- fetch scheme compiler from a given username and branch
FetchSchemeCompilerI String String
| TestI TestInput
| CreateAuthorI NameSegment {- identifier -} Text {- name -}
| -- Display provided definitions.

View File

@ -52,7 +52,6 @@ import Unison.CommandLine.FZFResolvers qualified as Resolvers
import Unison.CommandLine.InputPattern (ArgumentType (..), InputPattern (InputPattern), IsOptional (..), unionSuggestions)
import Unison.CommandLine.InputPattern qualified as I
import Unison.HashQualified qualified as HQ
import Unison.JitInfo qualified as JitInfo
import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment)
@ -2540,73 +2539,6 @@ compileScheme =
Input.CompileSchemeI (Text.pack file) <$> parseHashQualifiedName main
_ -> Left $ showPatternHelp compileScheme
schemeLibgen :: InputPattern
schemeLibgen =
InputPattern
"compile.native.genlibs"
[]
I.Visible
[("target directory", Optional, filePathArg)]
( P.wrapColumn2
[ ( makeExample schemeLibgen ["[targetDir]"],
"Generates libraries necessary for scheme compilation.\n\n\
\There is no need to run this before"
<> P.group (makeExample compileScheme [])
<> "as\
\ the latter will check if the libraries are missing and\
\ auto-generate them. However, this will generate the\
\ libraries even if their files already exist, so if the\
\ compiler has been upgraded, this can be used to ensure\
\ the generated libraries are up to date."
)
]
)
\case
[] -> pure $ Input.GenSchemeLibsI Nothing
[dir] -> pure . Input.GenSchemeLibsI $ Just dir
_ -> Left $ showPatternHelp schemeLibgen
fetchScheme :: InputPattern
fetchScheme =
InputPattern
"compile.native.fetch"
[]
I.Visible
[("name", Optional, noCompletionsArg), ("branch", Optional, noCompletionsArg)]
( P.wrapColumn2
[ ( makeExample fetchScheme [],
P.lines . fmap P.wrap $
[ "Fetches the unison library for compiling to scheme.",
"This is done automatically when"
<> P.group (makeExample compileScheme [])
<> "is run if the library is not already in the\
\ standard location (unison.internal). However,\
\ this command will force a pull even if the\
\ library already exists.",
"You can also specify a user and branch name to pull\
\ from in order to use an alternate version of the\
\ unison compiler (for development purposes, for\
\ example).",
"The default user is `unison`. The default branch\
\ for the `unison` user is a specified latest\
\ version of the compiler for stability. The\
\ default branch for other uses is `main`. The\
\ command fetches code from a project:",
P.indentN 2 ("@user/internal/branch")
]
)
]
)
\case
[] -> pure (Input.FetchSchemeCompilerI "unison" JitInfo.currentRelease)
[name] -> pure (Input.FetchSchemeCompilerI name branch)
where
branch
| name == "unison" = JitInfo.currentRelease
| otherwise = "main"
[name, branch] -> pure (Input.FetchSchemeCompilerI name branch)
_ -> Left $ showPatternHelp fetchScheme
createAuthor :: InputPattern
createAuthor =
InputPattern
@ -3049,7 +2981,6 @@ validInputs =
edit,
editNamespace,
execute,
fetchScheme,
find,
findAll,
findGlobal,
@ -3104,7 +3035,6 @@ validInputs =
resetRoot,
runScheme,
saveExecuteResult,
schemeLibgen,
squashMerge,
test,
testAll,

View File

@ -1,4 +0,0 @@
module Unison.JitInfo (currentRelease) where
currentRelease :: String
currentRelease = "releases/0.0.11"

View File

@ -107,7 +107,6 @@ library
Unison.CommandLine.OutputMessages
Unison.CommandLine.Types
Unison.CommandLine.Welcome
Unison.JitInfo
Unison.LSP
Unison.LSP.CancelRequest
Unison.LSP.CodeAction

View File

@ -9,13 +9,6 @@ jit-setup/main> pull @unison/internal/releases/0.0.11 lib.jit
```
```unison
generateSchemeBoot dir = do
saveDataInfoFile dir dataInfos
saveBaseFile dir bootSpec
saveWrapperFile dir simpleWrapperSpec
saveBaseFile dir builtinSpec
saveWrapperFile dir compoundWrapperSpec
go = generateSchemeBoot "scheme-libs/racket"
```

View File

@ -1,26 +1,55 @@
Fetch base, then fetch the compiler, then build the generated
libraries in the racket directory.
When we start out, `./scheme-libs/racket` contains a bunch of library files that we'll need. They define the Unison builtins for Racket.
Next, we'll download the jit project and generate a few Racket files from it.
```ucm
.> pull @unison/base/releases/2.5.0 .base
.> project.create-empty jit-setup
Downloaded 12426 entities.
🎉 I've created the project jit-setup.
🎨 Type `ui` to explore this project's code in your browser.
🔭 Discover libraries at https://share.unison-lang.org
📖 Use `help-topic projects` to learn more about projects.
Write your first Unison code with UCM:
1. Open scratch.u.
2. Write some Unison code and save the file.
3. In UCM, type `add` to save it to your new project.
🎉 🥳 Happy coding!
jit-setup/main> pull @unison/internal/releases/0.0.11 lib.jit
Downloaded 13900 entities.
Successfully pulled into lib.jit, which was empty.
Successfully pulled into .base, which was empty.
```
```unison
go = generateSchemeBoot "scheme-libs/racket"
```
.> compile.native.fetch
```ucm
Downloaded 1465 entities.
Loading changes detected in scratch.u.
I found and typechecked these definitions in scratch.u. If you
do an `add` or `update`, here's how your codebase would
change:
⍟ These new definitions are ok to `add`:
go : '{IO, Exception} ()
Successfully updated .unison.internal from
@unison/internal/releases/0.0.10.
```
```ucm
jit-setup/main> run go
.> compile.native.genlibs scheme-libs/racket
()
```
After executing this, `scheme-libs/racket` will contain the full
@ -35,11 +64,11 @@ them. This is accomplished by running.
in the directory where the `unison directory is located. Then the
runtime executable can be built with
raco exe scheme-libs/racket/ucr.rkt
raco exe scheme-libs/racket/unison-runtime.rkt
and a distributable directory can be produced with:
raco distribute <output-dir> scheme-libs/racket/ucr
raco distribute <output-dir> scheme-libs/racket/unison-runtime
At that point, <output-dir> should contain the executable and all
dependencies necessary to run it.