Merge pull request #5204 from sellout/new-transcript-parser

This commit is contained in:
Arya Irani 2024-07-10 22:50:00 -04:00 committed by GitHub
commit a4b67cdf66
No known key found for this signature in database
GPG Key ID: B5690EEEBB952194
295 changed files with 2584 additions and 2365 deletions

View File

@ -1,6 +1,6 @@
# Integration test: transcript
```unison
``` unison
use .builtin
unique type MyBool = MyTrue | MyFalse
@ -27,7 +27,7 @@ main = do
_ -> ()
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -43,7 +43,7 @@ main = do
resume : Request {g, Break} x -> x
```
```ucm
``` ucm
.> add
⍟ I've added these definitions:

View File

@ -19,6 +19,7 @@ dependencies:
- base
- bytes
- bytestring
- cmark
- co-log-core
- code-page
- concurrent-output

View File

@ -18,6 +18,7 @@ module Unison.Codebase.TranscriptParser
)
where
import CMark qualified
import Control.Lens (use, (?~))
import Crypto.Random qualified as Random
import Data.Aeson qualified as Aeson
@ -121,12 +122,14 @@ instance Show APIRequest where
show (GetRequest txt) = "GET " <> Text.unpack txt
show (APIComment txt) = "-- " <> Text.unpack txt
pattern CMarkCodeBlock :: (Maybe CMark.PosInfo) -> Text -> Text -> CMark.Node
pattern CMarkCodeBlock pos info body = CMark.Node pos (CMark.CODE_BLOCK info body) []
data Stanza
= Ucm Hidden ExpectingError [UcmLine]
| Unison Hidden ExpectingError (Maybe ScratchFileName) Text
| API [APIRequest]
| UnprocessedFence FenceType Text
| Unfenced Text
| UnprocessedBlock CMark.Node
instance Show UcmLine where
show = \case
@ -138,43 +141,34 @@ instance Show UcmLine where
UcmContextProject projectAndBranch -> Text.unpack (into @Text projectAndBranch)
instance Show Stanza where
show s = case s of
show s = (<> "\n") . Text.unpack . CMark.nodeToCommonmark [] Nothing $ stanzaToNode s
stanzaToNode :: Stanza -> CMark.Node
stanzaToNode =
\case
Ucm _ _ cmds ->
unlines
[ "```ucm",
foldl (\x y -> x ++ show y) "" cmds,
"```"
]
CMarkCodeBlock Nothing "ucm" . Text.pack $
foldl (\x y -> x ++ show y) "" cmds
Unison _hide _ fname txt ->
unlines
[ "```unison",
case fname of
Nothing -> Text.unpack txt <> "```\n"
Just fname ->
unlines
[ "---",
"title: " <> Text.unpack fname,
"---",
Text.unpack txt,
"```",
""
]
]
CMarkCodeBlock Nothing "unison" . Text.pack $
unlines
[ case fname of
Nothing -> Text.unpack txt
Just fname ->
unlines
[ "---",
"title: " <> Text.unpack fname,
"---",
Text.unpack txt
]
]
API apiRequests ->
"```api\n"
<> ( apiRequests
& fmap show
& unlines
)
<> "```\n"
UnprocessedFence typ txt ->
unlines
[ "```" <> Text.unpack typ,
Text.unpack txt,
"```",
""
]
Unfenced txt -> Text.unpack txt
CMarkCodeBlock Nothing "api" . Text.pack $
( apiRequests
& fmap show
& unlines
)
UnprocessedBlock node -> node
parseFile :: FilePath -> IO (Either TranscriptError [Stanza])
parseFile filePath = do
@ -186,7 +180,7 @@ parseFile filePath = do
else pure . Left . TranscriptParseError . Text.pack $ filePath <> " does not exist"
parse :: String -> Text -> Either TranscriptError [Stanza]
parse srcName txt = case P.parse (stanzas <* P.eof) srcName txt of
parse srcName txt = case stanzas srcName txt of
Right a -> Right a
Left e -> Left . TranscriptParseError . Text.pack . P.errorBundlePretty $ e
@ -337,7 +331,7 @@ run verbosity dir stanzas codebase runtime sbRuntime nRuntime config ucmVersion
for (reverse scratchFileUpdates) \(fp, contents) -> do
let fenceDescription = "unison:added-by-ucm " <> fp
-- Output blocks for any scratch file updates the ucm block triggered.
Q.undequeue inputQueue (UnprocessedFence fenceDescription contents, Nothing)
Q.undequeue inputQueue (UnprocessedBlock $ CMarkCodeBlock Nothing fenceDescription contents, Nothing)
awaitInput
-- ucm command to run
Just (Just ucmLine) -> do
@ -420,10 +414,7 @@ run verbosity dir stanzas codebase runtime sbRuntime nRuntime config ucmVersion
++ "."
IO.hFlush IO.stdout
case s of
Unfenced _ -> do
liftIO (output $ show s)
awaitInput
UnprocessedFence _ _ -> do
UnprocessedBlock _ -> do
liftIO (output $ show s)
awaitInput
Unison hide errOk filename txt -> do
@ -432,22 +423,22 @@ run verbosity dir stanzas codebase runtime sbRuntime nRuntime config ucmVersion
liftIO (writeIORef allowErrors errOk)
-- Open a ucm block which will contain the output from UCM
-- after processing the UnisonFileChanged event.
liftIO (output "```ucm\n")
liftIO (output "``` ucm\n")
-- Close the ucm block after processing the UnisonFileChanged event.
atomically . Q.enqueue cmdQueue $ Nothing
let sourceName = fromMaybe "scratch.u" filename
liftIO $ updateVirtualFile sourceName txt
pure $ Left (UnisonFileChanged sourceName txt)
API apiRequests -> do
liftIO (output "```api\n")
liftIO (output "``` api\n")
liftIO (for_ apiRequests apiRequest)
liftIO (output "```")
liftIO (output "```\n\n")
awaitInput
Ucm hide errOk cmds -> do
liftIO (writeIORef hidden hide)
liftIO (writeIORef allowErrors errOk)
liftIO (writeIORef hasErrors False)
liftIO (output "```ucm")
liftIO (output "``` ucm")
traverse_ (atomically . Q.enqueue cmdQueue . Just) cmds
atomically . Q.enqueue cmdQueue $ Nothing
awaitInput
@ -593,8 +584,12 @@ transcriptFailure out msg = do
type P = P.Parsec Void Text
stanzas :: P [Stanza]
stanzas = P.many (fenced <|> unfenced)
stanzas :: String -> Text -> Either (P.ParseErrorBundle Text Void) [Stanza]
stanzas srcName = (\(CMark.Node _ _DOCUMENT blocks) -> traverse stanzaFromBlock blocks) . CMark.commonmarkToNode []
where
stanzaFromBlock block = case block of
CMarkCodeBlock _ info body -> fromMaybe (UnprocessedBlock block) <$> P.parse (fenced info) srcName body
_ -> pure $ UnprocessedBlock block
ucmLine :: P UcmLine
ucmLine = ucmCommand <|> ucmComment
@ -636,18 +631,21 @@ apiRequest = do
spaces
pure (APIComment comment)
fenced :: P Stanza
fenced = do
fence
-- | Produce the correct parser for the code block based on the provided info string.
fenced :: Text -> P (Maybe Stanza)
fenced info = do
body <- P.getInput
P.setInput info
fenceType <- lineToken (word "ucm" <|> word "unison" <|> word "api" <|> language)
stanza <-
case fenceType of
"ucm" -> do
hide <- hidden
err <- expectingError
P.setInput body
_ <- spaces
cmds <- many ucmLine
pure $ Ucm hide err cmds
pure . pure $ Ucm hide err cmds
"unison" ->
do
-- todo: this has to be more interesting
@ -657,44 +655,17 @@ fenced = do
hide <- lineToken hidden
err <- lineToken expectingError
fileName <- optional untilSpace1
blob <- spaces *> untilFence
pure $ Unison hide err fileName blob
P.setInput body
blob <- spaces *> (Text.init <$> P.getInput)
pure . pure $ Unison hide err fileName blob
"api" -> do
P.setInput body
_ <- spaces
apiRequests <- many apiRequest
pure $ API apiRequests
_ -> UnprocessedFence fenceType <$> untilFence
fence
pure . pure $ API apiRequests
_ -> pure Nothing
pure stanza
-- Three backticks, consumes trailing spaces too
-- ```
fence :: P ()
fence = P.try $ do void (word "```"); spaces
-- Parses up until next fence
unfenced :: P Stanza
unfenced = Unfenced <$> untilFence
untilFence :: P Text
untilFence = do
_ <- P.lookAhead (P.takeP Nothing 1)
go mempty
where
go :: Seq Text -> P Text
go !acc = do
f <- P.lookAhead (P.optional fence)
case f of
Nothing -> do
oneOrTwoBackticks <- optional (word' "``" <|> word' "`")
let start = fromMaybe "" oneOrTwoBackticks
txt <- P.takeWhileP (Just "unfenced") (/= '`')
eof <- P.lookAhead (P.optional P.eof)
case eof of
Just _ -> pure $ fold (acc <> pure txt)
Nothing -> go (acc <> pure start <> pure txt)
Just _ -> pure $ fold acc
word' :: Text -> P Text
word' txt = P.try $ do
chs <- P.takeP (Just $ show txt) (Text.length txt)

View File

@ -196,6 +196,7 @@ library
, base
, bytes
, bytestring
, cmark
, co-log-core
, code-page
, concurrent-output
@ -337,6 +338,7 @@ executable transcripts
, base
, bytes
, bytestring
, cmark
, co-log-core
, code-page
, concurrent-output
@ -485,6 +487,7 @@ test-suite cli-tests
, base
, bytes
, bytestring
, cmark
, co-log-core
, code-page
, concurrent-output

View File

@ -4,7 +4,7 @@ If you want to add or update tests, you can create a branch of that project, and
Before merging the PR on Github, we'll merge your branch on Share and restore `runtime_tests_version` to /main or maybe a release.
```ucm
``` ucm
runtime-tests/selected> run tests
()

View File

@ -4,7 +4,7 @@ If you want to add or update tests, you can create a branch of that project, and
Before merging the PR on Github, we'll merge your branch on Share and restore `runtime_tests_version` to /main or maybe a release.
```ucm
``` ucm
runtime-tests/selected> run.native tests
()
@ -17,7 +17,8 @@ runtime-tests/selected> run.native tests.jit.only
Per Dan:
It's testing a flaw in how we were sending code from a scratch file to the native runtime, when that happened multiple times.
Related to the verifiable refs and recursive functions.
```unison
``` unison
foo = do
go : Nat ->{Exception} ()
go = cases
@ -26,20 +27,20 @@ foo = do
go 1000
```
```ucm
``` ucm
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`:
foo : '{Exception} ()
```
```ucm
``` ucm
scratch/main> run.native foo
()
@ -53,14 +54,14 @@ This can also only be tested by separately running this test, because
it is exercising the protocol that ucm uses to talk to the jit during
an exception.
```ucm
``` ucm
runtime-tests/selected> run.native testBug
💔💥
I've encountered a call to builtin.bug with the following
value:
"testing"
```

View File

@ -1,10 +1,10 @@
```ucm
``` ucm
test-html-docs/main> builtins.mergeio lib.builtins
Done.
```
```unison
``` unison
{{A doc directly in the namespace.}}
some.ns.direct = 1
@ -15,7 +15,7 @@ some.ns.pretty.deeply.nested = 2
some.outside = 3
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -33,7 +33,7 @@ some.outside = 3
some.outside.doc : Doc2
```
```ucm
``` ucm
test-html-docs/main> add
⍟ I've added these definitions:

View File

@ -1,9 +1,8 @@
## Structural find and replace
Here's a scratch file with some rewrite rules:
```unison
``` unison
ex1 = List.map (x -> x + 1) [1,2,3,4,5,6,7]
eitherToOptional e a =
@ -30,7 +29,7 @@ rule2 x = @rewrite signature Optional ==> Optional2
Let's rewrite these:
```ucm
``` ucm
scratch/main> rewrite rule1
☝️
@ -49,7 +48,7 @@ scratch/main> rewrite eitherToOptional
The rewritten file has been added to the top of scratch.u
```
```unison:added-by-ucm scratch.u
``` unison:added-by-ucm scratch.u
-- | Rewrote using:
-- | Modified definition(s): ex1
@ -79,7 +78,7 @@ type Optional2 a = Some2 a | None2
rule2 x = @rewrite signature Optional ==> Optional2
```
```unison:added-by-ucm scratch.u
``` unison:added-by-ucm scratch.u
-- | Rewrote using:
-- | Modified definition(s): Either.mapRight
@ -111,7 +110,7 @@ rule2 x = @rewrite signature Optional ==> Optional2
After adding to the codebase, here's the rewritten source:
```ucm
``` ucm
scratch/main> view ex1 Either.mapRight rule1
Either.mapRight : (a ->{g} b) -> Optional a ->{g} Optional b
@ -137,7 +136,7 @@ scratch/main> view ex1 Either.mapRight rule1
```
Another example, showing that we can rewrite to definitions that only exist in the file:
```unison
``` unison
unique ability Woot1 where woot1 : () -> Nat
unique ability Woot2 where woot2 : () -> Nat
@ -157,7 +156,7 @@ blah2 = 456
Let's apply the rewrite `woot1to2`:
```ucm
``` ucm
scratch/main> rewrite woot1to2
☝️
@ -167,7 +166,7 @@ scratch/main> rewrite woot1to2
The rewritten file has been added to the top of scratch.u
```
```unison:added-by-ucm scratch.u
``` unison:added-by-ucm scratch.u
-- | Rewrote using:
-- | Modified definition(s): wootEx
@ -193,7 +192,7 @@ blah2 = 456
After adding the rewritten form to the codebase, here's the rewritten `Woot1` to `Woot2`:
```ucm
``` ucm
scratch/main> view wootEx
wootEx : Nat ->{Woot2} Nat
@ -204,7 +203,7 @@ scratch/main> view wootEx
```
This example shows that rewrite rules can to refer to term definitions that only exist in the file:
```unison
``` unison
foo1 =
b = "b"
123
@ -225,7 +224,7 @@ sameFileEx =
After adding the rewritten form to the codebase, here's the rewritten definitions:
```ucm
``` ucm
scratch/main> view foo1 foo2 sameFileEx
foo1 : Nat
@ -246,7 +245,7 @@ scratch/main> view foo1 foo2 sameFileEx
```
## Capture avoidance
```unison
``` unison
bar1 =
b = "bar"
123
@ -266,7 +265,7 @@ sameFileEx =
In the above example, `bar2` is locally bound by the rule, so when applied, it should not refer to the `bar2` top level binding.
```ucm
``` ucm
scratch/main> rewrite rule
☝️
@ -276,7 +275,7 @@ scratch/main> rewrite rule
The rewritten file has been added to the top of scratch.u
```
```unison:added-by-ucm scratch.u
``` unison:added-by-ucm scratch.u
-- | Rewrote using:
-- | Modified definition(s): sameFileEx
@ -300,7 +299,7 @@ sameFileEx =
Instead, it should be an unbound free variable, which doesn't typecheck:
```ucm
``` ucm
scratch/main> load
Loading changes detected in scratch.u.
@ -321,7 +320,7 @@ scratch/main> load
```
In this example, the `a` is locally bound by the rule, so it shouldn't capture the `a = 39494` binding which is in scope at the point of the replacement:
```unison
``` unison
bar2 =
a = 39494
233
@ -331,7 +330,7 @@ rule a = @rewrite
term 233 ==> a
```
```ucm
``` ucm
scratch/main> rewrite rule
☝️
@ -341,7 +340,7 @@ scratch/main> rewrite rule
The rewritten file has been added to the top of scratch.u
```
```unison:added-by-ucm scratch.u
``` unison:added-by-ucm scratch.u
-- | Rewrote using:
-- | Modified definition(s): bar2
@ -357,7 +356,7 @@ rule a =
The `a` introduced will be freshened to not capture the `a` in scope, so it remains as an unbound variable and is a type error:
```ucm
``` ucm
scratch/main> load
Loading changes detected in scratch.u.
@ -378,16 +377,16 @@ scratch/main> load
```
## Structural find
```unison
``` unison
eitherEx = Left ("hello", "there")
```
```unison
``` unison
findEitherEx x = @rewrite term Left ("hello", x) ==> Left ("hello" Text.++ x)
findEitherFailure = @rewrite signature a . Either Failure a ==> ()
```
```ucm
``` ucm
scratch/main> sfind findEitherEx
🔎

View File

@ -1,10 +1,10 @@
This transcript verifies that the pretty-printer produces code that can be successfully parsed, for a variety of examples. Terms or types that fail to round-trip can be added to either `reparses-with-same-hash.u` or `reparses.u` as regression tests.
```unison
``` unison
x = ()
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -19,7 +19,7 @@ x = ()
```
So we can see the pretty-printed output:
```ucm
``` ucm
.a1> edit 1-1000
☝️
@ -30,7 +30,7 @@ So we can see the pretty-printed output:
definitions currently in this namespace.
```
```unison:added-by-ucm scratch.u
````` unison:added-by-ucm scratch.u
structural ability Abort where abort : {Abort} a
structural ability Ask a where ask : {Ask a} a
@ -766,11 +766,11 @@ UUID.randomUUIDBytes = do
(|>) : a -> (a ->{e} b) ->{e} b
a |> f = f a
```
`````
This diff should be empty if the two namespaces are equivalent. If it's nonempty, the diff will show us the hashes that differ.
```ucm
``` ucm
.> diff.namespace a1 a2
The namespaces are identical.
@ -780,11 +780,11 @@ Now check that definitions in 'reparses.u' at least parse on round trip:
This just makes 'roundtrip.u' the latest scratch file.
```unison
``` unison
x = ()
```
```ucm
``` ucm
.a3> edit 1-5000
☝️
@ -795,7 +795,7 @@ x = ()
definitions currently in this namespace.
```
```unison:added-by-ucm scratch.u
```` unison:added-by-ucm scratch.u
explanationOfThisFile : Text
explanationOfThisFile =
"""
@ -815,11 +815,11 @@ sloppyDocEval =
1 + 1
```
}}
```
````
These are currently all expected to have different hashes on round trip.
```ucm
``` ucm
.> diff.namespace a3 a3_old
Updates:

View File

@ -11,7 +11,7 @@ transcripts which contain less boilerplate.
The test shows that `hex (fromHex str) == str` as expected.
```unison
``` unison
test> hex.tests.ex1 = checks let
s = "3984af9b"
[hex (fromHex s) == s]
@ -20,7 +20,7 @@ test> hex.tests.ex1 = checks let
Lets do some basic testing of our test harness to make sure its
working.
```unison
``` unison
testAutoClean : '{io2.IO}[Result]
testAutoClean _ =
go: '{Stream Result, Exception, io2.IO, TempDirs} Text
@ -39,7 +39,7 @@ testAutoClean _ =
Left (Failure _ t _) -> results :+ (Fail t)
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -52,7 +52,7 @@ testAutoClean _ =
testAutoClean : '{IO} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,6 +1,6 @@
This transcript is intended to make visible accidental changes to the hashing algorithm.
```ucm
``` ucm
scratch/main> find.verbose
1. -- #sgesq8035ut22q779pl1g4gqsg8c81894jjonmrq1bjltphkath225up841hk8dku59tnnc4laj9nggbofamgei4klof0ldc20uj2oo

View File

@ -1,4 +1,4 @@
```unison
``` unison
unique type EncDec = EncDec Text (Nat -> Bytes) (Bytes -> Optional (Nat, Bytes))
BE64 = EncDec "64 bit Big Endian" encodeNat64be decodeNat64be
@ -53,7 +53,7 @@ testABunchOfNats _ =
(runTest (testNat 0))
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -75,7 +75,7 @@ testABunchOfNats _ =
testRoundTrip : Nat -> EncDec ->{IO, Stream Result} ()
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,10 +1,9 @@
Test for code serialization operations.
Define a function, serialize it, then deserialize it back to an actual
function. Also ask for its dependencies for display later.
```unison
``` unison
save : a -> Bytes
save x = Value.serialize (Value.value x)
@ -152,7 +151,7 @@ swapped name link =
rejected ("swapped " ++ name) rco
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -199,7 +198,7 @@ swapped name link =
->{Throw Text} ()
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -241,7 +240,7 @@ scratch/main> add
->{Throw Text} ()
```
```unison
``` unison
structural ability Zap where
zap : Three Nat Nat Nat
@ -316,7 +315,7 @@ badLoad _ =
Left _ -> [Fail "Exception"]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -343,7 +342,7 @@ This simply runs some functions to make sure there isn't a crash. Once
we gain the ability to capture output in a transcript, it can be modified
to actual show that the serialization works.
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -393,7 +392,7 @@ scratch/main> io.test badLoad
Tip: Use view 1 to view the source of a test.
```
```unison
``` unison
codeTests : '{io2.IO} [Result]
codeTests =
'[ idempotence "idem f" (termLink f)
@ -429,7 +428,7 @@ codeTests =
]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -442,7 +441,7 @@ codeTests =
codeTests : '{IO} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -489,7 +488,7 @@ scratch/main> io.test codeTests
Tip: Use view 1 to view the source of a test.
```
```unison
``` unison
validateTest : Link.Term ->{IO} Result
validateTest l = match Code.lookup l with
None -> Fail "Couldn't look up link"
@ -515,7 +514,7 @@ vtests _ =
]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -529,7 +528,7 @@ vtests _ =
vtests : '{IO} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -2,18 +2,18 @@
Unison documentation is written in Unison and has some neat features:
* The documentation type provides a rich vocabulary of elements that go beyond markdown, including asides, callouts, tooltips, and more.
* Docs may contain Unison code which is parsed and typechecked to ensure validity. No more out of date examples that don't compile or assume a bunch of implicit context!
* Embeded examples are live and can show the results of evaluation. This uses the same evaluation cache as Unison's scratch files, allowing Unison docs to function like well-commented spreadsheets or notebooks.
* Links to other definitions are typechecked to ensure they point to valid definitions. The links are resolved to hashes and won't be broken by name changes or moving definitions around.
* Docs can be included in other docs and you can assemble documentation programmatically, using Unison code.
* There's a powerful textual syntax for all of the above, which we'll introduce next.
- The documentation type provides a rich vocabulary of elements that go beyond markdown, including asides, callouts, tooltips, and more.
- Docs may contain Unison code which is parsed and typechecked to ensure validity. No more out of date examples that don't compile or assume a bunch of implicit context\!
- Embeded examples are live and can show the results of evaluation. This uses the same evaluation cache as Unison's scratch files, allowing Unison docs to function like well-commented spreadsheets or notebooks.
- Links to other definitions are typechecked to ensure they point to valid definitions. The links are resolved to hashes and won't be broken by name changes or moving definitions around.
- Docs can be included in other docs and you can assemble documentation programmatically, using Unison code.
- There's a powerful textual syntax for all of the above, which we'll introduce next.
## Introduction
Documentation blocks start with `{{` and end with a matching `}}`. You can introduce doc blocks anywhere you'd use an expression, and you can also have anonymous documentation blocks immediately before a top-level term or type.
```unison
``` unison
name = {{Alice}}
d1 = {{ Hello there {{name}}! }}
@ -28,7 +28,7 @@ The 7 days of the week, defined as:
unique type time.DayOfWeek = Sun | Mon | Tue | Wed | Thu | Fri | Sat
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -50,7 +50,7 @@ Notice that an anonymous documentation block `{{ ... }}` before a definition `Im
You can preview what docs will look like when rendered to the console using the `display` or `docs` commands:
```ucm
``` ucm
scratch/main> display d1
Hello there Alice!
@ -72,7 +72,7 @@ The `docs ImportantConstant` command will look for `ImportantConstant.doc` in th
First, we'll load the `syntax.u` file which has examples of all the syntax:
```ucm
``` ucm
scratch/main> load ./unison-src/transcripts-using-base/doc.md.files/syntax.u
Loading changes detected in
@ -99,7 +99,7 @@ Now we can review different portions of the guide.
we'll show both the pretty-printed source using `view`
and the rendered output using `display`:
```ucm
``` ucm
scratch/main> view basicFormatting
basicFormatting : Doc2
@ -548,7 +548,7 @@ scratch/main> display otherElements
```
Lastly, it's common to build longer documents including subdocuments via `{{ subdoc }}`. We can stitch together the full syntax guide in this way:
```ucm
``` ucm
scratch/main> view doc.guide
doc.guide : Doc2
@ -769,3 +769,4 @@ scratch/main> display doc.guide
```
🌻 THE END

View File

@ -6,7 +6,7 @@ Exception ability directly, and the last is code validation. I don't
have an easy way to test the last at the moment, but the other two are
tested here.
```unison
``` unison
test1 : '{IO, Exception} [Result]
test1 = do
_ = fromUtf8 0xsee
@ -18,7 +18,7 @@ test2 = do
[Ok "test2"]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -32,7 +32,7 @@ test2 = do
test2 : '{IO, Exception} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -41,7 +41,7 @@ scratch/main> add
test2 : '{IO, Exception} [Result]
```
```ucm
``` ucm
scratch/main> io.test test1
💔💥
@ -57,7 +57,7 @@ scratch/main> io.test test1
##raise
```
```ucm
``` ucm
scratch/main> io.test test2
💔💥

View File

@ -1,6 +1,6 @@
This transcript tests an ability check failure regression.
```unison
``` unison
structural ability Async t g where
fork : '{Async t g, g} a -> t a
await : t a -> a
@ -11,7 +11,7 @@ Async.parMap f as =
List.map await tasks
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -36,6 +36,7 @@ some subtyping.
However, the ability handling was just processing rows in whatever
order they occurred, and during inference it happened that `g`
occurred in the row before `Async t g. Processing the stricter parts
occurred in the row before `Async t g`. Processing the stricter parts
first is better, becauase it can solve things more precisely and avoid
ambiguities relating to subtyping.

View File

@ -1,7 +1,6 @@
This tests a case where a function was somehow discarding abilities.
```unison
``` unison
structural ability Trivial where
trivial : ()
@ -25,7 +24,7 @@ wat = handleTrivial testAction -- Somehow this completely forgets about Excepti
> handleTrivial testAction
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,7 +1,6 @@
Tests a former error due to bad calling conventions on delay.impl
```unison
``` unison
timingApp2 : '{IO, Exception} ()
timingApp2 _ =
printLine "Hello"
@ -9,7 +8,7 @@ timingApp2 _ =
printLine "World"
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -22,7 +21,7 @@ timingApp2 _ =
timingApp2 : '{IO, Exception} ()
```
```ucm
``` ucm
scratch/main> run timingApp2
()

View File

@ -1,7 +1,7 @@
This file tests some obscure issues involved with abilities and over-applied
functions.
```unison
``` unison
Stream.fromList : [a] -> '{Stream a} ()
Stream.fromList l _ =
_ = List.map (x -> emit x) l
@ -31,7 +31,7 @@ increment n = 1 + n
Stream.toList s2
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -62,7 +62,7 @@ increment n = 1 + n
[100, 200, 300, 400]
```
```unison
``` unison
structural ability E where
eff : () -> ()
@ -82,7 +82,7 @@ foo _ =
> h foo 337
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -105,7 +105,7 @@ foo _ =
7
```
```unison
``` unison
structural ability Over where
over : Nat ->{Over} (Nat -> Nat)
@ -126,7 +126,7 @@ hmm =
> hmm
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,4 +1,4 @@
```unison
``` unison
arrayList v n = do
use ImmutableByteArray read8
ma = Scope.bytearrayOf v n
@ -13,7 +13,7 @@ arrayList v n = do
> Scope.run '(catch (arrayList 7 8))
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,11 +1,11 @@
```unison
``` unison
{{
A simple doc.
}}
meh = 9
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -19,7 +19,7 @@ meh = 9
meh.doc : Doc2
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,7 +1,7 @@
Test case for a variable capture problem during let floating. The
encloser wasn't accounting for variables bound by matches.
```unison
``` unison
ability Issue t where
one : '{Issue t} () -> {Issue t} ()
two : '{Issue t} () -> {Issue t} ()
@ -35,7 +35,7 @@ run s =
()
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,7 +1,7 @@
Checks for some bad type checking behavior. Some ability subtyping was
too lenient when higher-order functions were involved.
```unison
``` unison
foreach : (a ->{g} ()) -> [a] ->{g} ()
foreach f = cases
[] -> ()
@ -22,7 +22,7 @@ go = do
foreach forkIt [thunk]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -38,9 +38,9 @@ go = do
```
This comes from issue #3513
This comes from issue \#3513
```unison
``` unison
(<<) : (b ->{e} c) -> (a ->{e} b) -> a ->{e} c
(<<) f g x = f (g x)
@ -56,7 +56,7 @@ fancyTryEval : '{g, IO, Exception} a ->{g, IO, Exception} a
fancyTryEval = reraise << catchAll.impl
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -2,7 +2,7 @@
Unison has cryptographic builtins for hashing and computing [HMACs](https://en.wikipedia.org/wiki/HMAC) (hash-based message authentication codes). This transcript shows their usage and has some test cases.
```ucm
``` ucm
scratch/main> ls builtin.Bytes
1. ++ (Bytes -> Bytes -> Bytes)
@ -45,7 +45,7 @@ Notice the `fromBase16` and `toBase16` functions. Here's some convenience functi
Here's a few usage examples:
```unison
``` unison
ex1 = fromHex "2947db"
|> crypto.hashBytes Sha3_512
|> hex
@ -74,7 +74,7 @@ ex5 = crypto.hmac Sha2_256 mysecret f |> hex
> ex5
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -119,7 +119,7 @@ ex5 = crypto.hmac Sha2_256 mysecret f |> hex
```
And here's the full API:
```ucm
``` ucm
scratch/main> find-in builtin.crypto
1. type CryptoFailure
@ -155,11 +155,11 @@ scratch/main> find-in builtin.crypto
```
Note that the universal versions of `hash` and `hmac` are currently unimplemented and will bomb at runtime:
```unison
``` unison
> hash Sha3_256 (fromHex "3849238492")
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -177,9 +177,9 @@ Note that the universal versions of `hash` and `hmac` are currently unimplemente
```
## Hashing tests
Here are some test vectors (taken from [here](https://www.di-mgt.com.au/sha_testvectors.html) and [here](https://en.wikipedia.org/wiki/BLAKE_(hash_function))) for the various hashing algorithms:
Here are some test vectors (taken from [here](https://www.di-mgt.com.au/sha_testvectors.html) and [here](https://en.wikipedia.org/wiki/BLAKE_\(hash_function\))) for the various hashing algorithms:
```unison
``` unison
ex alg input expected = checks [hashBytes alg (ascii input) == fromHex expected]
test> sha3_512.tests.ex1 =
@ -311,7 +311,7 @@ test> crypto.hash.numTests =
checks (List.map t (range 0 20))
```
```ucm
``` ucm
scratch/main> test
Cached test results (`help testcache` to learn more)
@ -351,7 +351,7 @@ scratch/main> test
These test vectors are taken from [RFC 4231](https://tools.ietf.org/html/rfc4231#section-4.3).
```unison
``` unison
ex' alg secret msg expected = checks [hmacBytes alg (fromHex secret) (ascii msg) == fromHex expected]
test> hmac_sha2_256.tests.ex1 =
@ -378,7 +378,7 @@ test> hmac_sha2_512.tests.ex2 =
"164b7a7bfcf819e2e395fbe73b56e0a387bd64222e831fd610270cd7ea2505549758bf75c05a994a6d034f65f8f0e6fdcaeab1a34d4a6b4b636e070a38bce737"
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -422,7 +422,7 @@ test> hmac_sha2_512.tests.ex2 =
Test vectors here pulled from [Wikipedia's writeup](https://en.wikipedia.org/wiki/MD5).
```unison
``` unison
ex alg input expected = checks [hashBytes alg (ascii input) == fromHex expected]
test> md5.tests.ex1 =
@ -441,7 +441,7 @@ test> md5.tests.ex3 =
"e4d909c290d0fb1ca068ffaddf22cbd0"
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -473,7 +473,7 @@ test> md5.tests.ex3 =
✅ Passed Passed
```
```ucm
``` ucm
scratch/main> test
Cached test results (`help testcache` to learn more)

View File

@ -9,8 +9,7 @@ MVars are the building block on which many other concurrency
primitives can be built, such as Futures, Run at most once initializer
blocks, Queues, etc.
```unison
``` unison
eitherCk : (a -> Boolean) -> Either e a -> Boolean
eitherCk f = cases
Left _ -> false
@ -51,7 +50,7 @@ testMvars _ =
runTest test
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -65,7 +64,7 @@ testMvars _ =
testMvars : '{IO} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,4 +1,4 @@
```unison
``` unison
testNat: Nat -> Optional Int -> Optional Float -> {Stream Result}()
testNat n expectInt expectFloat =
float = Float.fromRepresentation n
@ -31,7 +31,7 @@ test = 'let
runTest testABunchOfNats
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -48,7 +48,7 @@ test = 'let
->{Stream Result} ()
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,4 +1,4 @@
```unison
``` unison
serverSocket = compose2 reraise IO.serverSocket.impl
socketPort = compose reraise socketPort.impl
listen = compose reraise listen.impl
@ -16,14 +16,13 @@ socketAccept = compose reraise socketAccept.impl
This section tests functions in the IO builtin related to binding to
TCP server socket, as to be able to accept incoming TCP connections.
```builtin
.io2.IO.serverSocket : Optional Text -> Text ->{io2.IO} Either Failure io2.Socket
```
builtin.io2.IO.serverSocket : Optional Text -> Text ->{io2.IO} Either Failure io2.Socket
```
This function takes two parameters, The first is the Hostname. If None
is provided, We will attempt to bind to 0.0.0.0 (All ipv4
addresses). We currently only support IPV4 (we should fix this!)
addresses). We currently only support IPV4 (we should fix this\!)
The second is the name of the port to bind to. This can be
a decimal representation of a port number between 1-65535. This can be
a named port like "ssh" (for port 22) or "kermit" (for port 1649),
@ -34,11 +33,11 @@ stored in `/etc/services` and queried with the `getent` tool:
# map number to name
$ getent services 22
ssh 22/tcp
# map name to number
$ getent services finger
finger 79/tcp
# get a list of all known names
$ getent services | head
tcpmux 1/tcp
@ -54,7 +53,7 @@ stored in `/etc/services` and queried with the `getent` tool:
Below shows different examples of how we might specify the server coordinates.
```unison
``` unison
testExplicitHost : '{io2.IO} [Result]
testExplicitHost _ =
test = 'let
@ -91,7 +90,7 @@ testDefaultPort _ =
runTest test
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -106,7 +105,7 @@ testDefaultPort _ =
testExplicitHost : '{IO} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -130,7 +129,7 @@ scratch/main> io.test testDefaultPort
```
This example demonstrates connecting a TCP client socket to a TCP server socket. A thread is started for both client and server. The server socket asks for any availalbe port (by passing "0" as the port number). The server thread then queries for the actual assigned port number, and puts that into an MVar which the client thread can read. The client thread then reads a string from the server and reports it back to the main thread via a different MVar.
```unison
``` unison
serverThread: MVar Nat -> Text -> '{io2.IO}()
serverThread portVar toSend = 'let
go : '{io2.IO, Exception}()
@ -178,7 +177,7 @@ testTcpConnect = 'let
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -193,7 +192,7 @@ testTcpConnect = 'let
testTcpConnect : '{IO} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,4 +1,4 @@
```unison
``` unison
directory = "unison-src/transcripts-using-base/serialized-cases/"
availableCases : '{IO,Exception} [Text]
@ -55,7 +55,7 @@ serialTests = do
List.map snd (bSort (List.map runTestCase cs))
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -73,7 +73,7 @@ serialTests = do
shuffle : Nat -> [a] -> [a]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -3,7 +3,7 @@
Ref support a CAS operation that can be used as a building block to
change state atomically without locks.
```unison
``` unison
casTest: '{io2.IO} [Result]
casTest = do
test = do
@ -18,7 +18,7 @@ casTest = do
runTest test
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -31,7 +31,7 @@ casTest = do
casTest : '{IO} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -52,7 +52,7 @@ scratch/main> io.test casTest
```
Promise is a simple one-shot awaitable condition.
```unison
``` unison
promiseSequentialTest : '{IO} [Result]
promiseSequentialTest = do
test = do
@ -80,7 +80,7 @@ promiseConcurrentTest = do
runTest test
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -94,7 +94,7 @@ promiseConcurrentTest = do
promiseSequentialTest : '{IO} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -126,7 +126,7 @@ scratch/main> io.test promiseConcurrentTest
```
CAS can be used to write an atomic update function.
```unison
``` unison
atomicUpdate : Ref {IO} a -> (a -> a) ->{IO} ()
atomicUpdate ref f =
ticket = Ref.readForCas ref
@ -134,7 +134,7 @@ atomicUpdate ref f =
if Ref.cas ref ticket value then () else atomicUpdate ref f
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -147,7 +147,7 @@ atomicUpdate ref f =
atomicUpdate : Ref {IO} a -> (a -> a) ->{IO} ()
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -158,7 +158,7 @@ scratch/main> add
Promise can be used to write an operation that spawns N concurrent
tasks and collects their results
```unison
``` unison
spawnN : Nat -> '{IO} a ->{IO} [a]
spawnN n fa =
use Nat eq drop
@ -173,7 +173,7 @@ spawnN n fa =
map Promise.read (go n [])
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -186,7 +186,7 @@ spawnN n fa =
spawnN : Nat -> '{IO} a ->{IO} [a]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -198,7 +198,7 @@ We can use these primitives to write a more interesting example, where
multiple threads repeatedly update an atomic counter, we check that
the value of the counter is correct after all threads are done.
```unison
``` unison
fullTest : '{IO} [Result]
fullTest = do
use Nat * + eq drop
@ -222,7 +222,7 @@ fullTest = do
runTest test
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -235,7 +235,7 @@ fullTest = do
fullTest : '{IO} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,4 +1,4 @@
```unison
``` unison
structural type Tree a = Leaf | Node (Tree a) a (Tree a)
foldMap : r -> (r -> r -> r) -> (a -> r) -> Tree a -> r
@ -67,7 +67,7 @@ mkTestCase = do
saveTestCase "case-00" "v4" f tup
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -94,7 +94,7 @@ mkTestCase = do
tree3 : Tree Text
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,4 +1,4 @@
```unison
``` unison
l1 = [1.0,2.0,3.0]
l2 = [+1,+2,+3]
l3 = [?a, ?b, ?c]
@ -15,7 +15,7 @@ mkTestCase = do
saveTestCase "case-01" "v4" combines (l1, l2, l3)
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -32,7 +32,7 @@ mkTestCase = do
mkTestCase : '{IO, Exception} ()
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,4 +1,4 @@
```unison
``` unison
structural ability Exit a where
exit : a -> b
@ -29,7 +29,7 @@ mkTestCase = do
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -48,7 +48,7 @@ mkTestCase = do
products : ([Nat], [Nat], [Nat]) -> Text
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,4 +1,4 @@
```unison
``` unison
structural ability DC r where
shift : ((a -> r) -> r) -> a
@ -43,7 +43,7 @@ mkTestCase = do
saveTestCase "case-03" "v4" finish trip
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -67,7 +67,7 @@ mkTestCase = do
suspSum : [Nat] -> Delayed Nat
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,4 +1,4 @@
```unison
``` unison
mutual0 = cases
0 -> "okay"
n ->
@ -12,7 +12,7 @@ mkTestCase = do
saveTestCase "case-04" "v4" mutual1 5
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -27,7 +27,7 @@ mkTestCase = do
mutual1 : Nat -> Text
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,6 +1,7 @@
Loops that access a shared counter variable, accessed in transactions.
Some thread delaying is just accomplished by counting in a loop.
```unison
``` unison
count : Nat -> ()
count = cases
0 -> ()
@ -27,7 +28,7 @@ body k out v =
atomically '(TVar.write out (Some n))
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -43,7 +44,7 @@ body k out v =
loop : '{IO} Nat -> Nat -> Nat ->{IO} Nat
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -56,7 +57,7 @@ scratch/main> add
```
Test case.
```unison
``` unison
spawn : Nat ->{io2.IO} Result
spawn k = let
out1 = TVar.newIO None
@ -89,7 +90,7 @@ tests : '{io2.IO} [Result]
tests = '(map spawn nats)
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -105,7 +106,7 @@ tests = '(map spawn nats)
tests : '{IO} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -4,18 +4,18 @@ https://github.com/unisonweb/unison/issues/2195
We add a simple definition.
```unison
``` unison
x = 999
```
Now, we update that definition and define a test-watch which depends on it.
```unison
``` unison
x = 1000
test> mytest = checks [x + 1 == 1001]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -42,7 +42,7 @@ test> mytest = checks [x + 1 == 1001]
```
We expect this 'add' to fail because the test is blocked by the update to `x`.
```ucm
``` ucm
scratch/main> add
x These definitions failed:
@ -54,14 +54,14 @@ scratch/main> add
Tip: Use `help filestatus` to learn more.
```
---
-----
```unison
``` unison
y = 42
test> useY = checks [y + 1 == 43]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -84,7 +84,7 @@ test> useY = checks [y + 1 == 43]
```
This should correctly identify `y` as a dependency and add that too.
```ucm
``` ucm
scratch/main> add useY
⍟ I've added these definitions:

View File

@ -1,6 +1,6 @@
Lets just make sure we can start a thread
```unison
``` unison
otherThread : '{io2.IO}()
otherThread = 'let
watch "I'm the other Thread" ()
@ -16,7 +16,7 @@ testBasicFork = 'let
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -32,7 +32,7 @@ testBasicFork = 'let
```
See if we can get another thread to stuff a value into a MVar
```unison
``` unison
thread1 : Nat -> MVar Nat -> '{io2.IO}()
thread1 x mv = 'let
go = 'let
@ -56,7 +56,7 @@ testBasicMultiThreadMVar = 'let
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -70,7 +70,7 @@ testBasicMultiThreadMVar = 'let
thread1 : Nat -> MVar Nat -> '{IO} ()
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -89,7 +89,7 @@ scratch/main> io.test testBasicMultiThreadMVar
Tip: Use view 1 to view the source of a test.
```
```unison
``` unison
sendingThread: Nat -> MVar Nat -> '{io2.IO}()
sendingThread toSend mv = 'let
go = 'let
@ -127,7 +127,7 @@ testTwoThreads = 'let
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -143,7 +143,7 @@ testTwoThreads = 'let
testTwoThreads : '{IO} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,6 +1,6 @@
# Tests for TLS builtins
```unison
``` unison
-- generated with:
-- openssl req -newkey rsa:2048 -subj '/CN=test.unison.cloud/O=Unison/C=US' -nodes -keyout key.pem -x509 -days 3650 -out cert.pem
@ -15,7 +15,7 @@ not_a_cert = "-----BEGIN SCHERMIFICATE-----\n-----END SCHERMIFICATE-----"
First lets make sure we can load our cert and private key
```unison
``` unison
this_should_work=match (decodeCert.impl (toUtf8 self_signed_cert_pem2) with
Left (Failure _ t _) -> [Fail t]
Right _ -> [Ok "succesfully decoded self_signed_pem"]
@ -27,7 +27,7 @@ this_should_not_work=match (decodeCert.impl (toUtf8 not_a_cert) with
what_should_work _ = this_should_work ++ this_should_not_work
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -42,7 +42,7 @@ what_should_work _ = this_should_work ++ this_should_not_work
what_should_work : ∀ _. _ -> [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -71,7 +71,7 @@ We'll create a server and a client, and start threads for each.
The server will report the port it is bound to via a passed MVar which
the client can read.
```unison
``` unison
serverThread: MVar Nat -> Text -> '{io2.IO}()
serverThread portVar toSend = 'let
go: '{io2.IO, Exception}()
@ -217,7 +217,7 @@ testCNReject _ =
runTest test
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -237,7 +237,7 @@ testCNReject _ =
testConnectSelfSigned : '{IO} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,8 +1,8 @@
Test for new Text -> Bytes conversions explicitly using UTF-8 as the encoding
Test for new Text -\> Bytes conversions explicitly using UTF-8 as the encoding
Unison has function for converting between `Text` and a UTF-8 `Bytes` encoding of the Text.
```ucm
``` ucm
scratch/main> find Utf8
1. builtin.Text.toUtf8 : Text -> Bytes
@ -13,7 +13,7 @@ scratch/main> find Utf8
```
ascii characters are encoded as single bytes (in the range 0-127).
```unison
``` unison
ascii: Text
ascii = "ABCDE"
@ -21,7 +21,7 @@ ascii = "ABCDE"
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -44,14 +44,14 @@ ascii = "ABCDE"
```
non-ascii characters are encoded as multiple bytes.
```unison
``` unison
greek: Text
greek = "ΑΒΓΔΕ"
> toUtf8 greek
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -73,7 +73,7 @@ greek = "ΑΒΓΔΕ"
```
We can check that encoding and then decoding should give us back the same `Text` we started with
```unison
``` unison
checkRoundTrip: Text -> [Result]
checkRoundTrip t =
bytes = toUtf8 t
@ -86,7 +86,7 @@ greek = "ΑΒΓΔΕ"
test> greekTest = checkRoundTrip greek
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -110,7 +110,7 @@ test> greekTest = checkRoundTrip greek
```
If we try to decode an invalid set of bytes, we get back `Text` explaining the decoding error:
```unison
``` unison
greek_bytes = Bytes.fromList [206, 145, 206, 146, 206, 147, 206, 148, 206]
@ -121,7 +121,7 @@ greek_bytes = Bytes.fromList [206, 145, 206, 146, 206, 147, 206, 148, 206]
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,7 +1,6 @@
Some random ability stuff to ensure things work.
```unison
``` unison
unique ability A where
one : Nat ->{A} Nat
two : Nat -> Nat ->{A} Nat
@ -17,7 +16,7 @@ ha = cases
{ four i -> c } -> handle c (j k l -> i+j+k+l) with ha
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -31,7 +30,7 @@ ha = cases
ha : Request {A} r -> r
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,6 +1,6 @@
The order of a set of abilities is normalized before hashing.
```unison
``` unison
unique ability Foo where
foo : ()
@ -14,7 +14,7 @@ term2 : () ->{Bar, Foo} ()
term2 _ = ()
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -30,7 +30,7 @@ term2 _ = ()
term2 : '{Bar, Foo} ()
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -5,12 +5,12 @@ https://github.com/unisonweb/unison/issues/2786
First we add an ability to the codebase.
Note that this will create the name `Channels.send` as an ability constructor.
```unison
``` unison
unique ability Channels where
send : a -> {Channels} ()
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -23,7 +23,7 @@ unique ability Channels where
ability Channels
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -31,11 +31,11 @@ scratch/main> add
ability Channels
```
Now we update the ability, changing the name of the constructor, _but_, we simultaneously
Now we update the ability, changing the name of the constructor, *but*, we simultaneously
add a new top-level term with the same name as the constructor which is being
removed from Channels.
```unison
``` unison
unique ability Channels where
sends : [a] -> {Channels} ()
@ -46,7 +46,7 @@ thing : '{Channels} ()
thing _ = send 1
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -67,7 +67,7 @@ thing _ = send 1
```
These should fail with a term/ctor conflict since we exclude the ability from the update.
```ucm
``` ucm
scratch/main> update.old patch Channels.send
x These definitions failed:
@ -89,9 +89,9 @@ scratch/main> update.old patch thing
ability Channels
```
If however, `Channels.send` and `thing` _depend_ on `Channels`, updating them should succeed since it pulls in the ability as a dependency.
If however, `Channels.send` and `thing` *depend* on `Channels`, updating them should succeed since it pulls in the ability as a dependency.
```unison
``` unison
unique ability Channels where
sends : [a] -> {Channels} ()
@ -102,7 +102,7 @@ thing : '{Channels} ()
thing _ = send 1
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -121,7 +121,7 @@ thing _ = send 1
```
These updates should succeed since `Channels` is a dependency.
```ucm
``` ucm
scratch/main> update.old.preview patch Channels.send
I found and typechecked these definitions in scratch.u. If you
@ -152,7 +152,7 @@ scratch/main> update.old.preview patch thing
```
We should also be able to successfully update the whole thing.
```ucm
``` ucm
scratch/main> update.old
⊡ Ignored previously added definitions: Channels
@ -165,11 +165,11 @@ scratch/main> update.old
```
# Constructor-term conflict
```unison
``` unison
X.x = 1
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -182,7 +182,7 @@ X.x = 1
X.x : Nat
```
```ucm
``` ucm
scratch/main2> add
⍟ I've added these definitions:
@ -190,12 +190,12 @@ scratch/main2> add
X.x : Nat
```
```unison
``` unison
structural ability X where
x : ()
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -214,7 +214,7 @@ structural ability X where
```
This should fail with a ctor/term conflict.
```ucm
``` ucm
scratch/main2> add
x These definitions failed:

View File

@ -2,7 +2,7 @@
## Basic usage
```unison
``` unison
even : Nat -> Boolean
even x = if x == 0 then true else odd (drop x 1)
@ -13,7 +13,7 @@ is2even : 'Boolean
is2even = '(even 2)
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -30,7 +30,7 @@ is2even = '(even 2)
```
it errors if there isn't a previous run
```ucm
``` ucm
scratch/main> add.run foo
⚠️
@ -39,7 +39,7 @@ scratch/main> add.run foo
something before attempting to save it.
```
```ucm
``` ucm
scratch/main> run is2even
true
@ -47,7 +47,8 @@ scratch/main> run is2even
```
it errors if the desired result name conflicts with a name in the
unison file
```ucm
``` ucm
scratch/main> add.run is2even
⚠️
@ -57,7 +58,8 @@ scratch/main> add.run is2even
```
otherwise, the result is successfully persisted
```ucm
``` ucm
scratch/main> add.run foo.bar.baz
⍟ I've added these definitions:
@ -65,7 +67,7 @@ scratch/main> add.run foo.bar.baz
foo.bar.baz : Boolean
```
```ucm
``` ucm
scratch/main> view foo.bar.baz
foo.bar.baz : Boolean
@ -74,7 +76,7 @@ scratch/main> view foo.bar.baz
```
## It resolves references within the unison file
```unison
``` unison
z b = b Nat.+ 12
y a b = a Nat.+ b Nat.+ z 10
@ -85,7 +87,7 @@ main : '{IO, Exception} (Nat -> Nat -> Nat)
main _ = y
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -100,7 +102,7 @@ main _ = y
z : Nat -> Nat
```
```ucm
``` ucm
scratch/main> run main
a b -> a Nat.+ b Nat.+ z 10
@ -115,12 +117,12 @@ scratch/main> add.run result
```
## It resolves references within the codebase
```unison
``` unison
inc : Nat -> Nat
inc x = x + 1
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -133,7 +135,7 @@ inc x = x + 1
inc : Nat -> Nat
```
```ucm
``` ucm
scratch/main> add inc
⍟ I've added these definitions:
@ -141,12 +143,12 @@ scratch/main> add inc
inc : Nat -> Nat
```
```unison
``` unison
main : '(Nat -> Nat)
main _ x = inc x
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -159,7 +161,7 @@ main _ x = inc x
main : '(Nat -> Nat)
```
```ucm
``` ucm
scratch/main> run main
inc
@ -178,13 +180,13 @@ scratch/main> view natfoo
```
## It captures scratch file dependencies at run time
```unison
``` unison
x = 1
y = x + x
main = 'y
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -199,17 +201,17 @@ main = 'y
y : Nat
```
```ucm
``` ucm
scratch/main> run main
2
```
```unison
``` unison
x = 50
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -223,7 +225,8 @@ x = 50
```
this saves 2 to xres, rather than 100
```ucm
``` ucm
scratch/main> add.run xres
⍟ I've added these definitions:
@ -238,11 +241,11 @@ scratch/main> view xres
```
## It fails with a message if add cannot complete cleanly
```unison
``` unison
main = '5
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -255,7 +258,7 @@ main = '5
main : 'Nat
```
```ucm
``` ucm
scratch/main> run main
5
@ -272,11 +275,11 @@ scratch/main> add.run xres
```
## It works with absolute names
```unison
``` unison
main = '5
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -289,7 +292,7 @@ main = '5
main : 'Nat
```
```ucm
``` ucm
.> run main
5

View File

@ -1,11 +1,11 @@
```unison
``` unison
test> foo : [Test.Result]
foo = []
```
Apparently when we add a test watch, we add a type annotation to it, even if it already has one. We don't want this to happen though!
Apparently when we add a test watch, we add a type annotation to it, even if it already has one. We don't want this to happen though\!
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -2,7 +2,7 @@
Let's set up some definitions to start:
```unison
``` unison
x = 1
y = 2
@ -10,7 +10,7 @@ structural type X = One Nat
structural type Y = Two Nat Nat
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -28,7 +28,7 @@ structural type Y = Two Nat Nat
```
Expected: `x` and `y`, `X`, and `Y` exist as above. UCM tells you this.
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -41,13 +41,13 @@ scratch/main> add
```
Let's add an alias for `1` and `One`:
```unison
``` unison
z = 1
structural type Z = One Nat
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -66,7 +66,7 @@ structural type Z = One Nat
Expected: `z` is now `1`. UCM tells you that this definition is also called `x`.
Also, `Z` is an alias for `X`.
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -79,12 +79,12 @@ scratch/main> add
```
Let's update something that has an alias (to a value that doesn't have a name already):
```unison
``` unison
x = 3
structural type X = Three Nat Nat Nat
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -103,7 +103,7 @@ structural type X = Three Nat Nat Nat
```
Expected: `x` is now `3` and `X` has constructor `Three`. UCM tells you the old definitions were also called `z` and `Z` and these names have also been updated.
```ucm
``` ucm
scratch/main> update
Okay, I'm searching the branch for code that needs to be
@ -118,12 +118,12 @@ scratch/main> update
```
Update it to something that already exists with a different name:
```unison
``` unison
x = 2
structural type X = Two Nat Nat
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -142,7 +142,7 @@ structural type X = Two Nat Nat
```
Expected: `x` is now `2` and `X` is `Two`. UCM says the old definition was also named `z/Z`, and was also updated. And it says the new definition is also named `y/Y`.
```ucm
``` ucm
scratch/main> update
Okay, I'm searching the branch for code that needs to be

View File

@ -1,19 +1,16 @@
The `alias.many` command can be used to copy definitions from the current namespace into your curated one.
The names that will be used in the target namespace are the names you specify, relative to the current namespace:
```scratch
/main> help alias.many
scratch/main> help alias.many
alias.many (or copy)
`alias.many <relative1> [relative2...] <namespace>` creates aliases `relative1`, `relative2`, ...
in the namespace `namespace`.
`alias.many foo.foo bar.bar .quux` creates aliases `.quux.foo.foo` and `.quux.bar.bar`.
alias.many (or copy)
`alias.many <relative1> [relative2...] <namespace>` creates aliases `relative1`, `relative2`, ...
in the namespace `namespace`.
`alias.many foo.foo bar.bar .quux` creates aliases `.quux.foo.foo` and `.quux.bar.bar`.
Let's try it\!
```
Let's try it!
```ucm
``` ucm
scratch/main> alias.many List.adjacentPairs List.all List.any List.chunk List.chunksOf List.dropWhile List.first List.init List.intersperse List.isEmpty List.last List.replicate List.splitAt List.tail List.takeWhile mylib
Here's what changed in mylib :
@ -62,4 +59,5 @@ scratch/main> find-in mylib
```
Thanks, `alias.many!
Thanks, `alias.many`\!

View File

@ -1,6 +1,6 @@
`alias.term` makes a new name for a term.
```ucm
``` ucm
project/main> alias.term lib.builtins.bug foo
Done.
@ -13,7 +13,7 @@ project/main> ls
```
It won't create a conflicted name, though.
```ucm
``` ucm
project/main> alias.term lib.builtins.todo foo
⚠️
@ -21,7 +21,7 @@ project/main> alias.term lib.builtins.todo foo
A term by that name already exists.
```
```ucm
``` ucm
project/main> ls
1. foo (a -> b)
@ -30,7 +30,7 @@ project/main> ls
```
You can use `debug.alias.term.force` for that.
```ucm
``` ucm
project/main> debug.alias.term.force lib.builtins.todo foo
Done.

View File

@ -1,6 +1,6 @@
`alias.type` makes a new name for a type.
```ucm
``` ucm
project/main> alias.type lib.builtins.Nat Foo
Done.
@ -13,7 +13,7 @@ project/main> ls
```
It won't create a conflicted name, though.
```ucm
``` ucm
project/main> alias.type lib.builtins.Int Foo
⚠️
@ -21,7 +21,7 @@ project/main> alias.type lib.builtins.Int Foo
A type by that name already exists.
```
```ucm
``` ucm
project/main> ls
1. Foo (builtin type)
@ -30,7 +30,7 @@ project/main> ls
```
You can use `debug.alias.type.force` for that.
```ucm
``` ucm
project/main> debug.alias.type.force lib.builtins.Int Foo
Done.

View File

@ -1,15 +1,14 @@
This tests a variable related bug in the ANF compiler.
The nested let would get flattened out, resulting in:
bar = result
which would be handled by renaming. However, the _context_ portion of
which would be handled by renaming. However, the *context* portion of
the rest of the code was not being renamed correctly, so `bar` would
remain in the definition of `baz`.
```unison
``` unison
foo _ =
id x = x
void x = ()
@ -24,7 +23,7 @@ foo _ =
> !foo
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -44,7 +43,7 @@ foo _ =
5
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -2,7 +2,7 @@
Any.unsafeExtract is a way to extract the value contained in an Any. This is unsafe because it allows the programmer to coerce a value into any type, which would cause undefined behaviour if used to coerce a value to the wrong type.
```unison
``` unison
test> Any.unsafeExtract.works =
use Nat !=
checks [1 == Any.unsafeExtract (Any 1),
@ -11,7 +11,7 @@ test> Any.unsafeExtract.works =
]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -31,7 +31,7 @@ test> Any.unsafeExtract.works =
✅ Passed Passed
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,6 +1,6 @@
# Doc rendering
```unison
``` unison
structural type Maybe a = Nothing | Just a
otherTerm = "text"
@ -77,7 +77,7 @@ Transclusion/evaluation:
term = 42
```
```ucm
``` ucm
scratch/main> display term.doc
# Heading
@ -146,7 +146,7 @@ scratch/main> display term.doc
message
```
```api
``` api
GET /api/projects/scratch/branches/main/getDefinition?names=term
{
"missingDefinitions": [],
@ -940,4 +940,5 @@ GET /api/projects/scratch/branches/main/getDefinition?names=term
},
"typeDefinitions": {}
}
```
```

View File

@ -1,13 +1,13 @@
# find api
```unison
``` unison
rachel.filesystem.x = 42
ross.httpClient.y = 43
joey.httpServer.z = 44
joey.yaml.zz = 45
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -23,7 +23,7 @@ joey.yaml.zz = 45
ross.httpClient.y : ##Nat
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -34,7 +34,7 @@ scratch/main> add
ross.httpClient.y : ##Nat
```
```api
``` api
-- Namespace segment prefix search
GET /api/projects/scratch/branches/main/find?query=http
[
@ -252,4 +252,5 @@ GET /api/projects/scratch/branches/main/find?query=joey.http
}
]
]
```
```

View File

@ -1,11 +1,11 @@
# Get Definitions Test
```unison
``` unison
nested.names.x.doc = {{ Documentation }}
nested.names.x = 42
```
```api
``` api
-- Should NOT find names by suffix
GET /api/projects/scratch/branches/main/getDefinition?names=x
{
@ -205,7 +205,9 @@ GET /api/projects/scratch/branches/main/getDefinition?names=%23qkhkl0n238&relati
},
"typeDefinitions": {}
}
``````unison
```
``` unison
doctest.thing.doc = {{ The correct docs for the thing }}
doctest.thing = "A thing"
doctest.thingalias.doc = {{ Docs for the alias, should not be displayed }}
@ -216,7 +218,7 @@ doctest.otherstuff.thing = "A different thing"
Only docs for the term we request should be returned, even if there are other term docs with the same suffix.
```api
``` api
GET /api/projects/scratch/branches/main/getDefinition?names=thing&relativeTo=doctest
{
"missingDefinitions": [],
@ -332,9 +334,11 @@ GET /api/projects/scratch/branches/main/getDefinition?names=thing&relativeTo=doc
},
"typeDefinitions": {}
}
```If we request a doc, the api should return the source, but also the rendered doc should appear in the 'termDocs' list.
```
```api
If we request a doc, the api should return the source, but also the rendered doc should appear in the 'termDocs' list.
``` api
GET /api/projects/scratch/branches/main/getDefinition?names=thing.doc&relativeTo=doctest
{
"missingDefinitions": [],
@ -507,4 +511,5 @@ GET /api/projects/scratch/branches/main/getDefinition?names=thing.doc&relativeTo
},
"typeDefinitions": {}
}
```
```

View File

@ -1,6 +1,6 @@
# List Projects And Branches Test
```api
``` api
-- Should list all projects
GET /api/projects
[
@ -53,4 +53,5 @@ GET /api/projects/project-one/branches?prefix=branch-t
"branchName": "branch-two"
}
]
```
```

View File

@ -1,6 +1,6 @@
# Namespace Details Test
```unison
``` unison
{{ Documentation }}
nested.names.x = 42
@ -9,7 +9,7 @@ Here's a *README*!
}}
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -24,7 +24,7 @@ Here's a *README*!
nested.names.x.doc : Doc2
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -34,7 +34,7 @@ scratch/main> add
nested.names.x.doc : Doc2
```
```api
``` api
-- Should find names by suffix
GET /api/projects/scratch/branches/main/namespaces/nested.names
{
@ -78,4 +78,5 @@ GET /api/projects/scratch/branches/main/namespaces/nested.names
"tag": "Paragraph"
}
}
```
```

View File

@ -1,13 +1,13 @@
# Namespace list api
```unison
``` unison
{{ Documentation }}
nested.names.x = 42
nested.names.readme = {{ I'm a readme! }}
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -22,7 +22,7 @@ nested.names.readme = {{ I'm a readme! }}
nested.names.x.doc : Doc2
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -32,7 +32,7 @@ scratch/main> add
nested.names.x.doc : Doc2
```
```api
``` api
GET /api/projects/scratch/branches/main/list?namespace=nested.names
{
"namespaceListingChildren": [
@ -131,4 +131,5 @@ GET /api/projects/scratch/branches/main/list?namespace=names&relativeTo=nested
"namespaceListingFQN": "nested.names",
"namespaceListingHash": "#oms19b4f9s3c8tb5skeb8jii95ij35n3hdg038pu6rv5b0fikqe4gd7lnu6a1i6aq5tdh2opdo4s0sfrupvk6vfkr9lf0n752gbl8o0"
}
```
```

View File

@ -1,6 +1,6 @@
# Definition Summary APIs
```unison
``` unison
nat : Nat
nat = 42
doc : Doc2
@ -21,7 +21,7 @@ structural ability Stream s where
## Term Summary APIs
```api
``` api
-- term
GET /api/projects/scratch/branches/main/definitions/terms/by-hash/@qkhkl0n238s1eqibd1ecb8605sqj1m4hpoaag177cu572otqlaf1u28c8suuuqgljdtthsjtr07rv04np05o6oa27ml9105k7uas0t8/summary?name=nat
{
@ -667,9 +667,11 @@ GET /api/projects/scratch/branches/main/definitions/terms/by-hash/@@IO.putBytes.
},
"tag": "Plain"
}
```## Type Summary APIs
```
```api
## Type Summary APIs
``` api
-- data
GET /api/projects/scratch/branches/main/definitions/types/by-hash/@altimqs66j3dh94dpab5pg7j5adjrndq61n803j7fg0v0ohdiut6or66bu1fiongpd45s5euiuo8ru47b928aqv8osln1ikdeg05hq0/summary?name=Thing
{
@ -823,4 +825,5 @@ GET /api/projects/scratch/branches/main/definitions/types/by-hash/@@Nat/summary?
},
"tag": "Data"
}
```
```

View File

@ -2,11 +2,11 @@
Should block an `add` if it requires an update on an in-file dependency.
```unison
``` unison
x = 1
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -19,7 +19,7 @@ x = 1
x : Nat
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -29,12 +29,12 @@ scratch/main> add
```
Update `x`, and add a new `y` which depends on the update
```unison
``` unison
x = 10
y = x + 1
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -54,7 +54,7 @@ y = x + 1
```
Try to add only the new `y`. This should fail because it requires an update to `x`, but we only ran an 'add'.
```ucm
``` ucm
scratch/main> add y
x These definitions failed:

View File

@ -4,7 +4,7 @@
For example:
```unison
``` unison
ex thing =
thing y = y
-- refers to `thing` in this block
@ -15,7 +15,7 @@ ex thing =
> ex "hello"
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -39,7 +39,7 @@ ex thing =
The `thing` reference in `bar` refers to the one declared locally in the block that `bar` is part of. This is true even if the declaration which shadows the outer name appears later in the block, for instance:
```unison
``` unison
ex thing =
bar x = thing x + 1
thing y = y
@ -48,7 +48,7 @@ ex thing =
> ex "hello"
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -72,7 +72,7 @@ ex thing =
This is just the normal lexical scoping behavior. For example:
```unison
``` unison
ex thing =
bar x = thing x + 1 -- references outer `thing`
baz z =
@ -83,7 +83,7 @@ ex thing =
> ex (x -> x * 100)
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -103,9 +103,9 @@ ex thing =
4201
```
Here's another example, showing that bindings cannot reference bindings declared in blocks nested in the _body_ (the final expression) of a block:
Here's another example, showing that bindings cannot reference bindings declared in blocks nested in the *body* (the final expression) of a block:
```unison
``` unison
ex thing =
bar x = thing x + 1 -- refers to outer thing
let
@ -115,7 +115,7 @@ ex thing =
> ex (x -> x * 100)
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -137,9 +137,9 @@ ex thing =
```
### Blocks can define one or more functions which are recursive or mutually recursive
We call these groups of definitions that reference each other in a block _cycles_. For instance:
We call these groups of definitions that reference each other in a block *cycles*. For instance:
```unison
``` unison
sumTo n =
-- A recursive function, defined inside a block
go acc n =
@ -154,7 +154,7 @@ ex n =
ping 42
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -174,14 +174,14 @@ The `go` function is a one-element cycle (it reference itself), and `ping` and `
For instance, this works:
```unison
``` unison
ex n =
ping x = pong + 1 + x
pong = 42
ping 0
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -198,14 +198,14 @@ Since the forward reference to `pong` appears inside `ping`.
This, however, will not compile:
```unison
``` unison
ex n =
pong = ping + 1
ping = 42
pong
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -217,13 +217,13 @@ ex n =
```
This also won't compile; it's a cyclic reference that isn't guarded:
```unison
``` unison
ex n =
loop = loop
loop
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -234,13 +234,13 @@ ex n =
```
This, however, will compile. This also shows that `'expr` is another way of guarding a definition.
```unison
``` unison
ex n =
loop = '(!loop)
!loop
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -253,13 +253,13 @@ ex n =
ex : n -> r
```
Just don't try to run it as it's an infinite loop!
Just don't try to run it as it's an infinite loop\!
### Cyclic definitions in a block don't have access to any abilities
The reason is it's unclear what the order should be of any requests that are made. It can also be viewed of a special case of the restriction that elements of a cycle must all be guarded. Here's an example:
```unison
``` unison
structural ability SpaceAttack where
launchMissiles : Text -> Nat
@ -269,7 +269,7 @@ ex n =
zap1
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -279,11 +279,11 @@ ex n =
```
### The _body_ of recursive functions can certainly access abilities
### The *body* of recursive functions can certainly access abilities
For instance, this works fine:
```unison
``` unison
structural ability SpaceAttack where
launchMissiles : Text -> Nat
@ -293,7 +293,7 @@ ex n =
zap1 "pluto"
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -311,7 +311,7 @@ ex n =
For instance, `zap` here isn't considered part of the cycle (it doesn't reference `ping` or `pong`), so this typechecks fine:
```unison
``` unison
structural ability SpaceAttack where
launchMissiles : Text -> Nat
@ -322,7 +322,7 @@ ex n =
ping 42
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -338,7 +338,7 @@ ex n =
```
This is actually parsed as if you moved `zap` after the cycle it find itself a part of:
```unison
``` unison
structural ability SpaceAttack where
launchMissiles : Text -> Nat
@ -349,7 +349,7 @@ ex n =
ping 42
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,13 +1,13 @@
Regression test for https://github.com/unisonweb/unison/pull/2819
```unison
``` unison
hangExample : Boolean
hangExample =
("a long piece of text to hang the line" == "")
&& ("a long piece of text to hang the line" == "")
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -20,7 +20,7 @@ hangExample =
hangExample : Boolean
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -2,11 +2,11 @@ The `branch` command creates a new branch.
First, we'll create a term to include in the branches.
```unison
``` unison
someterm = 18
```
```ucm
``` ucm
scratch/main> builtins.merge lib.builtins
Done.
@ -23,7 +23,7 @@ Now, the `branch` demo:
`branch` can create a branch from a different branch in the same project, from a different branch in a different
project. It can also create an empty branch.
```ucm
``` ucm
foo/main> branch topic1
Done. I've created the topic1 branch based off of main.
@ -151,7 +151,7 @@ scratch/main> branch.empty foo/empty4
```
The `branch` command can create branches named `releases/drafts/*` (because why not).
```ucm
``` ucm
foo/main> branch releases/drafts/1.2.3
Done. I've created the releases/drafts/1.2.3 branch based off
@ -165,7 +165,7 @@ foo/main> switch /releases/drafts/1.2.3
```
The `branch` command can't create branches named `releases/*` nor `releases/drafts/*`.
```ucm
``` ucm
foo/main> branch releases/1.2.3
Branch names like releases/1.2.3 are reserved for releases.

View File

@ -1,9 +1,9 @@
```unison
``` unison
foo = 5
foo.bar = 1
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -17,7 +17,7 @@ foo.bar = 1
foo.bar : ##Nat
```
```ucm
``` ucm
p0/main> add
⍟ I've added these definitions:
@ -26,12 +26,12 @@ p0/main> add
foo.bar : ##Nat
```
```unison
``` unison
bonk = 5
donk.bonk = 1
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -47,7 +47,7 @@ donk.bonk = 1
(also named foo.bar)
```
```ucm
``` ucm
p1/main> add
⍟ I've added these definitions:

View File

@ -1,4 +1,4 @@
```unison
``` unison
bonk : forall a. a -> a
bonk x =
zonk : forall a. a -> a
@ -8,7 +8,7 @@ bonk x =
x
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,7 +1,6 @@
We can display the guide before and after adding it to the codebase:
```ucm
``` ucm
.> display doc.guide
# Unison computable documentation
@ -414,11 +413,11 @@ We can display the guide before and after adding it to the codebase:
```
But we can't display this due to a decompilation problem.
```unison
``` unison
rendered = Pretty.get (docFormatConsole doc.guide)
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -431,7 +430,7 @@ rendered = Pretty.get (docFormatConsole doc.guide)
rendered : Annotated () (Either SpecialForm ConsoleText)
```
```ucm
``` ucm
.> display rendered
# Unison computable documentation
@ -845,13 +844,13 @@ rendered = Pretty.get (docFormatConsole doc.guide)
```
And then this sometimes generates a GHC crash "strange closure error" but doesn't seem deterministic.
```unison
``` unison
rendered = Pretty.get (docFormatConsole doc.guide)
> rendered
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,6 +1,6 @@
The `builtins.merge` command adds the known builtins to the specified subnamespace within the current namespace.
```ucm
``` ucm
scratch/main> builtins.merge builtins
Done.

View File

@ -4,7 +4,7 @@ This transcript defines unit tests for builtin functions. There's a single `scra
## `Int` functions
```unison
``` unison
use Int
-- used for some take/drop tests later
@ -83,7 +83,7 @@ test> Int.tests.conversions =
## `Nat` functions
```unison
``` unison
use Nat
test> Nat.tests.arithmetic =
@ -153,7 +153,8 @@ test> Nat.tests.conversions =
```
## `Boolean` functions
```unison
``` unison
test> Boolean.tests.orTable =
checks [
true || true == true,
@ -177,7 +178,7 @@ test> Boolean.tests.notTable =
## `Text` functions
```unison
``` unison
test> Text.tests.takeDropAppend =
checks [
"yabba" ++ "dabba" == "yabbadabba",
@ -271,7 +272,7 @@ test> Text.tests.indexOfEmoji =
## `Bytes` functions
```unison
``` unison
test> Bytes.tests.at =
bs = Bytes.fromList [77, 13, 12]
checks [
@ -331,7 +332,7 @@ test> Bytes.tests.indexOf =
## `List` comparison
```unison
``` unison
test> checks [
compare [] [1,2,3] == -1,
compare [1,2,3] [1,2,3,4] == -1,
@ -345,7 +346,8 @@ test> checks [
```
Other list functions
```unison
``` unison
test> checks [
List.take bigN [1,2,3] == [1,2,3],
List.drop bigN [1,2,3] == []
@ -354,14 +356,14 @@ test> checks [
## `Any` functions
```unison
``` unison
> [Any "hi", Any (41 + 1)]
test> Any.test1 = checks [(Any "hi" == Any "hi")]
test> Any.test2 = checks [(not (Any "hi" == Any 42))]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -392,7 +394,7 @@ test> Any.test2 = checks [(not (Any "hi" == Any 42))]
```
## Sandboxing functions
```unison
``` unison
openFile1 t = openFile t
openFile2 t = openFile1 t
@ -413,7 +415,7 @@ test> Sandbox.test3 = checks [validateSandboxed [termLink openFile.impl]
openFile]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -453,7 +455,7 @@ openFile]
✅ Passed Passed
```
```unison
``` unison
openFilesIO = do
checks
[ not (validateSandboxedSimpl [] (value openFile))
@ -466,7 +468,7 @@ openFilesIO = do
]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -479,7 +481,7 @@ openFilesIO = do
openFilesIO : '{IO} [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -501,12 +503,12 @@ scratch/main> io.test openFilesIO
Just exercises the function
```unison
``` unison
> Universal.murmurHash 1
test> Universal.murmurHash.tests = checks [Universal.murmurHash [1,2,3] == Universal.murmurHash [1,2,3]]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -534,7 +536,7 @@ test> Universal.murmurHash.tests = checks [Universal.murmurHash [1,2,3] == Unive
Now that all the tests have been added to the codebase, let's view the test report. This will fail the transcript (with a nice message) if any of the tests are failing.
```ucm
``` ucm
scratch/main> test
Cached test results (`help testcache` to learn more)

View File

@ -1,11 +1,10 @@
This should render as `Bytes.fromList [1,2,3,4]`, not `##Bytes.fromSequence [1,2,3,4]`:
```unison
``` unison
> Bytes.fromList [1,2,3,4]
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,11 +1,11 @@
Regression test for https://github.com/unisonweb/unison/issues/763
```unison
``` unison
(+-+) : Nat -> Nat -> Nat
(+-+) x y = x * y
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -18,7 +18,7 @@ Regression test for https://github.com/unisonweb/unison/issues/763
+-+ : Nat -> Nat -> Nat
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,10 +1,10 @@
See [this ticket](https://github.com/unisonweb/unison/issues/873); the point being, this shouldn't crash the runtime. :)
```unison
``` unison
(-) = builtin.Nat.sub
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -17,7 +17,7 @@ See [this ticket](https://github.com/unisonweb/unison/issues/873); the point bei
- : Nat -> Nat -> Int
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -25,11 +25,11 @@ scratch/main> add
- : Nat -> Nat -> Int
```
```unison
``` unison
baz x = x - 1
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,11 +1,11 @@
```unison
``` unison
structural type Zoink a b c = Zoink a b c
> Any ()
> [ Zoink [0,1,2,3,4,5] [6,3,3,3,3,3,3,3,3,3,3,4,4,4,4,4,4,4,4,4,3] () ]
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,9 +1,9 @@
```unison
``` unison
f : (() -> a) -> Nat
f x = 42
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,6 +1,6 @@
Demonstrating `create.author`:
```ucm
``` ucm
scratch/main> create.author alicecoder "Alice McGee"
Added definitions:

View File

@ -1,6 +1,6 @@
Update a member of a cycle, but retain the cycle.
```unison
``` unison
ping : 'Nat
ping _ = !pong + 1
@ -8,7 +8,7 @@ pong : 'Nat
pong _ = !ping + 2
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -22,7 +22,7 @@ pong _ = !ping + 2
pong : 'Nat
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -31,12 +31,12 @@ scratch/main> add
pong : 'Nat
```
```unison
``` unison
ping : 'Nat
ping _ = !pong + 3
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -50,7 +50,7 @@ ping _ = !pong + 3
ping : 'Nat
```
```ucm
``` ucm
scratch/main> update
Okay, I'm searching the branch for code that needs to be

View File

@ -1,6 +1,6 @@
Update a member of a cycle with a type-preserving update, but sever the cycle.
```unison
``` unison
ping : 'Nat
ping _ = !pong + 1
@ -8,7 +8,7 @@ pong : 'Nat
pong _ = !ping + 2
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -22,7 +22,7 @@ pong _ = !ping + 2
pong : 'Nat
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -31,12 +31,12 @@ scratch/main> add
pong : 'Nat
```
```unison
``` unison
ping : 'Nat
ping _ = 3
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -50,7 +50,7 @@ ping _ = 3
ping : 'Nat
```
```ucm
``` ucm
scratch/main> update
Okay, I'm searching the branch for code that needs to be

View File

@ -1,6 +1,6 @@
Update a member of a cycle with a type-changing update, thus severing the cycle.
```unison
``` unison
ping : 'Nat
ping _ = !pong + 1
@ -8,7 +8,7 @@ pong : 'Nat
pong _ = !ping + 2
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -22,7 +22,7 @@ pong _ = !ping + 2
pong : 'Nat
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -31,12 +31,12 @@ scratch/main> add
pong : 'Nat
```
```unison
``` unison
ping : Nat
ping = 3
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -50,7 +50,7 @@ ping = 3
ping : Nat
```
```ucm
``` ucm
scratch/main> update.old
⍟ I've updated these names to your new definition:

View File

@ -1,6 +1,6 @@
`update` properly discovers and establishes new cycles.
```unison
``` unison
ping : 'Nat
ping _ = 1
@ -8,7 +8,7 @@ pong : 'Nat
pong _ = !ping + 2
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -22,7 +22,7 @@ pong _ = !ping + 2
pong : 'Nat
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -31,7 +31,7 @@ scratch/main> add
pong : 'Nat
```
```unison
``` unison
ping : 'Nat
ping _ = !clang + 1
@ -39,7 +39,7 @@ clang : 'Nat
clang _ = !pong + 3
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -57,7 +57,7 @@ clang _ = !pong + 3
ping : 'Nat
```
```ucm
``` ucm
scratch/main> update.old ping
⍟ I've added these definitions:

View File

@ -1,6 +1,6 @@
Not yet working: properly updating nameless implicit terms.
```unison
``` unison
inner.ping : 'Nat
inner.ping _ = !pong + 1
@ -8,7 +8,7 @@ pong : 'Nat
pong _ = !inner.ping + 2
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -22,7 +22,7 @@ pong _ = !inner.ping + 2
pong : 'Nat
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -34,12 +34,12 @@ scratch/main> add
Here we queue up an update by saving in a namespace where `inner.ping` and `pong` both have names, but then apply the
update in a namespace where only `ping` has a name.
```unison
``` unison
inner.ping : 'Nat
inner.ping _ = !pong + 3
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -53,7 +53,7 @@ inner.ping _ = !pong + 3
inner.ping : 'Nat
```
```ucm
``` ucm
☝️ The namespace .inner is empty.
.inner> update.old
@ -72,4 +72,5 @@ scratch/main> view inner.ping
```
The bug here is that `inner.ping` still refers to `pong` by name. But if we properly identified the nameless (in the
context that the update was applied) `pong` as an implicit term to include in the new `ping`'s cycle, then `ping` would
be left referring to a nameless thing (namely, `pong`, but updated to refer to the new `ping).
be left referring to a nameless thing (namely, `pong`, but updated to refer to the new `ping`).

View File

@ -1,4 +1,4 @@
```unison
``` unison
x = 30
y : Nat
@ -12,7 +12,7 @@ ability Ask a where
ask : a
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,4 +1,4 @@
```unison
``` unison
a.b.one = 1
a.two = 2
@ -9,7 +9,7 @@ structural type a.x.Foo = Foo | Bar
structural type a.b.Baz = Boo
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -27,7 +27,7 @@ structural type a.b.Baz = Boo
a.x.three : ##Nat
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,7 +1,8 @@
First we'll set up two libraries, and then we'll use them in some projects and show what `names` are deep-loaded for them.
Our two "libraries":
```unison
``` unison
text.a = 1
text.b = 2
text.c = 3
@ -12,7 +13,8 @@ http.z = 8
```
Our `app1` project includes the text library twice and the http library twice as direct dependencies.
```ucm
``` ucm
scratch/app1> fork text lib.text_v1
Done.
@ -39,7 +41,8 @@ scratch/app1> delete.namespace http
```
As such, we see two copies of `a` and two copies of `x` via these direct dependencies.
```ucm
``` ucm
scratch/app1> names a
Term
@ -59,7 +62,8 @@ scratch/app1> names x
```
Our `app2` project includes the `http` library twice as direct dependencies, and once as an indirect dependency via `webutil`.
It also includes the `text` library twice as indirect dependencies via `webutil`
```ucm
``` ucm
scratch/app2> fork http lib.http_v1
Done.
@ -91,7 +95,8 @@ scratch/app2> delete.namespace text
```
Now we see two copies of `x` via direct dependencies on `http`, and one copy of `a` via indirect dependency on `text` via `webutil`.
We see neither the second indirect copy of `a` nor the indirect copy of `x` via webutil because we already have names for them.
```ucm
``` ucm
scratch/app2> names a
Term

View File

@ -1,10 +1,10 @@
```ucm
``` ucm
diffs/main> builtins.merge
Done.
```
```unison
``` unison
term =
_ = "Here's some text"
1 + 1
@ -12,7 +12,7 @@ term =
type Type = Type Nat
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -26,7 +26,7 @@ type Type = Type Nat
term : Nat
```
```ucm
``` ucm
diffs/main> add
⍟ I've added these definitions:
@ -42,7 +42,7 @@ diffs/main> branch.create new
`switch /main` then `merge /new`.
```
```unison
``` unison
term =
_ = "Here's some different text"
1 + 2
@ -50,7 +50,7 @@ term =
type Type a = Type a Text
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -65,7 +65,7 @@ type Type a = Type a Text
term : Nat
```
```ucm
``` ucm
diffs/new> update
Okay, I'm searching the branch for code that needs to be
@ -76,7 +76,7 @@ diffs/new> update
```
Diff terms
```api
``` api
GET /api/projects/diffs/diff/terms?oldBranchRef=main&newBranchRef=new&oldTerm=term&newTerm=term
{
"diff": {
@ -558,9 +558,11 @@ GET /api/projects/diffs/diff/terms?oldBranchRef=main&newBranchRef=new&oldTerm=te
},
"project": "diffs"
}
```Diff types
```
```api
Diff types
``` api
GET /api/projects/diffs/diff/types?oldBranchRef=main&newBranchRef=new&oldType=Type&newType=Type
{
"diff": {
@ -804,4 +806,5 @@ GET /api/projects/diffs/diff/types?oldBranchRef=main&newBranchRef=new&oldType=Ty
},
"project": "diffs"
}
```
```

View File

@ -2,15 +2,15 @@
# Delete namespace dependents check
This is a regression test, previously `delete.namespace` allowed a delete as long as the deletions had a name _anywhere_ in your codebase, it should only check the current project branch.
This is a regression test, previously `delete.namespace` allowed a delete as long as the deletions had a name *anywhere* in your codebase, it should only check the current project branch.
```unison
``` unison
sub.dependency = 123
dependent = dependency + 99
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -24,7 +24,7 @@ dependent = dependency + 99
sub.dependency : Nat
```
```ucm
``` ucm
myproject/main> add
⍟ I've added these definitions:

View File

@ -1,6 +1,6 @@
# delete.namespace.force
```unison
``` unison
no_dependencies.thing = "no dependents on this term"
dependencies.term1 = 1
@ -12,7 +12,7 @@ dependents.usage2 = dependencies.term1 * dependencies.term2
Deleting a namespace with no external dependencies should succeed.
```ucm
``` ucm
scratch/main> delete.namespace no_dependencies
Done.
@ -20,7 +20,7 @@ scratch/main> delete.namespace no_dependencies
```
Deleting a namespace with external dependencies should fail and list all dependents.
```ucm
``` ucm
scratch/main> delete.namespace dependencies
⚠️
@ -41,7 +41,7 @@ scratch/main> delete.namespace dependencies
```
Deleting a namespace with external dependencies should succeed when using `delete.namespace.force`
```ucm
``` ucm
scratch/main> delete.namespace.force dependencies
Done.
@ -61,7 +61,7 @@ scratch/main> delete.namespace.force dependencies
```
I should be able to view an affected dependency by number
```ucm
``` ucm
scratch/main> view 2
dependents.usage2 : Nat
@ -72,7 +72,7 @@ scratch/main> view 2
```
Deleting the root namespace should require confirmation if not forced.
```ucm
``` ucm
scratch/main> delete.namespace .
⚠️
@ -94,7 +94,7 @@ scratch/main> history .
```
Deleting the root namespace shouldn't require confirmation if forced.
```ucm
``` ucm
scratch/main> delete.namespace.force .
Okay, I deleted everything except the history. Use `undo` to

View File

@ -1,7 +1,7 @@
Deleting the branch you are on takes you to its parent (though this is impossible to see in a transcript, since we set
your working directory with each command).
```ucm
``` ucm
foo/main> branch topic
Done. I've created the topic branch based off of main.
@ -14,7 +14,7 @@ foo/topic> delete.branch /topic
```
A branch need not be preceded by a forward slash.
```ucm
``` ucm
foo/main> branch topic
Done. I've created the topic branch based off of main.
@ -27,7 +27,7 @@ foo/topic> delete.branch topic
```
You can precede the branch name by a project name.
```ucm
``` ucm
foo/main> branch topic
Done. I've created the topic branch based off of main.
@ -40,7 +40,7 @@ scratch/main> delete.branch foo/topic
```
You can delete the only branch in a project.
```ucm
``` ucm
foo/main> delete.branch /main
```

View File

@ -1,6 +1,6 @@
# delete.project
```ucm
``` ucm
scratch/main> project.create-empty foo
🎉 I've created the project foo.

View File

@ -1,4 +1,4 @@
```ucm
``` ucm
scratch/main> delete foo
⚠️
@ -7,12 +7,12 @@ scratch/main> delete foo
foo
```
```unison
``` unison
foo = 1
structural type Foo = Foo ()
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -5,7 +5,7 @@ The delete command can delete both terms and types.
First, let's make sure it complains when we try to delete a name that doesn't
exist.
```ucm
``` ucm
.> delete.verbose foo
⚠️
@ -17,12 +17,12 @@ exist.
Now for some easy cases. Deleting an unambiguous term, then deleting an
unambiguous type.
```unison
``` unison
foo = 1
structural type Foo = Foo ()
```
```ucm
``` ucm
.> add
⍟ I've added these definitions:
@ -57,12 +57,12 @@ structural type Foo = Foo ()
```
How about an ambiguous term?
```unison
``` unison
foo = 1
bar = 2
```
```ucm
``` ucm
☝️ The namespace .a is empty.
.a> add
@ -79,7 +79,7 @@ bar = 2
```
A delete should remove both versions of the term.
```ucm
``` ucm
.> delete.verbose a.foo
Removed definitions:
@ -101,12 +101,12 @@ A delete should remove both versions of the term.
```
Let's repeat all that on a type, for completeness.
```unison
``` unison
structural type Foo = Foo ()
structural type Bar = Bar
```
```ucm
``` ucm
.a> add
⍟ I've added these definitions:
@ -144,12 +144,12 @@ structural type Bar = Bar
```
Finally, let's try to delete a term and a type with the same name.
```unison
``` unison
foo = 1
structural type foo = Foo ()
```
```ucm
``` ucm
.> add
⍟ I've added these definitions:
@ -169,13 +169,13 @@ structural type foo = Foo ()
```
We want to be able to delete multiple terms at once
```unison
``` unison
a = "a"
b = "b"
c = "c"
```
```ucm
``` ucm
.> add
⍟ I've added these definitions:
@ -197,14 +197,14 @@ c = "c"
```
We can delete terms and types in the same invocation of delete
```unison
``` unison
structural type Foo = Foo ()
a = "a"
b = "b"
c = "c"
```
```ucm
``` ucm
.> add
⍟ I've added these definitions:
@ -238,11 +238,11 @@ c = "c"
```
We can delete a type and its constructors
```unison
``` unison
structural type Foo = Foo ()
```
```ucm
``` ucm
.> add
⍟ I've added these definitions:
@ -266,14 +266,14 @@ structural type Foo = Foo ()
```
You should not be able to delete terms which are referenced by other terms
```unison
``` unison
a = 1
b = 2
c = 3
d = a + b + c
```
```ucm
``` ucm
.> add
⍟ I've added these definitions:
@ -299,14 +299,14 @@ d = a + b + c
```
But you should be able to delete all terms which reference each other in a single command
```unison
``` unison
e = 11
f = 12 + e
g = 13 + f
h = e + f + g
```
```ucm
``` ucm
.> add
⍟ I've added these definitions:
@ -330,7 +330,7 @@ h = e + f + g
```
You should be able to delete a type and all the functions that reference it in a single command
```unison
``` unison
structural type Foo = Foo Nat
incrementFoo : Foo -> Nat
@ -338,7 +338,7 @@ incrementFoo = cases
(Foo n) -> n + 1
```
```ucm
``` ucm
.> add
⍟ I've added these definitions:
@ -359,14 +359,14 @@ incrementFoo = cases
```
If you mess up on one of the names of your command, delete short circuits
```unison
``` unison
e = 11
f = 12 + e
g = 13 + f
h = e + f + g
```
```ucm
``` ucm
.> add
⍟ I've added these definitions:
@ -386,12 +386,12 @@ h = e + f + g
```
Cyclical terms which are guarded by a lambda are allowed to be deleted
```unison
``` unison
ping _ = 1 Nat.+ !pong
pong _ = 4 Nat.+ !ping
```
```ucm
``` ucm
.> add
⍟ I've added these definitions:

View File

@ -1,8 +1,10 @@
### `debug.file`
I can use `debug.file` to see the hashes of the last typechecked file.
Given this .u file:
```unison
``` unison
structural type outside.A = A Nat outside.B
structural type outside.B = B Int
outside.c = 3
@ -14,7 +16,7 @@ inside.q x = x + p * p
inside.r = d
```
```ucm
``` ucm
scratch/main> debug.file
type inside.M#h37a56c5ep
@ -30,8 +32,10 @@ scratch/main> debug.file
This will help me make progress in some situations when UCM is being deficient or broken.
### `dependents` / `dependencies`
But wait, there's more. I can check the dependencies and dependents of a definition:
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -110,3 +114,4 @@ scratch/main> dependents d
```
We don't have an index for dependents of constructors, but iirc if you ask for that, it will show you dependents of the structural type that provided the constructor.

View File

@ -2,7 +2,7 @@
Here's a couple examples:
```unison
``` unison
ex0 : Nat -> Nat
ex0 n =
(a, _, (c,d)) = ("uno", "dos", (n, 7))
@ -14,7 +14,7 @@ ex1 tup =
c + d
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -28,7 +28,7 @@ ex1 tup =
ex1 : (a, b, (Nat, Nat)) -> Nat
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -52,13 +52,13 @@ Notice that `ex0` is printed using the `cases` syntax (but `ex1` is not). The pr
A destructuring bind is just syntax for a single branch pattern match. Notice that Unison detects this function as an alias of `ex1`:
```unison
``` unison
ex2 : (a,b,(Nat,Nat)) -> Nat
ex2 tup = match tup with
(a, b, (c,d)) -> c + d
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -76,13 +76,13 @@ ex2 tup = match tup with
Destructuring binds can't be recursive: the left-hand side bound variables aren't available on the right hand side. For instance, this doesn't typecheck:
```unison
``` unison
ex4 =
(a,b) = (a Nat.+ b, 19)
"Doesn't typecheck"
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -104,7 +104,7 @@ ex4 =
```
Even though the parser accepts any pattern on the LHS of a bind, it looks pretty weird to see things like `12 = x`, so we avoid showing a destructuring bind when the LHS is a "literal" pattern (like `42` or "hi"). Again these examples wouldn't compile with coverage checking.
```unison
``` unison
ex5 : 'Text
ex5 _ = match 99 + 1 with
12 -> "Hi"
@ -116,7 +116,7 @@ ex5a _ = match (99 + 1, "hi") with
_ -> "impossible"
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -130,7 +130,7 @@ ex5a _ = match (99 + 1, "hi") with
ex5a : 'Text
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -155,14 +155,14 @@ Notice how it prints both an ordinary match.
Also, for clarity, the pretty-printer shows a single-branch match if the match shadows free variables of the scrutinee, for example:
```unison
``` unison
ex6 x = match x with
(x, y) -> x Nat.+ y
```
For clarity, the pretty-printer leaves this alone, even though in theory it could be written `(x,y) = x; x + y`:
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -1,4 +1,4 @@
```unison
``` unison
b1.x = 23
b1.fslkdjflskdjflksjdf = 663
b2.x = 23
@ -6,7 +6,7 @@ b2.fslkdjflskdjflksjdf = 23
b2.abc = 23
```
```ucm
``` ucm
.> add
⍟ I've added these definitions:
@ -22,7 +22,7 @@ b2.abc = 23
Done.
```
```ucm
``` ucm
.> diff.namespace b1 b2
Resolved name conflicts:
@ -58,16 +58,16 @@ b2.abc = 23
```
Things we want to test:
* Diffing identical namespaces
* Adds, removes, updates
* Adds with multiple names
* Moved and copied definitions
* Moves that have more that 1 initial or final name
* ... terms and types
* New patches, modified patches, deleted patches, moved patches
* With and without propagated updates
- Diffing identical namespaces
- Adds, removes, updates
- Adds with multiple names
- Moved and copied definitions
- Moves that have more that 1 initial or final name
- ... terms and types
- New patches, modified patches, deleted patches, moved patches
- With and without propagated updates
```unison
``` unison
fromJust = 1
b = 2
bdependent = b
@ -78,7 +78,7 @@ structural type A a = A ()
structural ability X a1 a2 where x : ()
```
```ucm
``` ucm
☝️ The namespace .ns1 is empty.
.ns1> add
@ -108,7 +108,7 @@ structural ability X a1 a2 where x : ()
```
Here's what we've done so far:
```ucm
``` ucm
.> diff.namespace nothing ns1
⚠️
@ -116,17 +116,17 @@ Here's what we've done so far:
The namespace .nothing is empty. Was there a typo?
```
```ucm
``` ucm
.> diff.namespace ns1 ns2
The namespaces are identical.
```
```unison
``` unison
junk = "asldkfjasldkfj"
```
```ucm
``` ucm
.ns1> add
⍟ I've added these definitions:
@ -142,7 +142,7 @@ junk = "asldkfjasldkfj"
Done.
```
```unison
``` unison
fromJust = 99
b = "oog"
d = 4
@ -151,7 +151,7 @@ f = 6
unique type Y a b = Y a b
```
```ucm
``` ucm
.ns2> update.old
⍟ I've added these definitions:
@ -283,11 +283,11 @@ unique type Y a b = Y a b
3. fromJust' ┘ 4. fromJust' (removed)
```
```unison
``` unison
bdependent = "banana"
```
```ucm
``` ucm
.ns3> update.old
⍟ I've updated these names to your new definition:
@ -316,12 +316,12 @@ bdependent = "banana"
Currently, the auto-propagated name-conflicted definitions are not explicitly
shown, only their also-conflicted dependency is shown.
```unison
``` unison
a = 333
b = a + 1
```
```ucm
``` ucm
☝️ The namespace .nsx is empty.
.nsx> add
@ -340,11 +340,11 @@ b = a + 1
Done.
```
```unison
``` unison
a = 444
```
```ucm
``` ucm
.nsy> update.old
⍟ I've updated these names to your new definition:
@ -352,11 +352,11 @@ a = 444
a : ##Nat
```
```unison
``` unison
a = 555
```
```ucm
``` ucm
.nsz> update.old
⍟ I've updated these names to your new definition:
@ -376,7 +376,7 @@ a = 555
Done.
```
```ucm
``` ucm
.> diff.namespace nsx nsw
New name conflicts:
@ -412,11 +412,11 @@ a = 555
```
## Should be able to diff a namespace hash from history.
```unison
``` unison
x = 1
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -429,7 +429,7 @@ x = 1
x : ##Nat
```
```ucm
``` ucm
☝️ The namespace .hashdiff is empty.
.hashdiff> add
@ -439,11 +439,11 @@ x = 1
x : ##Nat
```
```unison
``` unison
y = 2
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -456,7 +456,7 @@ y = 2
y : ##Nat
```
```ucm
``` ucm
.hashdiff> add
⍟ I've added these definitions:
@ -483,49 +483,50 @@ y = 2
1. y : ##Nat
```
##
##
Updates: -- 1 to 1
New name conflicts: -- updates where RHS has multiple hashes (excluding when RHS=LHS)
1. foo#jk19sm5bf8 : Nat - do we want to force a hashqualified? Arya thinks so
2. ┌ foo#0ja1qfpej6 : Nat
3. └ foo#jk19sm5bf8 : Nat
1. foo\#jk19sm5bf8 : Nat - do we want to force a hashqualified? Arya thinks so
2. ┌ foo\#0ja1qfpej6 : Nat
3. └ foo\#jk19sm5bf8 : Nat
Resolved name conflicts: -- updates where LHS had multiple hashes and RHS has one
4. ┌ bar#0ja1qfpej6 : Nat
5. └ bar#jk19sm5bf8 : Nat
6. bar#jk19sm5bf8 : Nat
4. ┌ bar\#0ja1qfpej6 : Nat
5. └ bar\#jk19sm5bf8 : Nat
6. bar\#jk19sm5bf8 : Nat
## Display issues to fixup
- [d] Do we want to surface new edit conflicts in patches?
- [t] two different auto-propagated changes creating a name conflict should show
up somewhere besides the auto-propagate count
- [t] Things look screwy when the type signature doesn't fit and has to get broken
up into multiple lines. Maybe just disallow that?
- [d] Delete blank line in between copies / renames entries if all entries are 1 to 1
see todo in the code
- [x] incorrectly calculated bracket alignment on hashqualified "Name changes" (delete.output.md)
- [x] just handle deletion of isPropagated in propagate function, leave HandleInput alone (assuming this does the trick)
- [x] might want unqualified names to be qualified sometimes:
- [x] if a name is updated to a not-yet-named reference, it's shown as both an update and an add
- [x] similarly, if a conflicted name is resolved by deleting the last name to
a reference, I (arya) suspect it will show up as a Remove
- [d] Maybe group and/or add headings to the types, constructors, terms
- [x] add tagging of propagated updates to test propagated updates output
- [x] missing old names in deletion ppe (delete.output.md) (superseded by \#1143)
- [x] delete.term has some bonkers output
- [x] Make a decision about how we want to show constructors in the diff
- [x] 12.patch patch needs a space
- [x] This looks like garbage
- [x] Extra 2 blank lines at the end of the add section
- [x] Fix alignment issues with buildTable, convert to column3M (to be written)
- [x] adding an alias is showing up as an Add and a Copy; should just show as Copy
- [x] removing one of multiple aliases appears in removes + moves + copies section
- [x] some overlapping cases between Moves and Copies^
- [x] Maybe don't list the type signature twice for aliases?
- \[d\] Do we want to surface new edit conflicts in patches?
- \[t\] two different auto-propagated changes creating a name conflict should show
up somewhere besides the auto-propagate count
- \[t\] Things look screwy when the type signature doesn't fit and has to get broken
up into multiple lines. Maybe just disallow that?
- \[d\] Delete blank line in between copies / renames entries if all entries are 1 to 1
see todo in the code
- \[x\] incorrectly calculated bracket alignment on hashqualified "Name changes" (delete.output.md)
- \[x\] just handle deletion of isPropagated in propagate function, leave HandleInput alone (assuming this does the trick)
- \[x\] might want unqualified names to be qualified sometimes:
- \[x\] if a name is updated to a not-yet-named reference, it's shown as both an update and an add
- \[x\] similarly, if a conflicted name is resolved by deleting the last name to
a reference, I (arya) suspect it will show up as a Remove
- \[d\] Maybe group and/or add headings to the types, constructors, terms
- \[x\] add tagging of propagated updates to test propagated updates output
- \[x\] missing old names in deletion ppe (delete.output.md) (superseded by \#1143)
- \[x\] delete.term has some bonkers output
- \[x\] Make a decision about how we want to show constructors in the diff
- \[x\] 12.patch patch needs a space
- \[x\] This looks like garbage
- \[x\] Extra 2 blank lines at the end of the add section
- \[x\] Fix alignment issues with buildTable, convert to column3M (to be written)
- \[x\] adding an alias is showing up as an Add and a Copy; should just show as Copy
- \[x\] removing one of multiple aliases appears in removes + moves + copies section
- \[x\] some overlapping cases between Moves and Copies^
- \[x\] Maybe don't list the type signature twice for aliases?

View File

@ -2,14 +2,14 @@ This transcript explains a few minor details about doc parsing and pretty-printi
Docs can be used as inline code comments.
```unison
``` unison
foo : Nat -> Nat
foo n =
_ = [: do the thing :]
n + 1
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -22,7 +22,7 @@ foo n =
foo : Nat -> Nat
```
```ucm
``` ucm
scratch/main> view foo
foo : Nat -> Nat
@ -34,11 +34,11 @@ scratch/main> view foo
```
Note that `@` and `:]` must be escaped within docs.
```unison
``` unison
escaping = [: Docs look [: like \@this \:] :]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -51,7 +51,7 @@ escaping = [: Docs look [: like \@this \:] :]
escaping : Doc
```
```ucm
``` ucm
scratch/main> view escaping
escaping : Doc
@ -60,7 +60,7 @@ scratch/main> view escaping
```
(Alas you can't have `\@` or `\:]` in your doc, as there's currently no way to 'unescape' them.)
```unison
``` unison
-- Note that -- comments are preserved within doc literals.
commented = [:
example:
@ -70,7 +70,7 @@ commented = [:
:]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -83,7 +83,7 @@ commented = [:
commented : Doc
```
```ucm
``` ucm
scratch/main> view commented
commented : Doc
@ -98,14 +98,14 @@ scratch/main> view commented
Handling of indenting in docs between the parser and pretty-printer is a bit fiddly.
```unison
``` unison
-- The leading and trailing spaces are stripped from the stored Doc by the
-- lexer, and one leading and trailing space is inserted again on view/edit
-- by the pretty-printer.
doc1 = [: hi :]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -118,14 +118,14 @@ doc1 = [: hi :]
doc1 : Doc
```
```ucm
``` ucm
scratch/main> view doc1
doc1 : Doc
doc1 = [: hi :]
```
```unison
``` unison
-- Lines (apart from the first line, i.e. the bit between the [: and the
-- first newline) are unindented until at least one of
-- them hits the left margin (by a post-processing step in the parser).
@ -137,7 +137,7 @@ doc2 = [: hello
and the rest. :]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -150,7 +150,7 @@ doc2 = [: hello
doc2 : Doc
```
```ucm
``` ucm
scratch/main> view doc2
doc2 : Doc
@ -161,7 +161,7 @@ scratch/main> view doc2
and the rest. :]
```
```unison
``` unison
doc3 = [: When Unison identifies a paragraph, it removes any newlines from it before storing it, and then reflows the paragraph text to fit the display window on display/view/edit.
For these purposes, a paragraph is any sequence of non-empty lines that have zero indent (after the unindenting mentioned above.)
@ -176,7 +176,7 @@ Note that because of the special treatment of the first line mentioned above, wh
:]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -189,7 +189,7 @@ Note that because of the special treatment of the first line mentioned above, wh
doc3 : Doc
```
```ucm
``` ucm
scratch/main> view doc3
doc3 : Doc
@ -215,7 +215,7 @@ scratch/main> view doc3
:]
```
```unison
``` unison
doc4 = [: Here's another example of some paragraphs.
All these lines have zero indent.
@ -223,7 +223,7 @@ doc4 = [: Here's another example of some paragraphs.
- Apart from this one. :]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -236,7 +236,7 @@ doc4 = [: Here's another example of some paragraphs.
doc4 : Doc
```
```ucm
``` ucm
scratch/main> view doc4
doc4 : Doc
@ -248,7 +248,7 @@ scratch/main> view doc4
- Apart from this one. :]
```
```unison
``` unison
-- The special treatment of the first line does mean that the following
-- is pretty-printed not so prettily. To fix that we'd need to get the
-- lexer to help out with interpreting doc literal indentation (because
@ -258,7 +258,7 @@ doc5 = [: - foo
and the rest. :]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -271,7 +271,7 @@ doc5 = [: - foo
doc5 : Doc
```
```ucm
``` ucm
scratch/main> view doc5
doc5 : Doc
@ -281,7 +281,7 @@ scratch/main> view doc5
and the rest. :]
```
```unison
``` unison
-- You can do the following to avoid that problem.
doc6 = [:
- foo
@ -290,7 +290,7 @@ doc6 = [:
:]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -303,7 +303,7 @@ doc6 = [:
doc6 : Doc
```
```ucm
``` ucm
scratch/main> view doc6
doc6 : Doc
@ -316,14 +316,14 @@ scratch/main> view doc6
```
### More testing
```unison
``` unison
-- Check empty doc works.
empty = [::]
expr = foo 1
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -337,14 +337,14 @@ expr = foo 1
expr : Nat
```
```ucm
``` ucm
scratch/main> view empty
empty : Doc
empty = [: :]
```
```unison
``` unison
test1 = [:
The internal logic starts to get hairy when you use the \@ features, for example referencing a name like @List.take. Internally, the text between each such usage is its own blob (blob ends here --> @List.take), so paragraph reflow has to be aware of multiple blobs to do paragraph reflow (or, more accurately, to do the normalization step where newlines with a paragraph are removed.)
@ -384,7 +384,7 @@ para line lorem ipsum dolor lorem ipsum dolor lorem ipsum dolor lorem ipsum dolo
:]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -397,7 +397,7 @@ para line lorem ipsum dolor lorem ipsum dolor lorem ipsum dolor lorem ipsum dolo
test1 : Doc
```
```ucm
``` ucm
scratch/main> view test1
test1 : Doc
@ -460,13 +460,13 @@ scratch/main> view test1
:]
```
```unison
``` unison
-- Regression test for #1363 - preservation of spaces after @ directives in first line when unindenting
reg1363 = [: `@List.take foo` bar
baz :]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -479,14 +479,14 @@ reg1363 = [: `@List.take foo` bar
reg1363 : Doc
```
```ucm
``` ucm
scratch/main> view reg1363
reg1363 : Doc
reg1363 = [: `@List.take foo` bar baz :]
```
```unison
``` unison
-- Demonstrate doc display when whitespace follows a @[source] or @[evaluate]
-- whose output spans multiple lines.
@ -496,7 +496,7 @@ test2 = [:
:]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -510,7 +510,8 @@ test2 = [:
```
View is fine.
```ucm
``` ucm
scratch/main> view test2
test2 : Doc
@ -521,7 +522,8 @@ scratch/main> view test2
```
But note it's not obvious how display should best be handling this. At the moment it just does the simplest thing:
```ucm
``` ucm
scratch/main> display test2
Take a look at this:

View File

@ -6,7 +6,7 @@ not the ability `Patterns`; the lexer should see this as a single identifier.
See https://github.com/unisonweb/unison/issues/2642 for an example.
```unison
``` unison
abilityPatterns : ()
abilityPatterns = ()
@ -25,7 +25,7 @@ docs.example4 = {{A doc that links to the {type Labels} type}}
Now we check that each doc links to the object of the correct name:
```ucm
``` ucm
scratch/main> display docs.example1
A doc that links to the abilityPatterns term

View File

@ -2,7 +2,7 @@
Unison documentation is written in Unison. Documentation is a value of the following type:
```ucm
``` ucm
scratch/main> view lib.builtins.Doc
type lib.builtins.Doc
@ -16,7 +16,7 @@ scratch/main> view lib.builtins.Doc
```
You can create these `Doc` values with ordinary code, or you can use the special syntax. A value of structural type `Doc` can be created via syntax like:
```unison
``` unison
doc1 = [: This is some documentation.
It can span multiple lines.
@ -26,7 +26,7 @@ Can link to definitions like @List.drop or @List
:]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -43,22 +43,22 @@ Syntax:
`[:` starts a documentation block; `:]` finishes it. Within the block:
* Links to definitions are done with `@List`. `\@` (and `\:]`) if you want to escape.
* `@[signature] List.take` expands to the type signature of `List.take`
* `@[source] List.map` expands to the full source of `List.map`
* `@[include] someOtherDoc`, inserts a value `someOtherDoc : Doc` here.
* `@[evaluate] someDefinition` expands to the result of evaluating `someDefinition`, which must be a pre-existing definition in the codebase (can't be an arbitrary expression).
- Links to definitions are done with `@List`. `\@` (and `\:]`) if you want to escape.
- `@[signature] List.take` expands to the type signature of `List.take`
- `@[source] List.map` expands to the full source of `List.map`
- `@[include] someOtherDoc`, inserts a value `someOtherDoc : Doc` here.
- `@[evaluate] someDefinition` expands to the result of evaluating `someDefinition`, which must be a pre-existing definition in the codebase (can't be an arbitrary expression).
### An example
We are going to document `List.take` using some verbiage and a few examples. First we have to add the examples to the codebase:
```unison
``` unison
List.take.ex1 = take 0 [1,2,3,4,5]
List.take.ex2 = take 2 [1,2,3,4,5]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -72,7 +72,7 @@ List.take.ex2 = take 2 [1,2,3,4,5]
List.take.ex2 : [Nat]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -83,7 +83,7 @@ scratch/main> add
```
And now let's write our docs and reference these examples:
```unison
``` unison
List.take.doc = [:
`@List.take n xs` returns the first `n` elements of `xs`. (No need to add line breaks manually. The display command will do wrapping of text for you. Indent any lines where you don't want it to do this.)
@ -100,7 +100,7 @@ List.take.doc = [:
:]
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -115,7 +115,7 @@ List.take.doc = [:
```
Let's add it to the codebase.
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -125,7 +125,7 @@ scratch/main> add
```
We can view it with `docs`, which shows the `Doc` value that is associated with a definition.
```ucm
``` ucm
scratch/main> docs List.take
`List.take n xs` returns the first `n` elements of `xs`. (No
@ -150,7 +150,7 @@ scratch/main> docs List.take
```
Note that if we view the source of the documentation, the various references are *not* expanded.
```ucm
``` ucm
scratch/main> view List.take
builtin lib.builtins.List.take :

View File

@ -1,6 +1,6 @@
# Test parsing and round-trip of doc2 syntax elements
```unison
``` unison
otherDoc : a -> Doc2
otherDoc _ = {{ yo }}
@ -109,11 +109,11 @@ Inline '' text literal with 1 space of padding '' in the middle of a sentence.
Format it to check that everything pretty-prints in a valid way.
```ucm
``` ucm
scratch/main> debug.format
```
```unison:added-by-ucm scratch.u
``` unison:added-by-ucm scratch.u
otherDoc : a -> Doc2
otherDoc _ = {{ yo }}

View File

@ -1,4 +1,4 @@
```unison
``` unison
otherDoc : a -> Doc2
otherDoc _ = {{ yo }}
@ -81,7 +81,7 @@ Table
}}
```
```ucm
``` ucm
scratch/main> debug.doc-to-markdown fulldoc
Heres some text with a soft line break
@ -159,7 +159,7 @@ scratch/main> debug.doc-to-markdown fulldoc
```
You can add docs to a term or type with a top-level doc literal above the binding:
```unison
``` unison
{{ This is a term doc }}
myTerm = 10
@ -174,7 +174,7 @@ unique type MyUniqueType = MyUniqueType
structural type MyStructuralType = MyStructuralType
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,14 +1,14 @@
If `foo#old` exists in old, and `foo#new` exists in new, you might think `upgrade old new` would rewrite references to
`#old` with references to `#new`. And it will... !!unless!! `#old` still exists in new.
`#old` with references to `#new`. And it will... \!\!unless\!\! `#old` still exists in new.
```unison
``` unison
lib.old.foo = 18
lib.new.other = 18
lib.new.foo = 19
mything = lib.old.foo + lib.old.foo
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -24,7 +24,7 @@ mything = lib.old.foo + lib.old.foo
mything : Nat
```
```ucm
``` ucm
foo/main> add
⍟ I've added these definitions:

View File

@ -2,7 +2,7 @@
Term and ability constructor collisions should cause a parse error.
```unison
``` unison
structural ability Stream where
send : a -> ()
@ -10,7 +10,7 @@ Stream.send : a -> ()
Stream.send _ = ()
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -26,14 +26,14 @@ Stream.send _ = ()
```
Term and type constructor collisions should cause a parse error.
```unison
``` unison
structural type X = x
X.x : a -> ()
X.x _ = ()
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -49,13 +49,13 @@ X.x _ = ()
```
Ability and type constructor collisions should cause a parse error.
```unison
``` unison
structural type X = x
structural ability X where
x : ()
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -69,14 +69,14 @@ structural ability X where
```
Field accessors and terms with the same name should cause a parse error.
```unison
``` unison
structural type X = {x : ()}
X.x.modify = ()
X.x.set = ()
X.x = ()
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -103,13 +103,13 @@ X.x = ()
```
Types and terms with the same name are allowed.
```unison
``` unison
structural type X = Z
X = ()
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -124,7 +124,7 @@ X = ()
X : ()
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:

View File

@ -2,12 +2,12 @@
Trivial duplicate terms should be detected:
```unison
``` unison
x = 1
x = 2
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -21,12 +21,12 @@ x = 2
```
Equivalent duplicate terms should be detected:
```unison
``` unison
x = 1
x = 1
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -40,14 +40,14 @@ x = 1
```
Duplicates from record accessors/setters should be detected
```unison
``` unison
structural type Record = {x: Nat, y: Nat}
Record.x = 1
Record.x.set = 2
Record.x.modify = 2
```
```ucm
``` ucm
Loading changes detected in scratch.u.
@ -74,7 +74,7 @@ Record.x.modify = 2
```
Duplicate terms and constructors should be detected:
```unison
``` unison
structural type SumType = X
SumType.X = 1
@ -85,7 +85,7 @@ structural ability AnAbility where
AnAbility.thing = 2
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,5 +1,4 @@
```unison
``` unison
up = 0xs0123456789abcdef
down = 0xsfedcba9876543210
@ -20,7 +19,7 @@ sigOkay = match signature with
> sigOkay
```
```ucm
``` ucm
Loading changes detected in scratch.u.

View File

@ -1,10 +1,10 @@
```ucm
``` ucm
scratch/main> builtins.merge
Done.
```
```unison
``` unison
---
title: /private/tmp/scratch.u
---
@ -16,8 +16,7 @@ mytest = [Ok "ok"]
```
```ucm
``` ucm
Loading changes detected in /private/tmp/scratch.u.
@ -32,7 +31,7 @@ mytest = [Ok "ok"]
mytest : [Result]
```
```ucm
``` ucm
scratch/main> add
⍟ I've added these definitions:
@ -60,7 +59,7 @@ scratch/main> edit mytest
definitions currently in this namespace.
```
```unison:added-by-ucm /private/tmp/scratch.u
``` unison:added-by-ucm /private/tmp/scratch.u
bar : Nat
bar = 456
@ -68,11 +67,11 @@ foo : Nat
foo = 123
```
```unison:added-by-ucm /private/tmp/scratch.u
``` unison:added-by-ucm /private/tmp/scratch.u
test> mytest = [Ok "ok"]
```
```ucm
``` ucm
scratch/main> edit missing
⚠️

Some files were not shown because too many files have changed in this diff Show More