⅄ trunk → 21-10-05-unify-types

This commit is contained in:
Mitchell Rosen 2021-10-05 22:25:25 -04:00
commit 0f5c270ca2
30 changed files with 892 additions and 630 deletions

View File

@ -13,6 +13,7 @@ git checkout series/M2
git merge origin/trunk
git tag -a release/$RELEASE_NAME -m "release"
git push origin release/$RELEASE_NAME
git push origin series/M2
```
__2__
@ -25,7 +26,7 @@ Create a release notes draft issue, following [this template](https://github.com
__4__
Update trunk of `base` to include any new builtins added since last release. Suggestion for how to do this: look through the release notes draft to find the PRs merged since last release. @runarorma does this usually.
Update trunk of `base` to include any new builtins added since last release. Suggestion for how to do this: look through the release notes draft to find the PRs merged since last release. @runarorama does this usually.
```
git log --oneline release/M2h...release/M2i | grep 'Merge pull request #'
@ -38,12 +39,12 @@ __5__
Cut a release of base. @runarorama does this usually.
```
.> pull https://unisonweb/base basedev.release
.> cd basedev.release
.> pull git@github.com:unisonweb/base basedev.release
.> cd .basedev.release
.basedev.release> delete.namespace releases._latest
.basedev.release> squash trunk releases._<ReleaseName>
.basedev.release> fork releases._<ReleaseName> releases._latest
.basedev.release> push git@github.com/unisonweb/base
.basedev.release> push git@github.com:unisonweb/base
```
__6__
@ -54,22 +55,29 @@ Update homebrew.
git clone git@github.com/unisonweb/homebrew-unison
```
Update this file: https://github.com/unisonweb/homebrew-unison/blob/master/unison-language.rb and change the version number and the path to the release. Leave the SHA alone, and then run `brew upgrade`.
Update this file: https://github.com/unisonweb/homebrew-unison/blob/master/unison-language.rb and change the version number and the path to the release tar files.
Do `brew upgrade unison-language`. It will tell you the SHA hash doesn't match. Update the file to use the hash it says.
Do the same for linux and mac - you can temporarily swap the mac / linux stanzas just to get the value for the other platform.
To get the updated sha256 values, use the following command, replacing the download link with the linux and mac downloads respectively.
```sh
curl -sSL https://github.com/unisonweb/unison/releases/download/release%2FM2h/ucm-linux.tar.gz | shasum -a 256 | cut -f1 -d" "
```
__7__
Merge and promote to production any PRs pending [on the docs site](https://github.com/unisonweb/unisonweb-org/pulls) which are associated with the new release. Confirm with @rlmark.
[In the docs site repository](https://github.com/unisonweb/unisonweb-org/pulls), find a branch with the matching release name (if one exists), merge it into the master branch, then merge master into the production branch. Confirm with @rlmark.
__8__
Bug @pchiusano to update [the Slack post](https://unisonlanguage.slack.com/files/TLL09QC85/FMT7TDDDY?origin_team=TLL09QC85) which provides install instructions for people coming from [the quickstart guide](https://www.unisonweb.org/docs/quickstart/).
__9__
Announce on #contrib Slack channel. Template below.
---
Release announcement template -
Release announcement template (be sure to update the release urls) -
We've just released a new version of Unison, $RELEASE_NAME, release notes here (link to the issue). Install/upgrade instructions in the thread.

View File

@ -44,6 +44,7 @@ library:
- configurator
- cryptonite
- data-default
- deepseq
- directory
- either
- fuzzyfind
@ -84,6 +85,8 @@ library:
- regex-tdfa
- safe
- safe-exceptions
- mwc-random
- NanoID
- servant
- servant-docs
- servant-openapi3
@ -109,6 +112,7 @@ library:
- x509
- x509-store
- x509-system
- zlib
- unison-codebase
- unison-codebase-sqlite
- unison-codebase-sync

View File

@ -436,6 +436,11 @@ builtinsSrc =
, B "Bytes.size" $ bytes --> nat
, B "Bytes.flatten" $ bytes --> bytes
, B "Bytes.zlib.compress" $ bytes --> bytes
, B "Bytes.zlib.decompress" $ bytes --> eithert text bytes
, B "Bytes.gzip.compress" $ bytes --> bytes
, B "Bytes.gzip.decompress" $ bytes --> eithert text bytes
{- These are all `Bytes -> Bytes`, rather than `Bytes -> Text`.
This is intentional: it avoids a round trip to `Text` if all
you are doing with the bytes is dumping them to a file or a

View File

@ -86,6 +86,7 @@ constructorId ref name = do
noneId, someId, okConstructorId, failConstructorId, docBlobId, docLinkId, docSignatureId, docSourceId, docEvaluateId, docJoinId, linkTermId, linkTypeId, eitherRightId, eitherLeftId :: ConstructorId
isPropagatedConstructorId, isTestConstructorId, bufferModeNoBufferingId, bufferModeLineBufferingId, bufferModeBlockBufferingId, bufferModeSizedBlockBufferingId :: ConstructorId
seqViewEmpty, seqViewElem :: ConstructorId
Just noneId = constructorId optionalRef "Optional.None"
Just someId = constructorId optionalRef "Optional.Some"
Just isPropagatedConstructorId = constructorId isPropagatedRef "IsPropagated.IsPropagated"
@ -102,6 +103,8 @@ Just linkTermId = constructorId linkRef "Link.Term"
Just linkTypeId = constructorId linkRef "Link.Type"
Just eitherRightId = constructorId eitherRef "Either.Right"
Just eitherLeftId = constructorId eitherRef "Either.Left"
Just seqViewEmpty = constructorId seqViewRef "SeqView.VEmpty"
Just seqViewElem = constructorId seqViewRef "SeqView.VElem"
Just bufferModeNoBufferingId = constructorId bufferModeRef "io2.BufferMode.NoBuffering"
Just bufferModeLineBufferingId = constructorId bufferModeRef "io2.BufferMode.LineBuffering"

View File

@ -241,18 +241,6 @@ loop = do
getHQ'Terms p = BranchUtil.getTerm (resolveSplit' p) root0
getHQ'Types :: Path.HQSplit' -> Set Reference
getHQ'Types p = BranchUtil.getType (resolveSplit' p) root0
getHQTerms :: HQ.HashQualified Name -> Action' m v (Set Referent)
getHQTerms hq = case hq of
HQ.NameOnly n -> let
-- absolute-ify the name, then lookup in deepTerms of root
path :: Path.Path'
path = Path.fromName' n
Path.Absolute absPath = resolveToAbsolute path
in pure $ R.lookupRan (Path.toName absPath) (Branch.deepTerms root0)
HQ.HashOnly sh -> hashOnly sh
HQ.HashQualified _ sh -> hashOnly sh
where
hashOnly sh = eval $ TermReferentsByShortHash sh
basicPrettyPrintNames0 =
Backend.basicPrettyPrintNames0 root' (Path.unabsolute currentPath')
@ -439,6 +427,7 @@ loop = do
(uncurry3 printNamespace) orepo
<> " "
<> p' dest
CreateMessage{} -> wat
LoadI{} -> wat
PreviewAddI{} -> wat
PreviewUpdateI{} -> wat
@ -560,61 +549,57 @@ loop = do
-- `mdValues` is (names of the) metadata to pass to `op`
-- `op` is the operation to add/remove/alter metadata mappings.
-- e.g. `Metadata.insert` is passed to add metadata links.
manageLinks :: Bool
-> [(Path', HQ'.HQSegment)]
-> [HQ.HashQualified Name]
-> (forall r. Ord r
=> (r, Metadata.Type, Metadata.Value)
-> Branch.Star r NameSegment
-> Branch.Star r NameSegment)
-> Action m (Either Event Input) v ()
manageLinks ::
Bool ->
[(Path', HQ'.HQSegment)] ->
[HQ.HashQualified Name] ->
( forall r.
Ord r =>
(r, Metadata.Type, Metadata.Value) ->
Branch.Star r NameSegment ->
Branch.Star r NameSegment
) ->
Action m (Either Event Input) v ()
manageLinks silent srcs mdValues op = do
mdValuels <- fmap (first toList) <$>
traverse (\x -> fmap (,x) (getHQTerms x)) mdValues
runExceptT (for mdValues \val -> ExceptT (getMetadataFromName val)) >>= \case
Left output -> respond output
Right metadata -> do
before <- Branch.head <$> use root
traverse_ go mdValuels
traverse_ go metadata
if silent
then respond DefaultMetadataNotification
else do
after <- Branch.head <$> use root
(ppe, outputDiff) <- diffHelper before after
if not silent then
if OBranchDiff.isEmpty outputDiff
then respond NoOp
else respondNumbered $ ShowDiffNamespace Path.absoluteEmpty
else
respondNumbered $
ShowDiffNamespace
Path.absoluteEmpty
Path.absoluteEmpty
ppe
outputDiff
else unless (OBranchDiff.isEmpty outputDiff) $
respond DefaultMetadataNotification
where
go (mdl, hqn) = do
go :: (Metadata.Type, Metadata.Value) -> Action m (Either Event Input) v ()
go (mdType, mdValue) = do
newRoot <- use root
let r0 = Branch.head newRoot
getTerms p = BranchUtil.getTerm (resolveSplit' p) r0
getTypes p = BranchUtil.getType (resolveSplit' p) r0
!srcle = toList . getTerms =<< srcs
!srclt = toList . getTypes =<< srcs
ppe = Backend.basicSuffixifiedNames
sbhLength
newRoot
(Path.unabsolute currentPath')
case mdl of
[r@(Referent.Ref mdValue)] -> do
mdType <- eval $ LoadTypeOfTerm mdValue
case mdType of
Nothing -> respond $ MetadataMissingType ppe r
Just ty -> do
let steps =
bimap (Path.unabsolute . resolveToAbsolute)
(const . step $ Hashing.typeToReference ty)
<$> srcs
stepManyAtNoSync steps
where
step mdType b0 =
let step b0 =
let tmUpdates terms = foldl' go terms srcle
where go terms src = op (src, mdType, mdValue) terms
where
go terms src = op (src, mdType, mdValue) terms
tyUpdates types = foldl' go types srclt
where go types src = op (src, mdType, mdValue) types
where
go types src = op (src, mdType, mdValue) types
in over Branch.terms tmUpdates . over Branch.types tyUpdates $ b0
mdValues -> respond $ MetadataAmbiguous hqn ppe mdValues
steps = srcs <&> \(path, _hq) -> (Path.unabsolute (resolveToAbsolute path), step)
stepManyAtNoSync steps
delete
:: (Path.HQSplit' -> Set Referent) -- compute matching terms
-> (Path.HQSplit' -> Set Reference) -- compute matching types
@ -675,6 +660,10 @@ loop = do
doDisplay outputLoc ns tm
in case input of
CreateMessage pretty ->
respond $ PrintMessage pretty
ShowReflogI -> do
entries <- convertEntries Nothing [] <$> eval LoadReflog
numberedArgs .=
@ -2236,6 +2225,56 @@ loadPropagateDiffDefaultPatch inputDescription dest0 dest = unsafeTime "Propagat
diffHelper (Branch.head original) (Branch.head patched) >>=
respondNumbered . uncurry (ShowDiffAfterMergePropagate dest0 dest patchPath)
-- | Get metadata type/value from a name.
--
-- May fail with either:
--
-- * 'MetadataMissingType', if the given name is associated with a single reference, but that reference doesn't have a
-- type.
-- * 'MetadataAmbiguous', if the given name is associated with more than one reference.
getMetadataFromName ::
Var v =>
HQ.HashQualified Name ->
Action m (Either Event Input) v (Either (Output v) (Metadata.Type, Metadata.Value))
getMetadataFromName name = do
(Set.toList <$> getHQTerms name) >>= \case
[ref@(Referent.Ref val)] ->
eval (LoadTypeOfTerm val) >>= \case
Nothing -> do
ppe <- getPPE
pure (Left (MetadataMissingType ppe ref))
Just ty -> pure (Right (Hashing.typeToReference ty, val))
-- FIXME: we want a different error message if the given name is associated with a data constructor (`Con`).
refs -> do
ppe <- getPPE
pure (Left (MetadataAmbiguous name ppe refs))
where
getPPE :: Action m (Either Event Input) v PPE.PrettyPrintEnv
getPPE = do
currentPath' <- use currentPath
sbhLength <- eval BranchHashLength
Backend.basicSuffixifiedNames sbhLength <$> use root <*> pure (Path.unabsolute currentPath')
-- | Get the set of terms related to a hash-qualified name.
getHQTerms :: HQ.HashQualified Name -> Action' m v (Set Referent)
getHQTerms = \case
HQ.NameOnly n -> do
root0 <- Branch.head <$> use root
currentPath' <- use currentPath
-- absolute-ify the name, then lookup in deepTerms of root
let path =
n
& Path.fromName'
& Path.resolve currentPath'
& Path.unabsolute
& Path.toName
pure $ R.lookupRan path (Branch.deepTerms root0)
HQ.HashOnly sh -> hashOnly sh
HQ.HashQualified _ sh -> hashOnly sh
where
hashOnly sh = eval $ TermReferentsByShortHash sh
getAt :: Functor m => Path.Absolute -> Action m i v (Branch m)
getAt (Path.Absolute p) =
use root <&> fromMaybe Branch.empty . Branch.getAt p

View File

@ -21,9 +21,10 @@ import Unison.ShortHash (ShortHash)
import Unison.Codebase.ShortBranchHash (ShortBranchHash)
import qualified Unison.Codebase.ShortBranchHash as SBH
import Unison.Codebase.SyncMode ( SyncMode )
import Unison.Codebase.Verbosity
import Unison.Name ( Name )
import Unison.NameSegment ( NameSegment )
import qualified Unison.Util.Pretty as P
import Unison.Codebase.Verbosity
import qualified Data.Text as Text
@ -60,6 +61,8 @@ data Input
| ResetRootI (Either ShortBranchHash Path')
-- todo: Q: Does it make sense to publish to not-the-root of a Github repo?
-- Does it make sense to fork from not-the-root of a Github repo?
-- used in Welcome module to give directions to user
| CreateMessage (P.Pretty P.ColorText)
-- change directory
| SwitchBranchI Path'
| UpI

View File

@ -93,6 +93,8 @@ data Output v
= Success
-- User did `add` or `update` before typechecking a file?
| NoUnisonFile
-- Used in Welcome module to instruct user
| PrintMessage (P.Pretty P.ColorText)
| InvalidSourceName String
| SourceLoadFailed String
-- No main function, the [Type v Ann] are the allowed types
@ -241,6 +243,7 @@ type SourceFileContents = Text
isFailure :: Ord v => Output v -> Bool
isFailure o = case o of
Success{} -> False
PrintMessage{} -> False
BadRootBranch{} -> True
CouldntLoadBranch{} -> True
NoUnisonFile{} -> True
@ -345,4 +348,3 @@ isNumberedFailure = \case
ShowDiffAfterCreatePR{} -> False
ShowDiffAfterCreateAuthor{} -> False

View File

@ -11,7 +11,9 @@ import qualified Data.Text as Text
import qualified Unison.Codebase.Path as Path
import Data.Void (Void)
-- |"release/M1j.2" -> "releases._M1j"
-- | Parse git version strings into valid unison namespaces.
-- "release/M1j" -> "releases._M1j"
-- "release/M1j.2" -> "releases._M1j_2"
-- "latest-*" -> "trunk"
defaultBaseLib :: Parsec Void Text ReadRemoteNamespace
defaultBaseLib = fmap makeNS $ latest <|> release
@ -19,8 +21,8 @@ defaultBaseLib = fmap makeNS $ latest <|> release
latest, release, version :: Parsec Void Text Text
latest = "latest-" *> many anyChar *> eof $> "trunk"
release = fmap ("releases._" <>) $ "release/" *> version <* eof
version = fmap Text.pack $
try (someTill anyChar "." <* many anyChar) <|> many anyChar
version = do
Text.pack <$> some (alphaNumChar <|> ('_' <$ oneOf ['.', '_', '-']))
makeNS :: Text -> ReadRemoteNamespace
makeNS t = ( ReadGitRepo "https://github.com/unisonweb/base"
, Nothing

View File

@ -115,14 +115,13 @@ main
-> IO ()
main dir welcome initialPath (config, cancelConfig) initialInputs runtime codebase serverBaseUrl = do
root <- fromMaybe Branch.empty . rightMay <$> Codebase.getRootBranch codebase
(welcomeCmds, welcomeMsg) <- Welcome.welcome codebase welcome
putPrettyLn welcomeMsg
eventQueue <- Q.newIO
welcomeEvents <-Welcome.run codebase welcome
do
-- we watch for root branch tip changes, but want to ignore ones we expect.
rootRef <- newIORef root
pathRef <- newIORef initialPath
initialInputsRef <- newIORef (welcomeCmds ++ initialInputs)
initialInputsRef <- newIORef $ welcomeEvents ++ initialInputs
numberedArgsRef <- newIORef []
pageOutput <- newIORef True
cancelFileSystemWatch <- watchFileSystem eventQueue dir

View File

@ -104,7 +104,6 @@ import Unison.Var (Var)
import qualified Unison.Var as Var
import qualified Unison.Codebase.Editor.SlurpResult as SlurpResult
import Unison.Codebase.Editor.DisplayObject (DisplayObject(MissingObject, BuiltinObject, UserObject))
import qualified Unison.Codebase.Editor.Input as Input
import qualified Unison.Hash as Hash
import qualified Unison.Codebase.Causal as Causal
import qualified Unison.Codebase.Editor.RemoteRepo as RemoteRepo
@ -118,6 +117,7 @@ import U.Codebase.Sqlite.DbId (SchemaVersion(SchemaVersion))
import Unison.Codebase.SqliteCodebase.GitError (GitSqliteCodebaseError(UnrecognizedSchemaVersion, GitCouldntParseRootBranchHash))
import qualified Unison.Referent' as Referent
import qualified Unison.WatchKind as WK
import qualified Unison.Codebase.Editor.Input as Input
type Pretty = P.Pretty P.ColorText
@ -257,6 +257,8 @@ prettyRemoteNamespace =
notifyUser :: forall v . Var v => FilePath -> Output v -> IO Pretty
notifyUser dir o = case o of
Success -> pure $ P.bold "Done."
PrintMessage pretty -> do
pure pretty
BadRootBranch e -> case e of
Codebase.NoRootBranch ->
pure . P.fatalCallout $ "I couldn't find the codebase root!"

View File

@ -7,83 +7,99 @@ import qualified Unison.Codebase as Codebase
import Prelude hiding (readFile, writeFile)
import qualified Unison.Util.Pretty as P
import System.Random (randomRIO)
import Unison.Codebase.Path (Path)
import qualified Unison.Codebase.Path as Path
import qualified Unison.Codebase.SyncMode as SyncMode
import Unison.Codebase.Editor.Input (Input (..), Event)
import Unison.Codebase.Editor.Input
import Data.Sequence (singleton)
import Unison.NameSegment (NameSegment(NameSegment))
import Unison.Codebase.Editor.RemoteRepo (ReadRemoteNamespace)
import qualified Unison.Codebase.Verbosity as Verbosity
-- Should Welcome include whether or not the codebase was created just now?
data DownloadBase = DownloadBase ReadRemoteNamespace | DontDownloadBase
data Welcome = Welcome
{ downloadBase :: DownloadBase
{ onboarding :: Onboarding -- Onboarding States
, downloadBase :: DownloadBase
, watchDir :: FilePath
, unisonVersion :: String
}
welcome :: Codebase IO v a -> Welcome -> IO ([Either Event Input], P.Pretty P.ColorText)
welcome codebase welcome' = do
let Welcome{downloadBase=downloadBase, watchDir=dir, unisonVersion=version} = welcome'
welcomeMsg <- welcomeMessage dir version
isBlankCodebase <- Codebase.isBlank codebase
pure $ case downloadBase of
DownloadBase ns@(_, _, path) | isBlankCodebase ->
let
cmd =
Right (pullBase ns)
data DownloadBase
= DownloadBase ReadRemoteNamespace | DontDownloadBase
baseVersion =
P.string (show path)
-- Previously Created is different from Previously Onboarded because a user can
-- 1.) create a new codebase
-- 2.) decide not to go through the onboarding flow until later and exit
-- 3.) then reopen their blank codebase
data CodebaseInitStatus
= NewlyCreatedCodebase -- Can transition to [Base, Author, Finished]
| PreviouslyCreatedCodebase -- Can transition to [Base, Author, Finished, PreviouslyOnboarded].
downloadMsg =
P.lines [ P.newline <> P.newline
, P.wrap ("🕐 Downloading"
<> P.blue baseVersion
<> "of the"
<> P.bold "base library"
<> "into"
<> P.group (P.blue ".base" <> ", this may take a minute..."))
]
in
([cmd], welcomeMsg <> downloadMsg)
_ ->
([], welcomeMsg)
data Onboarding
= Init CodebaseInitStatus -- Can transition to [DownloadingBase, Author, Finished, PreviouslyOnboarded]
| DownloadingBase ReadRemoteNamespace -- Can transition to [Author, Finished]
| Author -- Can transition to [Finished]
-- End States
| Finished
| PreviouslyOnboarded
welcomeMessage :: FilePath -> String -> IO (P.Pretty P.ColorText)
welcomeMessage dir version = do
earth <- (["🌎", "🌍", "🌏"] !!) <$> randomRIO (0, 2)
welcome :: CodebaseInitStatus -> DownloadBase -> FilePath -> String -> Welcome
welcome initStatus downloadBase filePath unisonVersion =
Welcome (Init initStatus) downloadBase filePath unisonVersion
pure $
asciiartUnison
<> P.newline
<> P.newline
<> P.linesSpaced
[ P.wrap "👋 Welcome to Unison!",
P.wrap ("You are running version: " <> P.bold (P.string version)) <> P.newline,
P.wrap "Get started:",
P.indentN
2
( P.column2
[ ("📖", "Type " <> P.hiBlue "help" <> " to list all commands, or " <> P.hiBlue "help <cmd>" <> " to view help for one command"),
("🎨", "Type " <> P.hiBlue "ui" <> " to open the Codebase UI in your default browser"),
("📚", "Read the official docs at " <> P.blue "https://unisonweb.org/docs"),
(earth, "Visit Unison Share at " <> P.blue "https://share.unison-lang.org" <> " to discover libraries"),
("👀", "I'm watching for changes to " <> P.bold ".u" <> " files under " <> (P.group . P.blue $ P.string dir))
]
)
]
pullBase :: ReadRemoteNamespace -> Input
pullBase ns = do
let
pullBase :: ReadRemoteNamespace -> Either Event Input
pullBase ns = let
seg = NameSegment "base"
rootPath = Path.Path { Path.toSeq = singleton seg }
abs = Path.Absolute {Path.unabsolute = rootPath}
PullRemoteBranchI (Just ns) (Path.Path' {Path.unPath' = Left abs}) SyncMode.Complete Verbosity.Silent
pullRemote = PullRemoteBranchI (Just ns) (Path.Path' {Path.unPath' = Left abs}) SyncMode.Complete Verbosity.Silent
in Right pullRemote
run :: Codebase IO v a -> Welcome -> IO [Either Event Input]
run codebase Welcome { onboarding = onboarding, downloadBase = downloadBase, watchDir = dir, unisonVersion = version } = do
go onboarding []
where
go :: Onboarding -> [Either Event Input] -> IO [Either Event Input]
go onboarding acc =
case onboarding of
Init NewlyCreatedCodebase -> do
determineFirstStep downloadBase codebase >>= \step -> go step (headerMsg : acc)
where
headerMsg = toInput (header version)
Init PreviouslyCreatedCodebase -> do
go PreviouslyOnboarded (headerMsg : acc)
where
headerMsg = toInput (header version)
DownloadingBase ns@(_, _, path) ->
go Author ([pullBaseInput, downloadMsg] ++ acc)
where
downloadMsg = Right $ CreateMessage (downloading path)
pullBaseInput = pullBase ns
Author ->
go Finished (authorMsg : acc)
where
authorMsg = toInput authorSuggestion
-- These are our two terminal Welcome conditions, at the end we reverse the order of the desired input commands otherwise they come out backwards
Finished -> do
startMsg <- getStarted dir
pure $ reverse (toInput startMsg : acc)
PreviouslyOnboarded -> do
startMsg <- getStarted dir
pure $ reverse (toInput startMsg : acc)
toInput :: P.Pretty P.ColorText -> Either Event Input
toInput pretty =
Right $ CreateMessage pretty
determineFirstStep :: DownloadBase -> Codebase IO v a -> IO Onboarding
determineFirstStep downloadBase codebase = do
isBlankCodebase <- Codebase.isBlank codebase
case downloadBase of
DownloadBase ns | isBlankCodebase ->
pure $ DownloadingBase ns
_ ->
pure PreviouslyOnboarded
asciiartUnison :: P.Pretty P.ColorText
asciiartUnison =
@ -110,3 +126,51 @@ asciiartUnison =
<> P.cyan "|___|"
<> P.purple "_|_|"
downloading :: Path -> P.Pretty P.ColorText
downloading path =
P.lines
[ P.group (P.wrap "🐣 Since this is a fresh codebase, let me download the base library for you." <> P.newline ),
P.wrap
("🕐 Downloading"
<> P.blue (P.string (show path))
<> "of the"
<> P.bold "base library"
<> "into"
<> P.group (P.blue ".base" <> ", this may take a minute...")
)
]
header :: String -> P.Pretty P.ColorText
header version =
asciiartUnison
<> P.newline
<> P.newline
<> P.linesSpaced
[ P.wrap "👋 Welcome to Unison!",
P.wrap ("You are running version: " <> P.bold (P.string version))
]
authorSuggestion :: P.Pretty P.ColorText
authorSuggestion =
P.newline <>
P.lines [ P.wrap "📜 🪶 You might want to set up your author information next.",
P.wrap "Type" <> P.hiBlue " create.author" <> " to create an author for this codebase",
P.group( P.newline <> P.wrap "Read about how to link your author to your code at"),
P.wrap $ P.blue "https://www.unisonweb.org/docs/configuration/#setting-default-metadata-like-license-and-author"
]
getStarted :: FilePath -> IO (P.Pretty P.ColorText)
getStarted dir = do
earth <- (["🌎", "🌍", "🌏"] !!) <$> randomRIO (0, 2)
pure $ P.linesSpaced [
P.wrap "Get started:",
P.indentN 2 $ P.column2
[ ("📖", "Type " <> P.hiBlue "help" <> " to list all commands, or " <> P.hiBlue "help <cmd>" <> " to view help for one command"),
("🎨", "Type " <> P.hiBlue "ui" <> " to open the Codebase UI in your default browser"),
("📚", "Read the official docs at " <> P.blue "https://unisonweb.org/docs"),
(earth, "Visit Unison Share at " <> P.blue "https://share.unison-lang.org" <> " to discover libraries"),
("👀", "I'm watching for changes to " <> P.bold ".u" <> " files under " <> (P.group . P.blue $ P.string dir))
]
]

View File

@ -1022,8 +1022,8 @@ anfBlock (Match' scrut cas) = do
, pure . TMatch r
$ MatchDataCover Ty.seqViewRef
(EC.mapFromList
[ (0, ([], em))
, (1, ([BX,BX], bd))
[ (toEnum Ty.seqViewEmpty, ([], em))
, (toEnum Ty.seqViewElem, ([BX,BX], bd))
]
)
)

View File

@ -18,6 +18,9 @@ module Unison.Runtime.Builtin
) where
import Control.Monad.State.Strict (State, modify, execState)
import qualified Control.Exception.Safe as Exception
import Control.Monad.Catch (MonadCatch)
import Control.DeepSeq (NFData)
import Unison.ABT.Normalized hiding (TTm)
import Unison.Reference
@ -32,7 +35,6 @@ import Unison.Runtime.Foreign
( Foreign(Wrap), HashAlgorithm(..), pattern Failure)
import qualified Unison.Runtime.Foreign as F
import Unison.Runtime.Foreign.Function
import Unison.Runtime.IOSource (eitherReference)
import qualified Unison.Type as Ty
import qualified Unison.Builtin as Ty (builtinTypes)
@ -58,7 +60,7 @@ import Data.PEM (pemContent, pemParseLBS, PEM)
import Data.Set (insert)
import qualified Data.Map as Map
import Unison.Prelude
import Unison.Prelude hiding (some)
import qualified Unison.Util.Bytes as Bytes
import Network.Socket as SYS
( accept
@ -182,6 +184,17 @@ fls, tru :: Var v => ANormal v
fls = TCon Ty.booleanRef 0 []
tru = TCon Ty.booleanRef 1 []
none :: Var v => ANormal v
none = TCon Ty.optionalRef (toEnum Ty.noneId) []
some, left, right :: Var v => v -> ANormal v
some a = TCon Ty.optionalRef (toEnum Ty.someId) [a]
left x = TCon Ty.eitherRef (toEnum Ty.eitherLeftId) [x]
right x = TCon Ty.eitherRef (toEnum Ty.eitherRightId) [x]
seqViewEmpty :: Var v => ANormal v
seqViewEmpty = TCon Ty.seqViewRef (toEnum Ty.seqViewEmpty) []
seqViewElem :: Var v => v -> v -> ANormal v
seqViewElem l r = TCon Ty.seqViewRef (toEnum Ty.seqViewElem) [l,r]
boolift :: Var v => v -> ANormal v
boolift v
= TMatch v $ MatchIntegral (mapFromList [(0,fls), (1,tru)]) Nothing
@ -440,24 +453,24 @@ sizet = unop0 1 $ \[x,r]
unconst = unop0 7 $ \[x,t,c0,c,y,p,u,yp]
-> TLetD t UN (TPrm UCNS [x])
. TMatch t . MatchSum $ mapFromList
[ (0, ([], TCon Ty.optionalRef 0 []))
[ (0, ([], none))
, (1, ([UN,BX], TAbss [c0,y]
. TLetD u BX (TCon Ty.unitRef 0 [])
. TLetD yp BX (TCon Ty.pairRef 0 [y,u])
. TLetD c BX (TCon Ty.charRef 0 [c0])
. TLetD p BX (TCon Ty.pairRef 0 [c,yp])
$ TCon Ty.optionalRef 1 [p]))
$ some p))
]
unsnoct = unop0 7 $ \[x,t,c0,c,y,p,u,cp]
-> TLetD t UN (TPrm USNC [x])
. TMatch t . MatchSum $ mapFromList
[ (0, ([], TCon Ty.optionalRef 0 []))
[ (0, ([], none))
, (1, ([BX,UN], TAbss [y,c0]
. TLetD u BX (TCon Ty.unitRef 0 [])
. TLetD c BX (TCon Ty.charRef 0 [c0])
. TLetD cp BX (TCon Ty.pairRef 0 [c,u])
. TLetD p BX (TCon Ty.pairRef 0 [y,cp])
$ TCon Ty.optionalRef 1 [p]))
$ some p))
]
appends, conss, snocs :: Var v => SuperNormal v
@ -484,8 +497,8 @@ ats = binop0 3 $ \[x0,y,x,t,r]
-> unbox x0 Ty.natRef x
. TLetD t UN (TPrm IDXS [x,y])
. TMatch t . MatchSum $ mapFromList
[ (0, ([], TCon Ty.optionalRef 0 []))
, (1, ([BX], TAbs r $ TCon Ty.optionalRef 1 [r]))
[ (0, ([], none))
, (1, ([BX], TAbs r $ some r))
]
emptys = Lambda [] $ TPrm BLDS []
@ -493,14 +506,14 @@ viewls, viewrs :: Var v => SuperNormal v
viewls = unop0 3 $ \[s,u,h,t]
-> TLetD u UN (TPrm VWLS [s])
. TMatch u . MatchSum $ mapFromList
[ (0, ([], TCon Ty.seqViewRef 0 []))
, (1, ([BX,BX], TAbss [h,t] $ TCon Ty.seqViewRef 1 [h,t]))
[ (0, ([], seqViewEmpty))
, (1, ([BX,BX], TAbss [h,t] $ seqViewElem h t))
]
viewrs = unop0 3 $ \[s,u,i,l]
-> TLetD u UN (TPrm VWRS [s])
. TMatch u . MatchSum $ mapFromList
[ (0, ([], TCon Ty.seqViewRef 0 []))
, (1, ([BX,BX], TAbss [i,l] $ TCon Ty.seqViewRef 1 [i,l]))
[ (0, ([], seqViewEmpty))
, (1, ([BX,BX], TAbss [i,l] $ seqViewElem i l))
]
eqt, neqt, leqt, geqt, lesst, great :: Var v => SuperNormal v
@ -551,10 +564,10 @@ atb = binop0 4 $ \[n0,b,n,t,r0,r]
-> unbox n0 Ty.natRef n
. TLetD t UN (TPrm IDXB [n,b])
. TMatch t . MatchSum $ mapFromList
[ (0, ([], TCon Ty.optionalRef 0 []))
[ (0, ([], none))
, (1, ([UN], TAbs r0
. TLetD r BX (TCon Ty.natRef 0 [r0])
$ TCon Ty.optionalRef 1 [r]))
$ some r))
]
sizeb = unop0 1 $ \[b,n]
@ -578,26 +591,26 @@ t2i, t2n, t2f :: Var v => SuperNormal v
t2i = unop0 3 $ \[x,t,n0,n]
-> TLetD t UN (TPrm TTOI [x])
. TMatch t . MatchSum $ mapFromList
[ (0, ([], TCon Ty.optionalRef 0 []))
[ (0, ([], none))
, (1, ([UN], TAbs n0
. TLetD n BX (TCon Ty.intRef 0 [n0])
$ TCon Ty.optionalRef 1 [n]))
$ some n))
]
t2n = unop0 3 $ \[x,t,n0,n]
-> TLetD t UN (TPrm TTON [x])
. TMatch t . MatchSum $ mapFromList
[ (0, ([], TCon Ty.optionalRef 0 []))
[ (0, ([], none))
, (1, ([UN], TAbs n0
. TLetD n BX (TCon Ty.natRef 0 [n0])
$ TCon Ty.optionalRef 1 [n]))
$ some n))
]
t2f = unop0 3 $ \[x,t,f0,f]
-> TLetD t UN (TPrm TTOF [x])
. TMatch t . MatchSum $ mapFromList
[ (0, ([], TCon Ty.optionalRef 0 []))
[ (0, ([], none))
, (1, ([UN], TAbs f0
. TLetD f BX (TCon Ty.floatRef 0 [f0])
$ TCon Ty.optionalRef 1 [f]))
$ some f))
]
equ :: Var v => SuperNormal v
@ -734,8 +747,8 @@ code'lookup
= unop0 2 $ \[link,t,r]
-> TLetD t UN (TPrm LKUP [link])
. TMatch t . MatchSum $ mapFromList
[ (0, ([], TCon Ty.optionalRef 0 []))
, (1, ([BX], TAbs r $ TCon Ty.optionalRef 1 [r]))
[ (0, ([], none))
, (1, ([BX], TAbs r $ some r))
]
code'validate :: Var v => SuperNormal v
@ -747,9 +760,9 @@ code'validate
[ (1, ([BX, BX, BX],)
. TAbss [ref, msg, extra]
. TLetD fail BX (TCon Ty.failureRef 0 [ref, msg, extra])
$ TCon Ty.optionalRef 1 [fail])
$ some fail)
, (0, ([],)
$ TCon Ty.optionalRef 0 [])
$ none)
]
term'link'to'text :: Var v => SuperNormal v
@ -761,8 +774,8 @@ value'load
= unop0 2 $ \[vlu,t,r]
-> TLetD t UN (TPrm LOAD [vlu])
. TMatch t . MatchSum $ mapFromList
[ (0, ([BX], TAbs r $ TCon Ty.eitherRef 0 [r]))
, (1, ([BX], TAbs r $ TCon Ty.eitherRef 1 [r]))
[ (0, ([BX], TAbs r $ left r))
, (1, ([BX], TAbs r $ right r))
]
value'create :: Var v => SuperNormal v
@ -925,9 +938,9 @@ inMaybeBx arg1 arg2 arg3 mb result cont instr =
. TAbss [arg1, arg2]
. TMatch arg1 . flip (MatchData Ty.optionalRef) Nothing
$ mapFromList
[ (0, ([], TLetD mb UN (TLit $ I 0)
[ (toEnum Ty.noneId, ([], TLetD mb UN (TLit $ I 0)
$ TLetD result UN (TFOp instr [mb, arg2]) cont))
, (1, ([BX], TAbs arg3 . TLetD mb UN (TLit $ I 1) $ TLetD result UN (TFOp instr [mb, arg3, arg2]) cont))
, (toEnum Ty.someId, ([BX], TAbs arg3 . TLetD mb UN (TLit $ I 1) $ TLetD result UN (TFOp instr [mb, arg3, arg2]) cont))
]
-- a -> b -> ...
@ -967,20 +980,20 @@ inBxIomr arg1 arg2 fm result cont instr
outMaybe :: forall v. Var v => v -> v -> ANormal v
outMaybe maybe result =
TMatch result . MatchSum $ mapFromList
[ (0, ([], TCon Ty.optionalRef 0 []))
, (1, ([BX], TAbs maybe $ TCon Ty.optionalRef 1 [maybe]))
[ (0, ([], none))
, (1, ([BX], TAbs maybe $ some maybe))
]
outMaybeTup :: forall v. Var v => v -> v -> v -> v -> v -> v -> v -> ANormal v
outMaybeTup a b n u bp p result =
TMatch result . MatchSum $ mapFromList
[ (0, ([], TCon Ty.optionalRef 0 []))
[ (0, ([], none))
, (1, ([UN,BX], TAbss [a,b]
. TLetD u BX (TCon Ty.unitRef 0 [])
. TLetD bp BX (TCon Ty.pairRef 0 [b,u])
. TLetD n BX (TCon Ty.natRef 0 [a])
. TLetD p BX (TCon Ty.pairRef 0 [n,bp])
$ TCon Ty.optionalRef 1 [p]))
$ some p))
]
outIoFail :: forall v. Var v => v -> v -> v -> v -> ANormal v
@ -989,8 +1002,8 @@ outIoFail stack1 stack2 fail result =
[ (0, ([BX, BX],)
. TAbss [stack1, stack2]
. TLetD fail BX (TCon Ty.failureRef 0 [stack1, stack2])
$ TCon eitherReference 0 [fail])
, (1, ([BX], TAbs stack1 $ TCon eitherReference 1 [stack1]))
$ left fail)
, (1, ([BX], TAbs stack1 $ right stack1))
]
outIoFailNat :: forall v. Var v => v -> v -> v -> v -> v -> v -> ANormal v
@ -999,11 +1012,11 @@ outIoFailNat stack1 stack2 stack3 fail nat result =
[ (0, ([BX, BX],)
. TAbss [stack1, stack2]
. TLetD fail BX (TCon Ty.failureRef 0 [stack1, stack2])
$ TCon eitherReference 0 [fail])
$ left fail)
, (1, ([UN],)
. TAbs stack3
. TLetD nat BX (TCon Ty.natRef 0 [stack3])
$ TCon eitherReference 1 [nat])
$ right nat)
]
outIoFailBox :: forall v. Var v => v -> v -> v -> v -> ANormal v
@ -1012,10 +1025,10 @@ outIoFailBox stack1 stack2 fail result =
[ (0, ([BX, BX],)
. TAbss [stack1, stack2]
. TLetD fail BX (TCon Ty.failureRef 0 [stack1, stack2])
$ TCon eitherReference 0 [fail])
$ left fail)
, (1, ([BX],)
. TAbs stack1
$ TCon eitherReference 1 [stack1])
$ right stack1)
]
outIoFailUnit :: forall v. Var v => v -> v -> v -> v -> v -> v -> ANormal v
@ -1025,11 +1038,11 @@ outIoFailUnit stack1 stack2 stack3 unit fail result =
[ (0, ([BX, BX],)
. TAbss [stack1, stack2]
. TLetD fail BX (TCon Ty.failureRef 0 [stack1, stack2])
$ TCon eitherReference 0 [fail])
$ left fail)
, (1, ([BX],)
. TAbss [stack3]
. TLetD unit BX (TCon Ty.unitRef 0 [])
$ TCon eitherReference 1 [unit])
$ right unit)
]
outIoFailBool :: forall v. Var v => v -> v -> v -> v -> v -> v -> ANormal v
@ -1039,11 +1052,11 @@ outIoFailBool stack1 stack2 stack3 bool fail result =
[ (0, ([BX, BX],)
. TAbss [stack1, stack2]
. TLetD fail BX (TCon Ty.failureRef 0 [stack1, stack2])
$ TCon eitherReference 0 [fail])
$ left fail)
, (1, ([UN],)
. TAbs stack3
. TLet (Indirect 1) bool BX (boolift stack3)
$ TCon eitherReference 1 [bool])
$ right bool)
]
outIoFailG
@ -1055,9 +1068,9 @@ outIoFailG stack1 stack2 fail result output k
[ (0, ([BX, BX],)
. TAbss [stack1, stack2]
. TLetD fail BX (TCon Ty.failureRef 0 [stack1, stack2])
$ TCon eitherReference 0 [fail])
$ left fail)
, (1, k $ \t -> TLetD output BX t
$ TCon eitherReference 1 [output])
$ right output)
]
-- Input / Output glue
@ -1196,8 +1209,8 @@ boxToEFMBox
= inBx arg result
. outIoFailG stack1 stack2 fail result output $ \k ->
([UN], TAbs stack3 . TMatch stack3 . MatchSum $ mapFromList
[ (0, ([], k $ TCon Ty.optionalRef 0 []))
, (1, ([BX], TAbs stack4 . k $ TCon Ty.optionalRef 1 [stack4]))
[ (0, ([], k $ none))
, (1, ([BX], TAbs stack4 . k $ some stack4))
])
where
(arg, result, stack1, stack2, stack3, stack4, fail, output) = fresh8
@ -1282,10 +1295,10 @@ natToEFUnit
[ (0, ([BX, BX],)
. TAbss [stack1, stack2]
. TLetD fail BX (TCon Ty.failureRef 0 [stack1, stack2])
$ TCon eitherReference 0 [fail])
$ left fail)
, (1, ([],)
. TLetD unit BX (TCon Ty.unitRef 0 [])
$ TCon eitherReference 1 [unit])
$ right unit)
]
where
@ -1299,8 +1312,8 @@ boxToEBoxBox instr
. TLetD e UN (TFOp instr [b])
. TMatch e . MatchSum
$ mapFromList
[ (0, ([BX], TAbs ev $ TCon eitherReference 0 [ev]))
, (1, ([BX], TAbs ev $ TCon eitherReference 1 [ev]))
[ (0, ([BX], TAbs ev $ left ev))
, (1, ([BX], TAbs ev $ right ev))
]
where
(e,b,ev) = fresh3
@ -1890,6 +1903,21 @@ declareForeigns = do
in pure . Bytes.fromArray . hmac alg $ serializeValueLazy x
let
catchAll :: (MonadCatch m, MonadIO m, NFData a) => m a -> m (Either Text a)
catchAll e = do
e <- Exception.tryAnyDeep e
pure $ case e of
Left se -> Left (Text.pack (show se))
Right a -> Right a
declareForeign "Bytes.zlib.compress" boxDirect . mkForeign $ pure . Bytes.zlibCompress
declareForeign "Bytes.gzip.compress" boxDirect . mkForeign $ pure . Bytes.gzipCompress
declareForeign "Bytes.zlib.decompress" boxToEBoxBox . mkForeign $ \bs ->
catchAll (pure (Bytes.zlibDecompress bs))
declareForeign "Bytes.gzip.decompress" boxToEBoxBox . mkForeign $ \bs ->
catchAll (pure (Bytes.gzipDecompress bs))
declareForeign "Bytes.toBase16" boxDirect . mkForeign $ pure . Bytes.toBase16
declareForeign "Bytes.toBase32" boxDirect . mkForeign $ pure . Bytes.toBase32
declareForeign "Bytes.toBase64" boxDirect . mkForeign $ pure . Bytes.toBase64

View File

@ -16,7 +16,6 @@ import qualified Network.URI.Encode as URI
import Control.Lens ((&), (.~))
import Data.Aeson ()
import qualified Data.ByteString as Strict
import qualified Data.ByteString.Base64 as Base64
import qualified Data.ByteString.Char8 as C8
import qualified Data.ByteString.Lazy as Lazy
import qualified Data.ByteString.Lazy.UTF8 as BLU
@ -27,6 +26,7 @@ import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import GHC.Generics ()
import Network.HTTP.Media ((//), (/:))
import Data.NanoID (customNanoID, defaultAlphabet, unNanoID)
import Network.HTTP.Types.Status (ok200)
import Network.Wai (responseLBS)
import Network.Wai.Handler.Warp
@ -75,7 +75,7 @@ import System.Directory (canonicalizePath, doesFileExist)
import System.Environment (getExecutablePath)
import System.FilePath ((</>))
import qualified System.FilePath as FilePath
import System.Random.Stateful (getStdGen, newAtomicGenM, uniformByteStringM)
import System.Random.MWC (createSystemRandom)
import Unison.Codebase (Codebase)
import qualified Unison.Codebase.Runtime as Rt
import Unison.Parser.Ann (Ann)
@ -186,11 +186,13 @@ app
app rt codebase uiPath expectedToken =
serve serverAPI $ server rt codebase uiPath expectedToken
-- The Token is used to help prevent multiple users on a machine gain access to
-- each others codebases.
genToken :: IO Strict.ByteString
genToken = do
gen <- getStdGen
g <- newAtomicGenM gen
Base64.encode <$> uniformByteStringM 24 g
g <- createSystemRandom
n <- customNanoID defaultAlphabet 16 g
pure $ unNanoID n
data Waiter a
= Waiter {

View File

@ -3,6 +3,7 @@
module Unison.Util.Bytes where
import Control.DeepSeq (NFData(..))
import Data.Bits (shiftR, shiftL, (.|.))
import Data.Char
import Data.Memory.PtrMethods (memCompare, memEqual)
@ -17,6 +18,8 @@ import qualified Data.ByteArray as B
import qualified Data.ByteArray.Encoding as BE
import qualified Data.FingerTree as T
import qualified Data.Text as Text
import qualified Codec.Compression.Zlib as Zlib
import qualified Codec.Compression.GZip as GZip
-- Block is just `newtype Block a = Block ByteArray#`
type ByteString = Block Word8
@ -35,12 +38,27 @@ empty = Bytes mempty
fromArray :: B.ByteArrayAccess ba => ba -> Bytes
fromArray = snoc empty
zlibCompress :: Bytes -> Bytes
zlibCompress = fromLazyByteString . Zlib.compress . toLazyByteString
gzipCompress :: Bytes -> Bytes
gzipCompress = fromLazyByteString . GZip.compress . toLazyByteString
gzipDecompress :: Bytes -> Bytes
gzipDecompress = fromLazyByteString . GZip.decompress . toLazyByteString
zlibDecompress :: Bytes -> Bytes
zlibDecompress = fromLazyByteString . Zlib.decompress . toLazyByteString
toArray :: forall bo . B.ByteArray bo => Bytes -> bo
toArray b = B.concat (map B.convert (chunks b) :: [bo])
toLazyByteString :: Bytes -> LB.ByteString
toLazyByteString b = LB.fromChunks $ map B.convert $ chunks b
fromLazyByteString :: LB.ByteString -> Bytes
fromLazyByteString b = fromChunks (map (view . B.convert) $ LB.toChunks b)
size :: Bytes -> Int
size (Bytes bs) = getSum (T.measure bs)
@ -361,3 +379,9 @@ instance B.ByteArrayAccess bytes => B.ByteArrayAccess (View bytes) where
length = viewSize
withByteArray v f = B.withByteArray (unView v) $
\ptr -> f (ptr `plusPtr` (viewOffset v))
instance NFData (View bs) where
rnf bs = seq bs ()
instance NFData Bytes where
rnf bs = rnf (chunks bs)

View File

@ -12,8 +12,10 @@ import Text.Megaparsec
test :: Test ()
test = scope "versionparser" . tests . fmap makeTest $
[ ("release/M1j", "releases._M1j")
, ("release/M1j.2", "releases._M1j")
, ("release/M1j.2", "releases._M1j_2")
, ("latest-abc", "trunk")
, ("release/M2i_3", "releases._M2i_3")
, ("release/M2i-HOTFIX", "releases._M2i_HOTFIX")
]
makeTest :: (Text, Text) -> Test ()

View File

@ -213,6 +213,7 @@ library
ghc-options: -Wall -O0 -fno-warn-name-shadowing -fno-warn-missing-pattern-synonym-signatures
build-depends:
ListLike
, NanoID
, aeson
, ansi-terminal
, async
@ -228,6 +229,7 @@ library
, cryptonite
, data-default
, data-memocombinators
, deepseq
, directory
, either
, errors
@ -250,6 +252,7 @@ library
, monad-validate
, mtl
, mutable-containers
, mwc-random
, natural-transformation
, network
, network-simple
@ -300,6 +303,7 @@ library
, x509
, x509-store
, x509-system
, zlib
if flag(optimized)
ghc-options: -funbox-strict-fields -O2
default-language: Haskell2010

View File

@ -58,6 +58,7 @@ import ArgParse
parseCLIArgs )
import Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as NonEmpty
import Unison.CommandLine.Welcome (CodebaseInitStatus(..))
main :: IO ()
main = do
@ -65,7 +66,7 @@ main = do
-- hSetBuffering stdout NoBuffering -- cool
void installSignalHandlers
(renderUsageInfo, globalOptions, command) <- parseCLIArgs progName Version.gitDescribe
(renderUsageInfo, globalOptions, command) <- parseCLIArgs progName Version.gitDescribeWithDate
let GlobalOptions{codebasePathOption=mCodePathOption} = globalOptions
let mcodepath = fmap codebasePathOptionToPath mCodePathOption
@ -76,7 +77,7 @@ main = do
Exit.die "Your .unisonConfig could not be loaded. Check that it's correct!"
case command of
PrintVersion ->
putStrLn $ progName ++ " version: " ++ Version.gitDescribe
putStrLn $ progName ++ " version: " ++ Version.gitDescribeWithDate
Init -> do
PT.putPrettyLn $
P.callout
@ -91,7 +92,7 @@ main = do
])
Run (RunFromSymbol mainName) -> do
(closeCodebase, theCodebase) <- getCodebaseOrExit mCodePathOption
((closeCodebase, theCodebase),_) <- getCodebaseOrExit mCodePathOption
runtime <- RTI.startRuntime
execute theCodebase runtime mainName
closeCodebase
@ -102,17 +103,17 @@ main = do
case e of
Left _ -> PT.putPrettyLn $ P.callout "⚠️" "I couldn't find that file or it is for some reason unreadable."
Right contents -> do
(closeCodebase, theCodebase) <- getCodebaseOrExit mCodePathOption
((closeCodebase, theCodebase), initRes) <- getCodebaseOrExit mCodePathOption
rt <- RTI.startRuntime
let fileEvent = Input.UnisonFileChanged (Text.pack file) contents
launch currentDir config rt theCodebase [Left fileEvent, Right $ Input.ExecuteI mainName, Right Input.QuitI] Nothing ShouldNotDownloadBase
launch currentDir config rt theCodebase [Left fileEvent, Right $ Input.ExecuteI mainName, Right Input.QuitI] Nothing ShouldNotDownloadBase initRes
closeCodebase
Run (RunFromPipe mainName) -> do
e <- safeReadUtf8StdIn
case e of
Left _ -> PT.putPrettyLn $ P.callout "⚠️" "I had trouble reading this input."
Right contents -> do
(closeCodebase, theCodebase) <- getCodebaseOrExit mCodePathOption
((closeCodebase, theCodebase), initRes) <- getCodebaseOrExit mCodePathOption
rt <- RTI.startRuntime
let fileEvent = Input.UnisonFileChanged (Text.pack "<standard input>") contents
launch
@ -120,11 +121,12 @@ main = do
[Left fileEvent, Right $ Input.ExecuteI mainName, Right Input.QuitI]
Nothing
ShouldNotDownloadBase
initRes
closeCodebase
Transcript shouldFork shouldSaveCodebase transcriptFiles ->
runTranscripts renderUsageInfo shouldFork shouldSaveCodebase mCodePathOption transcriptFiles
Launch isHeadless codebaseServerOpts downloadBase -> do
(closeCodebase, theCodebase) <- getCodebaseOrExit mCodePathOption
((closeCodebase, theCodebase),initRes) <- getCodebaseOrExit mCodePathOption
runtime <- RTI.startRuntime
Server.startServer codebaseServerOpts runtime theCodebase $ \baseUrl -> do
case isHeadless of
@ -146,7 +148,7 @@ main = do
takeMVar mvar
WithCLI -> do
PT.putPrettyLn $ P.string "Now starting the Unison Codebase Manager (UCM)..."
launch currentDir config runtime theCodebase [] (Just baseUrl) downloadBase
launch currentDir config runtime theCodebase [] (Just baseUrl) downloadBase initRes
closeCodebase
prepareTranscriptDir :: ShouldForkCodebase -> Maybe CodebasePathOption -> IO FilePath
@ -187,7 +189,7 @@ runTranscripts' mcodepath transcriptDir args = do
Right stanzas -> do
configFilePath <- getConfigFilePath mcodepath
-- We don't need to create a codebase through `getCodebaseOrExit` as we've already done so previously.
(closeCodebase, theCodebase) <- getCodebaseOrExit (Just (DontCreateCodebaseWhenMissing transcriptDir))
((closeCodebase, theCodebase),_) <- getCodebaseOrExit (Just (DontCreateCodebaseWhenMissing transcriptDir))
mdOut <- TR.run transcriptDir configFilePath stanzas theCodebase
closeCodebase
let out = currentDir FP.</>
@ -246,14 +248,19 @@ launch
-> [Either Input.Event Input.Input]
-> Maybe Server.BaseUrl
-> ShouldDownloadBase
-> InitResult IO Symbol Ann
-> IO ()
launch dir config runtime codebase inputs serverBaseUrl shouldDownloadBase =
launch dir config runtime codebase inputs serverBaseUrl shouldDownloadBase initResult =
let
downloadBase = case defaultBaseLib of
Just remoteNS | shouldDownloadBase == ShouldDownloadBase -> Welcome.DownloadBase remoteNS
_ -> Welcome.DontDownloadBase
isNewCodebase = case initResult of
CreatedCodebase{} -> NewlyCreatedCodebase
_ -> PreviouslyCreatedCodebase
welcome = Welcome.Welcome downloadBase dir Version.gitDescribe
(gitRef, _date) = Version.gitDescribe
welcome = Welcome.welcome isNewCodebase downloadBase dir gitRef
in
CommandLine.main
dir
@ -284,9 +291,11 @@ getConfigFilePath mcodepath = (FP.</> ".unisonConfig") <$> Codebase.getCodebaseD
defaultBaseLib :: Maybe ReadRemoteNamespace
defaultBaseLib = rightMay $
runParser VP.defaultBaseLib "version" (Text.pack Version.gitDescribe)
getCodebaseOrExit :: Maybe CodebasePathOption -> IO (IO (), Codebase.Codebase IO Symbol Ann)
runParser VP.defaultBaseLib "version" (Text.pack gitRef)
where
(gitRef, _date) = Version.gitDescribe
-- (Unison.Codebase.Init.FinalizerAndCodebase IO Symbol Ann, InitResult IO Symbol Ann)
getCodebaseOrExit :: Maybe CodebasePathOption -> IO ((IO (), Codebase.Codebase IO Symbol Ann), InitResult IO Symbol Ann)
getCodebaseOrExit codebasePathOption = do
initOptions <- argsToCodebaseInitOptions codebasePathOption
CodebaseInit.openOrCreateCodebase SC.init "main" initOptions >>= \case
@ -316,14 +325,14 @@ getCodebaseOrExit codebasePathOption = do
PT.putPrettyLn' msg
Exit.exitFailure
CreatedCodebase dir cb -> do
c@(CreatedCodebase dir cb) -> do
pDir <- prettyDir dir
PT.putPrettyLn' ""
PT.putPrettyLn' . P.indentN 2 . P.wrap $ "I created a new codebase for you at" <> P.blue pDir
pure cb
pure (cb, c)
OpenedCodebase _ cb ->
pure cb
o@(OpenedCodebase _ cb) ->
pure (cb, o)
where
prettyDir dir = P.string <$> canonicalizePath dir

View File

@ -3,23 +3,37 @@
module Version where
import Language.Haskell.TH (runIO)
import Language.Haskell.TH (runIO, Exp(TupE))
import Language.Haskell.TH.Syntax (Exp(LitE), Lit(StringL))
import Shellmet
import Data.Text
-- | A formatted descriptor of when and against which commit this unison executable was built
-- E.g. latest-149-g5cef8f851 (built on 2021-10-04)
-- release/M2i (built on 2021-10-05)
gitDescribeWithDate :: String
gitDescribeWithDate =
let formatDate d = " (built on " <> d <> ")"
(gitRef, date) = gitDescribe
in gitRef <> formatDate date
type CommitDate = String
type GitRef = String
-- | Uses Template Haskell to embed a git descriptor of the commit
-- which was used to build the executable.
gitDescribe :: String
gitDescribe = $( fmap (LitE . StringL . unpack) . runIO $ do
let formatDate d = " (built on " <> d <> ")"
-- E.g. latest-149-g5cef8f851 (built on 2021-10-04)
-- release/M2i (built on 2021-10-05)
gitDescribe :: (GitRef, CommitDate)
gitDescribe = $( runIO $ do
-- Outputs date of current commit; E.g. 2021-08-06
let getDate = "git" $| ["show", "-s", "--format=%cs"]
date <- (formatDate <$> getDate) $? pure ""
date <- getDate $? pure ""
-- Fetches a unique tag-name to represent the current commit.
-- Uses human-readable names whenever possible.
-- Marks version with a `'` suffix if building on a dirty worktree.
let getTag = "git" $| ["describe", "--tags", "--always", "--dirty='"]
tag <- getTag $? pure "unknown"
pure (tag <> date)
pure (TupE [Just . LitE . StringL . unpack $ tag, Just . LitE . StringL . unpack $ date])
)

View File

@ -39,6 +39,7 @@ extra-deps:
- strings-1.1@sha256:0285dec4c8ab262359342b3e5ef1eb567074669461b9b38404f1cb870c881c5c,1617
- fuzzyfind-3.0.0
- monad-validate-1.2.0.0@sha256:9850f408431098b28806dd464b6825a88a0b56c84f380d7fe0454c1df9d6f881,3505
- NanoID-3.1.0@sha256:9118ab00e8650b5a56a10c90295d357eb77a8057a598b7e56dfedc9c6d53c77d,1524
ghc-options:
# All packages

View File

@ -27,13 +27,15 @@ Unison has cryptographic builtins for hashing and computing [HMACs](https://en.w
20. fromBase64 (Bytes -> Either Text Bytes)
21. fromBase64UrlUnpadded (Bytes -> Either Text Bytes)
22. fromList ([Nat] -> Bytes)
23. size (Bytes -> Nat)
24. take (Nat -> Bytes -> Bytes)
25. toBase16 (Bytes -> Bytes)
26. toBase32 (Bytes -> Bytes)
27. toBase64 (Bytes -> Bytes)
28. toBase64UrlUnpadded (Bytes -> Bytes)
29. toList (Bytes -> [Nat])
23. gzip/ (2 definitions)
24. size (Bytes -> Nat)
25. take (Nat -> Bytes -> Bytes)
26. toBase16 (Bytes -> Bytes)
27. toBase32 (Bytes -> Bytes)
28. toBase64 (Bytes -> Bytes)
29. toBase64UrlUnpadded (Bytes -> Bytes)
30. toList (Bytes -> [Nat])
31. zlib/ (2 definitions)
```
Notice the `fromBase16` and `toBase16` functions. Here's some convenience functions for converting `Bytes` to and from base-16 `Text`.

View File

@ -47,420 +47,424 @@ Let's try it!
27. Bytes.fromBase64 : Bytes -> Either Text Bytes
28. Bytes.fromBase64UrlUnpadded : Bytes -> Either Text Bytes
29. Bytes.fromList : [Nat] -> Bytes
30. Bytes.size : Bytes -> Nat
31. Bytes.take : Nat -> Bytes -> Bytes
32. Bytes.toBase16 : Bytes -> Bytes
33. Bytes.toBase32 : Bytes -> Bytes
34. Bytes.toBase64 : Bytes -> Bytes
35. Bytes.toBase64UrlUnpadded : Bytes -> Bytes
36. Bytes.toList : Bytes -> [Nat]
37. builtin type Char
38. Char.fromNat : Nat -> Char
39. Char.toNat : Char -> Nat
40. Char.toText : Char -> Text
41. builtin type Code
42. Code.cache_ : [(Term, Code)] ->{IO} [Term]
43. Code.dependencies : Code -> [Term]
44. Code.deserialize : Bytes -> Either Text Code
45. Code.display : Text -> Code -> Text
46. Code.isMissing : Term ->{IO} Boolean
47. Code.lookup : Term ->{IO} Optional Code
48. Code.serialize : Code -> Bytes
49. Code.validate : [(Term, Code)] ->{IO} Optional Failure
50. crypto.hash : HashAlgorithm -> a -> Bytes
51. builtin type crypto.HashAlgorithm
52. crypto.HashAlgorithm.Blake2b_256 : HashAlgorithm
53. crypto.HashAlgorithm.Blake2b_512 : HashAlgorithm
54. crypto.HashAlgorithm.Blake2s_256 : HashAlgorithm
55. crypto.HashAlgorithm.Sha2_256 : HashAlgorithm
56. crypto.HashAlgorithm.Sha2_512 : HashAlgorithm
57. crypto.HashAlgorithm.Sha3_256 : HashAlgorithm
58. crypto.HashAlgorithm.Sha3_512 : HashAlgorithm
59. crypto.hashBytes : HashAlgorithm -> Bytes -> Bytes
60. crypto.hmac : HashAlgorithm -> Bytes -> a -> Bytes
61. crypto.hmacBytes : HashAlgorithm
30. Bytes.gzip.compress : Bytes -> Bytes
31. Bytes.gzip.decompress : Bytes -> Either Text Bytes
32. Bytes.size : Bytes -> Nat
33. Bytes.take : Nat -> Bytes -> Bytes
34. Bytes.toBase16 : Bytes -> Bytes
35. Bytes.toBase32 : Bytes -> Bytes
36. Bytes.toBase64 : Bytes -> Bytes
37. Bytes.toBase64UrlUnpadded : Bytes -> Bytes
38. Bytes.toList : Bytes -> [Nat]
39. Bytes.zlib.compress : Bytes -> Bytes
40. Bytes.zlib.decompress : Bytes -> Either Text Bytes
41. builtin type Char
42. Char.fromNat : Nat -> Char
43. Char.toNat : Char -> Nat
44. Char.toText : Char -> Text
45. builtin type Code
46. Code.cache_ : [(Term, Code)] ->{IO} [Term]
47. Code.dependencies : Code -> [Term]
48. Code.deserialize : Bytes -> Either Text Code
49. Code.display : Text -> Code -> Text
50. Code.isMissing : Term ->{IO} Boolean
51. Code.lookup : Term ->{IO} Optional Code
52. Code.serialize : Code -> Bytes
53. Code.validate : [(Term, Code)] ->{IO} Optional Failure
54. crypto.hash : HashAlgorithm -> a -> Bytes
55. builtin type crypto.HashAlgorithm
56. crypto.HashAlgorithm.Blake2b_256 : HashAlgorithm
57. crypto.HashAlgorithm.Blake2b_512 : HashAlgorithm
58. crypto.HashAlgorithm.Blake2s_256 : HashAlgorithm
59. crypto.HashAlgorithm.Sha2_256 : HashAlgorithm
60. crypto.HashAlgorithm.Sha2_512 : HashAlgorithm
61. crypto.HashAlgorithm.Sha3_256 : HashAlgorithm
62. crypto.HashAlgorithm.Sha3_512 : HashAlgorithm
63. crypto.hashBytes : HashAlgorithm -> Bytes -> Bytes
64. crypto.hmac : HashAlgorithm -> Bytes -> a -> Bytes
65. crypto.hmacBytes : HashAlgorithm
-> Bytes
-> Bytes
-> Bytes
62. Debug.watch : Text -> a -> a
63. unique type Doc
64. Doc.Blob : Text -> Doc
65. Doc.Evaluate : Term -> Doc
66. Doc.Join : [Doc] -> Doc
67. Doc.Link : Link -> Doc
68. Doc.Signature : Term -> Doc
69. Doc.Source : Link -> Doc
70. structural type Either a b
71. Either.Left : a -> Either a b
72. Either.Right : b -> Either a b
73. structural ability Exception
74. Exception.raise : Failure ->{Exception} x
75. builtin type Float
76. Float.* : Float -> Float -> Float
77. Float.+ : Float -> Float -> Float
78. Float.- : Float -> Float -> Float
79. Float./ : Float -> Float -> Float
80. Float.abs : Float -> Float
81. Float.acos : Float -> Float
82. Float.acosh : Float -> Float
83. Float.asin : Float -> Float
84. Float.asinh : Float -> Float
85. Float.atan : Float -> Float
86. Float.atan2 : Float -> Float -> Float
87. Float.atanh : Float -> Float
88. Float.ceiling : Float -> Int
89. Float.cos : Float -> Float
90. Float.cosh : Float -> Float
91. Float.eq : Float -> Float -> Boolean
92. Float.exp : Float -> Float
93. Float.floor : Float -> Int
94. Float.fromRepresentation : Nat -> Float
95. Float.fromText : Text -> Optional Float
96. Float.gt : Float -> Float -> Boolean
97. Float.gteq : Float -> Float -> Boolean
98. Float.log : Float -> Float
99. Float.logBase : Float -> Float -> Float
100. Float.lt : Float -> Float -> Boolean
101. Float.lteq : Float -> Float -> Boolean
102. Float.max : Float -> Float -> Float
103. Float.min : Float -> Float -> Float
104. Float.pow : Float -> Float -> Float
105. Float.round : Float -> Int
106. Float.sin : Float -> Float
107. Float.sinh : Float -> Float
108. Float.sqrt : Float -> Float
109. Float.tan : Float -> Float
110. Float.tanh : Float -> Float
111. Float.toRepresentation : Float -> Nat
112. Float.toText : Float -> Text
113. Float.truncate : Float -> Int
114. builtin type Int
115. Int.* : Int -> Int -> Int
116. Int.+ : Int -> Int -> Int
117. Int.- : Int -> Int -> Int
118. Int./ : Int -> Int -> Int
119. Int.and : Int -> Int -> Int
120. Int.complement : Int -> Int
121. Int.eq : Int -> Int -> Boolean
122. Int.fromRepresentation : Nat -> Int
123. Int.fromText : Text -> Optional Int
124. Int.gt : Int -> Int -> Boolean
125. Int.gteq : Int -> Int -> Boolean
126. Int.increment : Int -> Int
127. Int.isEven : Int -> Boolean
128. Int.isOdd : Int -> Boolean
129. Int.leadingZeros : Int -> Nat
130. Int.lt : Int -> Int -> Boolean
131. Int.lteq : Int -> Int -> Boolean
132. Int.mod : Int -> Int -> Int
133. Int.negate : Int -> Int
134. Int.or : Int -> Int -> Int
135. Int.popCount : Int -> Nat
136. Int.pow : Int -> Nat -> Int
137. Int.shiftLeft : Int -> Nat -> Int
138. Int.shiftRight : Int -> Nat -> Int
139. Int.signum : Int -> Int
140. Int.toFloat : Int -> Float
141. Int.toRepresentation : Int -> Nat
142. Int.toText : Int -> Text
143. Int.trailingZeros : Int -> Nat
144. Int.truncate0 : Int -> Nat
145. Int.xor : Int -> Int -> Int
146. unique type io2.BufferMode
147. io2.BufferMode.BlockBuffering : BufferMode
148. io2.BufferMode.LineBuffering : BufferMode
149. io2.BufferMode.NoBuffering : BufferMode
150. io2.BufferMode.SizedBlockBuffering : Nat -> BufferMode
151. unique type io2.Failure
152. io2.Failure.Failure : Type -> Text -> Any -> Failure
153. unique type io2.FileMode
154. io2.FileMode.Append : FileMode
155. io2.FileMode.Read : FileMode
156. io2.FileMode.ReadWrite : FileMode
157. io2.FileMode.Write : FileMode
158. builtin type io2.Handle
159. builtin type io2.IO
160. io2.IO.clientSocket.impl : Text
66. Debug.watch : Text -> a -> a
67. unique type Doc
68. Doc.Blob : Text -> Doc
69. Doc.Evaluate : Term -> Doc
70. Doc.Join : [Doc] -> Doc
71. Doc.Link : Link -> Doc
72. Doc.Signature : Term -> Doc
73. Doc.Source : Link -> Doc
74. structural type Either a b
75. Either.Left : a -> Either a b
76. Either.Right : b -> Either a b
77. structural ability Exception
78. Exception.raise : Failure ->{Exception} x
79. builtin type Float
80. Float.* : Float -> Float -> Float
81. Float.+ : Float -> Float -> Float
82. Float.- : Float -> Float -> Float
83. Float./ : Float -> Float -> Float
84. Float.abs : Float -> Float
85. Float.acos : Float -> Float
86. Float.acosh : Float -> Float
87. Float.asin : Float -> Float
88. Float.asinh : Float -> Float
89. Float.atan : Float -> Float
90. Float.atan2 : Float -> Float -> Float
91. Float.atanh : Float -> Float
92. Float.ceiling : Float -> Int
93. Float.cos : Float -> Float
94. Float.cosh : Float -> Float
95. Float.eq : Float -> Float -> Boolean
96. Float.exp : Float -> Float
97. Float.floor : Float -> Int
98. Float.fromRepresentation : Nat -> Float
99. Float.fromText : Text -> Optional Float
100. Float.gt : Float -> Float -> Boolean
101. Float.gteq : Float -> Float -> Boolean
102. Float.log : Float -> Float
103. Float.logBase : Float -> Float -> Float
104. Float.lt : Float -> Float -> Boolean
105. Float.lteq : Float -> Float -> Boolean
106. Float.max : Float -> Float -> Float
107. Float.min : Float -> Float -> Float
108. Float.pow : Float -> Float -> Float
109. Float.round : Float -> Int
110. Float.sin : Float -> Float
111. Float.sinh : Float -> Float
112. Float.sqrt : Float -> Float
113. Float.tan : Float -> Float
114. Float.tanh : Float -> Float
115. Float.toRepresentation : Float -> Nat
116. Float.toText : Float -> Text
117. Float.truncate : Float -> Int
118. builtin type Int
119. Int.* : Int -> Int -> Int
120. Int.+ : Int -> Int -> Int
121. Int.- : Int -> Int -> Int
122. Int./ : Int -> Int -> Int
123. Int.and : Int -> Int -> Int
124. Int.complement : Int -> Int
125. Int.eq : Int -> Int -> Boolean
126. Int.fromRepresentation : Nat -> Int
127. Int.fromText : Text -> Optional Int
128. Int.gt : Int -> Int -> Boolean
129. Int.gteq : Int -> Int -> Boolean
130. Int.increment : Int -> Int
131. Int.isEven : Int -> Boolean
132. Int.isOdd : Int -> Boolean
133. Int.leadingZeros : Int -> Nat
134. Int.lt : Int -> Int -> Boolean
135. Int.lteq : Int -> Int -> Boolean
136. Int.mod : Int -> Int -> Int
137. Int.negate : Int -> Int
138. Int.or : Int -> Int -> Int
139. Int.popCount : Int -> Nat
140. Int.pow : Int -> Nat -> Int
141. Int.shiftLeft : Int -> Nat -> Int
142. Int.shiftRight : Int -> Nat -> Int
143. Int.signum : Int -> Int
144. Int.toFloat : Int -> Float
145. Int.toRepresentation : Int -> Nat
146. Int.toText : Int -> Text
147. Int.trailingZeros : Int -> Nat
148. Int.truncate0 : Int -> Nat
149. Int.xor : Int -> Int -> Int
150. unique type io2.BufferMode
151. io2.BufferMode.BlockBuffering : BufferMode
152. io2.BufferMode.LineBuffering : BufferMode
153. io2.BufferMode.NoBuffering : BufferMode
154. io2.BufferMode.SizedBlockBuffering : Nat -> BufferMode
155. unique type io2.Failure
156. io2.Failure.Failure : Type -> Text -> Any -> Failure
157. unique type io2.FileMode
158. io2.FileMode.Append : FileMode
159. io2.FileMode.Read : FileMode
160. io2.FileMode.ReadWrite : FileMode
161. io2.FileMode.Write : FileMode
162. builtin type io2.Handle
163. builtin type io2.IO
164. io2.IO.clientSocket.impl : Text
-> Text
->{IO} Either Failure Socket
161. io2.IO.closeFile.impl : Handle ->{IO} Either Failure ()
162. io2.IO.closeSocket.impl : Socket ->{IO} Either Failure ()
163. io2.IO.createDirectory.impl : Text
165. io2.IO.closeFile.impl : Handle ->{IO} Either Failure ()
166. io2.IO.closeSocket.impl : Socket ->{IO} Either Failure ()
167. io2.IO.createDirectory.impl : Text
->{IO} Either Failure ()
164. io2.IO.createTempDirectory.impl : Text
168. io2.IO.createTempDirectory.impl : Text
->{IO} Either
Failure Text
165. io2.IO.delay.impl : Nat ->{IO} Either Failure ()
166. io2.IO.directoryContents.impl : Text
169. io2.IO.delay.impl : Nat ->{IO} Either Failure ()
170. io2.IO.directoryContents.impl : Text
->{IO} Either
Failure [Text]
167. io2.IO.fileExists.impl : Text
171. io2.IO.fileExists.impl : Text
->{IO} Either Failure Boolean
168. io2.IO.forkComp : '{IO} a ->{IO} ThreadId
169. io2.IO.getBuffering.impl : Handle
172. io2.IO.forkComp : '{IO} a ->{IO} ThreadId
173. io2.IO.getBuffering.impl : Handle
->{IO} Either
Failure BufferMode
170. io2.IO.getBytes.impl : Handle
174. io2.IO.getBytes.impl : Handle
-> Nat
->{IO} Either Failure Bytes
171. io2.IO.getCurrentDirectory.impl : '{IO} Either
175. io2.IO.getCurrentDirectory.impl : '{IO} Either
Failure Text
172. io2.IO.getEnv.impl : Text ->{IO} Either Failure Text
173. io2.IO.getFileSize.impl : Text ->{IO} Either Failure Nat
174. io2.IO.getFileTimestamp.impl : Text
176. io2.IO.getEnv.impl : Text ->{IO} Either Failure Text
177. io2.IO.getFileSize.impl : Text ->{IO} Either Failure Nat
178. io2.IO.getFileTimestamp.impl : Text
->{IO} Either Failure Nat
175. io2.IO.getLine.impl : Handle ->{IO} Either Failure Text
176. io2.IO.getTempDirectory.impl : '{IO} Either Failure Text
177. io2.IO.handlePosition.impl : Handle
179. io2.IO.getLine.impl : Handle ->{IO} Either Failure Text
180. io2.IO.getTempDirectory.impl : '{IO} Either Failure Text
181. io2.IO.handlePosition.impl : Handle
->{IO} Either Failure Nat
178. io2.IO.isDirectory.impl : Text
182. io2.IO.isDirectory.impl : Text
->{IO} Either Failure Boolean
179. io2.IO.isFileEOF.impl : Handle
183. io2.IO.isFileEOF.impl : Handle
->{IO} Either Failure Boolean
180. io2.IO.isFileOpen.impl : Handle
184. io2.IO.isFileOpen.impl : Handle
->{IO} Either Failure Boolean
181. io2.IO.isSeekable.impl : Handle
185. io2.IO.isSeekable.impl : Handle
->{IO} Either Failure Boolean
182. io2.IO.kill.impl : ThreadId ->{IO} Either Failure ()
183. io2.IO.listen.impl : Socket ->{IO} Either Failure ()
184. io2.IO.openFile.impl : Text
186. io2.IO.kill.impl : ThreadId ->{IO} Either Failure ()
187. io2.IO.listen.impl : Socket ->{IO} Either Failure ()
188. io2.IO.openFile.impl : Text
-> FileMode
->{IO} Either Failure Handle
185. io2.IO.putBytes.impl : Handle
189. io2.IO.putBytes.impl : Handle
-> Bytes
->{IO} Either Failure ()
186. io2.IO.ref : a ->{IO} Ref {IO} a
187. io2.IO.removeDirectory.impl : Text
190. io2.IO.ref : a ->{IO} Ref {IO} a
191. io2.IO.removeDirectory.impl : Text
->{IO} Either Failure ()
188. io2.IO.removeFile.impl : Text ->{IO} Either Failure ()
189. io2.IO.renameDirectory.impl : Text
192. io2.IO.removeFile.impl : Text ->{IO} Either Failure ()
193. io2.IO.renameDirectory.impl : Text
-> Text
->{IO} Either Failure ()
190. io2.IO.renameFile.impl : Text
194. io2.IO.renameFile.impl : Text
-> Text
->{IO} Either Failure ()
191. io2.IO.seekHandle.impl : Handle
195. io2.IO.seekHandle.impl : Handle
-> SeekMode
-> Int
->{IO} Either Failure ()
192. io2.IO.serverSocket.impl : Optional Text
196. io2.IO.serverSocket.impl : Optional Text
-> Text
->{IO} Either Failure Socket
193. io2.IO.setBuffering.impl : Handle
197. io2.IO.setBuffering.impl : Handle
-> BufferMode
->{IO} Either Failure ()
194. io2.IO.setCurrentDirectory.impl : Text
198. io2.IO.setCurrentDirectory.impl : Text
->{IO} Either
Failure ()
195. io2.IO.socketAccept.impl : Socket
199. io2.IO.socketAccept.impl : Socket
->{IO} Either Failure Socket
196. io2.IO.socketPort.impl : Socket ->{IO} Either Failure Nat
197. io2.IO.socketReceive.impl : Socket
200. io2.IO.socketPort.impl : Socket ->{IO} Either Failure Nat
201. io2.IO.socketReceive.impl : Socket
-> Nat
->{IO} Either Failure Bytes
198. io2.IO.socketSend.impl : Socket
202. io2.IO.socketSend.impl : Socket
-> Bytes
->{IO} Either Failure ()
199. io2.IO.stdHandle : StdHandle -> Handle
200. io2.IO.systemTime.impl : '{IO} Either Failure Nat
201. io2.IO.systemTimeMicroseconds : '{IO} Int
202. unique type io2.IOError
203. io2.IOError.AlreadyExists : IOError
204. io2.IOError.EOF : IOError
205. io2.IOError.IllegalOperation : IOError
206. io2.IOError.NoSuchThing : IOError
207. io2.IOError.PermissionDenied : IOError
208. io2.IOError.ResourceBusy : IOError
209. io2.IOError.ResourceExhausted : IOError
210. io2.IOError.UserError : IOError
211. unique type io2.IOFailure
212. builtin type io2.MVar
213. io2.MVar.isEmpty : MVar a ->{IO} Boolean
214. io2.MVar.new : a ->{IO} MVar a
215. io2.MVar.newEmpty : '{IO} MVar a
216. io2.MVar.put.impl : MVar a -> a ->{IO} Either Failure ()
217. io2.MVar.read.impl : MVar a ->{IO} Either Failure a
218. io2.MVar.swap.impl : MVar a -> a ->{IO} Either Failure a
219. io2.MVar.take.impl : MVar a ->{IO} Either Failure a
220. io2.MVar.tryPut.impl : MVar a
203. io2.IO.stdHandle : StdHandle -> Handle
204. io2.IO.systemTime.impl : '{IO} Either Failure Nat
205. io2.IO.systemTimeMicroseconds : '{IO} Int
206. unique type io2.IOError
207. io2.IOError.AlreadyExists : IOError
208. io2.IOError.EOF : IOError
209. io2.IOError.IllegalOperation : IOError
210. io2.IOError.NoSuchThing : IOError
211. io2.IOError.PermissionDenied : IOError
212. io2.IOError.ResourceBusy : IOError
213. io2.IOError.ResourceExhausted : IOError
214. io2.IOError.UserError : IOError
215. unique type io2.IOFailure
216. builtin type io2.MVar
217. io2.MVar.isEmpty : MVar a ->{IO} Boolean
218. io2.MVar.new : a ->{IO} MVar a
219. io2.MVar.newEmpty : '{IO} MVar a
220. io2.MVar.put.impl : MVar a -> a ->{IO} Either Failure ()
221. io2.MVar.read.impl : MVar a ->{IO} Either Failure a
222. io2.MVar.swap.impl : MVar a -> a ->{IO} Either Failure a
223. io2.MVar.take.impl : MVar a ->{IO} Either Failure a
224. io2.MVar.tryPut.impl : MVar a
-> a
->{IO} Either Failure Boolean
221. io2.MVar.tryRead.impl : MVar a
225. io2.MVar.tryRead.impl : MVar a
->{IO} Either
Failure (Optional a)
222. io2.MVar.tryTake : MVar a ->{IO} Optional a
223. unique type io2.SeekMode
224. io2.SeekMode.AbsoluteSeek : SeekMode
225. io2.SeekMode.RelativeSeek : SeekMode
226. io2.SeekMode.SeekFromEnd : SeekMode
227. builtin type io2.Socket
228. unique type io2.StdHandle
229. io2.StdHandle.StdErr : StdHandle
230. io2.StdHandle.StdIn : StdHandle
231. io2.StdHandle.StdOut : StdHandle
232. builtin type io2.STM
233. io2.STM.atomically : '{STM} a ->{IO} a
234. io2.STM.retry : '{STM} a
235. builtin type io2.ThreadId
236. builtin type io2.Tls
237. builtin type io2.Tls.Cipher
238. builtin type io2.Tls.ClientConfig
239. io2.Tls.ClientConfig.certificates.set : [SignedCert]
226. io2.MVar.tryTake : MVar a ->{IO} Optional a
227. unique type io2.SeekMode
228. io2.SeekMode.AbsoluteSeek : SeekMode
229. io2.SeekMode.RelativeSeek : SeekMode
230. io2.SeekMode.SeekFromEnd : SeekMode
231. builtin type io2.Socket
232. unique type io2.StdHandle
233. io2.StdHandle.StdErr : StdHandle
234. io2.StdHandle.StdIn : StdHandle
235. io2.StdHandle.StdOut : StdHandle
236. builtin type io2.STM
237. io2.STM.atomically : '{STM} a ->{IO} a
238. io2.STM.retry : '{STM} a
239. builtin type io2.ThreadId
240. builtin type io2.Tls
241. builtin type io2.Tls.Cipher
242. builtin type io2.Tls.ClientConfig
243. io2.Tls.ClientConfig.certificates.set : [SignedCert]
-> ClientConfig
-> ClientConfig
240. io2.TLS.ClientConfig.ciphers.set : [Cipher]
244. io2.TLS.ClientConfig.ciphers.set : [Cipher]
-> ClientConfig
-> ClientConfig
241. io2.Tls.ClientConfig.default : Text
245. io2.Tls.ClientConfig.default : Text
-> Bytes
-> ClientConfig
242. io2.Tls.ClientConfig.versions.set : [Version]
246. io2.Tls.ClientConfig.versions.set : [Version]
-> ClientConfig
-> ClientConfig
243. io2.Tls.decodeCert.impl : Bytes
247. io2.Tls.decodeCert.impl : Bytes
-> Either Failure SignedCert
244. io2.Tls.decodePrivateKey : Bytes -> [PrivateKey]
245. io2.Tls.encodeCert : SignedCert -> Bytes
246. io2.Tls.encodePrivateKey : PrivateKey -> Bytes
247. io2.Tls.handshake.impl : Tls ->{IO} Either Failure ()
248. io2.Tls.newClient.impl : ClientConfig
248. io2.Tls.decodePrivateKey : Bytes -> [PrivateKey]
249. io2.Tls.encodeCert : SignedCert -> Bytes
250. io2.Tls.encodePrivateKey : PrivateKey -> Bytes
251. io2.Tls.handshake.impl : Tls ->{IO} Either Failure ()
252. io2.Tls.newClient.impl : ClientConfig
-> Socket
->{IO} Either Failure Tls
249. io2.Tls.newServer.impl : ServerConfig
253. io2.Tls.newServer.impl : ServerConfig
-> Socket
->{IO} Either Failure Tls
250. builtin type io2.Tls.PrivateKey
251. io2.Tls.receive.impl : Tls ->{IO} Either Failure Bytes
252. io2.Tls.send.impl : Tls -> Bytes ->{IO} Either Failure ()
253. builtin type io2.Tls.ServerConfig
254. io2.Tls.ServerConfig.certificates.set : [SignedCert]
254. builtin type io2.Tls.PrivateKey
255. io2.Tls.receive.impl : Tls ->{IO} Either Failure Bytes
256. io2.Tls.send.impl : Tls -> Bytes ->{IO} Either Failure ()
257. builtin type io2.Tls.ServerConfig
258. io2.Tls.ServerConfig.certificates.set : [SignedCert]
-> ServerConfig
-> ServerConfig
255. io2.Tls.ServerConfig.ciphers.set : [Cipher]
259. io2.Tls.ServerConfig.ciphers.set : [Cipher]
-> ServerConfig
-> ServerConfig
256. io2.Tls.ServerConfig.default : [SignedCert]
260. io2.Tls.ServerConfig.default : [SignedCert]
-> PrivateKey
-> ServerConfig
257. io2.Tls.ServerConfig.versions.set : [Version]
261. io2.Tls.ServerConfig.versions.set : [Version]
-> ServerConfig
-> ServerConfig
258. builtin type io2.Tls.SignedCert
259. io2.Tls.terminate.impl : Tls ->{IO} Either Failure ()
260. builtin type io2.Tls.Version
261. unique type io2.TlsFailure
262. builtin type io2.TVar
263. io2.TVar.new : a ->{STM} TVar a
264. io2.TVar.newIO : a ->{IO} TVar a
265. io2.TVar.read : TVar a ->{STM} a
266. io2.TVar.readIO : TVar a ->{IO} a
267. io2.TVar.swap : TVar a -> a ->{STM} a
268. io2.TVar.write : TVar a -> a ->{STM} ()
269. unique type IsPropagated
270. IsPropagated.IsPropagated : IsPropagated
271. unique type IsTest
272. IsTest.IsTest : IsTest
273. unique type Link
274. builtin type Link.Term
275. Link.Term : Term -> Link
276. Link.Term.toText : Term -> Text
277. builtin type Link.Type
278. Link.Type : Type -> Link
279. builtin type List
280. List.++ : [a] -> [a] -> [a]
281. List.+: : a -> [a] -> [a]
282. List.:+ : [a] -> a -> [a]
283. List.at : Nat -> [a] -> Optional a
284. List.cons : a -> [a] -> [a]
285. List.drop : Nat -> [a] -> [a]
286. List.empty : [a]
287. List.size : [a] -> Nat
288. List.snoc : [a] -> a -> [a]
289. List.take : Nat -> [a] -> [a]
290. metadata.isPropagated : IsPropagated
291. metadata.isTest : IsTest
292. builtin type Nat
293. Nat.* : Nat -> Nat -> Nat
294. Nat.+ : Nat -> Nat -> Nat
295. Nat./ : Nat -> Nat -> Nat
296. Nat.and : Nat -> Nat -> Nat
297. Nat.complement : Nat -> Nat
298. Nat.drop : Nat -> Nat -> Nat
299. Nat.eq : Nat -> Nat -> Boolean
300. Nat.fromText : Text -> Optional Nat
301. Nat.gt : Nat -> Nat -> Boolean
302. Nat.gteq : Nat -> Nat -> Boolean
303. Nat.increment : Nat -> Nat
304. Nat.isEven : Nat -> Boolean
305. Nat.isOdd : Nat -> Boolean
306. Nat.leadingZeros : Nat -> Nat
307. Nat.lt : Nat -> Nat -> Boolean
308. Nat.lteq : Nat -> Nat -> Boolean
309. Nat.mod : Nat -> Nat -> Nat
310. Nat.or : Nat -> Nat -> Nat
311. Nat.popCount : Nat -> Nat
312. Nat.pow : Nat -> Nat -> Nat
313. Nat.shiftLeft : Nat -> Nat -> Nat
314. Nat.shiftRight : Nat -> Nat -> Nat
315. Nat.sub : Nat -> Nat -> Int
316. Nat.toFloat : Nat -> Float
317. Nat.toInt : Nat -> Int
318. Nat.toText : Nat -> Text
319. Nat.trailingZeros : Nat -> Nat
320. Nat.xor : Nat -> Nat -> Nat
321. structural type Optional a
322. Optional.None : Optional a
323. Optional.Some : a -> Optional a
324. builtin type Ref
325. Ref.read : Ref g a ->{g} a
326. Ref.write : Ref g a -> a ->{g} ()
327. builtin type Request
328. builtin type Scope
329. Scope.ref : a ->{Scope s} Ref {Scope s} a
330. Scope.run : (∀ s. '{g, Scope s} r) ->{g} r
331. structural type SeqView a b
332. SeqView.VElem : a -> b -> SeqView a b
333. SeqView.VEmpty : SeqView a b
334. unique type Test.Result
335. Test.Result.Fail : Text -> Result
336. Test.Result.Ok : Text -> Result
337. builtin type Text
338. Text.!= : Text -> Text -> Boolean
339. Text.++ : Text -> Text -> Text
340. Text.drop : Nat -> Text -> Text
341. Text.empty : Text
342. Text.eq : Text -> Text -> Boolean
343. Text.fromCharList : [Char] -> Text
344. Text.fromUtf8.impl : Bytes -> Either Failure Text
345. Text.gt : Text -> Text -> Boolean
346. Text.gteq : Text -> Text -> Boolean
347. Text.lt : Text -> Text -> Boolean
348. Text.lteq : Text -> Text -> Boolean
349. Text.repeat : Nat -> Text -> Text
350. Text.size : Text -> Nat
351. Text.take : Nat -> Text -> Text
352. Text.toCharList : Text -> [Char]
353. Text.toUtf8 : Text -> Bytes
354. Text.uncons : Text -> Optional (Char, Text)
355. Text.unsnoc : Text -> Optional (Text, Char)
356. todo : a -> b
357. structural type Tuple a b
358. Tuple.Cons : a -> b -> Tuple a b
359. structural type Unit
360. Unit.Unit : ()
361. Universal.< : a -> a -> Boolean
362. Universal.<= : a -> a -> Boolean
363. Universal.== : a -> a -> Boolean
364. Universal.> : a -> a -> Boolean
365. Universal.>= : a -> a -> Boolean
366. Universal.compare : a -> a -> Int
367. unsafe.coerceAbilities : (a ->{e1} b) -> a ->{e2} b
368. builtin type Value
369. Value.dependencies : Value -> [Term]
370. Value.deserialize : Bytes -> Either Text Value
371. Value.load : Value ->{IO} Either [Term] a
372. Value.serialize : Value -> Bytes
373. Value.value : a -> Value
262. builtin type io2.Tls.SignedCert
263. io2.Tls.terminate.impl : Tls ->{IO} Either Failure ()
264. builtin type io2.Tls.Version
265. unique type io2.TlsFailure
266. builtin type io2.TVar
267. io2.TVar.new : a ->{STM} TVar a
268. io2.TVar.newIO : a ->{IO} TVar a
269. io2.TVar.read : TVar a ->{STM} a
270. io2.TVar.readIO : TVar a ->{IO} a
271. io2.TVar.swap : TVar a -> a ->{STM} a
272. io2.TVar.write : TVar a -> a ->{STM} ()
273. unique type IsPropagated
274. IsPropagated.IsPropagated : IsPropagated
275. unique type IsTest
276. IsTest.IsTest : IsTest
277. unique type Link
278. builtin type Link.Term
279. Link.Term : Term -> Link
280. Link.Term.toText : Term -> Text
281. builtin type Link.Type
282. Link.Type : Type -> Link
283. builtin type List
284. List.++ : [a] -> [a] -> [a]
285. List.+: : a -> [a] -> [a]
286. List.:+ : [a] -> a -> [a]
287. List.at : Nat -> [a] -> Optional a
288. List.cons : a -> [a] -> [a]
289. List.drop : Nat -> [a] -> [a]
290. List.empty : [a]
291. List.size : [a] -> Nat
292. List.snoc : [a] -> a -> [a]
293. List.take : Nat -> [a] -> [a]
294. metadata.isPropagated : IsPropagated
295. metadata.isTest : IsTest
296. builtin type Nat
297. Nat.* : Nat -> Nat -> Nat
298. Nat.+ : Nat -> Nat -> Nat
299. Nat./ : Nat -> Nat -> Nat
300. Nat.and : Nat -> Nat -> Nat
301. Nat.complement : Nat -> Nat
302. Nat.drop : Nat -> Nat -> Nat
303. Nat.eq : Nat -> Nat -> Boolean
304. Nat.fromText : Text -> Optional Nat
305. Nat.gt : Nat -> Nat -> Boolean
306. Nat.gteq : Nat -> Nat -> Boolean
307. Nat.increment : Nat -> Nat
308. Nat.isEven : Nat -> Boolean
309. Nat.isOdd : Nat -> Boolean
310. Nat.leadingZeros : Nat -> Nat
311. Nat.lt : Nat -> Nat -> Boolean
312. Nat.lteq : Nat -> Nat -> Boolean
313. Nat.mod : Nat -> Nat -> Nat
314. Nat.or : Nat -> Nat -> Nat
315. Nat.popCount : Nat -> Nat
316. Nat.pow : Nat -> Nat -> Nat
317. Nat.shiftLeft : Nat -> Nat -> Nat
318. Nat.shiftRight : Nat -> Nat -> Nat
319. Nat.sub : Nat -> Nat -> Int
320. Nat.toFloat : Nat -> Float
321. Nat.toInt : Nat -> Int
322. Nat.toText : Nat -> Text
323. Nat.trailingZeros : Nat -> Nat
324. Nat.xor : Nat -> Nat -> Nat
325. structural type Optional a
326. Optional.None : Optional a
327. Optional.Some : a -> Optional a
328. builtin type Ref
329. Ref.read : Ref g a ->{g} a
330. Ref.write : Ref g a -> a ->{g} ()
331. builtin type Request
332. builtin type Scope
333. Scope.ref : a ->{Scope s} Ref {Scope s} a
334. Scope.run : (∀ s. '{g, Scope s} r) ->{g} r
335. structural type SeqView a b
336. SeqView.VElem : a -> b -> SeqView a b
337. SeqView.VEmpty : SeqView a b
338. unique type Test.Result
339. Test.Result.Fail : Text -> Result
340. Test.Result.Ok : Text -> Result
341. builtin type Text
342. Text.!= : Text -> Text -> Boolean
343. Text.++ : Text -> Text -> Text
344. Text.drop : Nat -> Text -> Text
345. Text.empty : Text
346. Text.eq : Text -> Text -> Boolean
347. Text.fromCharList : [Char] -> Text
348. Text.fromUtf8.impl : Bytes -> Either Failure Text
349. Text.gt : Text -> Text -> Boolean
350. Text.gteq : Text -> Text -> Boolean
351. Text.lt : Text -> Text -> Boolean
352. Text.lteq : Text -> Text -> Boolean
353. Text.repeat : Nat -> Text -> Text
354. Text.size : Text -> Nat
355. Text.take : Nat -> Text -> Text
356. Text.toCharList : Text -> [Char]
357. Text.toUtf8 : Text -> Bytes
358. Text.uncons : Text -> Optional (Char, Text)
359. Text.unsnoc : Text -> Optional (Text, Char)
360. todo : a -> b
361. structural type Tuple a b
362. Tuple.Cons : a -> b -> Tuple a b
363. structural type Unit
364. Unit.Unit : ()
365. Universal.< : a -> a -> Boolean
366. Universal.<= : a -> a -> Boolean
367. Universal.== : a -> a -> Boolean
368. Universal.> : a -> a -> Boolean
369. Universal.>= : a -> a -> Boolean
370. Universal.compare : a -> a -> Int
371. unsafe.coerceAbilities : (a ->{e1} b) -> a ->{e2} b
372. builtin type Value
373. Value.dependencies : Value -> [Term]
374. Value.deserialize : Bytes -> Either Text Value
375. Value.load : Value ->{IO} Either [Term] a
376. Value.serialize : Value -> Bytes
377. Value.value : a -> Value
.builtin> alias.many 94-104 .mylib
@ -469,17 +473,17 @@ Let's try it!
Added definitions:
1. Float.fromRepresentation : Nat -> Float
2. Float.fromText : Text -> Optional Float
3. Float.gt : Float -> Float -> Boolean
4. Float.gteq : Float -> Float -> Boolean
5. Float.log : Float -> Float
6. Float.logBase : Float -> Float -> Float
7. Float.lt : Float -> Float -> Boolean
8. Float.lteq : Float -> Float -> Boolean
9. Float.max : Float -> Float -> Float
10. Float.min : Float -> Float -> Float
11. Float.pow : Float -> Float -> Float
1. Float.cosh : Float -> Float
2. Float.eq : Float -> Float -> Boolean
3. Float.exp : Float -> Float
4. Float.floor : Float -> Int
5. Float.fromRepresentation : Nat -> Float
6. Float.fromText : Text -> Optional Float
7. Float.gt : Float -> Float -> Boolean
8. Float.gteq : Float -> Float -> Boolean
9. Float.log : Float -> Float
10. Float.logBase : Float -> Float -> Float
11. Float.lt : Float -> Float -> Boolean
Tip: You can use `undo` or `reflog` to undo this change.
@ -539,17 +543,17 @@ I want to incorporate a few more from another namespace:
.mylib> find
1. Float.fromRepresentation : Nat -> Float
2. Float.fromText : Text -> Optional Float
3. Float.gt : Float -> Float -> Boolean
4. Float.gteq : Float -> Float -> Boolean
5. Float.log : Float -> Float
6. Float.logBase : Float -> Float -> Float
7. Float.lt : Float -> Float -> Boolean
8. Float.lteq : Float -> Float -> Boolean
9. Float.max : Float -> Float -> Float
10. Float.min : Float -> Float -> Float
11. Float.pow : Float -> Float -> Float
1. Float.cosh : Float -> Float
2. Float.eq : Float -> Float -> Boolean
3. Float.exp : Float -> Float
4. Float.floor : Float -> Int
5. Float.fromRepresentation : Nat -> Float
6. Float.fromText : Text -> Optional Float
7. Float.gt : Float -> Float -> Boolean
8. Float.gteq : Float -> Float -> Boolean
9. Float.log : Float -> Float
10. Float.logBase : Float -> Float -> Float
11. Float.lt : Float -> Float -> Boolean
12. List.adjacentPairs : [a] -> [(a, a)]
13. List.all : (a ->{g} Boolean) -> [a] ->{g} Boolean
14. List.any : (a ->{g} Boolean) -> [a] ->{g} Boolean

View File

@ -37,6 +37,4 @@ x = 1
Tip: Try again and supply one of the above definitions
explicitly.
I didn't make any changes.
```

View File

@ -14,7 +14,7 @@ The `builtins.merge` command adds the known builtins to a `builtin` subnamespace
3. Boolean (builtin type)
4. Boolean/ (1 definition)
5. Bytes (builtin type)
6. Bytes/ (29 definitions)
6. Bytes/ (33 definitions)
7. Char (builtin type)
8. Char/ (3 definitions)
9. Code (builtin type)

View File

@ -227,6 +227,27 @@ test> Bytes.tests.at =
Bytes.at 0 bs == Some 77,
Bytes.at 99 bs == None
]
test> Bytes.tests.compression =
roundTrip b =
(Bytes.zlib.decompress (Bytes.zlib.compress b) == Right b)
&& (Bytes.gzip.decompress (Bytes.gzip.compress b) == Right b)
isLeft = cases
Left _ -> true
Right _ -> false
checks [
roundTrip 0xs2093487509823745709827345789023457892345,
roundTrip 0xs00000000000000000000000000000000000000000000,
roundTrip 0xs,
roundTrip 0xs11111111111111111111111111,
roundTrip 0xsffffffffffffffffffffffffffffff,
roundTrip 0xs222222222fffffffffffffffffffffffffffffff,
-- these fail due to bad checksums and/or headers
isLeft (zlib.decompress 0xs2093487509823745709827345789023457892345),
isLeft (gzip.decompress 0xs201209348750982374593939393939709827345789023457892345)
]
```
```ucm:hide

View File

@ -204,6 +204,27 @@ test> Bytes.tests.at =
Bytes.at 0 bs == Some 77,
Bytes.at 99 bs == None
]
test> Bytes.tests.compression =
roundTrip b =
(Bytes.zlib.decompress (Bytes.zlib.compress b) == Right b)
&& (Bytes.gzip.decompress (Bytes.gzip.compress b) == Right b)
isLeft = cases
Left _ -> true
Right _ -> false
checks [
roundTrip 0xs2093487509823745709827345789023457892345,
roundTrip 0xs00000000000000000000000000000000000000000000,
roundTrip 0xs,
roundTrip 0xs11111111111111111111111111,
roundTrip 0xsffffffffffffffffffffffffffffff,
roundTrip 0xs222222222fffffffffffffffffffffffffffffff,
-- these fail due to bad checksums and/or headers
isLeft (zlib.decompress 0xs2093487509823745709827345789023457892345),
isLeft (gzip.decompress 0xs201209348750982374593939393939709827345789023457892345)
]
```
## `Any` functions
@ -257,6 +278,7 @@ Now that all the tests have been added to the codebase, let's view the test repo
◉ Boolean.tests.notTable Passed
◉ Boolean.tests.orTable Passed
◉ Bytes.tests.at Passed
◉ Bytes.tests.compression Passed
◉ Int.tests.arithmetic Passed
◉ Int.tests.bitTwiddling Passed
◉ Int.tests.conversions Passed
@ -267,7 +289,7 @@ Now that all the tests have been added to the codebase, let's view the test repo
◉ Text.tests.repeat Passed
◉ Text.tests.takeDropAppend Passed
✅ 15 test(s) passing
✅ 16 test(s) passing
Tip: Use view Any.test1 to view the source of a test.

View File

@ -23,7 +23,7 @@ Technically, the definitions all exist, but they have no names. `builtins.merge`
.foo> ls
1. builtin/ (373 definitions)
1. builtin/ (377 definitions)
```
And for a limited time, you can get even more builtin goodies:
@ -35,7 +35,7 @@ And for a limited time, you can get even more builtin goodies:
.foo> ls
1. builtin/ (541 definitions)
1. builtin/ (545 definitions)
```
More typically, you'd start out by pulling `base.

View File

@ -112,13 +112,13 @@ We can also delete the fork if we're done with it. (Don't worry, it's still in t
Note: The most recent namespace hash is immediately below this
message.
#og6imo9b5c
#ndukqgvtrb
- Deletes:
feature1.y
#ejjdq2ngge
#08c5fdtq6k
+ Adds / updates:
@ -129,26 +129,26 @@ We can also delete the fork if we're done with it. (Don't worry, it's still in t
Original name New name(s)
feature1.y master.y
#h52in37m2i
#o17okbu7ug
+ Adds / updates:
feature1.y
#j82gbg1uvj
#l37haj73av
> Moves:
Original name New name
x master.x
#avc2r4cma9
#1h0i8koq55
+ Adds / updates:
x
#4hqp1f8m4t (start of history)
#2t9dm55015 (start of history)
```
To resurrect an old version of a namespace, you can learn its hash via the `history` command, then use `fork #namespacehash .newname`.

View File

@ -59,16 +59,16 @@ y = 2
most recent, along with the command that got us there. Try:
`fork 2 .old`
`fork #u52c5mi247 .old` to make an old namespace
`fork #a0efcgu3if .old` to make an old namespace
accessible again,
`reset-root #u52c5mi247` to reset the root namespace and
`reset-root #a0efcgu3if` to reset the root namespace and
its history to that of the
specified namespace.
1. #67d4sv0vfo : add
2. #u52c5mi247 : add
3. #4hqp1f8m4t : builtins.merge
1. #bu1ni2nh4n : add
2. #a0efcgu3if : add
3. #2t9dm55015 : builtins.merge
4. #sjg2v58vn2 : (initial reflogged namespace)
```

View File

@ -13,7 +13,7 @@ Let's look at some examples. We'll start with a namespace with just the builtins
#1j4m54701m (start of history)
#a1l0ads644 (start of history)
.> fork builtin builtin2
@ -42,21 +42,21 @@ Now suppose we `fork` a copy of builtin, then rename `Nat.+` to `frobnicate`, th
Note: The most recent namespace hash is immediately below this
message.
#c1nv5mm0nq
#d4pjujecp5
> Moves:
Original name New name
Nat.frobnicate Nat.+
#a01ahtlahp
#36p4l2nurp
> Moves:
Original name New name
Nat.+ Nat.frobnicate
#1j4m54701m (start of history)
#a1l0ads644 (start of history)
```
If we merge that back into `builtin`, we get that same chain of history:
@ -71,21 +71,21 @@ If we merge that back into `builtin`, we get that same chain of history:
Note: The most recent namespace hash is immediately below this
message.
#c1nv5mm0nq
#d4pjujecp5
> Moves:
Original name New name
Nat.frobnicate Nat.+
#a01ahtlahp
#36p4l2nurp
> Moves:
Original name New name
Nat.+ Nat.frobnicate
#1j4m54701m (start of history)
#a1l0ads644 (start of history)
```
Let's try again, but using a `merge.squash` (or just `squash`) instead. The history will be unchanged:
@ -106,7 +106,7 @@ Let's try again, but using a `merge.squash` (or just `squash`) instead. The hist
#1j4m54701m (start of history)
#a1l0ads644 (start of history)
```
The churn that happened in `mybuiltin` namespace ended up back in the same spot, so the squash merge of that namespace with our original namespace had no effect.
@ -485,13 +485,13 @@ This checks to see that squashing correctly preserves deletions:
Note: The most recent namespace hash is immediately below this
message.
#bof572e8h8
#q2j8o0ianj
- Deletes:
Nat.* Nat.+
#1j4m54701m (start of history)
#a1l0ads644 (start of history)
```
Notice that `Nat.+` and `Nat.*` are deleted by the squash, and we see them deleted in one atomic step in the history.