diff --git a/unison-cli/src/Unison/Codebase/Transcript.hs b/unison-cli/src/Unison/Codebase/Transcript.hs index 81d56e7e8c..590c9f8d28 100644 --- a/unison-cli/src/Unison/Codebase/Transcript.hs +++ b/unison-cli/src/Unison/Codebase/Transcript.hs @@ -3,6 +3,7 @@ -- | The data model for Unison transcripts. module Unison.Codebase.Transcript ( ExpectingError, + HasBug, ScratchFileName, Hidden (..), UcmLine (..), @@ -25,6 +26,8 @@ import Unison.Project (ProjectAndBranch) type ExpectingError = Bool +type HasBug = Bool + type ScratchFileName = Text data Hidden = Shown | HideOutput | HideAll @@ -56,13 +59,14 @@ type Stanza = Either CMark.Node ProcessedBlock data InfoTags a = InfoTags { hidden :: Hidden, expectingError :: ExpectingError, + hasBug :: HasBug, generated :: Bool, additionalTags :: a } deriving (Eq, Ord, Read, Show) defaultInfoTags :: a -> InfoTags a -defaultInfoTags = InfoTags Shown False False +defaultInfoTags = InfoTags Shown False False False -- | If the `additionalTags` form a `Monoid`, then you don’t need to provide a default value for them. defaultInfoTags' :: (Monoid a) => InfoTags a diff --git a/unison-cli/src/Unison/Codebase/Transcript/Parser.hs b/unison-cli/src/Unison/Codebase/Transcript/Parser.hs index 4943b5442a..cc335e9f7c 100644 --- a/unison-cli/src/Unison/Codebase/Transcript/Parser.hs +++ b/unison-cli/src/Unison/Codebase/Transcript/Parser.hs @@ -23,7 +23,7 @@ import Data.Char qualified as Char import Data.Text qualified as Text import Text.Megaparsec qualified as P import Text.Megaparsec.Char qualified as P -import Unison.Codebase.Transcript hiding (expectingError, generated, hidden) +import Unison.Codebase.Transcript hiding (expectingError, generated, hasBug, hidden) import Unison.Prelude import Unison.Project (fullyQualifiedProjectAndBranchNamesParser) @@ -50,9 +50,9 @@ formatStanzas = processedBlockToNode :: ProcessedBlock -> CMark.Node processedBlockToNode = \case - Ucm tags cmds -> mkNode (\() -> "") "ucm" tags $ foldr ((<>) . formatUcmLine) "" cmds - Unison tags txt -> mkNode (maybe "" (" " <>)) "unison" tags txt - API tags apiRequests -> mkNode (\() -> "") "api" tags $ foldr ((<>) . formatAPIRequest) "" apiRequests + Ucm tags cmds -> mkNode (\() -> Nothing) "ucm" tags $ foldr ((<>) . formatUcmLine) "" cmds + Unison tags txt -> mkNode id "unison" tags txt + API tags apiRequests -> mkNode (\() -> Nothing) "api" tags $ foldr ((<>) . formatAPIRequest) "" apiRequests where mkNode formatA lang = CMarkCodeBlock Nothing . formatInfoString formatA lang @@ -98,20 +98,28 @@ apiRequest = <|> APIComment <$> (P.chunk "--" *> restOfLine) <|> APIResponseLine <$> (P.chunk " " *> restOfLine <|> "" <$ P.single '\n' <|> "" <$ P.chunk " \n") -formatInfoString :: (a -> Text) -> Text -> InfoTags a -> Text +formatInfoString :: (a -> Maybe Text) -> Text -> InfoTags a -> Text formatInfoString formatA language infoTags = let infoTagText = formatInfoTags formatA infoTags in if Text.null infoTagText then language else language <> " " <> infoTagText -formatInfoTags :: (a -> Text) -> InfoTags a -> Text -formatInfoTags formatA (InfoTags hidden expectingError generated additionalTags) = - formatHidden hidden <> formatExpectingError expectingError <> formatGenerated generated <> formatA additionalTags +formatInfoTags :: (a -> Maybe Text) -> InfoTags a -> Text +formatInfoTags formatA (InfoTags hidden expectingError hasBug generated additionalTags) = + Text.intercalate " " $ + catMaybes + [ formatHidden hidden, + formatExpectingError expectingError, + formatHasBug hasBug, + formatGenerated generated, + formatA additionalTags + ] infoTags :: P a -> P (InfoTags a) infoTags p = InfoTags <$> lineToken hidden <*> lineToken expectingError + <*> lineToken hasBug <*> lineToken generated <*> p <* P.single '\n' @@ -135,26 +143,32 @@ lineToken p = p <* nonNewlineSpaces nonNewlineSpaces :: P () nonNewlineSpaces = void $ P.takeWhileP Nothing (\ch -> ch == ' ' || ch == '\t') -formatHidden :: Hidden -> Text +formatHidden :: Hidden -> Maybe Text formatHidden = \case - HideAll -> ":hide:all" - HideOutput -> ":hide" - Shown -> "" + HideAll -> pure ":hide-all" + HideOutput -> pure ":hide" + Shown -> Nothing hidden :: P Hidden hidden = - (HideAll <$ word ":hide:all") + (HideAll <$ word ":hide-all") <|> (HideOutput <$ word ":hide") <|> pure Shown -formatExpectingError :: ExpectingError -> Text -formatExpectingError = bool "" ":error" +formatExpectingError :: ExpectingError -> Maybe Text +formatExpectingError = bool Nothing $ pure ":error" expectingError :: P ExpectingError expectingError = isJust <$> optional (word ":error") -formatGenerated :: ExpectingError -> Text -formatGenerated = bool "" ":added-by-ucm" +formatHasBug :: HasBug -> Maybe Text +formatHasBug = bool Nothing $ pure ":bug" + +hasBug :: P HasBug +hasBug = isJust <$> optional (word ":bug") + +formatGenerated :: ExpectingError -> Maybe Text +formatGenerated = bool Nothing $ pure ":added-by-ucm" generated :: P Bool generated = isJust <$> optional (word ":added-by-ucm") diff --git a/unison-cli/src/Unison/Codebase/Transcript/Runner.hs b/unison-cli/src/Unison/Codebase/Transcript/Runner.hs index 9c06e31da8..97082cfab5 100644 --- a/unison-cli/src/Unison/Codebase/Transcript/Runner.hs +++ b/unison-cli/src/Unison/Codebase/Transcript/Runner.hs @@ -171,6 +171,7 @@ run isTest verbosity dir codebase runtime sbRuntime nRuntime ucmVersion baseURL currentTags <- newIORef Nothing isHidden <- newIORef Shown allowErrors <- newIORef False + expectFailure <- newIORef False hasErrors <- newIORef False mBlock <- newIORef Nothing let patternMap = Map.fromList $ (\p -> (patternName p, p) : ((,p) <$> aliases p)) =<< validInputs @@ -204,12 +205,25 @@ run isTest verbosity dir codebase runtime sbRuntime nRuntime ucmVersion baseURL -- We shorten the terminal width, because "Transcript" manages a 2-space indent for output lines. Pretty.toPlain (terminalWidth - 2) line - maybeDieWithMsg :: String -> IO () + maybeDieWithMsg :: Pretty.Pretty Pretty.ColorText -> IO () maybeDieWithMsg msg = do - errOk <- readIORef allowErrors - if errOk - then writeIORef hasErrors True - else dieWithMsg msg + liftIO $ writeIORef hasErrors True + liftIO (liftA2 (,) (readIORef allowErrors) (readIORef expectFailure)) >>= \case + (False, False) -> liftIO . dieWithMsg $ Pretty.toPlain terminalWidth msg + (True, True) -> do + appendFailingStanza + fixedBug out $ + Text.unlines + [ "The stanza above marked with `:error :bug` is now failing with", + "", + "```", + Text.pack $ Pretty.toPlain terminalWidth msg, + "```", + "", + "so you can remove `:bug` and close any appropriate Github issues. If the error message is different \ + \from the expected error message, open a new issue and reference it in this transcript." + ] + (_, _) -> pure () apiRequest :: APIRequest -> IO [APIRequest] apiRequest req = do @@ -220,9 +234,13 @@ run isTest verbosity dir codebase runtime sbRuntime nRuntime ucmVersion baseURL APIComment {} -> pure $ pure req GetRequest path -> either - (([] <$) . maybeDieWithMsg . show) + (([] <$) . maybeDieWithMsg . Pretty.string . show) ( either - (([] <$) . maybeDieWithMsg . (("Error decoding response from " <> Text.unpack path <> ": ") <>)) + ( ([] <$) + . maybeDieWithMsg + . (("Error decoding response from " <> Pretty.text path <> ": ") <>) + . Pretty.string + ) ( \(v :: Aeson.Value) -> pure $ if hide @@ -309,12 +327,9 @@ run isTest verbosity dir codebase runtime sbRuntime nRuntime ucmVersion baseURL >>= either -- invalid command is treated as a failure ( \msg -> do - liftIO $ writeIORef hasErrors True - liftIO (readIORef allowErrors) >>= \case - True -> do - liftIO $ outputUcmResult msg - Cli.returnEarlyWithoutOutput - False -> liftIO . dieWithMsg $ Pretty.toPlain terminalWidth msg + liftIO $ outputUcmResult msg + liftIO $ maybeDieWithMsg msg + Cli.returnEarlyWithoutOutput ) -- No input received from this line, try again. (maybe Cli.returnEarlyWithoutOutput $ pure . Right . snd) @@ -325,6 +340,7 @@ run isTest verbosity dir codebase runtime sbRuntime nRuntime ucmVersion baseURL writeIORef isHidden $ hidden infoTags outputEcho $ pure block writeIORef allowErrors $ expectingError infoTags + writeIORef expectFailure $ hasBug infoTags -- Open a ucm block which will contain the output from UCM after processing the `UnisonFileChanged` event. -- Close the ucm block after processing the UnisonFileChanged event. atomically . Q.enqueue cmdQueue $ Nothing @@ -335,6 +351,7 @@ run isTest verbosity dir codebase runtime sbRuntime nRuntime ucmVersion baseURL liftIO do writeIORef isHidden $ hidden infoTags writeIORef allowErrors $ expectingError infoTags + writeIORef expectFailure $ hasBug infoTags outputEcho . pure . API infoTags . fold =<< traverse apiRequest apiRequests Cli.returnEarlyWithoutOutput Ucm infoTags cmds -> do @@ -342,6 +359,7 @@ run isTest verbosity dir codebase runtime sbRuntime nRuntime ucmVersion baseURL writeIORef currentTags $ pure infoTags writeIORef isHidden $ hidden infoTags writeIORef allowErrors $ expectingError infoTags + writeIORef expectFailure $ hasBug infoTags writeIORef hasErrors False traverse_ (atomically . Q.enqueue cmdQueue . Just) cmds atomically . Q.enqueue cmdQueue $ Nothing @@ -382,6 +400,7 @@ run isTest verbosity dir codebase runtime sbRuntime nRuntime ucmVersion baseURL liftIO $ writeIORef currentTags Nothing liftIO $ writeIORef isHidden Shown liftIO $ writeIORef allowErrors False + liftIO $ writeIORef expectFailure False maybe (liftIO finishTranscript) (uncurry processStanza) =<< atomically (Q.tryDequeue inputQueue) awaitInput :: Cli (Either Event Input) @@ -409,22 +428,14 @@ run isTest verbosity dir codebase runtime sbRuntime nRuntime ucmVersion baseURL print :: Output.Output -> IO () print o = do msg <- notifyUser dir o - errOk <- readIORef allowErrors outputUcmResult msg - when (Output.isFailure o) $ - if errOk - then writeIORef hasErrors True - else dieWithMsg $ Pretty.toPlain terminalWidth msg + when (Output.isFailure o) $ maybeDieWithMsg msg printNumbered :: Output.NumberedOutput -> IO Output.NumberedArgs printNumbered o = do let (msg, numberedArgs) = notifyNumbered o - errOk <- readIORef allowErrors outputUcmResult msg - when (Output.isNumberedFailure o) $ - if errOk - then writeIORef hasErrors True - else dieWithMsg $ Pretty.toPlain terminalWidth msg + when (Output.isNumberedFailure o) $ maybeDieWithMsg msg pure numberedArgs -- Looks at the current stanza and decides if it is contained in the @@ -447,13 +458,21 @@ run isTest verbosity dir codebase runtime sbRuntime nRuntime ucmVersion baseURL dieUnexpectedSuccess :: IO () dieUnexpectedSuccess = do errOk <- readIORef allowErrors + expectBug <- readIORef expectFailure hasErr <- readIORef hasErrors - when (errOk && not hasErr) $ do - appendFailingStanza - transcriptFailure - out - "The transcript was expecting an error in the stanza above, but did not encounter one." - Nothing + case (errOk, expectBug, hasErr) of + (True, False, False) -> do + appendFailingStanza + transcriptFailure + out + "The transcript was expecting an error in the stanza above, but did not encounter one." + Nothing + (False, True, False) -> do + fixedBug + out + "The stanza above with `:bug` is now passing! You can remove `:bug` and close any appropriate Github \ + \issues." + (_, _, _) -> pure () authenticatedHTTPClient <- AuthN.newAuthenticatedHTTPClient tokenProvider ucmVersion @@ -508,6 +527,22 @@ transcriptFailure out heading mbody = do <> foldr ((:) . CMarkCodeBlock Nothing "") [] mbody ) +fixedBug :: IORef (Seq Stanza) -> Text -> IO b +fixedBug out body = do + texts <- readIORef out + -- `CMark.commonmarkToNode` returns a @DOCUMENT@, which won’t be rendered inside another document, so we strip the + -- outer `CMark.Node`. + let CMark.Node _ _DOCUMENT bodyNodes = CMark.commonmarkToNode [CMark.optNormalize] body + UnliftIO.throwIO . RunFailure $ + texts + <> Seq.fromList + ( Left + <$> [ CMark.Node Nothing CMark.PARAGRAPH [CMark.Node Nothing (CMark.TEXT "🎉") []], + CMark.Node Nothing (CMark.HEADING 2) [CMark.Node Nothing (CMark.TEXT "You fixed a bug!") []] + ] + <> bodyNodes + ) + data Error = ParseError (P.ParseErrorBundle Text Void) | RunFailure (Seq Stanza) diff --git a/unison-src/builtin-tests/interpreter-tests.output.md b/unison-src/builtin-tests/interpreter-tests.output.md index 8f313d114f..87de1b4977 100644 --- a/unison-src/builtin-tests/interpreter-tests.output.md +++ b/unison-src/builtin-tests/interpreter-tests.output.md @@ -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 :hide:error +``` ucm :hide :error scratch/main> this is a hack to trigger an error, in order to swallow any error on the next line. scratch/main> we delete the project to avoid any merge conflicts or complaints from ucm. diff --git a/unison-src/builtin-tests/jit-tests.output.md b/unison-src/builtin-tests/jit-tests.output.md index 616d2d5d9c..94225ebd14 100644 --- a/unison-src/builtin-tests/jit-tests.output.md +++ b/unison-src/builtin-tests/jit-tests.output.md @@ -4,6 +4,18 @@ 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 :hide :error +scratch/main> this is a hack to trigger an error, in order to swallow any error on the next line. + +scratch/main> we delete the project to avoid any merge conflicts or complaints from ucm. + +scratch/main> delete.project runtime-tests +``` + +``` ucm :hide +scratch/main> clone @unison/runtime-tests/releases/0.0.1 runtime-tests/selected +``` + ``` ucm runtime-tests/selected> run.native tests @@ -12,8 +24,8 @@ runtime-tests/selected> run.native tests 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. @@ -27,19 +39,18 @@ foo = do go 1000 ``` -``` ucm - +``` ucm :added-by-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 scratch/main> run.native foo @@ -48,20 +59,19 @@ scratch/main> run.native foo scratch/main> run.native foo () - ``` + 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 :error runtime-tests/selected> run.native testBug 💔💥 - + I've encountered a call to builtin.bug with the following value: - - "testing" + "testing" ``` diff --git a/unison-src/transcripts-using-base/fix5178.md b/unison-src/transcripts-using-base/fix5178.md new file mode 100644 index 0000000000..e03d38eed5 --- /dev/null +++ b/unison-src/transcripts-using-base/fix5178.md @@ -0,0 +1,20 @@ +``` unison +foo = {{ +@source{Stream.emit} +}} +``` + +``` ucm +scratch/main> add +``` + +Viewing `foo` via `scratch/main> ui` shows the correct source, but `display foo` gives us an error message (but not an error – this is incorrectly considered a successful result) + +I think there are two separate issues here: + +1. this message should be considered an error, not success; and +2. this should actually work like `ui` and give us the source of the ability member, not complain about there being no such term in the codebase. + +``` ucm :error :bug +scratch/main> display foo +``` diff --git a/unison-src/transcripts-using-base/fix5178.output.md b/unison-src/transcripts-using-base/fix5178.output.md new file mode 100644 index 0000000000..c01343f2db --- /dev/null +++ b/unison-src/transcripts-using-base/fix5178.output.md @@ -0,0 +1,43 @@ +``` unison +foo = {{ +@source{Stream.emit} +}} +``` + +``` ucm :added-by-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 : Doc2 +``` + +``` ucm +scratch/main> add + + ⍟ I've added these definitions: + + foo : Doc2 +``` + +Viewing `foo` via `scratch/main> ui` shows the correct source, but `display foo` gives us an error message (but not an error – this is incorrectly considered a successful result) + +I think there are two separate issues here: + +1. this message should be considered an error, not success; and +2. this should actually work like `ui` and give us the source of the ability member, not complain about there being no such term in the codebase. + +``` ucm :error :bug +scratch/main> display foo + + -- The name #rfi1v9429f is assigned to the reference + ShortHash {prefix = + "rfi1v9429f9qluv533l2iba77aadttilrpmnhljfapfnfa6sru2nr8ibpqvib9nc4s4nb9s1as45upsfqfqe6ivqi2p82b2vd866it8", + cycle = Nothing, cid = Nothing}, which is missing from the + codebase. + Tip: You might need to repair the codebase manually. +``` diff --git a/unison-src/transcripts/alias-many.md b/unison-src/transcripts/alias-many.md index 4cc88d489a..e693e50a5b 100644 --- a/unison-src/transcripts/alias-many.md +++ b/unison-src/transcripts/alias-many.md @@ -1,7 +1,7 @@ ``` ucm :hide scratch/main> builtins.merge lib.builtins ``` -``` unison :hide:all +``` unison :hide-all List.adjacentPairs : [a] -> [(a, a)] List.adjacentPairs as = go xs acc = diff --git a/unison-src/transcripts/errors/dont-hide-unexpected-ucm-errors.output.md b/unison-src/transcripts/errors/dont-hide-unexpected-ucm-errors.output.md index 218f5288a2..322dfe8484 100644 --- a/unison-src/transcripts/errors/dont-hide-unexpected-ucm-errors.output.md +++ b/unison-src/transcripts/errors/dont-hide-unexpected-ucm-errors.output.md @@ -1,6 +1,6 @@ Since this code block is expecting an error, we still hide it. It seems unusual to want to hide an error, but maybe it’s just too verbose or something. This follows the author’s intent. -``` ucm :hide:error +``` ucm :hide :error scratch/main> help pull scratch/main> not.a.command diff --git a/unison-src/transcripts/errors/dont-hide-unexpected-unison-errors.output.md b/unison-src/transcripts/errors/dont-hide-unexpected-unison-errors.output.md index b0874d13e7..e73b5e616a 100644 --- a/unison-src/transcripts/errors/dont-hide-unexpected-unison-errors.output.md +++ b/unison-src/transcripts/errors/dont-hide-unexpected-unison-errors.output.md @@ -1,6 +1,6 @@ Since this code block is expecting an error, we still hide it. It seems unusual to want to hide an error, but maybe it’s just too verbose or something. This follows the author’s intent. -``` unison :hide:error +``` unison :hide :error x + x + ``` diff --git a/unison-src/transcripts/errors/info-string-parse-error.output.md b/unison-src/transcripts/errors/info-string-parse-error.output.md index 7c6ea84d4b..3ef6a22af4 100644 --- a/unison-src/transcripts/errors/info-string-parse-error.output.md +++ b/unison-src/transcripts/errors/info-string-parse-error.output.md @@ -3,4 +3,4 @@ 1 | ``` ucm :hode | ^ unexpected ':' -expecting ":added-by-ucm", ":error", ":hide", ":hide:all", or newline +expecting ":added-by-ucm", ":bug", ":error", ":hide", ":hide-all", or newline diff --git a/unison-src/transcripts/errors/missing-result-typed.md b/unison-src/transcripts/errors/missing-result-typed.md index 0e6e52b806..70949bec81 100644 --- a/unison-src/transcripts/errors/missing-result-typed.md +++ b/unison-src/transcripts/errors/missing-result-typed.md @@ -1,6 +1,6 @@ ### Transcript parser hidden errors -When an error is encountered in a `unison :hide:all` block +When an error is encountered in a `unison :hide-all` block then the transcript parser should print the stanza and surface a helpful message. @@ -8,7 +8,7 @@ and surface a helpful message. scratch/main> builtins.merge ``` -``` unison :hide:all +``` unison :hide-all a : Nat a = b = 24 diff --git a/unison-src/transcripts/errors/missing-result-typed.output.md b/unison-src/transcripts/errors/missing-result-typed.output.md index 87c2308bec..f28268036c 100644 --- a/unison-src/transcripts/errors/missing-result-typed.output.md +++ b/unison-src/transcripts/errors/missing-result-typed.output.md @@ -1,6 +1,6 @@ ### Transcript parser hidden errors -When an error is encountered in a `unison :hide:all` block +When an error is encountered in a `unison :hide-all` block then the transcript parser should print the stanza and surface a helpful message. @@ -8,7 +8,7 @@ and surface a helpful message. scratch/main> builtins.merge ``` -``` unison :hide:all +``` unison :hide-all a : Nat a = b = 24 diff --git a/unison-src/transcripts/errors/missing-result.md b/unison-src/transcripts/errors/missing-result.md index f177ee81c8..a94c3bb3c5 100644 --- a/unison-src/transcripts/errors/missing-result.md +++ b/unison-src/transcripts/errors/missing-result.md @@ -1,10 +1,10 @@ ### Transcript parser hidden errors -When an error is encountered in a `unison :hide:all` block +When an error is encountered in a `unison :hide-all` block then the transcript parser should print the stanza and surface a helpful message. -``` unison :hide:all +``` unison :hide-all x = y = 24 ``` diff --git a/unison-src/transcripts/errors/missing-result.output.md b/unison-src/transcripts/errors/missing-result.output.md index fb0ab98c9f..faf91774a6 100644 --- a/unison-src/transcripts/errors/missing-result.output.md +++ b/unison-src/transcripts/errors/missing-result.output.md @@ -1,10 +1,10 @@ ### Transcript parser hidden errors -When an error is encountered in a `unison :hide:all` block +When an error is encountered in a `unison :hide-all` block then the transcript parser should print the stanza and surface a helpful message. -``` unison :hide:all +``` unison :hide-all x = y = 24 ``` diff --git a/unison-src/transcripts/errors/obsolete-bug.md b/unison-src/transcripts/errors/obsolete-bug.md new file mode 100644 index 0000000000..6f2a9641eb --- /dev/null +++ b/unison-src/transcripts/errors/obsolete-bug.md @@ -0,0 +1,5 @@ +This transcript will error, because we’re claiming that the stanza has a bug, but `help` works as expected. + +``` ucm :bug +scratch/main> help edit +``` diff --git a/unison-src/transcripts/errors/obsolete-bug.output.md b/unison-src/transcripts/errors/obsolete-bug.output.md new file mode 100644 index 0000000000..b88fe47b32 --- /dev/null +++ b/unison-src/transcripts/errors/obsolete-bug.output.md @@ -0,0 +1,15 @@ +This transcript will error, because we’re claiming that the stanza has a bug, but `help` works as expected. + +``` ucm :bug +scratch/main> help edit + + edit + `edit foo` prepends the definition of `foo` to the top of the most recently saved file. + `edit` without arguments invokes a search to select a definition for editing, which requires that `fzf` can be found within your PATH. +``` + +🎉 + +## You fixed a bug\! + +The stanza above with `:bug` is now passing\! You can remove `:bug` and close any appropriate Github issues. diff --git a/unison-src/transcripts/errors/obsolete-error-bug.md b/unison-src/transcripts/errors/obsolete-error-bug.md new file mode 100644 index 0000000000..39b6f667ad --- /dev/null +++ b/unison-src/transcripts/errors/obsolete-error-bug.md @@ -0,0 +1,5 @@ +This transcript will fail, because we’re claiming that the stanza has a bug, but `do.something` errors as expected. + +``` ucm :error :bug +scratch/main> do.something +``` diff --git a/unison-src/transcripts/errors/obsolete-error-bug.output.md b/unison-src/transcripts/errors/obsolete-error-bug.output.md new file mode 100644 index 0000000000..7a3a16789b --- /dev/null +++ b/unison-src/transcripts/errors/obsolete-error-bug.output.md @@ -0,0 +1,19 @@ +This transcript will fail, because we’re claiming that the stanza has a bug, but `do.something` errors as expected. + +``` ucm :error :bug +scratch/main> do.something +``` + +🎉 + +## You fixed a bug\! + +The stanza above marked with `:error :bug` is now failing with + +``` +⚠️ +I don't know how to do.something. Type `help` or `?` to get +help. +``` + +so you can remove `:bug` and close any appropriate Github issues. If the error message is different from the expected error message, open a new issue and reference it in this transcript. diff --git a/unison-src/transcripts/errors/ucm-hide-all-error.md b/unison-src/transcripts/errors/ucm-hide-all-error.md index 7444155923..7a56730f69 100644 --- a/unison-src/transcripts/errors/ucm-hide-all-error.md +++ b/unison-src/transcripts/errors/ucm-hide-all-error.md @@ -2,10 +2,10 @@ Dangerous scary words! -When an expected error is not encountered in a `ucm :hide:all` block +When an expected error is not encountered in a `ucm :hide-all` block then the transcript parser should print the stanza and surface a helpful message. -``` ucm :hide:all:error +``` ucm :hide-all :error scratch/main> history ``` diff --git a/unison-src/transcripts/errors/ucm-hide-all-error.output.md b/unison-src/transcripts/errors/ucm-hide-all-error.output.md index c416257ade..6f7c903cbd 100644 --- a/unison-src/transcripts/errors/ucm-hide-all-error.output.md +++ b/unison-src/transcripts/errors/ucm-hide-all-error.output.md @@ -2,11 +2,11 @@ Dangerous scary words\! -When an expected error is not encountered in a `ucm :hide:all` block +When an expected error is not encountered in a `ucm :hide-all` block then the transcript parser should print the stanza and surface a helpful message. -``` ucm :hide:all:error +``` ucm :hide-all :error scratch/main> history ``` diff --git a/unison-src/transcripts/errors/ucm-hide-all.md b/unison-src/transcripts/errors/ucm-hide-all.md index cb79d26753..a3e6d3443f 100644 --- a/unison-src/transcripts/errors/ucm-hide-all.md +++ b/unison-src/transcripts/errors/ucm-hide-all.md @@ -2,10 +2,10 @@ Dangerous scary words! -When an error is encountered in a `ucm :hide:all` block +When an error is encountered in a `ucm :hide-all` block then the transcript parser should print the stanza and surface a helpful message. -``` ucm :hide:all +``` ucm :hide-all scratch/main> move.namespace foo bar ``` diff --git a/unison-src/transcripts/errors/ucm-hide-all.output.md b/unison-src/transcripts/errors/ucm-hide-all.output.md index 2753dd7f11..fc6d21cbc6 100644 --- a/unison-src/transcripts/errors/ucm-hide-all.output.md +++ b/unison-src/transcripts/errors/ucm-hide-all.output.md @@ -2,11 +2,11 @@ Dangerous scary words\! -When an error is encountered in a `ucm :hide:all` block +When an error is encountered in a `ucm :hide-all` block then the transcript parser should print the stanza and surface a helpful message. -``` ucm :hide:all +``` ucm :hide-all scratch/main> move.namespace foo bar ``` diff --git a/unison-src/transcripts/errors/ucm-hide-error.output.md b/unison-src/transcripts/errors/ucm-hide-error.output.md index e2045b6ee5..8deec0bfaf 100644 --- a/unison-src/transcripts/errors/ucm-hide-error.output.md +++ b/unison-src/transcripts/errors/ucm-hide-error.output.md @@ -6,7 +6,7 @@ When an expected error is not encountered in a `ucm :hide` block then the transcript parser should print the stanza and surface a helpful message. -``` ucm :hide:error +``` ucm :hide :error scratch/main> history ``` diff --git a/unison-src/transcripts/errors/unison-hide-all-error.md b/unison-src/transcripts/errors/unison-hide-all-error.md index e35de94e1d..ca2bd023ba 100644 --- a/unison-src/transcripts/errors/unison-hide-all-error.md +++ b/unison-src/transcripts/errors/unison-hide-all-error.md @@ -1,9 +1,9 @@ ### Transcript parser hidden errors -When an expected error is not encountered in a `unison :hide:all:error` block +When an expected error is not encountered in a `unison :hide-all :error` block then the transcript parser should print the stanza and surface a helpful message. -``` unison :hide:all:error +``` unison :hide-all :error myVal = 3 ``` diff --git a/unison-src/transcripts/errors/unison-hide-all-error.output.md b/unison-src/transcripts/errors/unison-hide-all-error.output.md index 3652dfebe5..6205069903 100644 --- a/unison-src/transcripts/errors/unison-hide-all-error.output.md +++ b/unison-src/transcripts/errors/unison-hide-all-error.output.md @@ -1,10 +1,10 @@ ### Transcript parser hidden errors -When an expected error is not encountered in a `unison :hide:all:error` block +When an expected error is not encountered in a `unison :hide-all :error` block then the transcript parser should print the stanza and surface a helpful message. -``` unison :hide:all:error +``` unison :hide-all :error myVal = 3 ``` diff --git a/unison-src/transcripts/errors/unison-hide-all.md b/unison-src/transcripts/errors/unison-hide-all.md index 48907e75e7..9288252881 100644 --- a/unison-src/transcripts/errors/unison-hide-all.md +++ b/unison-src/transcripts/errors/unison-hide-all.md @@ -1,9 +1,9 @@ ### Transcript parser hidden errors -When an error is encountered in a `unison :hide:all` block +When an error is encountered in a `unison :hide-all` block then the transcript parser should print the stanza and surface a helpful message. -``` unison :hide:all +``` unison :hide-all g 3 ``` diff --git a/unison-src/transcripts/errors/unison-hide-all.output.md b/unison-src/transcripts/errors/unison-hide-all.output.md index c27b7dd28f..89cd4724b7 100644 --- a/unison-src/transcripts/errors/unison-hide-all.output.md +++ b/unison-src/transcripts/errors/unison-hide-all.output.md @@ -1,10 +1,10 @@ ### Transcript parser hidden errors -When an error is encountered in a `unison :hide:all` block +When an error is encountered in a `unison :hide-all` block then the transcript parser should print the stanza and surface a helpful message. -``` unison :hide:all +``` unison :hide-all g 3 ``` diff --git a/unison-src/transcripts/errors/unison-hide-error.output.md b/unison-src/transcripts/errors/unison-hide-error.output.md index 3a9477e8f8..7bc464673c 100644 --- a/unison-src/transcripts/errors/unison-hide-error.output.md +++ b/unison-src/transcripts/errors/unison-hide-error.output.md @@ -4,7 +4,7 @@ When an expected error is not encountered in a `unison :hide:error` block then the transcript parser should print the stanza and surface a helpful message. -``` unison :hide:error +``` unison :hide :error myVal = 3 ``` diff --git a/unison-src/transcripts/fix2840.md b/unison-src/transcripts/fix2840.md index 6c6ac6abe9..31d4c103df 100644 --- a/unison-src/transcripts/fix2840.md +++ b/unison-src/transcripts/fix2840.md @@ -6,7 +6,7 @@ scratch/main> builtins.merge First, a few \[hidden] definitions necessary for typechecking a simple Doc2. -``` unison :hide:all +``` unison :hide-all structural type Optional a = None | Some a unique[b7a4fb87e34569319591130bf3ec6e24c9955b6a] type Doc2 diff --git a/unison-src/transcripts/hello.md b/unison-src/transcripts/hello.md index 7f5937a353..566e6b5694 100644 --- a/unison-src/transcripts/hello.md +++ b/unison-src/transcripts/hello.md @@ -52,9 +52,9 @@ This works for `ucm` blocks as well. scratch/main> rename.term x answerToUltimateQuestionOfLife ``` -Doing `unison :hide:all` hides the block altogether, both input and output - this is useful for doing behind-the-scenes control of `ucm`'s state. +Doing `unison :hide-all` hides the block altogether, both input and output - this is useful for doing behind-the-scenes control of `ucm`'s state. -``` unison :hide:all +``` unison :hide-all > [: you won't see me :] ``` diff --git a/unison-src/transcripts/hello.output.md b/unison-src/transcripts/hello.output.md index c7564924b7..9ab978d5ce 100644 --- a/unison-src/transcripts/hello.output.md +++ b/unison-src/transcripts/hello.output.md @@ -25,7 +25,7 @@ Take a look at [the elaborated output](hello.output.md) to see what this file lo In the `unison` fenced block, you can give an (optional) file name (defaults to `scratch.u`), like so: -``` unison myfile.u +``` unison myfile.u x = 42 ``` @@ -72,7 +72,7 @@ This works for `ucm` blocks as well. scratch/main> rename.term x answerToUltimateQuestionOfLife ``` -Doing `unison :hide:all` hides the block altogether, both input and output - this is useful for doing behind-the-scenes control of `ucm`'s state. +Doing `unison :hide-all` hides the block altogether, both input and output - this is useful for doing behind-the-scenes control of `ucm`'s state. ## Expecting failures diff --git a/unison-src/transcripts/idempotent/bug.md b/unison-src/transcripts/idempotent/bug.md new file mode 100644 index 0000000000..9469b77067 --- /dev/null +++ b/unison-src/transcripts/idempotent/bug.md @@ -0,0 +1,19 @@ +This tests that `:bug` behaves similarly to `:error` when the stanza fails. + +``` ucm :bug +scratch/main> do.something + + ⚠️ + I don't know how to do.something. Type `help` or `?` to get + help. +``` + +And when combined with `:error`, it should expect a successful result. + +``` ucm :error :bug +scratch/main> help edit + + edit + `edit foo` prepends the definition of `foo` to the top of the most recently saved file. + `edit` without arguments invokes a search to select a definition for editing, which requires that `fzf` can be found within your PATH. +``` diff --git a/unison-src/transcripts/idempotent/fix5337.md b/unison-src/transcripts/idempotent/fix5337.md new file mode 100644 index 0000000000..558f763771 --- /dev/null +++ b/unison-src/transcripts/idempotent/fix5337.md @@ -0,0 +1,30 @@ +``` ucm +scratch/main> builtins.mergeio + + Done. +``` + +The following `Doc` fails to typecheck with `ucm` `0.5.26`: + +``` unison :bug +testDoc : Doc2 +testDoc = {{ + key: '{{ docWord "value" }}'. +}} +``` + +``` ucm :added-by-ucm + Loading changes detected in scratch.u. + + I got confused here: + + 3 | key: '{{ docWord "value" }}'. + + + I was surprised to find a . here. + I was expecting one of these instead: + + * end of input +``` + +The same code typechecks ok with `0.5.25`. diff --git a/unison-src/transcripts/idempotent/transcript-parser-commands.md b/unison-src/transcripts/idempotent/transcript-parser-commands.md index 5782588136..ddc8e62dd6 100644 --- a/unison-src/transcripts/idempotent/transcript-parser-commands.md +++ b/unison-src/transcripts/idempotent/transcript-parser-commands.md @@ -30,7 +30,7 @@ scratch/main> add x : Nat ``` -``` unison :hide:error :scratch.u +``` unison :hide :error scratch.u z ``` diff --git a/unison-src/transcripts/merge.md b/unison-src/transcripts/merge.md index 6b759f44ce..7bbbd16cf6 100644 --- a/unison-src/transcripts/merge.md +++ b/unison-src/transcripts/merge.md @@ -870,7 +870,7 @@ scratch/alice> delete.term Foo.Bar.Baz scratch/alice> delete.term Foo.Bar.Qux ``` -``` unison :hide:all +``` unison :hide-all Foo.Bar.Baz : Nat Foo.Bar.Baz = 100 @@ -1301,7 +1301,7 @@ Alice's branch: scratch/main> branch alice ``` -``` unison :hide:all +``` unison :hide-all unique type Foo = Bar ``` @@ -1315,7 +1315,7 @@ Bob's branch: scratch/main> branch bob ``` -``` unison :hide:all +``` unison :hide-all bob : Nat bob = 101 ``` diff --git a/unison-src/transcripts/no-hash-in-term-declaration.md b/unison-src/transcripts/no-hash-in-term-declaration.md index 493c2f32ce..85ef6c0de2 100644 --- a/unison-src/transcripts/no-hash-in-term-declaration.md +++ b/unison-src/transcripts/no-hash-in-term-declaration.md @@ -2,7 +2,7 @@ There should not be hashes in the names used in term declarations, either in the type signature or the type definition. -``` unison :hide:all:error +``` unison :hide-all :error x##Nat : Int -> Int -> Boolean x##Nat = 5 ```