From f0c53eed282698d0c4cb951548c9b275a71aea65 Mon Sep 17 00:00:00 2001 From: Mitchell Rosen Date: Tue, 2 Jul 2024 11:39:11 -0400 Subject: [PATCH 01/16] show "defs in lib" merge precondition violation in `todo` output --- .../src/Unison/Codebase/Causal.hs | 5 +- .../Codebase/Editor/HandleInput/Merge2.hs | 22 +++-- .../Codebase/Editor/HandleInput/Todo.hs | 22 ++++- .../src/Unison/Codebase/Editor/Output.hs | 4 +- .../src/Unison/CommandLine/OutputMessages.hs | 23 +++-- unison-src/transcripts/todo.md | 68 ++++++++++--- unison-src/transcripts/todo.output.md | 97 +++++++++++++++++-- 7 files changed, 199 insertions(+), 42 deletions(-) diff --git a/parser-typechecker/src/Unison/Codebase/Causal.hs b/parser-typechecker/src/Unison/Codebase/Causal.hs index 8cca62cf0..9bdd08903 100644 --- a/parser-typechecker/src/Unison/Codebase/Causal.hs +++ b/parser-typechecker/src/Unison/Codebase/Causal.hs @@ -1,7 +1,7 @@ {-# LANGUAGE TemplateHaskell #-} module Unison.Codebase.Causal - ( Causal (currentHash, head, tail, tails), + ( Causal (currentHash, valueHash, head, tail, tails), pattern One, pattern Cons, pattern Merge, @@ -40,7 +40,8 @@ import Unison.Codebase.Causal.Type currentHash, head, tail, - tails + tails, + valueHash ), before, lca, diff --git a/unison-cli/src/Unison/Codebase/Editor/HandleInput/Merge2.hs b/unison-cli/src/Unison/Codebase/Editor/HandleInput/Merge2.hs index ceee0aa83..9289a692d 100644 --- a/unison-cli/src/Unison/Codebase/Editor/HandleInput/Merge2.hs +++ b/unison-cli/src/Unison/Codebase/Editor/HandleInput/Merge2.hs @@ -8,6 +8,9 @@ module Unison.Codebase.Editor.HandleInput.Merge2 LcaMergeInfo (..), doMerge, doMergeLocalBranch, + + -- * API exported for @todo@ + hasDefnsInLib, ) where @@ -85,6 +88,7 @@ import Unison.Merge.EitherWay (EitherWay (..)) import Unison.Merge.EitherWayI (EitherWayI (..)) import Unison.Merge.EitherWayI qualified as EitherWayI import Unison.Merge.Libdeps qualified as Merge +import Unison.Merge.PartialDeclNameLookup (PartialDeclNameLookup) import Unison.Merge.PartitionCombinedDiffs (partitionCombinedDiffs) import Unison.Merge.Synhashed (Synhashed (..)) import Unison.Merge.Synhashed qualified as Synhashed @@ -138,7 +142,6 @@ import Unison.Util.SyntaxText (SyntaxText') import Unison.Var (Var) import Witch (unsafeFrom) import Prelude hiding (unzip, zip, zipWith) -import Unison.Merge.PartialDeclNameLookup (PartialDeclNameLookup) handleMerge :: ProjectAndBranch (Maybe ProjectName) ProjectBranchName -> Cli () handleMerge (ProjectAndBranch maybeBobProjectName bobBranchName) = do @@ -238,11 +241,7 @@ doMerge info = do -- Assert that neither Alice nor Bob have defns in lib for_ [(mergeTarget, branches.alice), (mergeSource, branches.bob)] \(who, branch) -> do - libdeps <- - case Map.lookup NameSegment.libSegment branch.children of - Nothing -> pure V2.Branch.empty - Just libdeps -> Cli.runTransaction libdeps.value - when (not (Map.null libdeps.terms) || not (Map.null libdeps.types)) do + whenM (Cli.runTransaction (hasDefnsInLib branch)) do done (Output.MergeDefnsInLib who) -- Load Alice/Bob/LCA definitions and decl name lookups @@ -485,6 +484,17 @@ loadLibdeps branches = do libdepsBranch <- libdepsCausal.value pure libdepsBranch.children +------------------------------------------------------------------------------------------------------------------------ +-- Merge precondition violation checks + +hasDefnsInLib :: Applicative m => V2.Branch m -> m Bool +hasDefnsInLib branch = do + libdeps <- + case Map.lookup NameSegment.libSegment branch.children of + Nothing -> pure V2.Branch.empty + Just libdeps -> libdeps.value + pure (not (Map.null libdeps.terms) || not (Map.null libdeps.types)) + ------------------------------------------------------------------------------------------------------------------------ -- Creating Unison files diff --git a/unison-cli/src/Unison/Codebase/Editor/HandleInput/Todo.hs b/unison-cli/src/Unison/Codebase/Editor/HandleInput/Todo.hs index 1a8ccf64f..ef58f044b 100644 --- a/unison-cli/src/Unison/Codebase/Editor/HandleInput/Todo.hs +++ b/unison-cli/src/Unison/Codebase/Editor/HandleInput/Todo.hs @@ -5,6 +5,7 @@ module Unison.Codebase.Editor.HandleInput.Todo where import Data.Set qualified as Set +import U.Codebase.HashTags (BranchHash (..)) import U.Codebase.Sqlite.Operations qualified as Operations import Unison.Builtin qualified as Builtin import Unison.Cli.Monad (Cli) @@ -14,7 +15,10 @@ import Unison.Cli.PrettyPrintUtils qualified as Cli import Unison.Codebase qualified as Codebase import Unison.Codebase.Branch qualified as Branch import Unison.Codebase.Branch.Names qualified as Branch +import Unison.Codebase.Causal qualified as Causal +import Unison.Codebase.Editor.HandleInput.Merge2 (hasDefnsInLib) import Unison.Codebase.Editor.Output +import Unison.Hash (HashFor (..)) import Unison.Names qualified as Names import Unison.Prelude import Unison.Reference (TermReference) @@ -26,11 +30,22 @@ handleTodo :: Cli () handleTodo = do -- For now, we don't go through any great trouble to seek out the root of the project branch. Just assume the current -- namespace is the root, which will be the case unless the user uses `deprecated.cd`. - currentNamespace <- Cli.getCurrentBranch0 + currentCausal <- Cli.getCurrentBranch + let currentNamespace = Branch.head currentCausal let currentNamespaceWithoutLibdeps = Branch.deleteLibdeps currentNamespace - (dependentsOfTodo, directDependencies, hashLen) <- + (defnsInLib, dependentsOfTodo, directDependencies, hashLen) <- Cli.runTransaction do + -- We call a shared `hasDefnsLib` helper even though we could easily duplicate the logic with the branch in hand + defnsInLib <- do + branch <- + currentCausal + & Branch._history + & Causal.valueHash + & coerce @_ @BranchHash + & Operations.expectBranchByBranchHash + hasDefnsInLib branch + let todoReference :: TermReference todoReference = Set.asSingleton (Names.refTermsNamed Builtin.names (Name.unsafeParseText "todo")) @@ -51,7 +66,7 @@ handleTodo = do hashLen <- Codebase.hashLength - pure (dependentsOfTodo.terms, directDependencies, hashLen) + pure (defnsInLib, dependentsOfTodo.terms, directDependencies, hashLen) ppe <- Cli.currentPrettyPrintEnvDecl @@ -59,6 +74,7 @@ handleTodo = do Output'Todo TodoOutput { hashLen, + defnsInLib, dependentsOfTodo, directDependenciesWithoutNames = Defns diff --git a/unison-cli/src/Unison/Codebase/Editor/Output.hs b/unison-cli/src/Unison/Codebase/Editor/Output.hs index 1534f42d0..7ee842a07 100644 --- a/unison-cli/src/Unison/Codebase/Editor/Output.hs +++ b/unison-cli/src/Unison/Codebase/Editor/Output.hs @@ -153,7 +153,8 @@ data NumberedOutput (Map LabeledDependency (Set Name)) -- Mapping of external dependencies to their local dependents. data TodoOutput = TodoOutput - { dependentsOfTodo :: !(Set TermReferenceId), + { defnsInLib :: !Bool, + dependentsOfTodo :: !(Set TermReferenceId), directDependenciesWithoutNames :: !(DefnsF Set TermReference TypeReference), hashLen :: !Int, nameConflicts :: !Names, @@ -165,6 +166,7 @@ todoOutputIsEmpty todo = Set.null todo.dependentsOfTodo && defnsAreEmpty todo.directDependenciesWithoutNames && Names.isEmpty todo.nameConflicts + && not todo.defnsInLib data AmbiguousReset'Argument = AmbiguousReset'Hash diff --git a/unison-cli/src/Unison/CommandLine/OutputMessages.hs b/unison-cli/src/Unison/CommandLine/OutputMessages.hs index f17f483ad..0e3b93e5c 100644 --- a/unison-cli/src/Unison/CommandLine/OutputMessages.hs +++ b/unison-cli/src/Unison/CommandLine/OutputMessages.hs @@ -1423,6 +1423,7 @@ notifyUser dir = \case P.wrap $ "On" <> P.group (prettyMergeSourceOrTarget aliceOrBob <> ",") + -- Note [DefnsInLibMessage] If you change this, also change the other similar one <> "there's a type or term at the top level of the `lib` namespace, where I only expect to find" <> "subnamespaces representing library dependencies.", "", @@ -2665,11 +2666,6 @@ handleTodoOutput :: TodoOutput -> Numbered Pretty handleTodoOutput todo | todoOutputIsEmpty todo = pure "You have no pending todo items. Good work! ✅" | otherwise = do - prettyConflicts <- - if todo.nameConflicts == mempty - then pure mempty - else renderNameConflicts todo.ppe.unsuffixifiedPPE todo.nameConflicts - prettyDependentsOfTodo <- do if Set.null todo.dependentsOfTodo then pure mempty @@ -2718,11 +2714,26 @@ handleTodoOutput todo <> P.newline <> P.indentN 2 (P.lines types) + prettyConflicts <- + if todo.nameConflicts == mempty + then pure mempty + else renderNameConflicts todo.ppe.unsuffixifiedPPE todo.nameConflicts + + let prettyDefnsInLib = + if todo.defnsInLib + then + P.wrap $ + -- Note [DefnsInLibMessage] If you change this, also change the other similar one + "There's a type or term at the top level of the `lib` namespace, where I only expect to find" + <> "subnamespaces representing library dependencies. Please move or remove it." + else mempty + (pure . P.sep "\n\n" . P.nonEmpty) [ prettyDependentsOfTodo, prettyDirectTermDependenciesWithoutNames, prettyDirectTypeDependenciesWithoutNames, - prettyConflicts + prettyConflicts, + prettyDefnsInLib ] listOfDefinitions :: diff --git a/unison-src/transcripts/todo.md b/unison-src/transcripts/todo.md index b86a36e20..25f99aa40 100644 --- a/unison-src/transcripts/todo.md +++ b/unison-src/transcripts/todo.md @@ -3,19 +3,15 @@ When there's nothing to do, `todo` says this: ```ucm -project/main> todo +scratch/main> todo ``` -# Conflicted names - -The todo command shows conflicted names (not demonstrated here yet because it is not easy to create them for tests, yet). - # Dependents of `todo` The `todo` command shows local (outside `lib`) terms that directly call `todo`. ```ucm:hide -project/main> builtins.mergeio lib.builtins +scratch/main> builtins.mergeio lib.builtins ``` ```unison @@ -27,12 +23,12 @@ bar = foo + foo ``` ```ucm -project/main> add -project/main> todo +scratch/main> add +scratch/main> todo ``` ```ucm:hide -project/main> delete.project project +scratch/main> delete.project scratch ``` # Direct dependencies without names @@ -41,7 +37,7 @@ The `todo` command shows hashes of direct dependencies of local (outside `lib`) the current namespace. ```ucm:hide -project/main> builtins.mergeio lib.builtins +scratch/main> builtins.mergeio lib.builtins ``` ```unison @@ -50,11 +46,55 @@ baz = foo.bar + foo.bar ``` ```ucm -project/main> add -project/main> delete.namespace.force foo -project/main> todo +scratch/main> add +scratch/main> delete.namespace.force foo +scratch/main> todo ``` ```ucm:hide -project/main> delete.project project +scratch/main> delete.project scratch +``` + +# Conflicted names + +The `todo` command shows conflicted names. + +```ucm:hide +scratch/main> builtins.mergeio lib.builtins +``` + +```unison +foo = 16 +bar = 17 +``` + +```ucm +scratch/main> add +scratch/main> debug.alias.term.force foo bar +scratch/main> todo +``` + +```ucm:hide +scratch/main> delete.project scratch +``` + +# Definitions in lib + +The `todo` command complains about terms and types directly in `lib`. + +```ucm:hide +scratch/main> builtins.mergeio lib.builtins +``` + +```unison +lib.foo = 16 +``` + +```ucm +scratch/main> add +scratch/main> todo +``` + +```ucm:hide +scratch/main> delete.project scratch ``` diff --git a/unison-src/transcripts/todo.output.md b/unison-src/transcripts/todo.output.md index cfad74ec1..07f0b03c3 100644 --- a/unison-src/transcripts/todo.output.md +++ b/unison-src/transcripts/todo.output.md @@ -3,15 +3,11 @@ When there's nothing to do, `todo` says this: ```ucm -project/main> todo +scratch/main> todo You have no pending todo items. Good work! ✅ ``` -# Conflicted names - -The todo command shows conflicted names (not demonstrated here yet because it is not easy to create them for tests, yet). - # Dependents of `todo` The `todo` command shows local (outside `lib`) terms that directly call `todo`. @@ -39,14 +35,14 @@ bar = foo + foo ``` ```ucm -project/main> add +scratch/main> add ⍟ I've added these definitions: bar : Nat foo : Nat -project/main> todo +scratch/main> todo These terms call `todo`: @@ -78,14 +74,14 @@ baz = foo.bar + foo.bar ``` ```ucm -project/main> add +scratch/main> add ⍟ I've added these definitions: baz : Nat foo.bar : Nat -project/main> delete.namespace.force foo +scratch/main> delete.namespace.force foo Done. @@ -97,10 +93,91 @@ project/main> delete.namespace.force foo Dependency Referenced In bar 1. baz -project/main> todo +scratch/main> todo These terms do not have any names in the current namespace: 1. #1jujb8oelv ``` +# Conflicted names + +The `todo` command shows conflicted names. + +```unison +foo = 16 +bar = 17 +``` + +```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`: + + bar : Nat + foo : Nat + +``` +```ucm +scratch/main> add + + ⍟ I've added these definitions: + + bar : Nat + foo : Nat + +scratch/main> debug.alias.term.force foo bar + + Done. + +scratch/main> todo + + ❓ + + The term bar has conflicting definitions: 1. foo 2. + bar#cq22mm4sca + + Tip: Use `move.term` or `delete.term` to resolve the + conflicts. + +``` +# Definitions in lib + +The `todo` command complains about terms and types directly in `lib`. + +```unison +lib.foo = 16 +``` + +```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`: + + lib.foo : Nat + +``` +```ucm +scratch/main> add + + ⍟ I've added these definitions: + + lib.foo : Nat + +scratch/main> todo + + There's a type or term at the top level of the `lib` + namespace, where I only expect to find subnamespaces + representing library dependencies. Please move or remove it. + +``` From 50f28817e57fdcafeb3cca906f021ccd7055c0d6 Mon Sep 17 00:00:00 2001 From: Mitchell Rosen Date: Tue, 2 Jul 2024 13:06:03 -0400 Subject: [PATCH 02/16] add Names.lenientToNametree --- .../src/Unison/Util/BiMultimap.hs | 1 + .../src/Unison/Codebase/Branch.hs | 3 +- unison-core/package.yaml | 1 + unison-core/src/Unison/Names.hs | 74 ++++++++++++++----- unison-core/unison-core1.cabal | 2 + 5 files changed, 59 insertions(+), 22 deletions(-) diff --git a/lib/unison-util-relation/src/Unison/Util/BiMultimap.hs b/lib/unison-util-relation/src/Unison/Util/BiMultimap.hs index 9167d6e6b..e970281f0 100644 --- a/lib/unison-util-relation/src/Unison/Util/BiMultimap.hs +++ b/lib/unison-util-relation/src/Unison/Util/BiMultimap.hs @@ -178,6 +178,7 @@ invertDomain = g x acc y = Map.insert y x acc +-- | Construct a left-unique relation from a mapping from its right-elements to its left-elements. fromRange :: (Ord a, Ord b) => Map b a -> BiMultimap a b fromRange m = BiMultimap (Map.foldlWithKey' f Map.empty m) m diff --git a/parser-typechecker/src/Unison/Codebase/Branch.hs b/parser-typechecker/src/Unison/Codebase/Branch.hs index 68c55c88f..00e2f7690 100644 --- a/parser-typechecker/src/Unison/Codebase/Branch.hs +++ b/parser-typechecker/src/Unison/Codebase/Branch.hs @@ -139,6 +139,7 @@ import Unison.NameSegment (NameSegment) import Unison.NameSegment qualified as NameSegment import Unison.Prelude hiding (empty) import Unison.Reference (TermReference, TermReferenceId, TypeReference, TypeReferenceId) +import Unison.Reference qualified as Reference import Unison.Referent (Referent) import Unison.Referent qualified as Referent import Unison.Util.List qualified as List @@ -148,7 +149,6 @@ import Unison.Util.Set qualified as Set import Unison.Util.Star2 qualified as Star2 import Witherable (FilterableWithIndex (imapMaybe)) import Prelude hiding (head, read, subtract) -import qualified Unison.Reference as Reference instance AsEmpty (Branch m) where _Empty = prism' (const empty) matchEmpty @@ -215,7 +215,6 @@ deepTypeReferenceIds :: Branch0 m -> Set TypeReferenceId deepTypeReferenceIds = Set.mapMaybe Reference.toId . deepTypeReferences - namespaceStats :: Branch0 m -> NamespaceStats namespaceStats b = NamespaceStats diff --git a/unison-core/package.yaml b/unison-core/package.yaml index fb5b62b73..2b8bea50b 100644 --- a/unison-core/package.yaml +++ b/unison-core/package.yaml @@ -66,6 +66,7 @@ default-extensions: - DerivingStrategies - DerivingVia - DoAndIfThenElse + - DuplicateRecordFields - FlexibleContexts - FlexibleInstances - GADTs diff --git a/unison-core/src/Unison/Names.hs b/unison-core/src/Unison/Names.hs index b21b76192..1897ac117 100644 --- a/unison-core/src/Unison/Names.hs +++ b/unison-core/src/Unison/Names.hs @@ -49,12 +49,15 @@ module Unison.Names hashQualifyTypesRelation, hashQualifyTermsRelation, fromTermsAndTypes, + lenientToNametree, ) where import Data.Map qualified as Map +import Data.Semialign (alignWith) import Data.Set qualified as Set import Data.Text qualified as Text +import Data.These (These (..)) import Text.FuzzyFind qualified as FZF import Unison.ConstructorReference (GConstructorReference (..)) import Unison.ConstructorType qualified as CT @@ -64,6 +67,7 @@ import Unison.LabeledDependency (LabeledDependency) import Unison.LabeledDependency qualified as LD import Unison.Name (Name) import Unison.Name qualified as Name +import Unison.NameSegment (NameSegment) import Unison.Prelude import Unison.Reference (Reference, TermReference, TypeReference) import Unison.Reference qualified as Reference @@ -71,6 +75,10 @@ import Unison.Referent (Referent) import Unison.Referent qualified as Referent import Unison.ShortHash (ShortHash) import Unison.ShortHash qualified as SH +import Unison.Util.BiMultimap (BiMultimap) +import Unison.Util.BiMultimap qualified as BiMultimap +import Unison.Util.Defns (Defns (..), DefnsF) +import Unison.Util.Nametree (Nametree, unflattenNametree) import Unison.Util.Relation (Relation) import Unison.Util.Relation qualified as R import Unison.Util.Relation qualified as Relation @@ -95,7 +103,7 @@ instance Monoid (Names) where mempty = Names mempty mempty isEmpty :: Names -> Bool -isEmpty n = R.null (terms n) && R.null (types n) +isEmpty n = R.null n.terms && R.null n.types map :: (Name -> Name) -> Names -> Names map f (Names {terms, types}) = Names terms' types' @@ -122,8 +130,8 @@ fuzzyFind nameToText query names = . Prelude.filter prefilter . Map.toList -- `mapMonotonic` is safe here and saves a log n factor - $ (Set.mapMonotonic Left <$> R.toMultimap (terms names)) - <> (Set.mapMonotonic Right <$> R.toMultimap (types names)) + $ (Set.mapMonotonic Left <$> R.toMultimap names.terms) + <> (Set.mapMonotonic Right <$> R.toMultimap names.types) where lowerqueryt = Text.toLower . Text.pack <$> query -- For performance, case-insensitive substring matching as a pre-filter @@ -250,8 +258,8 @@ unionLeft' :: Names unionLeft' shouldOmit a b = Names terms' types' where - terms' = foldl' go (terms a) (R.toList $ terms b) - types' = foldl' go (types a) (R.toList $ types b) + terms' = foldl' go a.terms (R.toList b.terms) + types' = foldl' go a.types (R.toList b.types) go :: (Ord a, Ord b) => Relation a b -> (a, b) -> Relation a b go acc (n, r) = if shouldOmit n r acc then acc else R.insert n r acc @@ -260,7 +268,7 @@ numHashChars :: Int numHashChars = 3 termsNamed :: Names -> Name -> Set Referent -termsNamed = flip R.lookupDom . terms +termsNamed = flip R.lookupDom . (.terms) -- | Get all terms with a specific name. refTermsNamed :: Names -> Name -> Set TermReference @@ -281,13 +289,13 @@ refTermsHQNamed names = \case in Set.mapMaybe f (termsNamed names name) typesNamed :: Names -> Name -> Set TypeReference -typesNamed = flip R.lookupDom . types +typesNamed = flip R.lookupDom . (.types) namesForReferent :: Names -> Referent -> Set Name -namesForReferent names r = R.lookupRan r (terms names) +namesForReferent names r = R.lookupRan r names.terms namesForReference :: Names -> TypeReference -> Set Name -namesForReference names r = R.lookupRan r (types names) +namesForReference names r = R.lookupRan r names.types termAliases :: Names -> Name -> Referent -> Set Name termAliases names n r = Set.delete n $ namesForReferent names r @@ -422,20 +430,20 @@ filterTypes f (Names terms types) = Names terms (R.filterDom f types) difference :: Names -> Names -> Names difference a b = Names - (R.difference (terms a) (terms b)) - (R.difference (types a) (types b)) + (R.difference a.terms b.terms) + (R.difference a.types b.types) contains :: Names -> Reference -> Bool contains names = -- We want to compute `termsReferences` only once, if `contains` is partially applied to a `Names`, and called over -- and over for different references. GHC would probably float `termsReferences` out without the explicit lambda, but -- it's written like this just to be sure. - \r -> Set.member r termsReferences || R.memberRan r (types names) + \r -> Set.member r termsReferences || R.memberRan r names.types where -- this check makes `contains` O(n) instead of O(log n) termsReferences :: Set TermReference termsReferences = - Set.map Referent.toReference (R.ran (terms names)) + Set.map Referent.toReference (R.ran names.terms) -- | filters out everything from the domain except what's conflicted conflicts :: Names -> Names @@ -448,9 +456,9 @@ conflicts Names {..} = Names (R.filterManyDom terms) (R.filterManyDom types) -- See usage in `FileParser` for handling precendence of symbol -- resolution where local names are preferred to codebase names. shadowTerms :: [Name] -> Names -> Names -shadowTerms ns n0 = Names terms' (types n0) +shadowTerms ns n0 = Names terms' n0.types where - terms' = foldl' go (terms n0) ns + terms' = foldl' go n0.terms ns go ts name = R.deleteDom name ts -- | Given a mapping from name to qualified name, update a `Names`, @@ -461,8 +469,8 @@ shadowTerms ns n0 = Names terms' (types n0) importing :: [(Name, Name)] -> Names -> Names importing shortToLongName ns = Names - (foldl' go (terms ns) shortToLongName) - (foldl' go (types ns) shortToLongName) + (foldl' go ns.terms shortToLongName) + (foldl' go ns.types shortToLongName) where go :: (Ord r) => Relation Name r -> (Name, Name) -> Relation Name r go m (shortname, qname) = case Name.searchByRankedSuffix qname m of @@ -476,8 +484,8 @@ importing shortToLongName ns = -- `[(foo, io.foo), (bar, io.bar)]`. expandWildcardImport :: Name -> Names -> [(Name, Name)] expandWildcardImport prefix ns = - [(suffix, full) | Just (suffix, full) <- go <$> R.toList (terms ns)] - <> [(suffix, full) | Just (suffix, full) <- go <$> R.toList (types ns)] + [(suffix, full) | Just (suffix, full) <- go <$> R.toList ns.terms] + <> [(suffix, full) | Just (suffix, full) <- go <$> R.toList ns.types] where go :: (Name, a) -> Maybe (Name, Name) go (full, _) = do @@ -498,7 +506,7 @@ constructorsForType r ns = possibleDatas = [Referent.Con (ConstructorReference r cid) CT.Data | cid <- [0 ..]] possibleEffects = [Referent.Con (ConstructorReference r cid) CT.Effect | cid <- [0 ..]] trim [] = [] - trim (h : t) = case R.lookupRan h (terms ns) of + trim (h : t) = case R.lookupRan h ns.terms of s | Set.null s -> [] | otherwise -> [(n, h) | n <- toList s] ++ trim t @@ -517,3 +525,29 @@ hashQualifyRelation fromNamedRef rel = R.map go rel if Set.size (R.lookupDom n rel) > 1 then (HQ.take numHashChars $ fromNamedRef n r, r) else (HQ.NameOnly n, r) + +-- | "Leniently" view a Names as a NameTree +-- +-- This function is "lenient" in the sense that it does not handle conflicted names with any smarts whatsoever. The +-- resulting nametree will simply contain one of the associated references of a conflicted name - we don't specify +-- which. +lenientToNametree :: Names -> Nametree (DefnsF (Map NameSegment) Referent TypeReference) +lenientToNametree names = + alignWith + ( \case + This terms -> Defns {terms, types = Map.empty} + That types -> Defns {terms = Map.empty, types} + These terms types -> Defns {terms, types} + ) + (lenientRelationToNametree names.terms) + (lenientRelationToNametree names.types) + where + lenientRelationToNametree :: Ord a => Relation Name a -> Nametree (Map NameSegment a) + lenientRelationToNametree = + unflattenNametree . lenientRelationToLeftUniqueRelation + + lenientRelationToLeftUniqueRelation :: (Ord a, Ord b) => Relation a b -> BiMultimap b a + lenientRelationToLeftUniqueRelation = + -- The partial `Set.findMin` are fine here because Relation.domain only has non-empty Set values. A NESet would be + -- better. + BiMultimap.fromRange . Map.map Set.findMin . Relation.domain diff --git a/unison-core/unison-core1.cabal b/unison-core/unison-core1.cabal index f40185f4d..bde4b2a6f 100644 --- a/unison-core/unison-core1.cabal +++ b/unison-core/unison-core1.cabal @@ -72,6 +72,7 @@ library DerivingStrategies DerivingVia DoAndIfThenElse + DuplicateRecordFields FlexibleContexts FlexibleInstances GADTs @@ -140,6 +141,7 @@ test-suite tests DerivingStrategies DerivingVia DoAndIfThenElse + DuplicateRecordFields FlexibleContexts FlexibleInstances GADTs From fdf91bbce67e17a33220a67f02a0e81aba6be170 Mon Sep 17 00:00:00 2001 From: Mitchell Rosen Date: Tue, 2 Jul 2024 17:44:09 -0400 Subject: [PATCH 03/16] make decl coherency check more abstract to support "get all violations" use case --- .../src/Unison/Merge/DeclCoherencyCheck.hs | 190 +++++++++++------- 1 file changed, 122 insertions(+), 68 deletions(-) diff --git a/unison-merge/src/Unison/Merge/DeclCoherencyCheck.hs b/unison-merge/src/Unison/Merge/DeclCoherencyCheck.hs index 2a75252fc..907c453e2 100644 --- a/unison-merge/src/Unison/Merge/DeclCoherencyCheck.hs +++ b/unison-merge/src/Unison/Merge/DeclCoherencyCheck.hs @@ -87,11 +87,9 @@ module Unison.Merge.DeclCoherencyCheck where import Control.Lens ((%=), (.=), _2) -import Control.Monad.Except (ExceptT) import Control.Monad.Except qualified as Except import Control.Monad.State.Strict (StateT) import Control.Monad.State.Strict qualified as State -import Control.Monad.Trans.Except qualified as Except (except) import Data.Functor.Compose (Compose (..)) import Data.IntMap.Strict (IntMap) import Data.IntMap.Strict qualified as IntMap @@ -136,87 +134,143 @@ checkDeclCoherency :: (TypeReferenceId -> m Int) -> Nametree (DefnsF (Map NameSegment) Referent TypeReference) -> m (Either IncoherentDeclReason DeclNameLookup) -checkDeclCoherency loadDeclNumConstructors = +checkDeclCoherency loadDeclNumConstructors nametree = Except.runExceptT - . fmap (view #declNameLookup) + ( checkDeclCoherencyWith + (lift . loadDeclNumConstructors) + OnIncoherentDeclReasons + { onConstructorAlias = \x y z -> Except.throwError (IncoherentDeclReason'ConstructorAlias x y z), -- :: Name -> Name -> Name -> m (), + onMissingConstructorName = \x -> Except.throwError (IncoherentDeclReason'MissingConstructorName x), -- :: Name -> m (), + onNestedDeclAlias = \x y -> Except.throwError (IncoherentDeclReason'NestedDeclAlias x y), -- :: Name -> Name -> m (), + onStrayConstructor = \x -> Except.throwError (IncoherentDeclReason'StrayConstructor x) -- :: Name -> m () + } + nametree + ) + +data OnIncoherentDeclReasons m = OnIncoherentDeclReasons + { onConstructorAlias :: Name -> Name -> Name -> m (), + onMissingConstructorName :: Name -> m (), + onNestedDeclAlias :: Name -> Name -> m (), + onStrayConstructor :: Name -> m () + } + +checkDeclCoherencyWith :: + forall m. + Monad m => + (TypeReferenceId -> m Int) -> + OnIncoherentDeclReasons m -> + Nametree (DefnsF (Map NameSegment) Referent TypeReference) -> + m DeclNameLookup +checkDeclCoherencyWith loadDeclNumConstructors callbacks = + fmap (view #declNameLookup) . (`State.execStateT` DeclCoherencyCheckState Map.empty (DeclNameLookup Map.empty Map.empty)) . go [] where go :: [NameSegment] -> (Nametree (DefnsF (Map NameSegment) Referent TypeReference)) -> - StateT DeclCoherencyCheckState (ExceptT IncoherentDeclReason m) () + StateT DeclCoherencyCheckState m () go prefix (Nametree defns children) = do - for_ (Map.toList defns.terms) \case - (_, Referent.Ref _) -> pure () - (_, Referent.Con (ConstructorReference (ReferenceBuiltin _) _) _) -> pure () - (name, Referent.Con (ConstructorReference (ReferenceDerived typeRef) conId) _) -> do - DeclCoherencyCheckState {expectedConstructors} <- State.get - expectedConstructors1 <- lift (Except.except (Map.upsertF f typeRef expectedConstructors)) - #expectedConstructors .= expectedConstructors1 - where - f :: - Maybe (Name, ConstructorNames) -> - Either IncoherentDeclReason (Name, ConstructorNames) - f = \case - Nothing -> Left (IncoherentDeclReason'StrayConstructor name1) - Just (typeName, expected) -> - case recordConstructorName conId name1 expected of - Left existingName -> Left (IncoherentDeclReason'ConstructorAlias typeName existingName name1) - Right expected1 -> Right (typeName, expected1) - where - name1 = fullName name - + for_ (Map.toList defns.terms) (checkDeclCoherency_terms callbacks prefix) childrenWeWentInto <- - forMaybe (Map.toList defns.types) \case - (_, ReferenceBuiltin _) -> pure Nothing - (name, ReferenceDerived typeRef) -> do - DeclCoherencyCheckState {expectedConstructors} <- State.get - whatHappened <- do - let recordNewDecl :: - Maybe (Name, ConstructorNames) -> - Compose (ExceptT IncoherentDeclReason m) WhatHappened (Name, ConstructorNames) - recordNewDecl = - Compose . \case - Just (shorterTypeName, _) -> Except.throwError (IncoherentDeclReason'NestedDeclAlias shorterTypeName typeName) - Nothing -> - lift (loadDeclNumConstructors typeRef) <&> \case - 0 -> UninhabitedDecl - n -> InhabitedDecl (typeName, emptyConstructorNames n) - lift (getCompose (Map.upsertF recordNewDecl typeRef expectedConstructors)) - case whatHappened of - UninhabitedDecl -> do - #declNameLookup . #declToConstructors %= Map.insert typeName [] - pure Nothing - InhabitedDecl expectedConstructors1 -> do - child <- - Map.lookup name children & onNothing do - Except.throwError (IncoherentDeclReason'MissingConstructorName typeName) - #expectedConstructors .= expectedConstructors1 - go (name : prefix) child - DeclCoherencyCheckState {expectedConstructors} <- State.get - -- fromJust is safe here because we upserted `typeRef` key above - let (fromJust -> (_typeName, maybeConstructorNames), expectedConstructors1) = - Map.deleteLookup typeRef expectedConstructors - constructorNames <- - sequence (IntMap.elems maybeConstructorNames) & onNothing do - Except.throwError (IncoherentDeclReason'MissingConstructorName typeName) - #expectedConstructors .= expectedConstructors1 + forMaybe + (Map.toList defns.types) + (checkDeclCoherency_types loadDeclNumConstructors callbacks go prefix children) + let childrenWeHaventGoneInto = children `Map.withoutKeys` Set.fromList childrenWeWentInto + for_ (Map.toList childrenWeHaventGoneInto) \(name, child) -> go (name : prefix) child + +checkDeclCoherency_terms :: + forall m. + Monad m => + OnIncoherentDeclReasons m -> + [NameSegment] -> + (NameSegment, Referent) -> + StateT DeclCoherencyCheckState m () +checkDeclCoherency_terms callbacks prefix = \case + (_, Referent.Ref _) -> pure () + (_, Referent.Con (ConstructorReference (ReferenceBuiltin _) _) _) -> pure () + (name, Referent.Con (ConstructorReference (ReferenceDerived typeRef) conId) _) -> do + state <- State.get + whenJustM (lift (runMaybeT (Map.upsertF f typeRef state.expectedConstructors))) \expectedConstructors1 -> + #expectedConstructors .= expectedConstructors1 + where + f :: Maybe (Name, ConstructorNames) -> MaybeT m (Name, ConstructorNames) + f = \case + Nothing -> do + lift (callbacks.onStrayConstructor name1) + MaybeT (pure Nothing) + Just (typeName, expected) -> + case recordConstructorName conId name1 expected of + Left existingName -> do + lift (callbacks.onConstructorAlias typeName existingName name1) + MaybeT (pure Nothing) + Right expected1 -> pure (typeName, expected1) + where + name1 = + Name.fromReverseSegments (name :| prefix) + +checkDeclCoherency_types :: + forall m. + Monad m => + (TypeReferenceId -> m Int) -> + OnIncoherentDeclReasons m -> + ( [NameSegment] -> + (Nametree (DefnsF (Map NameSegment) Referent TypeReference)) -> + StateT DeclCoherencyCheckState m () + ) -> + [NameSegment] -> + Map NameSegment (Nametree (DefnsF (Map NameSegment) Referent TypeReference)) -> + (NameSegment, TypeReference) -> + StateT DeclCoherencyCheckState m (Maybe NameSegment) +checkDeclCoherency_types loadDeclNumConstructors callbacks go prefix children = \case + (_, ReferenceBuiltin _) -> pure Nothing + (name, ReferenceDerived typeRef) -> do + state <- State.get + maybeWhatHappened <- do + let recordNewDecl :: + Maybe (Name, ConstructorNames) -> + Compose (MaybeT m) WhatHappened (Name, ConstructorNames) + recordNewDecl = + Compose . \case + Just (shorterTypeName, _) -> do + lift (callbacks.onNestedDeclAlias shorterTypeName typeName) + MaybeT (pure Nothing) + Nothing -> + lift (loadDeclNumConstructors typeRef) <&> \case + 0 -> UninhabitedDecl + n -> InhabitedDecl (typeName, emptyConstructorNames n) + lift (runMaybeT (getCompose (Map.upsertF recordNewDecl typeRef state.expectedConstructors))) + case maybeWhatHappened of + Nothing -> pure Nothing + Just UninhabitedDecl -> do + #declNameLookup . #declToConstructors %= Map.insert typeName [] + pure Nothing + Just (InhabitedDecl expectedConstructors1) -> do + case Map.lookup name children of + Nothing -> do + lift (callbacks.onMissingConstructorName typeName) + pure Nothing + Just child -> do + #expectedConstructors .= expectedConstructors1 + go (name : prefix) child + state <- State.get + -- fromJust is safe here because we upserted `typeRef` key above + let (fromJust -> (_typeName, maybeConstructorNames), expectedConstructors1) = + Map.deleteLookup typeRef state.expectedConstructors + #expectedConstructors .= expectedConstructors1 + case sequence (IntMap.elems maybeConstructorNames) of + Nothing -> lift (callbacks.onMissingConstructorName typeName) + Just constructorNames -> do #declNameLookup . #constructorToDecl %= \constructorToDecl -> List.foldl' (\acc constructorName -> Map.insert constructorName typeName acc) constructorToDecl constructorNames #declNameLookup . #declToConstructors %= Map.insert typeName constructorNames - pure (Just name) - where - typeName = fullName name - - let childrenWeHaventGoneInto = children `Map.withoutKeys` Set.fromList childrenWeWentInto - for_ (Map.toList childrenWeHaventGoneInto) \(name, child) -> go (name : prefix) child - where - fullName name = - Name.fromReverseSegments (name :| prefix) + pure (Just name) + where + typeName = + Name.fromReverseSegments (name :| prefix) -- | A lenient variant of 'checkDeclCoherency' - so lenient it can't even fail! It returns partial decl name lookup, -- which doesn't require a name for every constructor, and allows a constructor with a nameless decl. From 06b731b7749c5a1aa8223d2fd15bbe13a68ebd5b Mon Sep 17 00:00:00 2001 From: Mitchell Rosen Date: Wed, 3 Jul 2024 11:19:18 -0400 Subject: [PATCH 04/16] report constructor aliases in `todo` --- .../Codebase/Editor/HandleInput/Todo.hs | 17 +++-- .../src/Unison/Codebase/Editor/Output.hs | 5 +- .../src/Unison/CommandLine/OutputMessages.hs | 31 ++++++++- .../src/Unison/Merge/DeclCoherencyCheck.hs | 63 +++++++++++++++++-- unison-src/transcripts/todo.md | 22 +++++++ unison-src/transcripts/todo.output.md | 41 ++++++++++++ 6 files changed, 167 insertions(+), 12 deletions(-) diff --git a/unison-cli/src/Unison/Codebase/Editor/HandleInput/Todo.hs b/unison-cli/src/Unison/Codebase/Editor/HandleInput/Todo.hs index ef58f044b..108ceee2a 100644 --- a/unison-cli/src/Unison/Codebase/Editor/HandleInput/Todo.hs +++ b/unison-cli/src/Unison/Codebase/Editor/HandleInput/Todo.hs @@ -4,6 +4,7 @@ module Unison.Codebase.Editor.HandleInput.Todo ) where +import Data.Either qualified as Either import Data.Set qualified as Set import U.Codebase.HashTags (BranchHash (..)) import U.Codebase.Sqlite.Operations qualified as Operations @@ -19,6 +20,7 @@ import Unison.Codebase.Causal qualified as Causal import Unison.Codebase.Editor.HandleInput.Merge2 (hasDefnsInLib) import Unison.Codebase.Editor.Output import Unison.Hash (HashFor (..)) +import Unison.Merge.DeclCoherencyCheck (IncoherentDeclReasons (..), checkAllDeclCoherency) import Unison.Names qualified as Names import Unison.Prelude import Unison.Reference (TermReference) @@ -34,7 +36,7 @@ handleTodo = do let currentNamespace = Branch.head currentCausal let currentNamespaceWithoutLibdeps = Branch.deleteLibdeps currentNamespace - (defnsInLib, dependentsOfTodo, directDependencies, hashLen) <- + (defnsInLib, dependentsOfTodo, directDependencies, hashLen, incoherentDeclReasons) <- Cli.runTransaction do -- We call a shared `hasDefnsLib` helper even though we could easily duplicate the logic with the branch in hand defnsInLib <- do @@ -66,21 +68,28 @@ handleTodo = do hashLen <- Codebase.hashLength - pure (defnsInLib, dependentsOfTodo.terms, directDependencies, hashLen) + incoherentDeclReasons <- + fmap (Either.fromLeft (IncoherentDeclReasons [] [] [] [])) $ + checkAllDeclCoherency + Operations.expectDeclNumConstructors + (Names.lenientToNametree (Branch.toNames currentNamespaceWithoutLibdeps)) + + pure (defnsInLib, dependentsOfTodo.terms, directDependencies, hashLen, incoherentDeclReasons) ppe <- Cli.currentPrettyPrintEnvDecl Cli.respondNumbered $ Output'Todo TodoOutput - { hashLen, - defnsInLib, + { defnsInLib, dependentsOfTodo, directDependenciesWithoutNames = Defns { terms = Set.difference directDependencies.terms (Branch.deepTermReferences currentNamespace), types = Set.difference directDependencies.types (Branch.deepTypeReferences currentNamespace) }, + hashLen, + incoherentDeclReasons, nameConflicts = Names.conflicts (Branch.toNames currentNamespaceWithoutLibdeps), ppe } diff --git a/unison-cli/src/Unison/Codebase/Editor/Output.hs b/unison-cli/src/Unison/Codebase/Editor/Output.hs index 7ee842a07..c85f88410 100644 --- a/unison-cli/src/Unison/Codebase/Editor/Output.hs +++ b/unison-cli/src/Unison/Codebase/Editor/Output.hs @@ -53,9 +53,11 @@ import Unison.DataDeclaration.ConstructorId (ConstructorId) import Unison.HashQualified qualified as HQ import Unison.HashQualified' qualified as HQ' import Unison.LabeledDependency (LabeledDependency) +import Unison.Merge.DeclCoherencyCheck (IncoherentDeclReasons (..)) import Unison.Name (Name) import Unison.NameSegment (NameSegment) import Unison.Names (Names) +import Unison.Names qualified as Names import Unison.Names.ResolutionResult qualified as Names import Unison.NamesWithHistory qualified as Names import Unison.Parser.Ann (Ann) @@ -82,7 +84,6 @@ import Unison.Util.Defns (DefnsF, defnsAreEmpty) import Unison.Util.Pretty qualified as P import Unison.Util.Relation (Relation) import Unison.WatchKind qualified as WK -import qualified Unison.Names as Names type ListDetailed = Bool @@ -157,6 +158,7 @@ data TodoOutput = TodoOutput dependentsOfTodo :: !(Set TermReferenceId), directDependenciesWithoutNames :: !(DefnsF Set TermReference TypeReference), hashLen :: !Int, + incoherentDeclReasons :: !IncoherentDeclReasons, nameConflicts :: !Names, ppe :: !PrettyPrintEnvDecl } @@ -167,6 +169,7 @@ todoOutputIsEmpty todo = && defnsAreEmpty todo.directDependenciesWithoutNames && Names.isEmpty todo.nameConflicts && not todo.defnsInLib + && todo.incoherentDeclReasons == IncoherentDeclReasons [] [] [] [] data AmbiguousReset'Argument = AmbiguousReset'Hash diff --git a/unison-cli/src/Unison/CommandLine/OutputMessages.hs b/unison-cli/src/Unison/CommandLine/OutputMessages.hs index 0e3b93e5c..470d6f88a 100644 --- a/unison-cli/src/Unison/CommandLine/OutputMessages.hs +++ b/unison-cli/src/Unison/CommandLine/OutputMessages.hs @@ -87,6 +87,7 @@ import Unison.Hash32 (Hash32) import Unison.HashQualified qualified as HQ import Unison.HashQualified' qualified as HQ' import Unison.LabeledDependency as LD +import Unison.Merge.DeclCoherencyCheck (IncoherentDeclReasons (..)) import Unison.Name (Name) import Unison.Name qualified as Name import Unison.NameSegment qualified as NameSegment @@ -1405,6 +1406,7 @@ notifyUser dir = \case pure . P.lines $ [ P.wrap "Sorry, I wasn't able to perform the merge:", "", + -- Note [ConstructorAliasMessage] If you change this, also change the other similar one P.wrap $ "On" <> P.group (prettyMergeSourceOrTarget aliceOrBob <> ",") @@ -2728,12 +2730,39 @@ handleTodoOutput todo <> "subnamespaces representing library dependencies. Please move or remove it." else mempty + prettyConstructorAliases <- + if null todo.incoherentDeclReasons.constructorAliases + then pure mempty + else do + things <- + for todo.incoherentDeclReasons.constructorAliases \(typeName, conName1, conName2) -> do + n1 <- addNumberedArg (SA.Name conName1) + n2 <- addNumberedArg (SA.Name conName2) + pure (typeName, formatNum n1 <> prettyName conName1, formatNum n2 <> prettyName conName2) + pure $ + things + & map + ( \(typeName, prettyCon1, prettyCon2) -> + -- Note [ConstructorAliasMessage] If you change this, also change the other similar one + P.wrap + ( "The type" + <> prettyName typeName + <> "has a constructor with multiple names. Please delete all but one name for each" + <> "constructor." + ) + <> P.newline + <> P.newline + <> P.indentN 2 (P.lines [prettyCon1, prettyCon2]) + ) + & P.sep "\n\n" + (pure . P.sep "\n\n" . P.nonEmpty) [ prettyDependentsOfTodo, prettyDirectTermDependenciesWithoutNames, prettyDirectTypeDependenciesWithoutNames, prettyConflicts, - prettyDefnsInLib + prettyDefnsInLib, + prettyConstructorAliases ] listOfDefinitions :: diff --git a/unison-merge/src/Unison/Merge/DeclCoherencyCheck.hs b/unison-merge/src/Unison/Merge/DeclCoherencyCheck.hs index 907c453e2..302e46a29 100644 --- a/unison-merge/src/Unison/Merge/DeclCoherencyCheck.hs +++ b/unison-merge/src/Unison/Merge/DeclCoherencyCheck.hs @@ -83,6 +83,10 @@ module Unison.Merge.DeclCoherencyCheck ( IncoherentDeclReason (..), checkDeclCoherency, lenientCheckDeclCoherency, + + -- * Getting all failures rather than just the first + IncoherentDeclReasons (..), + checkAllDeclCoherency, ) where @@ -147,6 +151,53 @@ checkDeclCoherency loadDeclNumConstructors nametree = nametree ) +data IncoherentDeclReasons = IncoherentDeclReasons + { constructorAliases :: ![(Name, Name, Name)], + missingConstructorNames :: ![Name], + nestedDeclAliases :: ![(Name, Name)], + strayConstructors :: ![Name] + } + deriving stock (Eq, Generic) + +-- | Like 'checkDeclCoherency', but returns info about all of the incoherent decls found, not just the first. +checkAllDeclCoherency :: + forall m. + Monad m => + (TypeReferenceId -> m Int) -> + Nametree (DefnsF (Map NameSegment) Referent TypeReference) -> + m (Either IncoherentDeclReasons DeclNameLookup) +checkAllDeclCoherency loadDeclNumConstructors nametree = do + State.runStateT doCheck emptyReasons <&> \(declNameLookup, reasons) -> + if reasons == emptyReasons + then Right declNameLookup + else Left (reverseReasons reasons) + where + doCheck :: StateT IncoherentDeclReasons m DeclNameLookup + doCheck = + checkDeclCoherencyWith + (lift . loadDeclNumConstructors) + ( OnIncoherentDeclReasons + { onConstructorAlias = \x y z -> #constructorAliases %= ((x, y, z) :), + onMissingConstructorName = \x -> #missingConstructorNames %= (x :), + onNestedDeclAlias = \x y -> #nestedDeclAliases %= ((x, y) :), + onStrayConstructor = \x -> #strayConstructors %= (x :) + } + ) + nametree + + emptyReasons :: IncoherentDeclReasons + emptyReasons = + IncoherentDeclReasons [] [] [] [] + + reverseReasons :: IncoherentDeclReasons -> IncoherentDeclReasons + reverseReasons reasons = + IncoherentDeclReasons + { constructorAliases = reverse reasons.constructorAliases, + missingConstructorNames = reverse reasons.missingConstructorNames, + nestedDeclAliases = reverse reasons.nestedDeclAliases, + strayConstructors = reverse reasons.strayConstructors + } + data OnIncoherentDeclReasons m = OnIncoherentDeclReasons { onConstructorAlias :: Name -> Name -> Name -> m (), onMissingConstructorName :: Name -> m (), @@ -171,22 +222,22 @@ checkDeclCoherencyWith loadDeclNumConstructors callbacks = (Nametree (DefnsF (Map NameSegment) Referent TypeReference)) -> StateT DeclCoherencyCheckState m () go prefix (Nametree defns children) = do - for_ (Map.toList defns.terms) (checkDeclCoherency_terms callbacks prefix) + for_ (Map.toList defns.terms) (checkDeclCoherencyWith_DoTerms callbacks prefix) childrenWeWentInto <- forMaybe (Map.toList defns.types) - (checkDeclCoherency_types loadDeclNumConstructors callbacks go prefix children) + (checkDeclCoherencyWith_DoTypes loadDeclNumConstructors callbacks go prefix children) let childrenWeHaventGoneInto = children `Map.withoutKeys` Set.fromList childrenWeWentInto for_ (Map.toList childrenWeHaventGoneInto) \(name, child) -> go (name : prefix) child -checkDeclCoherency_terms :: +checkDeclCoherencyWith_DoTerms :: forall m. Monad m => OnIncoherentDeclReasons m -> [NameSegment] -> (NameSegment, Referent) -> StateT DeclCoherencyCheckState m () -checkDeclCoherency_terms callbacks prefix = \case +checkDeclCoherencyWith_DoTerms callbacks prefix = \case (_, Referent.Ref _) -> pure () (_, Referent.Con (ConstructorReference (ReferenceBuiltin _) _) _) -> pure () (name, Referent.Con (ConstructorReference (ReferenceDerived typeRef) conId) _) -> do @@ -209,7 +260,7 @@ checkDeclCoherency_terms callbacks prefix = \case name1 = Name.fromReverseSegments (name :| prefix) -checkDeclCoherency_types :: +checkDeclCoherencyWith_DoTypes :: forall m. Monad m => (TypeReferenceId -> m Int) -> @@ -222,7 +273,7 @@ checkDeclCoherency_types :: Map NameSegment (Nametree (DefnsF (Map NameSegment) Referent TypeReference)) -> (NameSegment, TypeReference) -> StateT DeclCoherencyCheckState m (Maybe NameSegment) -checkDeclCoherency_types loadDeclNumConstructors callbacks go prefix children = \case +checkDeclCoherencyWith_DoTypes loadDeclNumConstructors callbacks go prefix children = \case (_, ReferenceBuiltin _) -> pure Nothing (name, ReferenceDerived typeRef) -> do state <- State.get diff --git a/unison-src/transcripts/todo.md b/unison-src/transcripts/todo.md index 25f99aa40..5b4a40dec 100644 --- a/unison-src/transcripts/todo.md +++ b/unison-src/transcripts/todo.md @@ -98,3 +98,25 @@ scratch/main> todo ```ucm:hide scratch/main> delete.project scratch ``` + +# Constructor aliases + +The `todo` command complains about constructor aliases. + +```ucm:hide +scratch/main> builtins.mergeio lib.builtins +``` + +```unison +type Foo = One +``` + +```ucm +scratch/main> add +scratch/main> alias.term Foo.One Foo.Two +scratch/main> todo +``` + +```ucm:hide +scratch/main> delete.project scratch +``` diff --git a/unison-src/transcripts/todo.output.md b/unison-src/transcripts/todo.output.md index 07f0b03c3..0de57bd2c 100644 --- a/unison-src/transcripts/todo.output.md +++ b/unison-src/transcripts/todo.output.md @@ -181,3 +181,44 @@ scratch/main> todo representing library dependencies. Please move or remove it. ``` +# Constructor aliases + +The `todo` command complains about constructor aliases. + +```unison +type Foo = One +``` + +```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`: + + type Foo + +``` +```ucm +scratch/main> add + + ⍟ I've added these definitions: + + type Foo + +scratch/main> alias.term Foo.One Foo.Two + + Done. + +scratch/main> todo + + The type Foo has a constructor with multiple names. Please + delete all but one name for each constructor. + + 1. Foo.One + 2. Foo.Two + +``` From 052fd5194817140b8525d1e6f4c145b1afec937f Mon Sep 17 00:00:00 2001 From: Mitchell Rosen Date: Wed, 3 Jul 2024 11:38:33 -0400 Subject: [PATCH 05/16] report missing constructor names in `todo` --- .../src/Unison/CommandLine/OutputMessages.hs | 32 +++++++++++---- unison-src/transcripts/todo.md | 22 +++++++++++ unison-src/transcripts/todo.output.md | 39 +++++++++++++++++++ 3 files changed, 86 insertions(+), 7 deletions(-) diff --git a/unison-cli/src/Unison/CommandLine/OutputMessages.hs b/unison-cli/src/Unison/CommandLine/OutputMessages.hs index 470d6f88a..0095974c1 100644 --- a/unison-cli/src/Unison/CommandLine/OutputMessages.hs +++ b/unison-cli/src/Unison/CommandLine/OutputMessages.hs @@ -1402,11 +1402,11 @@ notifyUser dir = \case <> "the same on both branches, or making neither of them a builtin, and then try the merge again." ) ] + -- Note [ConstructorAliasMessage] If you change this, also change the other similar one MergeConstructorAlias aliceOrBob typeName conName1 conName2 -> pure . P.lines $ [ P.wrap "Sorry, I wasn't able to perform the merge:", "", - -- Note [ConstructorAliasMessage] If you change this, also change the other similar one P.wrap $ "On" <> P.group (prettyMergeSourceOrTarget aliceOrBob <> ",") @@ -1418,6 +1418,7 @@ notifyUser dir = \case "", P.wrap "Please delete all but one name for each constructor, and then try merging again." ] + -- Note [DefnsInLibMessage] If you change this, also change the other similar one MergeDefnsInLib aliceOrBob -> pure . P.lines $ [ P.wrap "Sorry, I wasn't able to perform the merge:", @@ -1425,12 +1426,12 @@ notifyUser dir = \case P.wrap $ "On" <> P.group (prettyMergeSourceOrTarget aliceOrBob <> ",") - -- Note [DefnsInLibMessage] If you change this, also change the other similar one <> "there's a type or term at the top level of the `lib` namespace, where I only expect to find" <> "subnamespaces representing library dependencies.", "", P.wrap "Please move or remove it and then try merging again." ] + -- Note [MissingConstructorNameMessage] If you change this, also change the other similar one MergeMissingConstructorName aliceOrBob name -> pure . P.lines $ [ P.wrap "Sorry, I wasn't able to perform the merge:", @@ -2731,11 +2732,11 @@ handleTodoOutput todo else mempty prettyConstructorAliases <- - if null todo.incoherentDeclReasons.constructorAliases - then pure mempty - else do + case todo.incoherentDeclReasons.constructorAliases of + [] -> pure mempty + aliases -> do things <- - for todo.incoherentDeclReasons.constructorAliases \(typeName, conName1, conName2) -> do + for aliases \(typeName, conName1, conName2) -> do n1 <- addNumberedArg (SA.Name conName1) n2 <- addNumberedArg (SA.Name conName2) pure (typeName, formatNum n1 <> prettyName conName1, formatNum n2 <> prettyName conName2) @@ -2756,13 +2757,30 @@ handleTodoOutput todo ) & P.sep "\n\n" + prettyMissingConstructorNames <- + case todo.incoherentDeclReasons.missingConstructorNames of + [] -> pure mempty + types0 -> do + types1 <- + for types0 \typ -> do + n <- addNumberedArg (SA.Name typ) + pure (formatNum n <> prettyName typ) + -- Note [MissingConstructorNameMessage] If you change this, also change the other similar one + pure $ + P.wrap + "These types have some constructors with missing names:" + <> P.newline + <> P.newline + <> P.indentN 2 (P.lines types1) + (pure . P.sep "\n\n" . P.nonEmpty) [ prettyDependentsOfTodo, prettyDirectTermDependenciesWithoutNames, prettyDirectTypeDependenciesWithoutNames, prettyConflicts, prettyDefnsInLib, - prettyConstructorAliases + prettyConstructorAliases, + prettyMissingConstructorNames ] listOfDefinitions :: diff --git a/unison-src/transcripts/todo.md b/unison-src/transcripts/todo.md index 5b4a40dec..20ed37146 100644 --- a/unison-src/transcripts/todo.md +++ b/unison-src/transcripts/todo.md @@ -120,3 +120,25 @@ scratch/main> todo ```ucm:hide scratch/main> delete.project scratch ``` + +# Missing constructor names + +The `todo` command complains about missing constructor names. + +```ucm:hide +scratch/main> builtins.mergeio lib.builtins +``` + +```unison +type Foo = Bar +``` + +```ucm +scratch/main> add +scratch/main> delete.term Foo.Bar +scratch/main> todo +``` + +```ucm:hide +scratch/main> delete.project scratch +``` diff --git a/unison-src/transcripts/todo.output.md b/unison-src/transcripts/todo.output.md index 0de57bd2c..0e8e23332 100644 --- a/unison-src/transcripts/todo.output.md +++ b/unison-src/transcripts/todo.output.md @@ -222,3 +222,42 @@ scratch/main> todo 2. Foo.Two ``` +# Missing constructor names + +The `todo` command complains about missing constructor names. + +```unison +type Foo = Bar +``` + +```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`: + + type Foo + +``` +```ucm +scratch/main> add + + ⍟ I've added these definitions: + + type Foo + +scratch/main> delete.term Foo.Bar + + Done. + +scratch/main> todo + + These types have some constructors with missing names: + + 1. Foo + +``` From 1857640da47272948bbe8b5eda2589b4cf6ba4d1 Mon Sep 17 00:00:00 2001 From: Mitchell Rosen Date: Wed, 3 Jul 2024 11:53:45 -0400 Subject: [PATCH 06/16] report nested decl aliases in `todo` --- .../src/Unison/CommandLine/OutputMessages.hs | 94 ++++++++++++++----- unison-src/transcripts/todo.md | 22 +++++ unison-src/transcripts/todo.output.md | 40 ++++++++ 3 files changed, 131 insertions(+), 25 deletions(-) diff --git a/unison-cli/src/Unison/CommandLine/OutputMessages.hs b/unison-cli/src/Unison/CommandLine/OutputMessages.hs index 0095974c1..0e315216d 100644 --- a/unison-cli/src/Unison/CommandLine/OutputMessages.hs +++ b/unison-cli/src/Unison/CommandLine/OutputMessages.hs @@ -1450,6 +1450,7 @@ notifyUser dir = \case <> IP.makeExample IP.aliasTerm ["", prettyName name <> "."] <> "to give names to each unnamed constructor, and then try the merge again." ] + -- Note [NestedDeclAliasMessage] If you change this, also change the other similar one MergeNestedDeclAlias aliceOrBob shorterName longerName -> pure . P.wrap $ "On" @@ -2732,30 +2733,48 @@ handleTodoOutput todo else mempty prettyConstructorAliases <- - case todo.incoherentDeclReasons.constructorAliases of - [] -> pure mempty - aliases -> do - things <- - for aliases \(typeName, conName1, conName2) -> do - n1 <- addNumberedArg (SA.Name conName1) - n2 <- addNumberedArg (SA.Name conName2) - pure (typeName, formatNum n1 <> prettyName conName1, formatNum n2 <> prettyName conName2) - pure $ - things - & map - ( \(typeName, prettyCon1, prettyCon2) -> - -- Note [ConstructorAliasMessage] If you change this, also change the other similar one - P.wrap - ( "The type" - <> prettyName typeName - <> "has a constructor with multiple names. Please delete all but one name for each" - <> "constructor." - ) - <> P.newline - <> P.newline - <> P.indentN 2 (P.lines [prettyCon1, prettyCon2]) - ) - & P.sep "\n\n" + let -- We want to filter out constructor aliases whose types are part of a "nested decl alias" problem, because + -- otherwise we'd essentially be reporting those issues twice. + -- + -- That is, if we have two nested aliases like + -- + -- Foo = #XYZ + -- Foo.Bar = #XYZ#0 + -- + -- Foo.inner.Alias = #XYZ + -- Foo.inner.Alias.Constructor = #XYZ#0 + -- + -- then we'd prefer to say "oh no Foo and Foo.inner.Alias are aliases" but *not* additionally say "oh no + -- Foo.Bar and Foo.inner.Alias.Constructor are aliases". + notNestedDeclAlias (typeName, _, _) = + foldr + (\(short, long) acc -> typeName /= short && typeName /= long && acc) + True + todo.incoherentDeclReasons.nestedDeclAliases + in case filter notNestedDeclAlias todo.incoherentDeclReasons.constructorAliases of + [] -> pure mempty + aliases -> do + things <- + for aliases \(typeName, conName1, conName2) -> do + n1 <- addNumberedArg (SA.Name conName1) + n2 <- addNumberedArg (SA.Name conName2) + pure (typeName, formatNum n1 <> prettyName conName1, formatNum n2 <> prettyName conName2) + pure $ + things + & map + ( \(typeName, prettyCon1, prettyCon2) -> + -- Note [ConstructorAliasMessage] If you change this, also change the other similar one + P.wrap + ( "The type" + <> prettyName typeName + <> "has a constructor with multiple names. Please delete all but one name for each" + <> "constructor." + ) + <> P.newline + <> P.newline + <> P.indentN 2 (P.lines [prettyCon1, prettyCon2]) + ) + & P.sep "\n\n" prettyMissingConstructorNames <- case todo.incoherentDeclReasons.missingConstructorNames of @@ -2773,6 +2792,30 @@ handleTodoOutput todo <> P.newline <> P.indentN 2 (P.lines types1) + prettyNestedDeclAliases <- + case todo.incoherentDeclReasons.nestedDeclAliases of + [] -> pure mempty + aliases0 -> do + aliases1 <- + for aliases0 \(short, long) -> do + n1 <- addNumberedArg (SA.Name short) + n2 <- addNumberedArg (SA.Name long) + pure (formatNum n1 <> prettyName short, formatNum n2 <> prettyName long) + -- Note [NestedDeclAliasMessage] If you change this, also change the other similar one + pure $ + aliases1 + & map + ( \(short, long) -> + P.wrap + ( "These types are aliases, but one is nested under the other. Please separate them or delete" + <> "one copy." + ) + <> P.newline + <> P.newline + <> P.indentN 2 (P.lines [short, long]) + ) + & P.sep "\n\n" + (pure . P.sep "\n\n" . P.nonEmpty) [ prettyDependentsOfTodo, prettyDirectTermDependenciesWithoutNames, @@ -2780,7 +2823,8 @@ handleTodoOutput todo prettyConflicts, prettyDefnsInLib, prettyConstructorAliases, - prettyMissingConstructorNames + prettyMissingConstructorNames, + prettyNestedDeclAliases ] listOfDefinitions :: diff --git a/unison-src/transcripts/todo.md b/unison-src/transcripts/todo.md index 20ed37146..d3cf81166 100644 --- a/unison-src/transcripts/todo.md +++ b/unison-src/transcripts/todo.md @@ -142,3 +142,25 @@ scratch/main> todo ```ucm:hide scratch/main> delete.project scratch ``` + +# Nested decl aliases + +The `todo` command complains about nested decl aliases. + +```ucm:hide +scratch/main> builtins.mergeio lib.builtins +``` + +```unison +structural type Foo a = One a | Two a a +structural type Foo.inner.Bar a = Uno a | Dos a a +``` + +```ucm +scratch/main> add +scratch/main> todo +``` + +```ucm:hide +scratch/main> delete.project scratch +``` diff --git a/unison-src/transcripts/todo.output.md b/unison-src/transcripts/todo.output.md index 0e8e23332..32b35c50b 100644 --- a/unison-src/transcripts/todo.output.md +++ b/unison-src/transcripts/todo.output.md @@ -261,3 +261,43 @@ scratch/main> todo 1. Foo ``` +# Nested decl aliases + +The `todo` command complains about nested decl aliases. + +```unison +structural type Foo a = One a | Two a a +structural type Foo.inner.Bar a = Uno a | Dos a a +``` + +```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`: + + structural type Foo a + structural type Foo.inner.Bar a + +``` +```ucm +scratch/main> add + + ⍟ I've added these definitions: + + structural type Foo a + structural type Foo.inner.Bar a + +scratch/main> todo + + These types are aliases, but one is nested under the other. + Please separate them or delete one copy. + + 1. Foo + 2. Foo.inner.Bar + +``` From 05d34024bd219b6870f4bc394954e330a7971f20 Mon Sep 17 00:00:00 2001 From: Mitchell Rosen Date: Wed, 3 Jul 2024 11:59:17 -0400 Subject: [PATCH 07/16] report stray constructors in `todo` --- .../src/Unison/CommandLine/OutputMessages.hs | 30 ++++++++++-- unison-src/transcripts/todo.md | 22 +++++++++ unison-src/transcripts/todo.output.md | 46 +++++++++++++++++-- 3 files changed, 90 insertions(+), 8 deletions(-) diff --git a/unison-cli/src/Unison/CommandLine/OutputMessages.hs b/unison-cli/src/Unison/CommandLine/OutputMessages.hs index 0e315216d..d2684f190 100644 --- a/unison-cli/src/Unison/CommandLine/OutputMessages.hs +++ b/unison-cli/src/Unison/CommandLine/OutputMessages.hs @@ -1461,6 +1461,7 @@ notifyUser dir = \case <> P.group (prettyName shorterName <> ".") <> "I'm not able to perform a merge when a type exists nested under an alias of itself. Please separate them or" <> "delete one copy, and then try merging again." + -- Note [StrayConstructorMessage] If you change this, also change the other similar one MergeStrayConstructor aliceOrBob name -> pure . P.lines $ [ P.wrap $ @@ -2685,7 +2686,7 @@ handleTodoOutput todo & P.syntaxToColor pure (formatNum n <> name) pure $ - P.wrap "These terms call `todo`:" + P.wrap "These terms call `todo`." <> P.newline <> P.newline <> P.indentN 2 (P.lines terms) @@ -2699,7 +2700,7 @@ handleTodoOutput todo n <- addNumberedArg (SA.HashQualified (HQ.HashOnly (Reference.toShortHash term))) pure (formatNum n <> P.syntaxToColor (prettyReference todo.hashLen term)) pure $ - P.wrap "These terms do not have any names in the current namespace:" + P.wrap "These terms do not have any names in the current namespace." <> P.newline <> P.newline <> P.indentN 2 (P.lines terms) @@ -2713,7 +2714,7 @@ handleTodoOutput todo n <- addNumberedArg (SA.HashQualified (HQ.HashOnly (Reference.toShortHash typ))) pure (formatNum n <> P.syntaxToColor (prettyReference todo.hashLen typ)) pure $ - P.wrap "These types do not have any names in the current namespace:" + P.wrap "These types do not have any names in the current namespace." <> P.newline <> P.newline <> P.indentN 2 (P.lines types) @@ -2787,7 +2788,7 @@ handleTodoOutput todo -- Note [MissingConstructorNameMessage] If you change this, also change the other similar one pure $ P.wrap - "These types have some constructors with missing names:" + "These types have some constructors with missing names." <> P.newline <> P.newline <> P.indentN 2 (P.lines types1) @@ -2816,6 +2817,24 @@ handleTodoOutput todo ) & P.sep "\n\n" + prettyStrayConstructors <- + case todo.incoherentDeclReasons.strayConstructors of + [] -> pure mempty + constructors0 -> do + constructors1 <- + for constructors0 \constructor -> do + n <- addNumberedArg (SA.Name constructor) + pure (formatNum n <> prettyName constructor) + -- Note [StrayConstructorMessage] If you change this, also change the other similar one + pure $ + P.wrap + ( "These constructors are not nested beneath their corresponding type names. Please either move or" + <> "delete them." + ) + <> P.newline + <> P.newline + <> P.indentN 2 (P.lines constructors1) + (pure . P.sep "\n\n" . P.nonEmpty) [ prettyDependentsOfTodo, prettyDirectTermDependenciesWithoutNames, @@ -2824,7 +2843,8 @@ handleTodoOutput todo prettyDefnsInLib, prettyConstructorAliases, prettyMissingConstructorNames, - prettyNestedDeclAliases + prettyNestedDeclAliases, + prettyStrayConstructors ] listOfDefinitions :: diff --git a/unison-src/transcripts/todo.md b/unison-src/transcripts/todo.md index d3cf81166..46e1eb616 100644 --- a/unison-src/transcripts/todo.md +++ b/unison-src/transcripts/todo.md @@ -164,3 +164,25 @@ scratch/main> todo ```ucm:hide scratch/main> delete.project scratch ``` + +# Stray constructors + +The `todo` command complains about stray constructors. + +```ucm:hide +scratch/main> builtins.mergeio lib.builtins +``` + +```unison +type Foo = Bar +``` + +```ucm +scratch/main> add +scratch/main> alias.term Foo.Bar Baz +scratch/main> todo +``` + +```ucm:hide +scratch/main> delete.project scratch +``` diff --git a/unison-src/transcripts/todo.output.md b/unison-src/transcripts/todo.output.md index 32b35c50b..38c6cdb56 100644 --- a/unison-src/transcripts/todo.output.md +++ b/unison-src/transcripts/todo.output.md @@ -44,7 +44,7 @@ scratch/main> add scratch/main> todo - These terms call `todo`: + These terms call `todo`. 1. foo @@ -95,7 +95,7 @@ scratch/main> delete.namespace.force foo scratch/main> todo - These terms do not have any names in the current namespace: + These terms do not have any names in the current namespace. 1. #1jujb8oelv @@ -256,7 +256,7 @@ scratch/main> delete.term Foo.Bar scratch/main> todo - These types have some constructors with missing names: + These types have some constructors with missing names. 1. Foo @@ -301,3 +301,43 @@ scratch/main> todo 2. Foo.inner.Bar ``` +# Stray constructors + +The `todo` command complains about stray constructors. + +```unison +type Foo = Bar +``` + +```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`: + + type Foo + +``` +```ucm +scratch/main> add + + ⍟ I've added these definitions: + + type Foo + +scratch/main> alias.term Foo.Bar Baz + + Done. + +scratch/main> todo + + These constructors are not nested beneath their corresponding + type names. Please either move or delete them. + + 1. Baz + +``` From 1e5b925bcab2662eefd3b943a0b51e4a23d0fc66 Mon Sep 17 00:00:00 2001 From: Mitchell Rosen Date: Tue, 9 Jul 2024 18:19:32 -0400 Subject: [PATCH 08/16] adjust some output --- .../src/Unison/CommandLine/OutputMessages.hs | 77 +++++++++++++------ unison-src/transcripts/todo.output.md | 18 +++-- 2 files changed, 65 insertions(+), 30 deletions(-) diff --git a/unison-cli/src/Unison/CommandLine/OutputMessages.hs b/unison-cli/src/Unison/CommandLine/OutputMessages.hs index d2684f190..4bc0ea47a 100644 --- a/unison-cli/src/Unison/CommandLine/OutputMessages.hs +++ b/unison-cli/src/Unison/CommandLine/OutputMessages.hs @@ -2686,7 +2686,7 @@ handleTodoOutput todo & P.syntaxToColor pure (formatNum n <> name) pure $ - P.wrap "These terms call `todo`." + P.wrap "These terms call `todo`:" <> P.newline <> P.newline <> P.indentN 2 (P.lines terms) @@ -2700,7 +2700,7 @@ handleTodoOutput todo n <- addNumberedArg (SA.HashQualified (HQ.HashOnly (Reference.toShortHash term))) pure (formatNum n <> P.syntaxToColor (prettyReference todo.hashLen term)) pure $ - P.wrap "These terms do not have any names in the current namespace." + P.wrap "These terms do not have any names in the current namespace:" <> P.newline <> P.newline <> P.indentN 2 (P.lines terms) @@ -2714,7 +2714,7 @@ handleTodoOutput todo n <- addNumberedArg (SA.HashQualified (HQ.HashOnly (Reference.toShortHash typ))) pure (formatNum n <> P.syntaxToColor (prettyReference todo.hashLen typ)) pure $ - P.wrap "These types do not have any names in the current namespace." + P.wrap "These types do not have any names in the current namespace:" <> P.newline <> P.newline <> P.indentN 2 (P.lines types) @@ -2765,33 +2765,47 @@ handleTodoOutput todo & map ( \(typeName, prettyCon1, prettyCon2) -> -- Note [ConstructorAliasMessage] If you change this, also change the other similar one - P.wrap - ( "The type" - <> prettyName typeName - <> "has a constructor with multiple names. Please delete all but one name for each" - <> "constructor." - ) + P.wrap ("The type" <> prettyName typeName <> "has a constructor with multiple names.") <> P.newline <> P.newline <> P.indentN 2 (P.lines [prettyCon1, prettyCon2]) + <> P.newline + <> P.newline + <> P.wrap "Please delete all but one name for each constructor." ) & P.sep "\n\n" prettyMissingConstructorNames <- - case todo.incoherentDeclReasons.missingConstructorNames of - [] -> pure mempty - types0 -> do - types1 <- + case NEList.nonEmpty todo.incoherentDeclReasons.missingConstructorNames of + Nothing -> pure mempty + Just types0 -> do + stuff <- for types0 \typ -> do n <- addNumberedArg (SA.Name typ) - pure (formatNum n <> prettyName typ) + pure (n, typ) -- Note [MissingConstructorNameMessage] If you change this, also change the other similar one pure $ P.wrap "These types have some constructors with missing names." <> P.newline <> P.newline - <> P.indentN 2 (P.lines types1) + <> P.indentN 2 (P.lines (fmap (\(n, typ) -> formatNum n <> prettyName typ) stuff)) + <> P.newline + <> P.newline + <> P.wrap + ( "You can use" + <> IP.makeExample + IP.view + [ let firstNum = fst (NEList.head stuff) + lastNum = fst (NEList.last stuff) + in if firstNum == lastNum + then P.string (show firstNum) + else P.string (show firstNum) <> "-" <> P.string (show lastNum) + ] + <> "and" + <> IP.makeExample IP.aliasTerm ["", "."] + <> "to give names to each unnamed constructor." + ) prettyNestedDeclAliases <- case todo.incoherentDeclReasons.nestedDeclAliases of @@ -2820,20 +2834,33 @@ handleTodoOutput todo prettyStrayConstructors <- case todo.incoherentDeclReasons.strayConstructors of [] -> pure mempty - constructors0 -> do - constructors1 <- - for constructors0 \constructor -> do - n <- addNumberedArg (SA.Name constructor) - pure (formatNum n <> prettyName constructor) + constructors -> do + nums <- + for constructors \constructor -> do + addNumberedArg (SA.Name constructor) -- Note [StrayConstructorMessage] If you change this, also change the other similar one pure $ - P.wrap - ( "These constructors are not nested beneath their corresponding type names. Please either move or" - <> "delete them." - ) + P.wrap "These constructors are not nested beneath their corresponding type names:" <> P.newline <> P.newline - <> P.indentN 2 (P.lines constructors1) + <> P.indentN + 2 + ( P.lines + ( zipWith + (\n constructor -> formatNum n <> prettyName constructor) + nums + constructors + ) + ) + <> P.newline + <> P.newline + <> P.wrap + ( "For each one, please either use" + <> IP.makeExample' IP.moveAll + <> "to move if, or if it's an extra copy, you can simply" + <> IP.makeExample' IP.delete + <> "it." + ) (pure . P.sep "\n\n" . P.nonEmpty) [ prettyDependentsOfTodo, diff --git a/unison-src/transcripts/todo.output.md b/unison-src/transcripts/todo.output.md index 38c6cdb56..dbc5de722 100644 --- a/unison-src/transcripts/todo.output.md +++ b/unison-src/transcripts/todo.output.md @@ -44,7 +44,7 @@ scratch/main> add scratch/main> todo - These terms call `todo`. + These terms call `todo`: 1. foo @@ -95,7 +95,7 @@ scratch/main> delete.namespace.force foo scratch/main> todo - These terms do not have any names in the current namespace. + These terms do not have any names in the current namespace: 1. #1jujb8oelv @@ -215,11 +215,12 @@ scratch/main> alias.term Foo.One Foo.Two scratch/main> todo - The type Foo has a constructor with multiple names. Please - delete all but one name for each constructor. + The type Foo has a constructor with multiple names. 1. Foo.One 2. Foo.Two + + Please delete all but one name for each constructor. ``` # Missing constructor names @@ -259,6 +260,10 @@ scratch/main> todo These types have some constructors with missing names. 1. Foo + + You can use `view 1` and + `alias.term .` to give names + to each unnamed constructor. ``` # Nested decl aliases @@ -336,8 +341,11 @@ scratch/main> alias.term Foo.Bar Baz scratch/main> todo These constructors are not nested beneath their corresponding - type names. Please either move or delete them. + type names: 1. Baz + + For each one, please either use `move` to move if, or if it's + an extra copy, you can simply `delete` it. ``` From d78154d7c186c967a9eb12c0b661bd15427b663c Mon Sep 17 00:00:00 2001 From: Mitchell Rosen Date: Tue, 9 Jul 2024 18:58:42 -0400 Subject: [PATCH 09/16] better rendering of conflicted names in `todo` --- .../src/Unison/CommandLine/OutputMessages.hs | 25 ++++++++++--------- unison-src/transcripts/todo.output.md | 6 +++-- 2 files changed, 17 insertions(+), 14 deletions(-) diff --git a/unison-cli/src/Unison/CommandLine/OutputMessages.hs b/unison-cli/src/Unison/CommandLine/OutputMessages.hs index 4bc0ea47a..ef088071d 100644 --- a/unison-cli/src/Unison/CommandLine/OutputMessages.hs +++ b/unison-cli/src/Unison/CommandLine/OutputMessages.hs @@ -2593,20 +2593,20 @@ unsafePrettyTermResultSig' ppe = \case head (TypePrinter.prettySignaturesCT ppe [(r, name, typ)]) _ -> error "Don't pass Nothing" -renderNameConflicts :: PPE.PrettyPrintEnv -> Names -> Numbered Pretty -renderNameConflicts ppe conflictedNames = do +renderNameConflicts :: Int -> Names -> Numbered Pretty +renderNameConflicts hashLen conflictedNames = do let conflictedTypeNames :: Map Name [HQ.HashQualified Name] conflictedTypeNames = conflictedNames & Names.types & R.domain - & fmap (foldMap (pure @[] . PPE.typeName ppe)) + & Map.mapWithKey \name -> map (HQ.take hashLen . HQ.HashQualified name . Reference.toShortHash) . Set.toList let conflictedTermNames :: Map Name [HQ.HashQualified Name] conflictedTermNames = conflictedNames & Names.terms & R.domain - & fmap (foldMap (pure @[] . PPE.termName ppe)) + & Map.mapWithKey \name -> map (HQ.take hashLen . HQ.HashQualified name . Referent.toShortHash) . Set.toList let allConflictedNames :: [Name] allConflictedNames = Set.toList (Map.keysSet conflictedTermNames <> Map.keysSet conflictedTypeNames) prettyConflictedTypes <- showConflictedNames "type" conflictedTypeNames @@ -2639,13 +2639,14 @@ renderNameConflicts ppe conflictedNames = do prettyConflicts <- for hashes \hash -> do n <- addNumberedArg $ SA.HashQualified hash pure $ formatNum n <> (P.blue . P.syntaxToColor . prettyHashQualified $ hash) - pure . P.wrap $ - ( "The " - <> thingKind - <> " " - <> P.green (prettyName name) - <> " has conflicting definitions:" - ) + pure $ + P.wrap + ( "The " + <> thingKind + <> " " + <> P.green (prettyName name) + <> " has conflicting definitions:" + ) <> P.newline <> P.newline <> P.indentN 2 (P.lines prettyConflicts) @@ -2722,7 +2723,7 @@ handleTodoOutput todo prettyConflicts <- if todo.nameConflicts == mempty then pure mempty - else renderNameConflicts todo.ppe.unsuffixifiedPPE todo.nameConflicts + else renderNameConflicts todo.hashLen todo.nameConflicts let prettyDefnsInLib = if todo.defnsInLib diff --git a/unison-src/transcripts/todo.output.md b/unison-src/transcripts/todo.output.md index dbc5de722..639de4e52 100644 --- a/unison-src/transcripts/todo.output.md +++ b/unison-src/transcripts/todo.output.md @@ -139,8 +139,10 @@ scratch/main> todo ❓ - The term bar has conflicting definitions: 1. foo 2. - bar#cq22mm4sca + The term bar has conflicting definitions: + + 1. bar#14ibahkll6 + 2. bar#cq22mm4sca Tip: Use `move.term` or `delete.term` to resolve the conflicts. From 9e2fa2bbe74e72b2e751986f83cbead4b3848754 Mon Sep 17 00:00:00 2001 From: Greg Pfeil Date: Wed, 10 Jul 2024 08:11:59 -0600 Subject: [PATCH 10/16] Replace transcript parser with `cmark` MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit We don’t need a very rich parser for transcripts, but we _do_ need to reliably identify fenced code blocks, and that implies a number of subtle cases. Using a polished CommonMark parser/printer handles those subtleties for us. I chose `cmark` for a few reasons: - it’s a wrapper around `libcmark`, which is the reference implementation of CommonMark, so it should be correct; - it provides both a parser and a printer (unlike MMark); and - it is extremely fast (about 20x faster than MMark), so the fact that our home-rolled parser got to skip over everything that’s not a block isn’t an issue.). This only _partially_ uses the `cmark` printer. I think it should use it entirely, but for the cases where we do streaming output (processing UCM commands, etc.) it’s a more involved change. So I think it should be handled separately. --- unison-cli/package.yaml | 1 + .../src/Unison/Codebase/TranscriptParser.hs | 133 +++++++----------- unison-cli/unison-cli.cabal | 3 + 3 files changed, 56 insertions(+), 81 deletions(-) diff --git a/unison-cli/package.yaml b/unison-cli/package.yaml index d64ed16ae..23b18fa9d 100644 --- a/unison-cli/package.yaml +++ b/unison-cli/package.yaml @@ -19,6 +19,7 @@ dependencies: - base - bytes - bytestring + - cmark - co-log-core - code-page - concurrent-output diff --git a/unison-cli/src/Unison/Codebase/TranscriptParser.hs b/unison-cli/src/Unison/Codebase/TranscriptParser.hs index b9e82f7ed..ebabe7b4d 100644 --- a/unison-cli/src/Unison/Codebase/TranscriptParser.hs +++ b/unison-cli/src/Unison/Codebase/TranscriptParser.hs @@ -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 @@ -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) diff --git a/unison-cli/unison-cli.cabal b/unison-cli/unison-cli.cabal index d0b19db6a..dc7b8f2b8 100644 --- a/unison-cli/unison-cli.cabal +++ b/unison-cli/unison-cli.cabal @@ -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 From 1dc181b99aedbac9b8e64da3a88ca3dc3db6d8bb Mon Sep 17 00:00:00 2001 From: Greg Pfeil Date: Wed, 10 Jul 2024 08:46:18 -0600 Subject: [PATCH 11/16] Update the transcripts with `cmark` MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit `cmark`’s pretty-printer matches our output pretty well, with a few differences: - it puts a space between the fence and the info string for in code blocks; - it prefers `-` over `*` for bulleted lists (as do I) and it indents them; - it `\`-escapes certain chars very conservatively; - it prefers indented/unfenced code blocks if there is no info string; and - it prefers `*` over `_` (unlike any sane person). This also shows how the change fixes a number of issues: - fix2158-1.output.md also illustrates how this change fixes #1809; - alias-many.output.md and input-parse-errors.output.md show how fenced code blocks without an info string would use the beginning of the content as the info string; - transcripts-round-trip/main.output.md shows how output blocks for generated `unison` stanzas (which could contain nested fenced blocks) might not have long-enough fences; and - error-messages.output.md and generic-parse-errors.output.md show how Unison errors were reported on the wrong line number (and thus the printed error lines were also incorrect). --- .../IntegrationTests/transcript.output.md | 2 +- .../transcripts-manual/docs.to-html.output.md | 2 +- .../transcripts-manual/rewrites.output.md | 25 +- .../transcripts-round-trip/main.output.md | 12 +- .../transcripts-using-base/_base.output.md | 4 +- .../binary-encoding-nats.output.md | 2 +- .../transcripts-using-base/codeops.output.md | 9 +- .../transcripts-using-base/doc.output.md | 15 +- .../failure-tests.output.md | 2 +- .../fix2158-1.output.md | 5 +- .../transcripts-using-base/fix2297.output.md | 3 +- .../transcripts-using-base/fix2358.output.md | 3 +- .../transcripts-using-base/fix3166.output.md | 6 +- .../transcripts-using-base/fix3542.output.md | 2 +- .../transcripts-using-base/fix3939.output.md | 2 +- .../transcripts-using-base/fix4746.output.md | 2 +- .../transcripts-using-base/fix5129.output.md | 6 +- .../transcripts-using-base/hashing.output.md | 12 +- .../transcripts-using-base/mvar.output.md | 3 +- .../nat-coersion.output.md | 2 +- .../transcripts-using-base/net.output.md | 17 +- .../random-deserial.output.md | 2 +- .../ref-promise.output.md | 10 +- .../serial-test-00.output.md | 2 +- .../serial-test-01.output.md | 2 +- .../serial-test-02.output.md | 2 +- .../serial-test-03.output.md | 2 +- .../serial-test-04.output.md | 2 +- .../transcripts-using-base/stm.output.md | 5 +- .../test-watch-dependencies.output.md | 8 +- .../transcripts-using-base/thread.output.md | 6 +- .../transcripts-using-base/tls.output.md | 6 +- .../transcripts-using-base/utf8.output.md | 10 +- unison-src/transcripts/abilities.output.md | 3 +- ...ability-order-doesnt-affect-hash.output.md | 2 +- ...ability-term-conflicts-on-update.output.md | 14 +- unison-src/transcripts/add-run.output.md | 19 +- .../add-test-watch-roundtrip.output.md | 4 +- .../transcripts/addupdatemessages.output.md | 8 +- unison-src/transcripts/alias-many.output.md | 20 +- unison-src/transcripts/anf-tests.output.md | 5 +- unison-src/transcripts/any-extract.output.md | 2 +- .../transcripts/api-doc-rendering.output.md | 2 +- unison-src/transcripts/api-find.output.md | 2 +- .../transcripts/api-getDefinition.output.md | 4 +- .../api-namespace-details.output.md | 2 +- .../transcripts/api-namespace-list.output.md | 2 +- .../transcripts/api-summaries.output.md | 2 +- .../block-on-required-update.output.md | 4 +- unison-src/transcripts/blocks.output.md | 34 +-- .../boolean-op-pretty-print-2819.output.md | 2 +- .../transcripts/branch-command.output.md | 2 +- .../branch-relative-path.output.md | 4 +- unison-src/transcripts/bug-fix-4354.output.md | 2 +- .../transcripts/bug-strange-closure.output.md | 5 +- unison-src/transcripts/builtins.output.md | 24 +- .../transcripts/bytesFromList.output.md | 3 +- unison-src/transcripts/check763.output.md | 2 +- unison-src/transcripts/check873.output.md | 4 +- .../constructor-applied-to-unit.output.md | 2 +- .../transcripts/contrabilities.output.md | 2 +- .../transcripts/cycle-update-1.output.md | 4 +- .../transcripts/cycle-update-2.output.md | 4 +- .../transcripts/cycle-update-3.output.md | 4 +- .../transcripts/cycle-update-4.output.md | 4 +- .../transcripts/cycle-update-5.output.md | 7 +- .../transcripts/debug-definitions.output.md | 2 +- .../transcripts/debug-name-diffs.output.md | 2 +- unison-src/transcripts/deep-names.output.md | 7 +- .../transcripts/definition-diff-api.output.md | 4 +- ...elete-namespace-dependents-check.output.md | 4 +- .../transcripts/delete-namespace.output.md | 2 +- .../transcripts/delete-silent.output.md | 2 +- unison-src/transcripts/delete.output.md | 24 +- ...ependents-dependencies-debugfile.output.md | 7 +- .../transcripts/destructuring-binds.output.md | 10 +- .../transcripts/diff-namespace.output.md | 107 +++---- .../transcripts/doc-formatting.output.md | 28 +- .../doc-type-link-keywords.output.md | 2 +- unison-src/transcripts/doc1.output.md | 16 +- unison-src/transcripts/doc2.output.md | 4 +- unison-src/transcripts/doc2markdown.output.md | 4 +- ...t-upgrade-refs-that-exist-in-old.output.md | 4 +- .../transcripts/duplicate-names.output.md | 10 +- .../duplicate-term-detection.output.md | 8 +- unison-src/transcripts/ed25519.output.md | 3 +- unison-src/transcripts/edit-command.output.md | 7 +- .../transcripts/edit-namespace.output.md | 6 +- .../transcripts/empty-namespaces.output.md | 7 +- .../transcripts/emptyCodebase.output.md | 7 +- .../transcripts/error-messages.output.md | 47 +-- .../errors/missing-result-typed.output.md | 3 +- .../errors/missing-result.output.md | 3 +- .../errors/ucm-hide-all-error.output.md | 6 +- .../transcripts/errors/ucm-hide-all.output.md | 6 +- .../errors/ucm-hide-error.output.md | 6 +- .../transcripts/errors/ucm-hide.output.md | 6 +- .../errors/unison-hide-all-error.output.md | 3 +- .../errors/unison-hide-all.output.md | 3 +- .../errors/unison-hide-error.output.md | 3 +- .../transcripts/errors/unison-hide.output.md | 3 +- .../transcripts/escape-sequences.output.md | 2 +- unison-src/transcripts/find-by-type.output.md | 2 +- unison-src/transcripts/find-command.output.md | 2 +- .../fix-1381-excess-propagate.output.md | 8 +- .../fix-2258-if-as-list-element.output.md | 2 +- .../transcripts/fix-big-list-crash.output.md | 2 +- unison-src/transcripts/fix-ls.output.md | 2 +- unison-src/transcripts/fix1063.output.md | 2 +- unison-src/transcripts/fix1334.output.md | 2 +- unison-src/transcripts/fix1390.output.md | 5 +- unison-src/transcripts/fix1532.output.md | 2 +- unison-src/transcripts/fix1578.output.md | 22 +- unison-src/transcripts/fix1696.output.md | 3 +- unison-src/transcripts/fix1709.output.md | 4 +- unison-src/transcripts/fix1731.output.md | 5 +- unison-src/transcripts/fix1800.output.md | 9 +- unison-src/transcripts/fix1844.output.md | 3 +- unison-src/transcripts/fix1926.output.md | 4 +- unison-src/transcripts/fix2026.output.md | 2 +- unison-src/transcripts/fix2027.output.md | 4 +- unison-src/transcripts/fix2049.output.md | 4 +- unison-src/transcripts/fix2156.output.md | 3 +- unison-src/transcripts/fix2167.output.md | 3 +- unison-src/transcripts/fix2187.output.md | 2 +- unison-src/transcripts/fix2231.output.md | 2 +- unison-src/transcripts/fix2238.output.md | 3 +- unison-src/transcripts/fix2254.output.md | 9 +- unison-src/transcripts/fix2268.output.md | 2 +- unison-src/transcripts/fix2334.output.md | 3 +- unison-src/transcripts/fix2344.output.md | 3 +- unison-src/transcripts/fix2350.output.md | 3 +- unison-src/transcripts/fix2353.output.md | 2 +- unison-src/transcripts/fix2354.output.md | 3 +- unison-src/transcripts/fix2355.output.md | 3 +- unison-src/transcripts/fix2378.output.md | 3 +- unison-src/transcripts/fix2423.output.md | 2 +- unison-src/transcripts/fix2474.output.md | 23 +- unison-src/transcripts/fix2628.output.md | 2 +- unison-src/transcripts/fix2663.output.md | 5 +- unison-src/transcripts/fix2693.output.md | 7 +- unison-src/transcripts/fix2712.output.md | 4 +- unison-src/transcripts/fix2840.output.md | 13 +- unison-src/transcripts/fix2970.output.md | 4 +- unison-src/transcripts/fix3037.output.md | 4 +- unison-src/transcripts/fix3171.output.md | 2 +- unison-src/transcripts/fix3196.output.md | 3 +- unison-src/transcripts/fix3215.output.md | 2 +- unison-src/transcripts/fix3244.output.md | 2 +- unison-src/transcripts/fix3265.output.md | 15 +- unison-src/transcripts/fix3634.output.md | 2 +- unison-src/transcripts/fix3678.output.md | 3 +- unison-src/transcripts/fix3752.output.md | 2 +- unison-src/transcripts/fix3759.output.md | 5 +- unison-src/transcripts/fix3773.output.md | 3 +- unison-src/transcripts/fix4172.output.md | 5 +- unison-src/transcripts/fix4280.output.md | 2 +- unison-src/transcripts/fix4397.output.md | 2 +- unison-src/transcripts/fix4415.output.md | 3 +- unison-src/transcripts/fix4424.output.md | 4 +- unison-src/transcripts/fix4482.output.md | 4 +- unison-src/transcripts/fix4498.output.md | 2 +- unison-src/transcripts/fix4515.output.md | 4 +- unison-src/transcripts/fix4528.output.md | 2 +- unison-src/transcripts/fix4556.output.md | 4 +- unison-src/transcripts/fix4592.output.md | 2 +- unison-src/transcripts/fix4618.output.md | 4 +- unison-src/transcripts/fix4722.output.md | 5 +- unison-src/transcripts/fix4780.output.md | 2 +- unison-src/transcripts/fix4898.output.md | 2 +- unison-src/transcripts/fix5055.output.md | 2 +- unison-src/transcripts/fix5080.output.md | 2 +- unison-src/transcripts/fix614.output.md | 10 +- unison-src/transcripts/fix689.output.md | 2 +- unison-src/transcripts/fix693.output.md | 11 +- unison-src/transcripts/fix845.output.md | 11 +- unison-src/transcripts/fix849.output.md | 3 +- unison-src/transcripts/fix942.output.md | 8 +- unison-src/transcripts/fix987.output.md | 6 +- unison-src/transcripts/formatter.output.md | 6 +- .../transcripts/fuzzy-options.output.md | 3 +- .../generic-parse-errors.output.md | 18 +- unison-src/transcripts/hello.output.md | 23 +- unison-src/transcripts/help.output.md | 1 + unison-src/transcripts/higher-rank.output.md | 11 +- .../transcripts/input-parse-errors.output.md | 18 +- .../transcripts/io-test-command.output.md | 4 +- unison-src/transcripts/io.output.md | 58 ++-- .../transcripts/keyword-identifiers.output.md | 88 +++--- .../transcripts/kind-inference.output.md | 52 ++-- unison-src/transcripts/lambdacase.output.md | 14 +- .../transcripts/lsp-fold-ranges.output.md | 2 +- .../transcripts/lsp-name-completion.output.md | 3 +- unison-src/transcripts/merge.output.md | 270 +++++++++++------- unison-src/transcripts/move-all.output.md | 8 +- .../transcripts/move-namespace.output.md | 17 +- .../transcripts/name-selection.output.md | 14 +- unison-src/transcripts/names.output.md | 3 +- .../namespace-dependencies.output.md | 2 +- .../transcripts/numbered-args.output.md | 2 +- .../transcripts/old-fold-right.output.md | 2 +- .../pattern-match-coverage.output.md | 127 ++++---- .../pattern-pretty-print-2345.output.md | 3 +- .../transcripts/patternMatchTls.output.md | 4 +- unison-src/transcripts/patterns.output.md | 2 +- unison-src/transcripts/propagate.output.md | 12 +- unison-src/transcripts/records.output.md | 16 +- unison-src/transcripts/reflog.output.md | 5 +- .../release-draft-command.output.md | 2 +- unison-src/transcripts/reset.output.md | 14 +- .../transcripts/resolution-failures.output.md | 10 +- unison-src/transcripts/rsa.output.md | 3 +- unison-src/transcripts/scope-ref.output.md | 3 +- unison-src/transcripts/suffixes.output.md | 12 +- .../sum-type-update-conflicts.output.md | 6 +- .../transcripts/switch-command.output.md | 2 +- .../transcripts/tab-completion.output.md | 8 +- unison-src/transcripts/test-command.output.md | 4 +- .../transcripts/text-literals.output.md | 3 +- .../transcripts/todo-bug-builtins.output.md | 13 +- unison-src/transcripts/todo.output.md | 4 +- .../top-level-exceptions.output.md | 5 +- .../transcript-parser-commands.output.md | 17 +- unison-src/transcripts/type-deps.output.md | 5 +- .../type-modifier-are-optional.output.md | 2 +- .../transcripts/unique-type-churn.output.md | 8 +- .../transcripts/unitnamespace.output.md | 2 +- .../transcripts/universal-cmp.output.md | 5 +- .../transcripts/unsafe-coerce.output.md | 3 +- .../update-ignores-lib-namespace.output.md | 4 +- .../transcripts/update-on-conflict.output.md | 4 +- .../update-suffixifies-properly.output.md | 6 +- ...e-term-aliases-in-different-ways.output.md | 4 +- .../update-term-to-different-type.output.md | 4 +- .../update-term-with-alias.output.md | 4 +- ...with-dependent-to-different-type.output.md | 6 +- .../update-term-with-dependent.output.md | 4 +- unison-src/transcripts/update-term.output.md | 4 +- .../update-test-to-non-test.output.md | 4 +- .../update-test-watch-roundtrip.output.md | 7 +- .../update-type-add-constructor.output.md | 4 +- .../update-type-add-field.output.md | 4 +- .../update-type-add-new-record.output.md | 2 +- .../update-type-add-record-field.output.md | 4 +- .../update-type-constructor-alias.output.md | 4 +- ...elete-constructor-with-dependent.output.md | 6 +- .../update-type-delete-constructor.output.md | 4 +- .../update-type-delete-record-field.output.md | 6 +- .../update-type-missing-constructor.output.md | 4 +- .../update-type-nested-decl-aliases.output.md | 6 +- .../update-type-no-op-record.output.md | 2 +- ...ate-type-stray-constructor-alias.output.md | 4 +- .../update-type-stray-constructor.output.md | 4 +- ...nstructor-into-smart-constructor.output.md | 4 +- ...type-turn-non-record-into-record.output.md | 4 +- .../update-type-with-dependent-term.output.md | 6 +- ...dependent-type-to-different-kind.output.md | 6 +- .../update-type-with-dependent-type.output.md | 4 +- unison-src/transcripts/update-watch.output.md | 2 +- .../transcripts/upgrade-happy-path.output.md | 2 +- .../transcripts/upgrade-sad-path.output.md | 6 +- .../upgrade-suffixifies-properly.output.md | 4 +- .../upgrade-with-old-alias.output.md | 2 +- unison-src/transcripts/view.output.md | 2 +- .../transcripts/watch-expressions.output.md | 6 +- 265 files changed, 1116 insertions(+), 1059 deletions(-) diff --git a/unison-cli-integration/integration-tests/IntegrationTests/transcript.output.md b/unison-cli-integration/integration-tests/IntegrationTests/transcript.output.md index c74133f4b..09def1616 100644 --- a/unison-cli-integration/integration-tests/IntegrationTests/transcript.output.md +++ b/unison-cli-integration/integration-tests/IntegrationTests/transcript.output.md @@ -1,6 +1,6 @@ # Integration test: transcript -```unison +``` unison use .builtin unique type MyBool = MyTrue | MyFalse diff --git a/unison-src/transcripts-manual/docs.to-html.output.md b/unison-src/transcripts-manual/docs.to-html.output.md index 7755e2e2d..e59537da2 100644 --- a/unison-src/transcripts-manual/docs.to-html.output.md +++ b/unison-src/transcripts-manual/docs.to-html.output.md @@ -4,7 +4,7 @@ test-html-docs/main> builtins.mergeio lib.builtins Done. ``` -```unison +``` unison {{A doc directly in the namespace.}} some.ns.direct = 1 diff --git a/unison-src/transcripts-manual/rewrites.output.md b/unison-src/transcripts-manual/rewrites.output.md index d1ab897dc..91d1272ec 100644 --- a/unison-src/transcripts-manual/rewrites.output.md +++ b/unison-src/transcripts-manual/rewrites.output.md @@ -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 = @@ -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 @@ -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 @@ -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 @@ -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 @@ -246,7 +245,7 @@ scratch/main> view foo1 foo2 sameFileEx ``` ## Capture avoidance -```unison +``` unison bar1 = b = "bar" 123 @@ -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 @@ -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 @@ -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 @@ -378,11 +377,11 @@ 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 ==> () ``` diff --git a/unison-src/transcripts-round-trip/main.output.md b/unison-src/transcripts-round-trip/main.output.md index 2ece57588..05d85375e 100644 --- a/unison-src/transcripts-round-trip/main.output.md +++ b/unison-src/transcripts-round-trip/main.output.md @@ -1,6 +1,6 @@ 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 = () ``` @@ -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,7 +766,7 @@ 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. @@ -780,7 +780,7 @@ 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 = () ``` @@ -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,7 +815,7 @@ sloppyDocEval = 1 + 1 ``` }} -``` +```` These are currently all expected to have different hashes on round trip. diff --git a/unison-src/transcripts-using-base/_base.output.md b/unison-src/transcripts-using-base/_base.output.md index ebc131c83..ef2da4b88 100644 --- a/unison-src/transcripts-using-base/_base.output.md +++ b/unison-src/transcripts-using-base/_base.output.md @@ -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 diff --git a/unison-src/transcripts-using-base/binary-encoding-nats.output.md b/unison-src/transcripts-using-base/binary-encoding-nats.output.md index a0602ce7c..5f4b4c889 100644 --- a/unison-src/transcripts-using-base/binary-encoding-nats.output.md +++ b/unison-src/transcripts-using-base/binary-encoding-nats.output.md @@ -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 diff --git a/unison-src/transcripts-using-base/codeops.output.md b/unison-src/transcripts-using-base/codeops.output.md index 4cae121f3..4a4671c53 100644 --- a/unison-src/transcripts-using-base/codeops.output.md +++ b/unison-src/transcripts-using-base/codeops.output.md @@ -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) @@ -241,7 +240,7 @@ scratch/main> add ->{Throw Text} () ``` -```unison +``` unison structural ability Zap where zap : Three Nat Nat Nat @@ -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) @@ -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" diff --git a/unison-src/transcripts-using-base/doc.output.md b/unison-src/transcripts-using-base/doc.output.md index e47d8d073..12a284c07 100644 --- a/unison-src/transcripts-using-base/doc.output.md +++ b/unison-src/transcripts-using-base/doc.output.md @@ -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}}! }} @@ -769,3 +769,4 @@ scratch/main> display doc.guide ``` 🌻 THE END + diff --git a/unison-src/transcripts-using-base/failure-tests.output.md b/unison-src/transcripts-using-base/failure-tests.output.md index 7d33aad45..adbf9bc53 100644 --- a/unison-src/transcripts-using-base/failure-tests.output.md +++ b/unison-src/transcripts-using-base/failure-tests.output.md @@ -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 diff --git a/unison-src/transcripts-using-base/fix2158-1.output.md b/unison-src/transcripts-using-base/fix2158-1.output.md index e8014f284..2099749bc 100644 --- a/unison-src/transcripts-using-base/fix2158-1.output.md +++ b/unison-src/transcripts-using-base/fix2158-1.output.md @@ -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 @@ -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. + diff --git a/unison-src/transcripts-using-base/fix2297.output.md b/unison-src/transcripts-using-base/fix2297.output.md index 575c5a73a..3d8ca7d62 100644 --- a/unison-src/transcripts-using-base/fix2297.output.md +++ b/unison-src/transcripts-using-base/fix2297.output.md @@ -1,7 +1,6 @@ This tests a case where a function was somehow discarding abilities. - -```unison +``` unison structural ability Trivial where trivial : () diff --git a/unison-src/transcripts-using-base/fix2358.output.md b/unison-src/transcripts-using-base/fix2358.output.md index d20a06e16..8c8582c27 100644 --- a/unison-src/transcripts-using-base/fix2358.output.md +++ b/unison-src/transcripts-using-base/fix2358.output.md @@ -1,7 +1,6 @@ - Tests a former error due to bad calling conventions on delay.impl -```unison +``` unison timingApp2 : '{IO, Exception} () timingApp2 _ = printLine "Hello" diff --git a/unison-src/transcripts-using-base/fix3166.output.md b/unison-src/transcripts-using-base/fix3166.output.md index 4787e1767..35e5815f9 100644 --- a/unison-src/transcripts-using-base/fix3166.output.md +++ b/unison-src/transcripts-using-base/fix3166.output.md @@ -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 @@ -62,7 +62,7 @@ increment n = 1 + n [100, 200, 300, 400] ``` -```unison +``` unison structural ability E where eff : () -> () @@ -105,7 +105,7 @@ foo _ = 7 ``` -```unison +``` unison structural ability Over where over : Nat ->{Over} (Nat -> Nat) diff --git a/unison-src/transcripts-using-base/fix3542.output.md b/unison-src/transcripts-using-base/fix3542.output.md index e2d1e7c6a..5d6fe4b53 100644 --- a/unison-src/transcripts-using-base/fix3542.output.md +++ b/unison-src/transcripts-using-base/fix3542.output.md @@ -1,4 +1,4 @@ -```unison +``` unison arrayList v n = do use ImmutableByteArray read8 ma = Scope.bytearrayOf v n diff --git a/unison-src/transcripts-using-base/fix3939.output.md b/unison-src/transcripts-using-base/fix3939.output.md index ca4e6d909..75c0dcbea 100644 --- a/unison-src/transcripts-using-base/fix3939.output.md +++ b/unison-src/transcripts-using-base/fix3939.output.md @@ -1,4 +1,4 @@ -```unison +``` unison {{ A simple doc. }} diff --git a/unison-src/transcripts-using-base/fix4746.output.md b/unison-src/transcripts-using-base/fix4746.output.md index fd158585e..62f7632c0 100644 --- a/unison-src/transcripts-using-base/fix4746.output.md +++ b/unison-src/transcripts-using-base/fix4746.output.md @@ -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} () diff --git a/unison-src/transcripts-using-base/fix5129.output.md b/unison-src/transcripts-using-base/fix5129.output.md index af189d5a8..90f205bd4 100644 --- a/unison-src/transcripts-using-base/fix5129.output.md +++ b/unison-src/transcripts-using-base/fix5129.output.md @@ -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 [] -> () @@ -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) diff --git a/unison-src/transcripts-using-base/hashing.output.md b/unison-src/transcripts-using-base/hashing.output.md index e5d1be279..721c1ec3c 100644 --- a/unison-src/transcripts-using-base/hashing.output.md +++ b/unison-src/transcripts-using-base/hashing.output.md @@ -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 @@ -155,7 +155,7 @@ 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") ``` @@ -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 = @@ -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 = @@ -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 = diff --git a/unison-src/transcripts-using-base/mvar.output.md b/unison-src/transcripts-using-base/mvar.output.md index 7d92d90c5..466291ead 100644 --- a/unison-src/transcripts-using-base/mvar.output.md +++ b/unison-src/transcripts-using-base/mvar.output.md @@ -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 diff --git a/unison-src/transcripts-using-base/nat-coersion.output.md b/unison-src/transcripts-using-base/nat-coersion.output.md index d4aaf5ef6..dac858429 100644 --- a/unison-src/transcripts-using-base/nat-coersion.output.md +++ b/unison-src/transcripts-using-base/nat-coersion.output.md @@ -1,4 +1,4 @@ -```unison +``` unison testNat: Nat -> Optional Int -> Optional Float -> {Stream Result}() testNat n expectInt expectFloat = float = Float.fromRepresentation n diff --git a/unison-src/transcripts-using-base/net.output.md b/unison-src/transcripts-using-base/net.output.md index cae095824..702be91bb 100644 --- a/unison-src/transcripts-using-base/net.output.md +++ b/unison-src/transcripts-using-base/net.output.md @@ -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 @@ -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}() diff --git a/unison-src/transcripts-using-base/random-deserial.output.md b/unison-src/transcripts-using-base/random-deserial.output.md index 2606511ba..66d6354d5 100644 --- a/unison-src/transcripts-using-base/random-deserial.output.md +++ b/unison-src/transcripts-using-base/random-deserial.output.md @@ -1,4 +1,4 @@ -```unison +``` unison directory = "unison-src/transcripts-using-base/serialized-cases/" availableCases : '{IO,Exception} [Text] diff --git a/unison-src/transcripts-using-base/ref-promise.output.md b/unison-src/transcripts-using-base/ref-promise.output.md index 9f4c700b1..bcc4487c3 100644 --- a/unison-src/transcripts-using-base/ref-promise.output.md +++ b/unison-src/transcripts-using-base/ref-promise.output.md @@ -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 @@ -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 @@ -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 @@ -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 @@ -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 diff --git a/unison-src/transcripts-using-base/serial-test-00.output.md b/unison-src/transcripts-using-base/serial-test-00.output.md index 88a18a705..019289ccd 100644 --- a/unison-src/transcripts-using-base/serial-test-00.output.md +++ b/unison-src/transcripts-using-base/serial-test-00.output.md @@ -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 diff --git a/unison-src/transcripts-using-base/serial-test-01.output.md b/unison-src/transcripts-using-base/serial-test-01.output.md index 5825b36ff..a1a9668c1 100644 --- a/unison-src/transcripts-using-base/serial-test-01.output.md +++ b/unison-src/transcripts-using-base/serial-test-01.output.md @@ -1,4 +1,4 @@ -```unison +``` unison l1 = [1.0,2.0,3.0] l2 = [+1,+2,+3] l3 = [?a, ?b, ?c] diff --git a/unison-src/transcripts-using-base/serial-test-02.output.md b/unison-src/transcripts-using-base/serial-test-02.output.md index ecbe82ebe..3a352b88b 100644 --- a/unison-src/transcripts-using-base/serial-test-02.output.md +++ b/unison-src/transcripts-using-base/serial-test-02.output.md @@ -1,4 +1,4 @@ -```unison +``` unison structural ability Exit a where exit : a -> b diff --git a/unison-src/transcripts-using-base/serial-test-03.output.md b/unison-src/transcripts-using-base/serial-test-03.output.md index f21afcbbb..a1ca50f90 100644 --- a/unison-src/transcripts-using-base/serial-test-03.output.md +++ b/unison-src/transcripts-using-base/serial-test-03.output.md @@ -1,4 +1,4 @@ -```unison +``` unison structural ability DC r where shift : ((a -> r) -> r) -> a diff --git a/unison-src/transcripts-using-base/serial-test-04.output.md b/unison-src/transcripts-using-base/serial-test-04.output.md index 044eabd26..0b0b6230e 100644 --- a/unison-src/transcripts-using-base/serial-test-04.output.md +++ b/unison-src/transcripts-using-base/serial-test-04.output.md @@ -1,4 +1,4 @@ -```unison +``` unison mutual0 = cases 0 -> "okay" n -> diff --git a/unison-src/transcripts-using-base/stm.output.md b/unison-src/transcripts-using-base/stm.output.md index f54199f8e..fd8fb9728 100644 --- a/unison-src/transcripts-using-base/stm.output.md +++ b/unison-src/transcripts-using-base/stm.output.md @@ -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 -> () @@ -56,7 +57,7 @@ scratch/main> add ``` Test case. -```unison +``` unison spawn : Nat ->{io2.IO} Result spawn k = let out1 = TVar.newIO None diff --git a/unison-src/transcripts-using-base/test-watch-dependencies.output.md b/unison-src/transcripts-using-base/test-watch-dependencies.output.md index 7b71b244b..b38e4373a 100644 --- a/unison-src/transcripts-using-base/test-watch-dependencies.output.md +++ b/unison-src/transcripts-using-base/test-watch-dependencies.output.md @@ -4,13 +4,13 @@ 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] ``` @@ -54,9 +54,9 @@ scratch/main> add Tip: Use `help filestatus` to learn more. ``` ---- +----- -```unison +``` unison y = 42 test> useY = checks [y + 1 == 43] ``` diff --git a/unison-src/transcripts-using-base/thread.output.md b/unison-src/transcripts-using-base/thread.output.md index 6fe4e8800..bab82e7eb 100644 --- a/unison-src/transcripts-using-base/thread.output.md +++ b/unison-src/transcripts-using-base/thread.output.md @@ -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" () @@ -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 @@ -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 diff --git a/unison-src/transcripts-using-base/tls.output.md b/unison-src/transcripts-using-base/tls.output.md index a584bdfa9..fc0362d8c 100644 --- a/unison-src/transcripts-using-base/tls.output.md +++ b/unison-src/transcripts-using-base/tls.output.md @@ -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"] @@ -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}() diff --git a/unison-src/transcripts-using-base/utf8.output.md b/unison-src/transcripts-using-base/utf8.output.md index c06522211..0cd3d4c0d 100644 --- a/unison-src/transcripts-using-base/utf8.output.md +++ b/unison-src/transcripts-using-base/utf8.output.md @@ -1,4 +1,4 @@ -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. @@ -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" @@ -44,7 +44,7 @@ ascii = "ABCDE" ``` non-ascii characters are encoded as multiple bytes. -```unison +``` unison greek: Text greek = "ΑΒΓΔΕ" @@ -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 @@ -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] diff --git a/unison-src/transcripts/abilities.output.md b/unison-src/transcripts/abilities.output.md index 8fd69ddbc..52428c98f 100644 --- a/unison-src/transcripts/abilities.output.md +++ b/unison-src/transcripts/abilities.output.md @@ -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 diff --git a/unison-src/transcripts/ability-order-doesnt-affect-hash.output.md b/unison-src/transcripts/ability-order-doesnt-affect-hash.output.md index 6f6eac30e..7b98c2065 100644 --- a/unison-src/transcripts/ability-order-doesnt-affect-hash.output.md +++ b/unison-src/transcripts/ability-order-doesnt-affect-hash.output.md @@ -1,6 +1,6 @@ The order of a set of abilities is normalized before hashing. -```unison +``` unison unique ability Foo where foo : () diff --git a/unison-src/transcripts/ability-term-conflicts-on-update.output.md b/unison-src/transcripts/ability-term-conflicts-on-update.output.md index 7ea11e01c..a9bba9dbf 100644 --- a/unison-src/transcripts/ability-term-conflicts-on-update.output.md +++ b/unison-src/transcripts/ability-term-conflicts-on-update.output.md @@ -5,7 +5,7 @@ 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} () ``` @@ -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} () @@ -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} () @@ -165,7 +165,7 @@ scratch/main> update.old ``` # Constructor-term conflict -```unison +``` unison X.x = 1 ``` @@ -190,7 +190,7 @@ scratch/main2> add X.x : Nat ``` -```unison +``` unison structural ability X where x : () ``` diff --git a/unison-src/transcripts/add-run.output.md b/unison-src/transcripts/add-run.output.md index 53cc27b94..c1802922f 100644 --- a/unison-src/transcripts/add-run.output.md +++ b/unison-src/transcripts/add-run.output.md @@ -2,7 +2,7 @@ ## Basic usage -```unison +``` unison even : Nat -> Boolean even x = if x == 0 then true else odd (drop x 1) @@ -47,6 +47,7 @@ scratch/main> run is2even ``` it errors if the desired result name conflicts with a name in the unison file + ```ucm scratch/main> add.run is2even @@ -57,6 +58,7 @@ scratch/main> add.run is2even ``` otherwise, the result is successfully persisted + ```ucm scratch/main> add.run foo.bar.baz @@ -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 @@ -115,7 +117,7 @@ scratch/main> add.run result ``` ## It resolves references within the codebase -```unison +``` unison inc : Nat -> Nat inc x = x + 1 ``` @@ -141,7 +143,7 @@ scratch/main> add inc inc : Nat -> Nat ``` -```unison +``` unison main : '(Nat -> Nat) main _ x = inc x ``` @@ -178,7 +180,7 @@ scratch/main> view natfoo ``` ## It captures scratch file dependencies at run time -```unison +``` unison x = 1 y = x + x main = 'y @@ -205,7 +207,7 @@ scratch/main> run main 2 ``` -```unison +``` unison x = 50 ``` @@ -223,6 +225,7 @@ x = 50 ``` this saves 2 to xres, rather than 100 + ```ucm scratch/main> add.run xres @@ -238,7 +241,7 @@ scratch/main> view xres ``` ## It fails with a message if add cannot complete cleanly -```unison +``` unison main = '5 ``` @@ -272,7 +275,7 @@ scratch/main> add.run xres ``` ## It works with absolute names -```unison +``` unison main = '5 ``` diff --git a/unison-src/transcripts/add-test-watch-roundtrip.output.md b/unison-src/transcripts/add-test-watch-roundtrip.output.md index 114d9399f..e276eba24 100644 --- a/unison-src/transcripts/add-test-watch-roundtrip.output.md +++ b/unison-src/transcripts/add-test-watch-roundtrip.output.md @@ -1,9 +1,9 @@ -```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 scratch/main> add diff --git a/unison-src/transcripts/addupdatemessages.output.md b/unison-src/transcripts/addupdatemessages.output.md index ffd7bbd80..813639f58 100644 --- a/unison-src/transcripts/addupdatemessages.output.md +++ b/unison-src/transcripts/addupdatemessages.output.md @@ -2,7 +2,7 @@ Let's set up some definitions to start: -```unison +``` unison x = 1 y = 2 @@ -41,7 +41,7 @@ scratch/main> add ``` Let's add an alias for `1` and `One`: -```unison +``` unison z = 1 structural type Z = One Nat @@ -79,7 +79,7 @@ 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 ``` @@ -118,7 +118,7 @@ scratch/main> update ``` Update it to something that already exists with a different name: -```unison +``` unison x = 2 structural type X = Two Nat Nat ``` diff --git a/unison-src/transcripts/alias-many.output.md b/unison-src/transcripts/alias-many.output.md index b12422e09..942539b62 100644 --- a/unison-src/transcripts/alias-many.output.md +++ b/unison-src/transcripts/alias-many.output.md @@ -1,17 +1,14 @@ 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 [relative2...] ` 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 [relative2...] ` 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 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 @@ -62,4 +59,5 @@ scratch/main> find-in mylib ``` -Thanks, `alias.many! +Thanks, `alias.many`\! + diff --git a/unison-src/transcripts/anf-tests.output.md b/unison-src/transcripts/anf-tests.output.md index b9360ee4c..b1dc2f599 100644 --- a/unison-src/transcripts/anf-tests.output.md +++ b/unison-src/transcripts/anf-tests.output.md @@ -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 = () diff --git a/unison-src/transcripts/any-extract.output.md b/unison-src/transcripts/any-extract.output.md index c8fc99095..8f3488cb4 100644 --- a/unison-src/transcripts/any-extract.output.md +++ b/unison-src/transcripts/any-extract.output.md @@ -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), diff --git a/unison-src/transcripts/api-doc-rendering.output.md b/unison-src/transcripts/api-doc-rendering.output.md index f767c14cf..8afef59e8 100644 --- a/unison-src/transcripts/api-doc-rendering.output.md +++ b/unison-src/transcripts/api-doc-rendering.output.md @@ -1,6 +1,6 @@ # Doc rendering -```unison +``` unison structural type Maybe a = Nothing | Just a otherTerm = "text" diff --git a/unison-src/transcripts/api-find.output.md b/unison-src/transcripts/api-find.output.md index d44200e7a..aecfe603a 100644 --- a/unison-src/transcripts/api-find.output.md +++ b/unison-src/transcripts/api-find.output.md @@ -1,6 +1,6 @@ # find api -```unison +``` unison rachel.filesystem.x = 42 ross.httpClient.y = 43 joey.httpServer.z = 44 diff --git a/unison-src/transcripts/api-getDefinition.output.md b/unison-src/transcripts/api-getDefinition.output.md index 5e854a440..bf244e4a0 100644 --- a/unison-src/transcripts/api-getDefinition.output.md +++ b/unison-src/transcripts/api-getDefinition.output.md @@ -1,6 +1,6 @@ # Get Definitions Test -```unison +``` unison nested.names.x.doc = {{ Documentation }} nested.names.x = 42 ``` @@ -205,7 +205,7 @@ 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 }} diff --git a/unison-src/transcripts/api-namespace-details.output.md b/unison-src/transcripts/api-namespace-details.output.md index 0cdf2e88b..593efac4f 100644 --- a/unison-src/transcripts/api-namespace-details.output.md +++ b/unison-src/transcripts/api-namespace-details.output.md @@ -1,6 +1,6 @@ # Namespace Details Test -```unison +``` unison {{ Documentation }} nested.names.x = 42 diff --git a/unison-src/transcripts/api-namespace-list.output.md b/unison-src/transcripts/api-namespace-list.output.md index 4219aa191..6116dad61 100644 --- a/unison-src/transcripts/api-namespace-list.output.md +++ b/unison-src/transcripts/api-namespace-list.output.md @@ -1,6 +1,6 @@ # Namespace list api -```unison +``` unison {{ Documentation }} nested.names.x = 42 diff --git a/unison-src/transcripts/api-summaries.output.md b/unison-src/transcripts/api-summaries.output.md index e9f93e624..de7e14c3a 100644 --- a/unison-src/transcripts/api-summaries.output.md +++ b/unison-src/transcripts/api-summaries.output.md @@ -1,6 +1,6 @@ # Definition Summary APIs -```unison +``` unison nat : Nat nat = 42 doc : Doc2 diff --git a/unison-src/transcripts/block-on-required-update.output.md b/unison-src/transcripts/block-on-required-update.output.md index 0935b7317..49e133246 100644 --- a/unison-src/transcripts/block-on-required-update.output.md +++ b/unison-src/transcripts/block-on-required-update.output.md @@ -2,7 +2,7 @@ Should block an `add` if it requires an update on an in-file dependency. -```unison +``` unison x = 1 ``` @@ -29,7 +29,7 @@ scratch/main> add ``` Update `x`, and add a new `y` which depends on the update -```unison +``` unison x = 10 y = x + 1 ``` diff --git a/unison-src/transcripts/blocks.output.md b/unison-src/transcripts/blocks.output.md index 687ca9806..b017e0cfc 100644 --- a/unison-src/transcripts/blocks.output.md +++ b/unison-src/transcripts/blocks.output.md @@ -4,7 +4,7 @@ For example: -```unison +``` unison ex thing = thing y = y -- refers to `thing` in this block @@ -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 @@ -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 = @@ -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 @@ -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 = @@ -174,7 +174,7 @@ 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 @@ -198,7 +198,7 @@ Since the forward reference to `pong` appears inside `ping`. This, however, will not compile: -```unison +``` unison ex n = pong = ping + 1 ping = 42 @@ -217,7 +217,7 @@ ex n = ``` This also won't compile; it's a cyclic reference that isn't guarded: -```unison +``` unison ex n = loop = loop loop @@ -234,7 +234,7 @@ 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 @@ -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 @@ -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 @@ -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 @@ -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 diff --git a/unison-src/transcripts/boolean-op-pretty-print-2819.output.md b/unison-src/transcripts/boolean-op-pretty-print-2819.output.md index 48fbfecf6..7fe8f92cf 100644 --- a/unison-src/transcripts/boolean-op-pretty-print-2819.output.md +++ b/unison-src/transcripts/boolean-op-pretty-print-2819.output.md @@ -1,6 +1,6 @@ Regression test for https://github.com/unisonweb/unison/pull/2819 -```unison +``` unison hangExample : Boolean hangExample = ("a long piece of text to hang the line" == "") diff --git a/unison-src/transcripts/branch-command.output.md b/unison-src/transcripts/branch-command.output.md index 28dd680d5..569ab5d76 100644 --- a/unison-src/transcripts/branch-command.output.md +++ b/unison-src/transcripts/branch-command.output.md @@ -2,7 +2,7 @@ The `branch` command creates a new branch. First, we'll create a term to include in the branches. -```unison +``` unison someterm = 18 ``` diff --git a/unison-src/transcripts/branch-relative-path.output.md b/unison-src/transcripts/branch-relative-path.output.md index 4f2be5861..591fa64f8 100644 --- a/unison-src/transcripts/branch-relative-path.output.md +++ b/unison-src/transcripts/branch-relative-path.output.md @@ -1,4 +1,4 @@ -```unison +``` unison foo = 5 foo.bar = 1 ``` @@ -26,7 +26,7 @@ p0/main> add foo.bar : ##Nat ``` -```unison +``` unison bonk = 5 donk.bonk = 1 ``` diff --git a/unison-src/transcripts/bug-fix-4354.output.md b/unison-src/transcripts/bug-fix-4354.output.md index ca99d870d..8ef9e7370 100644 --- a/unison-src/transcripts/bug-fix-4354.output.md +++ b/unison-src/transcripts/bug-fix-4354.output.md @@ -1,4 +1,4 @@ -```unison +``` unison bonk : forall a. a -> a bonk x = zonk : forall a. a -> a diff --git a/unison-src/transcripts/bug-strange-closure.output.md b/unison-src/transcripts/bug-strange-closure.output.md index 8b9f7fa75..91f7ce998 100644 --- a/unison-src/transcripts/bug-strange-closure.output.md +++ b/unison-src/transcripts/bug-strange-closure.output.md @@ -1,4 +1,3 @@ - We can display the guide before and after adding it to the codebase: ```ucm @@ -414,7 +413,7 @@ 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) ``` @@ -845,7 +844,7 @@ 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 diff --git a/unison-src/transcripts/builtins.output.md b/unison-src/transcripts/builtins.output.md index 4f8967ae0..5ddc4b765 100644 --- a/unison-src/transcripts/builtins.output.md +++ b/unison-src/transcripts/builtins.output.md @@ -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,7 +356,7 @@ test> checks [ ## `Any` functions -```unison +``` unison > [Any "hi", Any (41 + 1)] test> Any.test1 = checks [(Any "hi" == Any "hi")] @@ -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 @@ -453,7 +455,7 @@ openFile] ✅ Passed Passed ``` -```unison +``` unison openFilesIO = do checks [ not (validateSandboxedSimpl [] (value openFile)) @@ -501,7 +503,7 @@ 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]] ``` diff --git a/unison-src/transcripts/bytesFromList.output.md b/unison-src/transcripts/bytesFromList.output.md index 7d28cfc07..099a73cb5 100644 --- a/unison-src/transcripts/bytesFromList.output.md +++ b/unison-src/transcripts/bytesFromList.output.md @@ -1,7 +1,6 @@ - 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] ``` diff --git a/unison-src/transcripts/check763.output.md b/unison-src/transcripts/check763.output.md index fe50b6834..0d5dcc0ba 100644 --- a/unison-src/transcripts/check763.output.md +++ b/unison-src/transcripts/check763.output.md @@ -1,6 +1,6 @@ Regression test for https://github.com/unisonweb/unison/issues/763 -```unison +``` unison (+-+) : Nat -> Nat -> Nat (+-+) x y = x * y ``` diff --git a/unison-src/transcripts/check873.output.md b/unison-src/transcripts/check873.output.md index 5f21cec20..cc952acca 100644 --- a/unison-src/transcripts/check873.output.md +++ b/unison-src/transcripts/check873.output.md @@ -1,6 +1,6 @@ See [this ticket](https://github.com/unisonweb/unison/issues/873); the point being, this shouldn't crash the runtime. :) -```unison +``` unison (-) = builtin.Nat.sub ``` @@ -25,7 +25,7 @@ scratch/main> add - : Nat -> Nat -> Int ``` -```unison +``` unison baz x = x - 1 ``` diff --git a/unison-src/transcripts/constructor-applied-to-unit.output.md b/unison-src/transcripts/constructor-applied-to-unit.output.md index 4acfdcd86..04cc3c417 100644 --- a/unison-src/transcripts/constructor-applied-to-unit.output.md +++ b/unison-src/transcripts/constructor-applied-to-unit.output.md @@ -1,4 +1,4 @@ -```unison +``` unison structural type Zoink a b c = Zoink a b c > Any () diff --git a/unison-src/transcripts/contrabilities.output.md b/unison-src/transcripts/contrabilities.output.md index d8c725660..f3b76a8c5 100644 --- a/unison-src/transcripts/contrabilities.output.md +++ b/unison-src/transcripts/contrabilities.output.md @@ -1,4 +1,4 @@ -```unison +``` unison f : (() -> a) -> Nat f x = 42 ``` diff --git a/unison-src/transcripts/cycle-update-1.output.md b/unison-src/transcripts/cycle-update-1.output.md index 25cd6f398..3cfeca6fc 100644 --- a/unison-src/transcripts/cycle-update-1.output.md +++ b/unison-src/transcripts/cycle-update-1.output.md @@ -1,6 +1,6 @@ Update a member of a cycle, but retain the cycle. -```unison +``` unison ping : 'Nat ping _ = !pong + 1 @@ -31,7 +31,7 @@ scratch/main> add pong : 'Nat ``` -```unison +``` unison ping : 'Nat ping _ = !pong + 3 ``` diff --git a/unison-src/transcripts/cycle-update-2.output.md b/unison-src/transcripts/cycle-update-2.output.md index 89e740faa..11b97f14d 100644 --- a/unison-src/transcripts/cycle-update-2.output.md +++ b/unison-src/transcripts/cycle-update-2.output.md @@ -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 @@ -31,7 +31,7 @@ scratch/main> add pong : 'Nat ``` -```unison +``` unison ping : 'Nat ping _ = 3 ``` diff --git a/unison-src/transcripts/cycle-update-3.output.md b/unison-src/transcripts/cycle-update-3.output.md index f21e3fe9d..cf8c1c72c 100644 --- a/unison-src/transcripts/cycle-update-3.output.md +++ b/unison-src/transcripts/cycle-update-3.output.md @@ -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 @@ -31,7 +31,7 @@ scratch/main> add pong : 'Nat ``` -```unison +``` unison ping : Nat ping = 3 ``` diff --git a/unison-src/transcripts/cycle-update-4.output.md b/unison-src/transcripts/cycle-update-4.output.md index 0eb134f0f..c3bcccbd1 100644 --- a/unison-src/transcripts/cycle-update-4.output.md +++ b/unison-src/transcripts/cycle-update-4.output.md @@ -1,6 +1,6 @@ `update` properly discovers and establishes new cycles. -```unison +``` unison ping : 'Nat ping _ = 1 @@ -31,7 +31,7 @@ scratch/main> add pong : 'Nat ``` -```unison +``` unison ping : 'Nat ping _ = !clang + 1 diff --git a/unison-src/transcripts/cycle-update-5.output.md b/unison-src/transcripts/cycle-update-5.output.md index b6c1a0717..a022fbed6 100644 --- a/unison-src/transcripts/cycle-update-5.output.md +++ b/unison-src/transcripts/cycle-update-5.output.md @@ -1,6 +1,6 @@ Not yet working: properly updating nameless implicit terms. -```unison +``` unison inner.ping : 'Nat inner.ping _ = !pong + 1 @@ -34,7 +34,7 @@ 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 ``` @@ -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`). + diff --git a/unison-src/transcripts/debug-definitions.output.md b/unison-src/transcripts/debug-definitions.output.md index 37d6591e2..8689d2d78 100644 --- a/unison-src/transcripts/debug-definitions.output.md +++ b/unison-src/transcripts/debug-definitions.output.md @@ -1,4 +1,4 @@ -```unison +``` unison x = 30 y : Nat diff --git a/unison-src/transcripts/debug-name-diffs.output.md b/unison-src/transcripts/debug-name-diffs.output.md index 9d15bfe47..0333dee6b 100644 --- a/unison-src/transcripts/debug-name-diffs.output.md +++ b/unison-src/transcripts/debug-name-diffs.output.md @@ -1,4 +1,4 @@ -```unison +``` unison a.b.one = 1 a.two = 2 diff --git a/unison-src/transcripts/deep-names.output.md b/unison-src/transcripts/deep-names.output.md index 833ae613a..dcaf16dbe 100644 --- a/unison-src/transcripts/deep-names.output.md +++ b/unison-src/transcripts/deep-names.output.md @@ -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,6 +13,7 @@ http.z = 8 ``` Our `app1` project includes the text library twice and the http library twice as direct dependencies. + ```ucm scratch/app1> fork text lib.text_v1 @@ -39,6 +41,7 @@ scratch/app1> delete.namespace http ``` As such, we see two copies of `a` and two copies of `x` via these direct dependencies. + ```ucm scratch/app1> names a @@ -59,6 +62,7 @@ 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 scratch/app2> fork http lib.http_v1 @@ -91,6 +95,7 @@ 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 scratch/app2> names a diff --git a/unison-src/transcripts/definition-diff-api.output.md b/unison-src/transcripts/definition-diff-api.output.md index 192367ff9..460e84d80 100644 --- a/unison-src/transcripts/definition-diff-api.output.md +++ b/unison-src/transcripts/definition-diff-api.output.md @@ -4,7 +4,7 @@ diffs/main> builtins.merge Done. ``` -```unison +``` unison term = _ = "Here's some text" 1 + 1 @@ -42,7 +42,7 @@ diffs/main> branch.create new `switch /main` then `merge /new`. ``` -```unison +``` unison term = _ = "Here's some different text" 1 + 2 diff --git a/unison-src/transcripts/delete-namespace-dependents-check.output.md b/unison-src/transcripts/delete-namespace-dependents-check.output.md index 4ab652409..ce131fcb7 100644 --- a/unison-src/transcripts/delete-namespace-dependents-check.output.md +++ b/unison-src/transcripts/delete-namespace-dependents-check.output.md @@ -2,9 +2,9 @@ # 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 diff --git a/unison-src/transcripts/delete-namespace.output.md b/unison-src/transcripts/delete-namespace.output.md index 563b98ad2..a57094d9e 100644 --- a/unison-src/transcripts/delete-namespace.output.md +++ b/unison-src/transcripts/delete-namespace.output.md @@ -1,6 +1,6 @@ # delete.namespace.force -```unison +``` unison no_dependencies.thing = "no dependents on this term" dependencies.term1 = 1 diff --git a/unison-src/transcripts/delete-silent.output.md b/unison-src/transcripts/delete-silent.output.md index 3ec5397fc..899a38b3b 100644 --- a/unison-src/transcripts/delete-silent.output.md +++ b/unison-src/transcripts/delete-silent.output.md @@ -7,7 +7,7 @@ scratch/main> delete foo foo ``` -```unison +``` unison foo = 1 structural type Foo = Foo () ``` diff --git a/unison-src/transcripts/delete.output.md b/unison-src/transcripts/delete.output.md index 14ca930fe..853f2ee38 100644 --- a/unison-src/transcripts/delete.output.md +++ b/unison-src/transcripts/delete.output.md @@ -17,7 +17,7 @@ exist. Now for some easy cases. Deleting an unambiguous term, then deleting an unambiguous type. -```unison +``` unison foo = 1 structural type Foo = Foo () ``` @@ -57,7 +57,7 @@ structural type Foo = Foo () ``` How about an ambiguous term? -```unison +``` unison foo = 1 bar = 2 ``` @@ -101,7 +101,7 @@ 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 ``` @@ -144,7 +144,7 @@ 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 () ``` @@ -169,7 +169,7 @@ structural type foo = Foo () ``` We want to be able to delete multiple terms at once -```unison +``` unison a = "a" b = "b" c = "c" @@ -197,7 +197,7 @@ c = "c" ``` We can delete terms and types in the same invocation of delete -```unison +``` unison structural type Foo = Foo () a = "a" b = "b" @@ -238,7 +238,7 @@ c = "c" ``` We can delete a type and its constructors -```unison +``` unison structural type Foo = Foo () ``` @@ -266,7 +266,7 @@ 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 @@ -299,7 +299,7 @@ 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 @@ -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 @@ -359,7 +359,7 @@ 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 @@ -386,7 +386,7 @@ 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 ``` diff --git a/unison-src/transcripts/dependents-dependencies-debugfile.output.md b/unison-src/transcripts/dependents-dependencies-debugfile.output.md index 90f3fefbc..19b2526d7 100644 --- a/unison-src/transcripts/dependents-dependencies-debugfile.output.md +++ b/unison-src/transcripts/dependents-dependencies-debugfile.output.md @@ -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 @@ -30,7 +32,9 @@ 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 scratch/main> add @@ -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. + diff --git a/unison-src/transcripts/destructuring-binds.output.md b/unison-src/transcripts/destructuring-binds.output.md index 4185a71b9..ec7f39182 100644 --- a/unison-src/transcripts/destructuring-binds.output.md +++ b/unison-src/transcripts/destructuring-binds.output.md @@ -2,7 +2,7 @@ Here's a couple examples: -```unison +``` unison ex0 : Nat -> Nat ex0 n = (a, _, (c,d)) = ("uno", "dos", (n, 7)) @@ -52,7 +52,7 @@ 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 @@ -76,7 +76,7 @@ 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" @@ -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" @@ -155,7 +155,7 @@ 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 ``` diff --git a/unison-src/transcripts/diff-namespace.output.md b/unison-src/transcripts/diff-namespace.output.md index 490fb3fa2..2c327bc83 100644 --- a/unison-src/transcripts/diff-namespace.output.md +++ b/unison-src/transcripts/diff-namespace.output.md @@ -1,4 +1,4 @@ -```unison +``` unison b1.x = 23 b1.fslkdjflskdjflksjdf = 663 b2.x = 23 @@ -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 @@ -122,7 +122,7 @@ Here's what we've done so far: The namespaces are identical. ``` -```unison +``` unison junk = "asldkfjasldkfj" ``` @@ -142,7 +142,7 @@ junk = "asldkfjasldkfj" Done. ``` -```unison +``` unison fromJust = 99 b = "oog" d = 4 @@ -283,7 +283,7 @@ unique type Y a b = Y a b 3. fromJust' ┘ 4. fromJust' (removed) ``` -```unison +``` unison bdependent = "banana" ``` @@ -316,7 +316,7 @@ 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 ``` @@ -340,7 +340,7 @@ b = a + 1 Done. ``` -```unison +``` unison a = 444 ``` @@ -352,7 +352,7 @@ a = 444 a : ##Nat ``` -```unison +``` unison a = 555 ``` @@ -412,7 +412,7 @@ a = 555 ``` ## Should be able to diff a namespace hash from history. -```unison +``` unison x = 1 ``` @@ -439,7 +439,7 @@ x = 1 x : ##Nat ``` -```unison +``` unison y = 2 ``` @@ -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? + diff --git a/unison-src/transcripts/doc-formatting.output.md b/unison-src/transcripts/doc-formatting.output.md index b472f9177..a99d2ca4b 100644 --- a/unison-src/transcripts/doc-formatting.output.md +++ b/unison-src/transcripts/doc-formatting.output.md @@ -2,7 +2,7 @@ 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 :] @@ -34,7 +34,7 @@ scratch/main> view foo ``` Note that `@` and `:]` must be escaped within docs. -```unison +``` unison escaping = [: Docs look [: like \@this \:] :] ``` @@ -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: @@ -98,7 +98,7 @@ 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. @@ -125,7 +125,7 @@ scratch/main> view doc1 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). @@ -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.) @@ -215,7 +215,7 @@ scratch/main> view doc3 :] ``` -```unison +``` unison doc4 = [: Here's another example of some paragraphs. All these lines have zero indent. @@ -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 @@ -281,7 +281,7 @@ scratch/main> view doc5 and the rest. :] ``` -```unison +``` unison -- You can do the following to avoid that problem. doc6 = [: - foo @@ -316,7 +316,7 @@ scratch/main> view doc6 ``` ### More testing -```unison +``` unison -- Check empty doc works. empty = [::] @@ -344,7 +344,7 @@ scratch/main> view empty 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.) @@ -460,7 +460,7 @@ 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 :] @@ -486,7 +486,7 @@ scratch/main> view reg1363 reg1363 = [: `@List.take foo` bar baz :] ``` -```unison +``` unison -- Demonstrate doc display when whitespace follows a @[source] or @[evaluate] -- whose output spans multiple lines. @@ -510,6 +510,7 @@ test2 = [: ``` View is fine. + ```ucm scratch/main> view test2 @@ -521,6 +522,7 @@ 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 scratch/main> display test2 diff --git a/unison-src/transcripts/doc-type-link-keywords.output.md b/unison-src/transcripts/doc-type-link-keywords.output.md index ed7b0b7b7..3229bed19 100644 --- a/unison-src/transcripts/doc-type-link-keywords.output.md +++ b/unison-src/transcripts/doc-type-link-keywords.output.md @@ -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 = () diff --git a/unison-src/transcripts/doc1.output.md b/unison-src/transcripts/doc1.output.md index 563932e2b..bd5b5b255 100644 --- a/unison-src/transcripts/doc1.output.md +++ b/unison-src/transcripts/doc1.output.md @@ -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. @@ -43,17 +43,17 @@ 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] ``` @@ -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.) diff --git a/unison-src/transcripts/doc2.output.md b/unison-src/transcripts/doc2.output.md index 7cb162400..0d09b5618 100644 --- a/unison-src/transcripts/doc2.output.md +++ b/unison-src/transcripts/doc2.output.md @@ -1,6 +1,6 @@ # Test parsing and round-trip of doc2 syntax elements -```unison +``` unison otherDoc : a -> Doc2 otherDoc _ = {{ yo }} @@ -113,7 +113,7 @@ Format it to check that everything pretty-prints in a valid way. scratch/main> debug.format ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u otherDoc : a -> Doc2 otherDoc _ = {{ yo }} diff --git a/unison-src/transcripts/doc2markdown.output.md b/unison-src/transcripts/doc2markdown.output.md index 5475c1cbf..e670bff8c 100644 --- a/unison-src/transcripts/doc2markdown.output.md +++ b/unison-src/transcripts/doc2markdown.output.md @@ -1,4 +1,4 @@ -```unison +``` unison otherDoc : a -> Doc2 otherDoc _ = {{ yo }} @@ -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 diff --git a/unison-src/transcripts/dont-upgrade-refs-that-exist-in-old.output.md b/unison-src/transcripts/dont-upgrade-refs-that-exist-in-old.output.md index a256f4e45..5bbf2fb0b 100644 --- a/unison-src/transcripts/dont-upgrade-refs-that-exist-in-old.output.md +++ b/unison-src/transcripts/dont-upgrade-refs-that-exist-in-old.output.md @@ -1,7 +1,7 @@ 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 diff --git a/unison-src/transcripts/duplicate-names.output.md b/unison-src/transcripts/duplicate-names.output.md index 9a15abbb7..a9d9f2ad0 100644 --- a/unison-src/transcripts/duplicate-names.output.md +++ b/unison-src/transcripts/duplicate-names.output.md @@ -2,7 +2,7 @@ Term and ability constructor collisions should cause a parse error. -```unison +``` unison structural ability Stream where send : a -> () @@ -26,7 +26,7 @@ Stream.send _ = () ``` Term and type constructor collisions should cause a parse error. -```unison +``` unison structural type X = x X.x : a -> () @@ -49,7 +49,7 @@ X.x _ = () ``` Ability and type constructor collisions should cause a parse error. -```unison +``` unison structural type X = x structural ability X where x : () @@ -69,7 +69,7 @@ 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 = () @@ -103,7 +103,7 @@ X.x = () ``` Types and terms with the same name are allowed. -```unison +``` unison structural type X = Z X = () diff --git a/unison-src/transcripts/duplicate-term-detection.output.md b/unison-src/transcripts/duplicate-term-detection.output.md index 35f4de11f..3751e75f8 100644 --- a/unison-src/transcripts/duplicate-term-detection.output.md +++ b/unison-src/transcripts/duplicate-term-detection.output.md @@ -2,7 +2,7 @@ Trivial duplicate terms should be detected: -```unison +``` unison x = 1 x = 2 ``` @@ -21,7 +21,7 @@ x = 2 ``` Equivalent duplicate terms should be detected: -```unison +``` unison x = 1 x = 1 ``` @@ -40,7 +40,7 @@ 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 @@ -74,7 +74,7 @@ Record.x.modify = 2 ``` Duplicate terms and constructors should be detected: -```unison +``` unison structural type SumType = X SumType.X = 1 diff --git a/unison-src/transcripts/ed25519.output.md b/unison-src/transcripts/ed25519.output.md index e204f7530..2679028d4 100644 --- a/unison-src/transcripts/ed25519.output.md +++ b/unison-src/transcripts/ed25519.output.md @@ -1,5 +1,4 @@ - -```unison +``` unison up = 0xs0123456789abcdef down = 0xsfedcba9876543210 diff --git a/unison-src/transcripts/edit-command.output.md b/unison-src/transcripts/edit-command.output.md index 644db7ce7..8470de948 100644 --- a/unison-src/transcripts/edit-command.output.md +++ b/unison-src/transcripts/edit-command.output.md @@ -4,7 +4,7 @@ scratch/main> builtins.merge Done. ``` -```unison +``` unison --- title: /private/tmp/scratch.u --- @@ -16,7 +16,6 @@ mytest = [Ok "ok"] ``` - ```ucm Loading changes detected in /private/tmp/scratch.u. @@ -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,7 +67,7 @@ foo : Nat foo = 123 ``` -```unison:added-by-ucm /private/tmp/scratch.u +``` unison:added-by-ucm /private/tmp/scratch.u test> mytest = [Ok "ok"] ``` diff --git a/unison-src/transcripts/edit-namespace.output.md b/unison-src/transcripts/edit-namespace.output.md index ab3bbbb54..67e24e064 100644 --- a/unison-src/transcripts/edit-namespace.output.md +++ b/unison-src/transcripts/edit-namespace.output.md @@ -1,4 +1,4 @@ -```unison +``` unison {{ ping doc }} nested.cycle.ping n = n Nat.+ pong n @@ -79,7 +79,7 @@ project/main> edit.namespace definitions currently in this namespace. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u type Foo = { bar : Nat, baz : Nat } nested.cycle.ping : Nat -> Nat @@ -121,7 +121,7 @@ project/main> edit.namespace nested simple definitions currently in this namespace. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u nested.cycle.ping : Nat -> Nat nested.cycle.ping n = use Nat + diff --git a/unison-src/transcripts/empty-namespaces.output.md b/unison-src/transcripts/empty-namespaces.output.md index 8eee1f1a1..4bea6f5b5 100644 --- a/unison-src/transcripts/empty-namespaces.output.md +++ b/unison-src/transcripts/empty-namespaces.output.md @@ -1,10 +1,11 @@ # Empty namespace behaviours -```unison +``` unison mynamespace.x = 1 ``` The deleted namespace shouldn't appear in `ls` output. + ```ucm scratch/main> ls @@ -57,7 +58,7 @@ scratch/main> history mynamespace ``` Add and then delete a term to add some history to a deleted namespace. -```unison +``` unison deleted.x = 1 stuff.thing = 2 ``` @@ -96,7 +97,7 @@ scratch/main> history deleted ``` ## move.namespace -```unison +``` unison moveoverme.x = 1 moveme.y = 2 ``` diff --git a/unison-src/transcripts/emptyCodebase.output.md b/unison-src/transcripts/emptyCodebase.output.md index bbb762a28..4a8b1cff1 100644 --- a/unison-src/transcripts/emptyCodebase.output.md +++ b/unison-src/transcripts/emptyCodebase.output.md @@ -2,9 +2,9 @@ The Unison codebase, when first initialized, contains no definitions in its namespace. -Not even `Nat` or `+`! +Not even `Nat` or `+`\! -BEHOLD!!! +BEHOLD\!\!\! ```ucm scratch/main> ls @@ -37,4 +37,5 @@ scratch/main> ls lib 2. builtinsio/ (643 terms, 92 types) ``` -More typically, you'd start out by pulling `base. +More typically, you'd start out by pulling `base`. + diff --git a/unison-src/transcripts/error-messages.output.md b/unison-src/transcripts/error-messages.output.md index 82ae8a88b..694f20f4c 100644 --- a/unison-src/transcripts/error-messages.output.md +++ b/unison-src/transcripts/error-messages.output.md @@ -1,4 +1,3 @@ - This file contains programs with parse errors and type errors, for visual inspection of error message quality and to check for regressions or changes to error reporting. ## Parse errors @@ -7,7 +6,7 @@ Some basic errors of literals. ### Floating point literals -```unison +``` unison x = 1. -- missing some digits after the decimal ``` @@ -23,7 +22,7 @@ x = 1. -- missing some digits after the decimal or `1.1e37`. ``` -```unison +``` unison x = 1e -- missing an exponent ``` @@ -39,7 +38,7 @@ x = 1e -- missing an exponent `1e37`. ``` -```unison +``` unison x = 1e- -- missing an exponent ``` @@ -55,7 +54,7 @@ x = 1e- -- missing an exponent `1e-37`. ``` -```unison +``` unison x = 1E+ -- missing an exponent ``` @@ -73,7 +72,7 @@ x = 1E+ -- missing an exponent ``` ### Hex, octal, and bytes literals -```unison +``` unison x = 0xoogabooga -- invalid hex chars ``` @@ -89,7 +88,7 @@ x = 0xoogabooga -- invalid hex chars 0123456789abcdefABCDEF) after the 0x. ``` -```unison +``` unison x = 0o987654321 -- 9 and 8 are not valid octal char ``` @@ -105,7 +104,7 @@ x = 0o987654321 -- 9 and 8 are not valid octal char the 0o. ``` -```unison +``` unison x = 0xsf -- odd number of hex chars in a bytes literal ``` @@ -121,7 +120,7 @@ x = 0xsf -- odd number of hex chars in a bytes literal of 0123456789abcdefABCDEF) after the 0xs. ``` -```unison +``` unison x = 0xsnotvalidhexchars -- invalid hex chars in a bytes literal ``` @@ -139,7 +138,7 @@ x = 0xsnotvalidhexchars -- invalid hex chars in a bytes literal ``` ### Layout errors -```unison +``` unison foo = else -- not matching if ``` @@ -153,7 +152,7 @@ foo = else -- not matching if ``` -```unison +``` unison foo = then -- unclosed ``` @@ -167,7 +166,7 @@ foo = then -- unclosed ``` -```unison +``` unison foo = with -- unclosed ``` @@ -183,7 +182,7 @@ foo = with -- unclosed ``` ### Matching -```unison +``` unison -- No cases foo = match 1 with ``` @@ -201,7 +200,7 @@ foo = match 1 with ``` -```unison +``` unison foo = match 1 with 2 -- no right-hand-side ``` @@ -212,7 +211,8 @@ foo = match 1 with I got confused here: - 3 | + 2 | 2 -- no right-hand-side + I was surprised to find an end of section here. I was expecting one of these instead: @@ -222,7 +222,7 @@ foo = match 1 with * pattern guard ``` -```unison +``` unison -- Mismatched arities foo = cases 1, 2 -> () @@ -243,7 +243,7 @@ foo = cases ``` -```unison +``` unison -- Missing a '->' x = match Some a with None -> @@ -258,7 +258,8 @@ x = match Some a with I got confused here: - 7 | + 6 | 2 + I was surprised to find an end of section here. I was expecting one of these instead: @@ -271,7 +272,7 @@ x = match Some a with * true ``` -```unison +``` unison -- Missing patterns x = match Some a with None -> 1 @@ -294,7 +295,7 @@ x = match Some a with * newline or semicolon ``` -```unison +``` unison -- Guards following an unguarded case x = match Some a with None -> 1 @@ -318,7 +319,7 @@ x = match Some a with ``` ### Watches -```unison +``` unison -- Empty watch > ``` @@ -335,7 +336,7 @@ x = match Some a with ``` ### Keywords -```unison +``` unison use.keyword.in.namespace = 1 ``` @@ -351,7 +352,7 @@ use.keyword.in.namespace = 1 or wrapping it in backticks (like `namespace` ). ``` -```unison +``` unison -- reserved operator a ! b = 1 ``` diff --git a/unison-src/transcripts/errors/missing-result-typed.output.md b/unison-src/transcripts/errors/missing-result-typed.output.md index 260b80617..2357371ec 100644 --- a/unison-src/transcripts/errors/missing-result-typed.output.md +++ b/unison-src/transcripts/errors/missing-result-typed.output.md @@ -1,11 +1,10 @@ - ### Transcript parser hidden errors 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 +``` unison a : Nat a = b = 24 diff --git a/unison-src/transcripts/errors/missing-result.output.md b/unison-src/transcripts/errors/missing-result.output.md index c099e7008..608f5c589 100644 --- a/unison-src/transcripts/errors/missing-result.output.md +++ b/unison-src/transcripts/errors/missing-result.output.md @@ -1,11 +1,10 @@ - ### Transcript parser hidden errors 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 +``` unison x = y = 24 ``` 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 9b8c0b43e..de409c16f 100644 --- a/unison-src/transcripts/errors/ucm-hide-all-error.output.md +++ b/unison-src/transcripts/errors/ucm-hide-all-error.output.md @@ -1,17 +1,17 @@ - ### Transcript parser hidden errors -Dangerous scary words! +Dangerous scary words\! 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 +``` ucm scratch/main> history ``` + 🛑 The transcript was expecting an error in the stanza above, but did not encounter one. diff --git a/unison-src/transcripts/errors/ucm-hide-all.output.md b/unison-src/transcripts/errors/ucm-hide-all.output.md index 56cf454d4..34b9b974a 100644 --- a/unison-src/transcripts/errors/ucm-hide-all.output.md +++ b/unison-src/transcripts/errors/ucm-hide-all.output.md @@ -1,17 +1,17 @@ - ### Transcript parser hidden errors -Dangerous scary words! +Dangerous scary words\! 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 +``` ucm scratch/main> move.namespace foo bar ``` + 🛑 The transcript failed due to an error in the stanza above. The error is: diff --git a/unison-src/transcripts/errors/ucm-hide-error.output.md b/unison-src/transcripts/errors/ucm-hide-error.output.md index 3e80bd4a7..893baf53e 100644 --- a/unison-src/transcripts/errors/ucm-hide-error.output.md +++ b/unison-src/transcripts/errors/ucm-hide-error.output.md @@ -1,17 +1,17 @@ - ### Transcript parser hidden errors -Dangerous scary words! +Dangerous scary words\! 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 +``` ucm scratch/main> history ``` + 🛑 The transcript was expecting an error in the stanza above, but did not encounter one. diff --git a/unison-src/transcripts/errors/ucm-hide.output.md b/unison-src/transcripts/errors/ucm-hide.output.md index 2c88db7f5..205870869 100644 --- a/unison-src/transcripts/errors/ucm-hide.output.md +++ b/unison-src/transcripts/errors/ucm-hide.output.md @@ -1,17 +1,17 @@ - ### Transcript parser hidden errors -Dangerous scary words! +Dangerous scary words\! When an error is encountered in a `ucm:hide` block then the transcript parser should print the stanza and surface a helpful message. -```ucm +``` ucm scratch/main> move.namespace foo bar ``` + 🛑 The transcript failed due to an error in the stanza above. The error is: 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 3c3e6f3e5..fbb8a35d6 100644 --- a/unison-src/transcripts/errors/unison-hide-all-error.output.md +++ b/unison-src/transcripts/errors/unison-hide-all-error.output.md @@ -1,11 +1,10 @@ - ### Transcript parser hidden errors 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 +``` unison myVal = 3 ``` diff --git a/unison-src/transcripts/errors/unison-hide-all.output.md b/unison-src/transcripts/errors/unison-hide-all.output.md index 9b313c82a..a093b5f5e 100644 --- a/unison-src/transcripts/errors/unison-hide-all.output.md +++ b/unison-src/transcripts/errors/unison-hide-all.output.md @@ -1,11 +1,10 @@ - ### Transcript parser hidden errors 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 +``` unison 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 30ab85dc5..bde72516f 100644 --- a/unison-src/transcripts/errors/unison-hide-error.output.md +++ b/unison-src/transcripts/errors/unison-hide-error.output.md @@ -1,11 +1,10 @@ - ### Transcript parser hidden errors 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 +``` unison myVal = 3 ``` diff --git a/unison-src/transcripts/errors/unison-hide.output.md b/unison-src/transcripts/errors/unison-hide.output.md index bf410ca30..1a8a9c78a 100644 --- a/unison-src/transcripts/errors/unison-hide.output.md +++ b/unison-src/transcripts/errors/unison-hide.output.md @@ -1,11 +1,10 @@ - ### Transcript parser hidden errors When an error is encountered in a `unison:hide` block then the transcript parser should print the stanza and surface a helpful message. -```unison +``` unison g 3 ``` diff --git a/unison-src/transcripts/escape-sequences.output.md b/unison-src/transcripts/escape-sequences.output.md index 46cb0e045..0834375f1 100644 --- a/unison-src/transcripts/escape-sequences.output.md +++ b/unison-src/transcripts/escape-sequences.output.md @@ -1,4 +1,4 @@ -```unison +``` unison > "Rúnar" > "῎Ανδρα μοι ἔννεπε, Μοῦσα, πολύτροπον" > "古池や蛙飛びこむ水の音" diff --git a/unison-src/transcripts/find-by-type.output.md b/unison-src/transcripts/find-by-type.output.md index 4fcbf2d85..476f6ff80 100644 --- a/unison-src/transcripts/find-by-type.output.md +++ b/unison-src/transcripts/find-by-type.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type A = A Text foo : A diff --git a/unison-src/transcripts/find-command.output.md b/unison-src/transcripts/find-command.output.md index f75da189b..e4c4f6fe7 100644 --- a/unison-src/transcripts/find-command.output.md +++ b/unison-src/transcripts/find-command.output.md @@ -1,4 +1,4 @@ -```unison +``` unison foo = 1 lib.foo = 2 lib.bar = 3 diff --git a/unison-src/transcripts/fix-1381-excess-propagate.output.md b/unison-src/transcripts/fix-1381-excess-propagate.output.md index d35a89262..373289970 100644 --- a/unison-src/transcripts/fix-1381-excess-propagate.output.md +++ b/unison-src/transcripts/fix-1381-excess-propagate.output.md @@ -1,7 +1,8 @@ We were seeing an issue where (it seemed) that every namespace that was visited during a propagate would get a new history node, even when it didn't contain any dependents. Example: -```unison + +``` unison a = "a term" X.foo = "a namespace" ``` @@ -16,7 +17,8 @@ scratch/main> add ``` Here is an update which should not affect `X`: -```unison + +``` unison a = "an update" ``` @@ -30,6 +32,7 @@ scratch/main> update ``` As of the time of this writing, the history for `X` should be a single node, `#4eeuo5bsfr`; + ```ucm scratch/main> history X @@ -42,6 +45,7 @@ scratch/main> history X ``` however, as of release/M1i, we saw an extraneous node appear. If your `ucm` is fixed, you won't see it below: + ```ucm scratch/main> history #7nl6ppokhg diff --git a/unison-src/transcripts/fix-2258-if-as-list-element.output.md b/unison-src/transcripts/fix-2258-if-as-list-element.output.md index 50c28c004..0e136a6be 100644 --- a/unison-src/transcripts/fix-2258-if-as-list-element.output.md +++ b/unison-src/transcripts/fix-2258-if-as-list-element.output.md @@ -1,6 +1,6 @@ Tests that `if` statements can appear as list and tuple elements. -```unison +``` unison > [ if true then 1 else 0 ] > [ if true then 1 else 0, 1] diff --git a/unison-src/transcripts/fix-big-list-crash.output.md b/unison-src/transcripts/fix-big-list-crash.output.md index 1d14e77d7..5661b0339 100644 --- a/unison-src/transcripts/fix-big-list-crash.output.md +++ b/unison-src/transcripts/fix-big-list-crash.output.md @@ -2,7 +2,7 @@ Big lists have been observed to crash, while in the garbage collection step. -```unison +``` unison unique type Direction = U | D | L | R x = [(R,1005),(U,563),(R,417),(U,509),(L,237),(U,555),(R,397),(U,414),(L,490),(U,336),(L,697),(D,682),(L,180),(U,951),(L,189),(D,547),(R,697),(U,583),(L,172),(D,859),(L,370),(D,114),(L,519),(U,829),(R,389),(U,608),(R,66),(D,634),(L,320),(D,49),(L,931),(U,137),(L,349),(D,689),(L,351),(D,829),(R,819),(D,138),(L,118),(D,849),(R,230),(U,858),(L,509),(D,311),(R,815),(U,217),(R,359),(U,840),(R,77),(U,230),(R,361),(U,322),(R,300),(D,646),(R,348),(U,815),(R,793),(D,752),(R,967),(U,128),(R,948),(D,499),(R,359),(U,572),(L,566),(U,815),(R,630),(D,290),(L,829),(D,736),(R,358),(U,778),(R,891),(U,941),(R,544),(U,889),(L,920),(U,913),(L,447),(D,604),(R,538),(U,818),(L,215),(D,437),(R,447),(U,576),(R,452),(D,794),(R,864),(U,269),(L,325),(D,35),(L,268),(D,639),(L,101),(U,777),(L,776),(U,958),(R,105),(U,517),(R,667),(D,423),(R,603),(U,469),(L,125),(D,919),(R,879),(U,994),(R,665),(D,377),(R,456),(D,570),(L,685),(U,291),(R,261),(U,846),(R,840),(U,418),(L,974),(D,270),(L,312),(D,426),(R,621),(D,334),(L,855),(D,378),(R,694),(U,845),(R,481),(U,895),(L,362),(D,840),(L,712),(U,57),(R,276),(D,643),(R,566),(U,348),(R,361),(D,144),(L,287),(D,864),(L,556),(U,610),(L,927),(U,322),(R,271),(D,90),(L,741),(U,446),(R,181),(D,527),(R,56),(U,805),(L,907),(D,406),(L,286),(U,873),(L,79),(D,280),(L,153),(D,377),(R,253),(D,61),(R,475),(D,804),(R,788),(U,393),(L,660),(U,314),(R,489),(D,491),(L,234),(D,712),(L,253),(U,651),(L,777),(D,726),(R,146),(U,47),(R,630),(U,517),(R,226),(U,624),(L,834),(D,153),(L,513),(U,799),(R,287),(D,868),(R,982),(U,390),(L,296),(D,373),(R,9),(U,994),(R,105),(D,673),(L,657),(D,868),(R,738),(D,277),(R,374),(U,828),(R,860),(U,247),(R,484),(U,986),(L,723),(D,847),(L,578),(U,487),(L,51),(D,865),(L,328),(D,199),(R,812),(D,726),(R,355),(D,463),(R,761),(U,69),(R,508),(D,753),(L,81),(D,50),(L,345),(D,66),(L,764),(D,466),(L,975),(U,619),(R,59),(D,788),(L,737),(D,360),(R,14),(D,253),(L,512),(D,417),(R,828),(D,188),(L,394),(U,212),(R,658),(U,369),(R,920),(U,927),(L,339),(U,552),(R,856),(D,458),(R,407),(U,41),(L,930),(D,460),(R,809),(U,467),(L,410),(D,800),(L,135),(D,596),(R,678),(D,4),(L,771),(D,637),(L,876),(U,192),(L,406),(D,136),(R,666),(U,730),(R,711),(D,291),(L,586),(U,845),(R,606),(U,2),(L,228),(D,759),(R,244),(U,946),(R,948),(U,160),(R,397),(U,134),(R,188),(U,850),(R,623),(D,315),(L,219),(D,450),(R,489),(U,374),(R,299),(D,474),(L,767),(D,679),(L,160),(D,403),(L,708)] diff --git a/unison-src/transcripts/fix-ls.output.md b/unison-src/transcripts/fix-ls.output.md index 56277c692..abf280b23 100644 --- a/unison-src/transcripts/fix-ls.output.md +++ b/unison-src/transcripts/fix-ls.output.md @@ -4,7 +4,7 @@ test-ls/main> builtins.merge Done. ``` -```unison +``` unison foo.bar.add x y = x Int.+ y foo.bar.subtract x y = x Int.- y diff --git a/unison-src/transcripts/fix1063.output.md b/unison-src/transcripts/fix1063.output.md index d9d2e8380..ca9f0ad57 100644 --- a/unison-src/transcripts/fix1063.output.md +++ b/unison-src/transcripts/fix1063.output.md @@ -1,6 +1,6 @@ Tests that functions named `.` are rendered correctly. -```unison +``` unison (`.`) f g x = f (g x) use Boolean not diff --git a/unison-src/transcripts/fix1334.output.md b/unison-src/transcripts/fix1334.output.md index 4e08c294b..b9b6f6a89 100644 --- a/unison-src/transcripts/fix1334.output.md +++ b/unison-src/transcripts/fix1334.output.md @@ -1,4 +1,4 @@ -Previously, the `alias.term` and `alias.type` would fail if the source argument was hash-only, and there was no way to create an alias for a definition that didn't already have a name. Also, the `replace.term` and `replace.type` _only_ worked on hashes, and they had to be _full_ hashes. +Previously, the `alias.term` and `alias.type` would fail if the source argument was hash-only, and there was no way to create an alias for a definition that didn't already have a name. Also, the `replace.term` and `replace.type` *only* worked on hashes, and they had to be *full* hashes. With this PR, the source of an alias can be a short hash (even of a definition that doesn't currently have a name in the namespace) along with a name or hash-qualified name from the current namespace as usual. diff --git a/unison-src/transcripts/fix1390.output.md b/unison-src/transcripts/fix1390.output.md index 164f3a8a6..4d50e86af 100644 --- a/unison-src/transcripts/fix1390.output.md +++ b/unison-src/transcripts/fix1390.output.md @@ -1,11 +1,10 @@ - ```ucm scratch/main> builtins.merge Done. ``` -```unison +``` unison -- List.map : (a -> b) -> [a] -> [b] List.map f = go acc = cases @@ -44,7 +43,7 @@ scratch/main> view List.map go [] ``` -```unison +``` unison List.map2 : (g -> g2) -> [g] -> [g2] List.map2 f = unused = "just to give this a different hash" diff --git a/unison-src/transcripts/fix1532.output.md b/unison-src/transcripts/fix1532.output.md index 6b856b35e..41ea7b2b9 100644 --- a/unison-src/transcripts/fix1532.output.md +++ b/unison-src/transcripts/fix1532.output.md @@ -6,7 +6,7 @@ scratch/main> builtins.merge ``` First, lets create two namespaces. `foo` and `bar`, and add some definitions. -```unison +``` unison foo.x = 42 foo.y = 100 bar.z = x + y diff --git a/unison-src/transcripts/fix1578.output.md b/unison-src/transcripts/fix1578.output.md index 1b57bcabd..0645dae51 100644 --- a/unison-src/transcripts/fix1578.output.md +++ b/unison-src/transcripts/fix1578.output.md @@ -4,7 +4,7 @@ This transcript shows how suffix-based name resolution works when definitions in As setup, we'll add a data type `Day` and a definition `foo.bar : Nat`. -```unison +``` unison unique type Day = Sun | Mon | Tue | Wed | Thu | Fri | Sat foo.bar : Nat @@ -13,15 +13,15 @@ foo.bar = 23 Suffix-based name resolution prefers to use names locally defined in the current file, then checks for matches in the codebase. Here are the precise rules, which will be explained below with examples: -* If a symbol, `s`, is a suffix of exactly one definition `d` in the file, then `s` refers to `d`. -* Otherwise, if `s` is a suffix of exactly one definition `d` in the codebase, then `s` refers to `d`. -* Otherwise, if `s` is a suffix of multiple definitions in the file or the codebase, then (at least for terms) type-directed name resolution will be attempted to figure out which definition `s` refers to. + - If a symbol, `s`, is a suffix of exactly one definition `d` in the file, then `s` refers to `d`. + - Otherwise, if `s` is a suffix of exactly one definition `d` in the codebase, then `s` refers to `d`. + - Otherwise, if `s` is a suffix of multiple definitions in the file or the codebase, then (at least for terms) type-directed name resolution will be attempted to figure out which definition `s` refers to. ## Example 1: local file term definitions shadow codebase term definitions This should typecheck, using the file's `bar : Text` rather than the codebase `foo.bar : Nat`: -```unison +``` unison use Text ++ bar : Text @@ -32,9 +32,9 @@ baz = bar ++ ", world!" ## Example 2: any locally unique term suffix shadows codebase term definitions -This should also typecheck, using the file's `oog.bar`. This shows you can refer to a definition in the file by any suffix that is unique to definitions in the file (even if that suffix may match other definitions in the _codebase_). See example 4 below for overriding this behavior. +This should also typecheck, using the file's `oog.bar`. This shows you can refer to a definition in the file by any suffix that is unique to definitions in the file (even if that suffix may match other definitions in the *codebase*). See example 4 below for overriding this behavior. -```unison +``` unison use Text ++ oog.bar = "hello" @@ -44,7 +44,7 @@ baz = bar ++ ", world!" This subtle test establishes that we aren't using type-directed name resolution (TDNR) for the local term references in the file. If this were using TDNR, it would fail with an ambiguity as there's nothing that pins down the expected type of `bar` here: -```unison +``` unison use Text ++ oog.bar = "hello" @@ -54,7 +54,7 @@ baz = (bar, 42) This subtle test establishes that locally introduced variables (within a function, say) correctly shadow definitions introduced at the file top level: -```unison +``` unison use Text ++ oog.bar = "hello" @@ -67,7 +67,7 @@ baz bar = (bar, 42) -- here, `bar` refers to the parameter This should also typecheck, using the local `Sun`, and not `Day.Sun` which exists in the codebase, and the local `Day`, not the codebase `Day`. -```unison +``` unison structural type Zoot = Zonk | Sun structural type Day = Day Int @@ -87,7 +87,7 @@ day1 = Day +1 Even though local definitions are preferred, you can refer to definitions in the codebase via any unique suffix that doesn't also exist in the file. -```unison +``` unison structural type Zoot = Zonk | Sun use Zoot Zonk diff --git a/unison-src/transcripts/fix1696.output.md b/unison-src/transcripts/fix1696.output.md index c0a9ccce8..47c1159a3 100644 --- a/unison-src/transcripts/fix1696.output.md +++ b/unison-src/transcripts/fix1696.output.md @@ -1,5 +1,4 @@ - -```unison +``` unison structural ability Ask where ask : Nat ability Zoot where diff --git a/unison-src/transcripts/fix1709.output.md b/unison-src/transcripts/fix1709.output.md index 8523d4e27..3aacb9753 100644 --- a/unison-src/transcripts/fix1709.output.md +++ b/unison-src/transcripts/fix1709.output.md @@ -1,4 +1,4 @@ -```unison +``` unison id x = x id2 x = @@ -29,7 +29,7 @@ scratch/main> add id2 : x -> x ``` -```unison +``` unison > id2 "hi" ``` diff --git a/unison-src/transcripts/fix1731.output.md b/unison-src/transcripts/fix1731.output.md index f3fc1c35d..8c8a7610a 100644 --- a/unison-src/transcripts/fix1731.output.md +++ b/unison-src/transcripts/fix1731.output.md @@ -1,5 +1,4 @@ - -```unison +``` unison structural ability CLI where print : Text ->{CLI} () input : {CLI} Text @@ -7,7 +6,7 @@ structural ability CLI where The `input` here should parse as a wildcard, not as `CLI.input`. -```unison +``` unison repro : Text -> () repro = cases input -> () diff --git a/unison-src/transcripts/fix1800.output.md b/unison-src/transcripts/fix1800.output.md index 915f50e70..8fb9e9297 100644 --- a/unison-src/transcripts/fix1800.output.md +++ b/unison-src/transcripts/fix1800.output.md @@ -1,5 +1,4 @@ - -```unison +``` unison printLine : Text ->{IO} () printLine msg = _ = putBytes.impl (stdHandle StdOut) (Text.toUtf8 (msg ++ "\n")) @@ -18,8 +17,8 @@ main3 _ = printLine "🦄 ☁️ 🌈" Testing a few variations here: -* Should be able to run annotated and unannotated main functions in the current file. -* Should be able to run annotated and unannotated main functions from the codebase. + - Should be able to run annotated and unannotated main functions in the current file. + - Should be able to run annotated and unannotated main functions from the codebase. ```ucm scratch/main> run main1 @@ -74,7 +73,7 @@ scratch/main> run code.main3 ``` Now testing a few variations that should NOT typecheck. -```unison +``` unison main4 : Nat ->{IO} Nat main4 n = n diff --git a/unison-src/transcripts/fix1844.output.md b/unison-src/transcripts/fix1844.output.md index 571daa8b9..bbc28208c 100644 --- a/unison-src/transcripts/fix1844.output.md +++ b/unison-src/transcripts/fix1844.output.md @@ -1,5 +1,4 @@ - -```unison +``` unison structural type One a = One a unique type Woot a b c = Woot a b c unique type Z = Z diff --git a/unison-src/transcripts/fix1926.output.md b/unison-src/transcripts/fix1926.output.md index a325470e9..6326666d2 100644 --- a/unison-src/transcripts/fix1926.output.md +++ b/unison-src/transcripts/fix1926.output.md @@ -4,7 +4,7 @@ scratch/main> builtins.merge Done. ``` -```unison +``` unison > 'sq sq = 2934892384 @@ -30,7 +30,7 @@ sq = 2934892384 do sq ``` -```unison +``` unison > 'sq sq = 2934892384 diff --git a/unison-src/transcripts/fix2026.output.md b/unison-src/transcripts/fix2026.output.md index e4f9d8d17..5718d9516 100644 --- a/unison-src/transcripts/fix2026.output.md +++ b/unison-src/transcripts/fix2026.output.md @@ -1,4 +1,4 @@ -```unison +``` unison structural ability Exception where raise : Failure -> x ex = unsafeRun! '(printLine "hello world") diff --git a/unison-src/transcripts/fix2027.output.md b/unison-src/transcripts/fix2027.output.md index 2a7b30dec..cb959dcc5 100644 --- a/unison-src/transcripts/fix2027.output.md +++ b/unison-src/transcripts/fix2027.output.md @@ -1,6 +1,4 @@ - - -```unison +``` unison structural ability Exception where raise : Failure -> x reraise = cases diff --git a/unison-src/transcripts/fix2049.output.md b/unison-src/transcripts/fix2049.output.md index 3db4fa2f2..492729b03 100644 --- a/unison-src/transcripts/fix2049.output.md +++ b/unison-src/transcripts/fix2049.output.md @@ -1,4 +1,4 @@ -```unison +``` unison id x = x structural ability Stream a where @@ -87,7 +87,7 @@ Fold.Stream.fold = ``` Tests some capabilities for catching runtime exceptions. -```unison +``` unison catcher : '{IO} () ->{IO} Result catcher act = handle tryEval act with cases diff --git a/unison-src/transcripts/fix2156.output.md b/unison-src/transcripts/fix2156.output.md index c4eed7557..acad8adb9 100644 --- a/unison-src/transcripts/fix2156.output.md +++ b/unison-src/transcripts/fix2156.output.md @@ -1,8 +1,7 @@ - Tests for a case where bad eta reduction was causing erroneous watch output/caching. -```unison +``` unison sqr : Nat -> Nat sqr n = n * n diff --git a/unison-src/transcripts/fix2167.output.md b/unison-src/transcripts/fix2167.output.md index 3d8c3251f..0a5c34eb1 100644 --- a/unison-src/transcripts/fix2167.output.md +++ b/unison-src/transcripts/fix2167.output.md @@ -1,7 +1,7 @@ This is just a simple transcript to regression check an ability inference/checking issue. -```unison +``` unison structural ability R t where die : () -> x near.impl : Nat -> Either () [Nat] @@ -37,3 +37,4 @@ fail because the type was invalid. The fix was to avoid dropping certain existential variables out of scope. + diff --git a/unison-src/transcripts/fix2187.output.md b/unison-src/transcripts/fix2187.output.md index 8f499449e..45fb5de8b 100644 --- a/unison-src/transcripts/fix2187.output.md +++ b/unison-src/transcripts/fix2187.output.md @@ -1,4 +1,4 @@ -```unison +``` unison lexicalScopeEx: [Text] lexicalScopeEx = parent = "outer" diff --git a/unison-src/transcripts/fix2231.output.md b/unison-src/transcripts/fix2231.output.md index b94ff2c9d..5dfb0b791 100644 --- a/unison-src/transcripts/fix2231.output.md +++ b/unison-src/transcripts/fix2231.output.md @@ -6,7 +6,7 @@ and while they are all valid and some may be equivalently general, the choices may not work equally well with the type checking strategies. -```unison +``` unison (<<) : (b ->{e} c) -> (a ->{e} b) -> a ->{e} c (<<) f g x = f (g x) diff --git a/unison-src/transcripts/fix2238.output.md b/unison-src/transcripts/fix2238.output.md index b9594f015..0133809e1 100644 --- a/unison-src/transcripts/fix2238.output.md +++ b/unison-src/transcripts/fix2238.output.md @@ -1,7 +1,6 @@ - This should not typecheck - the inline `@eval` expression uses abilities. -```unison +``` unison structural ability Abort where abort : x ex = {{ @eval{abort} }} diff --git a/unison-src/transcripts/fix2254.output.md b/unison-src/transcripts/fix2254.output.md index eed5075c1..7abb35233 100644 --- a/unison-src/transcripts/fix2254.output.md +++ b/unison-src/transcripts/fix2254.output.md @@ -1,7 +1,6 @@ - This transcript checks that updates to data types propagate successfully to dependent types and dependent terms that do pattern matching. First let's create some types and terms: -```unison +``` unison unique type A a b c d = A a | B b @@ -55,7 +54,7 @@ scratch/a> branch a2 ``` First let's edit the `A` type, adding another constructor `E`. Note that the functions written against the old type have a wildcard in their pattern match, so they should work fine after the update. -```unison +``` unison unique type A a b c d = A a | B b @@ -116,7 +115,7 @@ scratch/a2> todo Here's a test of updating a record: -```unison +``` unison structural type Rec = { uno : Nat, dos : Nat } combine r = uno r + dos r @@ -164,7 +163,7 @@ scratch/r1> branch r2 `switch /r1` then `merge /r2`. ``` -```unison +``` unison structural type Rec = { uno : Nat, dos : Nat, tres : Text } ``` diff --git a/unison-src/transcripts/fix2268.output.md b/unison-src/transcripts/fix2268.output.md index bfb65920f..1c170dd54 100644 --- a/unison-src/transcripts/fix2268.output.md +++ b/unison-src/transcripts/fix2268.output.md @@ -2,7 +2,7 @@ Tests for a TDNR case that wasn't working. The code wasn't 'relaxing' inferred types that didn't contain arrows, so effects that just yield a value weren't getting disambiguated. -```unison +``` unison unique ability A where a : Nat diff --git a/unison-src/transcripts/fix2334.output.md b/unison-src/transcripts/fix2334.output.md index 669017cd8..03e65bdcd 100644 --- a/unison-src/transcripts/fix2334.output.md +++ b/unison-src/transcripts/fix2334.output.md @@ -1,8 +1,7 @@ - Tests an issue where pattern matching matrices involving built-in types was discarding default cases in some branches. -```unison +``` unison f = cases 0, 0 -> 0 _, 1 -> 2 diff --git a/unison-src/transcripts/fix2344.output.md b/unison-src/transcripts/fix2344.output.md index 6d0ae41c4..4c35e7211 100644 --- a/unison-src/transcripts/fix2344.output.md +++ b/unison-src/transcripts/fix2344.output.md @@ -1,10 +1,9 @@ - Checks a corner case with type checking involving destructuring binds. The binds were causing some sequences of lets to be unnecessarily recursive. -```unison +``` unison unique ability Nate where nate: (Boolean, Nat) antiNate: () diff --git a/unison-src/transcripts/fix2350.output.md b/unison-src/transcripts/fix2350.output.md index d8f6bf43b..4fcf50790 100644 --- a/unison-src/transcripts/fix2350.output.md +++ b/unison-src/transcripts/fix2350.output.md @@ -1,4 +1,3 @@ - This tests an issue where ability variables were being defaulted over eagerly. In general, we want to avoid collecting up variables from the use of definitions with types like: @@ -17,7 +16,7 @@ abilities being collected aren't in the context, so types like: were a corner case. We would add `S e` to the wanted abilities, then not realize that `e` shouldn't be defaulted. -```unison +``` unison unique ability Storage d g where save.impl : a ->{Storage d g} ('{g} (d a)) diff --git a/unison-src/transcripts/fix2353.output.md b/unison-src/transcripts/fix2353.output.md index 74c9da016..72d0c465e 100644 --- a/unison-src/transcripts/fix2353.output.md +++ b/unison-src/transcripts/fix2353.output.md @@ -1,4 +1,4 @@ -```unison +``` unison use builtin Scope unique ability Async t g where async : {g} Nat unique ability Exception where raise : Nat -> x diff --git a/unison-src/transcripts/fix2354.output.md b/unison-src/transcripts/fix2354.output.md index 7fcfce26a..4dab20348 100644 --- a/unison-src/transcripts/fix2354.output.md +++ b/unison-src/transcripts/fix2354.output.md @@ -1,8 +1,7 @@ - Tests that delaying an un-annotated higher-rank type gives a normal type error, rather than an internal compiler error. -```unison +``` unison f : (forall a . a -> a) -> Nat f id = id 0 diff --git a/unison-src/transcripts/fix2355.output.md b/unison-src/transcripts/fix2355.output.md index 0bc382663..27337dbd6 100644 --- a/unison-src/transcripts/fix2355.output.md +++ b/unison-src/transcripts/fix2355.output.md @@ -1,7 +1,6 @@ - Tests for a loop that was previously occurring in the type checker. -```unison +``` unison structural ability A t g where fork : '{g, A t g} a -> t a await : t a -> a diff --git a/unison-src/transcripts/fix2378.output.md b/unison-src/transcripts/fix2378.output.md index 5acef2316..73c63de73 100644 --- a/unison-src/transcripts/fix2378.output.md +++ b/unison-src/transcripts/fix2378.output.md @@ -1,9 +1,8 @@ - Tests for an ability failure that was caused by order dependence of checking wanted vs. provided abilities. It was necessary to re-check rows until a fixed point is reached. -```unison +``` unison unique ability C c where new : c a receive : c a -> a diff --git a/unison-src/transcripts/fix2423.output.md b/unison-src/transcripts/fix2423.output.md index 6deb34d73..cc17ad15c 100644 --- a/unison-src/transcripts/fix2423.output.md +++ b/unison-src/transcripts/fix2423.output.md @@ -1,4 +1,4 @@ -```unison +``` unison structural ability Split where skip! : x both : a -> a -> a diff --git a/unison-src/transcripts/fix2474.output.md b/unison-src/transcripts/fix2474.output.md index f023e162b..4a0d8a08e 100644 --- a/unison-src/transcripts/fix2474.output.md +++ b/unison-src/transcripts/fix2474.output.md @@ -1,21 +1,20 @@ - Tests an issue with a lack of generality of handlers. In general, a set of cases: - { e ... -> k } +{ e ... -\> k } should be typed in the following way: - 1. The scrutinee has type `Request {E, g} r -> s` where `E` is all - the abilities being handled. `g` is a slack variable, because all - abilities that are used in the handled expression pass through - the handler. Previously this was being inferred as merely - `Request {E} r -> s` - 2. The continuation variable `k` should have type `o ->{E, g} r`, - matching the above types (`o` is the result type of `e`). - Previously this was being checked as `o ->{E0} r`, where `E0` is - the ability that contains `e`. +1. The scrutinee has type `Request {E, g} r -> s` where `E` is all + the abilities being handled. `g` is a slack variable, because all + abilities that are used in the handled expression pass through + the handler. Previously this was being inferred as merely + `Request {E} r -> s` +2. The continuation variable `k` should have type `o ->{E, g} r`, + matching the above types (`o` is the result type of `e`). + Previously this was being checked as `o ->{E0} r`, where `E0` is + the ability that contains `e`. ```ucm scratch/main> builtins.merge @@ -23,7 +22,7 @@ scratch/main> builtins.merge Done. ``` -```unison +``` unison structural ability Stream a where emit : a -> () diff --git a/unison-src/transcripts/fix2628.output.md b/unison-src/transcripts/fix2628.output.md index 6dba18bfa..cb51cf0d7 100644 --- a/unison-src/transcripts/fix2628.output.md +++ b/unison-src/transcripts/fix2628.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type foo.bar.baz.MyRecord = { value : Nat } diff --git a/unison-src/transcripts/fix2663.output.md b/unison-src/transcripts/fix2663.output.md index c250fb403..fcb73c75d 100644 --- a/unison-src/transcripts/fix2663.output.md +++ b/unison-src/transcripts/fix2663.output.md @@ -1,13 +1,12 @@ - Tests a variable capture problem. After pattern compilation, the match would end up: - T p1 p3 p3 +T p1 p3 p3 and z would end up referring to the first p3 rather than the second. -```unison +``` unison structural type Trip = T Nat Nat Nat bad : Nat -> (Nat, Nat) diff --git a/unison-src/transcripts/fix2693.output.md b/unison-src/transcripts/fix2693.output.md index 7bb6d6088..94961fc9e 100644 --- a/unison-src/transcripts/fix2693.output.md +++ b/unison-src/transcripts/fix2693.output.md @@ -1,5 +1,4 @@ - -```unison +``` unison loop : List Nat -> Nat -> List Nat loop l = cases 0 -> l @@ -32,7 +31,7 @@ scratch/main> add range : Nat -> [Nat] ``` -```unison +``` unison > range 2000 ``` @@ -2054,7 +2053,7 @@ scratch/main> add ``` Should be cached: -```unison +``` unison > range 2000 ``` diff --git a/unison-src/transcripts/fix2712.output.md b/unison-src/transcripts/fix2712.output.md index f691d22dc..04c8c46e3 100644 --- a/unison-src/transcripts/fix2712.output.md +++ b/unison-src/transcripts/fix2712.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Map k v = Tip | Bin Nat k v (Map k v) (Map k v) mapWithKey : (k ->{e} a ->{e} b) -> Map k a ->{e} Map k b @@ -28,7 +28,7 @@ scratch/main> add mapWithKey : (k ->{e} a ->{e} b) -> Map k a ->{e} Map k b ``` -```unison +``` unison naiomi = susan: Nat -> Nat -> () susan a b = () diff --git a/unison-src/transcripts/fix2840.output.md b/unison-src/transcripts/fix2840.output.md index ab59e8f1e..a84e33e4d 100644 --- a/unison-src/transcripts/fix2840.output.md +++ b/unison-src/transcripts/fix2840.output.md @@ -1,6 +1,6 @@ This bugfix addresses an issue where embedded Unison code in UCM was expected to be present in the active codebase when the `display` command was used render `Doc` values. -First, a few \[hidden] definitions necessary for typechecking a simple Doc2. +First, a few \[hidden\] definitions necessary for typechecking a simple Doc2. ```ucm scratch/main> add @@ -18,7 +18,8 @@ scratch/main> add ``` Next, define and display a simple Doc: -```unison + +``` unison README = {{ Hi }} @@ -32,10 +33,8 @@ scratch/main> display README ``` Previously, the error was: -``` -⚙️ Processing stanza 5 of 7.ucm: PE [("die",SrcLoc {srcLocPackage = "unison-parser-typechecker-0.0.0-He2Hp1llokT2nN4MnUfUXz", srcLocModule = "Unison.Runtime.Interface", srcLocFile = "src/Unison/Runtime/Interface.hs", srcLocStartLine = 118, srcLocStartCol = 18, srcLocEndLine = 118, srcLocEndCol = 60})] Lit - AnnotatedText (fromList [Segment {segment = "Unknown term reference: #4522d", annotation = Nothing}]) - -``` + ⚙️ Processing stanza 5 of 7.ucm: PE [("die",SrcLoc {srcLocPackage = "unison-parser-typechecker-0.0.0-He2Hp1llokT2nN4MnUfUXz", srcLocModule = "Unison.Runtime.Interface", srcLocFile = "src/Unison/Runtime/Interface.hs", srcLocStartLine = 118, srcLocStartCol = 18, srcLocEndLine = 118, srcLocEndCol = 60})] Lit + AnnotatedText (fromList [Segment {segment = "Unknown term reference: #4522d", annotation = Nothing}]) but as of this PR, it's okay. + diff --git a/unison-src/transcripts/fix2970.output.md b/unison-src/transcripts/fix2970.output.md index 52d017e84..2d4915f4a 100644 --- a/unison-src/transcripts/fix2970.output.md +++ b/unison-src/transcripts/fix2970.output.md @@ -1,4 +1,4 @@ -Also fixes #1519 (it's the same issue). +Also fixes \#1519 (it's the same issue). ```ucm scratch/main> builtins.merge @@ -6,7 +6,7 @@ scratch/main> builtins.merge Done. ``` -```unison +``` unison foo.+.doc : Nat foo.+.doc = 10 ``` diff --git a/unison-src/transcripts/fix3037.output.md b/unison-src/transcripts/fix3037.output.md index 1ffd18c3b..be813afc7 100644 --- a/unison-src/transcripts/fix3037.output.md +++ b/unison-src/transcripts/fix3037.output.md @@ -2,7 +2,7 @@ Tests for an unsound case of ability checking that was erroneously being accepted before. In certain cases, abilities were able to be added to rows in invariant positions. -```unison +``` unison structural type Runner g = Runner (forall a. '{g} a -> {} a) pureRunner : Runner {} @@ -35,7 +35,7 @@ runner = pureRunner ``` Application version: -```unison +``` unison structural type A g = A (forall a. '{g} a ->{} a) anA : A {} diff --git a/unison-src/transcripts/fix3171.output.md b/unison-src/transcripts/fix3171.output.md index 6a6ba0496..0fdaf8377 100644 --- a/unison-src/transcripts/fix3171.output.md +++ b/unison-src/transcripts/fix3171.output.md @@ -1,7 +1,7 @@ Tests an case where decompiling could cause function arguments to occur in the opposite order for partially applied functions. -```unison +``` unison f : Nat -> Nat -> Nat -> () -> Nat f x y z _ = x + y * z diff --git a/unison-src/transcripts/fix3196.output.md b/unison-src/transcripts/fix3196.output.md index 3a5e2944d..95f0764c0 100644 --- a/unison-src/transcripts/fix3196.output.md +++ b/unison-src/transcripts/fix3196.output.md @@ -1,11 +1,10 @@ - Tests ability checking in scenarios where one side is concrete and the other is a variable. This was supposed to be covered, but the method wasn't actually symmetric, so doing `equate l r` might work, but not `equate r l`. Below were cases that caused the failing order. -```unison +``` unison structural type W es = W unique ability Zoot where diff --git a/unison-src/transcripts/fix3215.output.md b/unison-src/transcripts/fix3215.output.md index aaa3e8f4c..492d69016 100644 --- a/unison-src/transcripts/fix3215.output.md +++ b/unison-src/transcripts/fix3215.output.md @@ -3,7 +3,7 @@ inferred type. This was due to the pre-pass that figures out which abilities are being matched on. It was just concatenating the ability for each pattern into a list, and not checking whether there were duplicates. -```unison +``` unison structural ability T where nat : Nat int : Int diff --git a/unison-src/transcripts/fix3244.output.md b/unison-src/transcripts/fix3244.output.md index 94231d174..5eca2f4f7 100644 --- a/unison-src/transcripts/fix3244.output.md +++ b/unison-src/transcripts/fix3244.output.md @@ -2,7 +2,7 @@ This tests an previously erroneous case in the pattern compiler. It was assuming that the variables bound in a guard matched the variables bound in the rest of the branch exactly, but apparently this needn't be the case. -```unison +``` unison foo t = (x, _) = t f w = w + x diff --git a/unison-src/transcripts/fix3265.output.md b/unison-src/transcripts/fix3265.output.md index 93e8db747..2db3893b8 100644 --- a/unison-src/transcripts/fix3265.output.md +++ b/unison-src/transcripts/fix3265.output.md @@ -1,12 +1,13 @@ Tests cases that produced bad decompilation output previously. There are three cases that need to be 'fixed up.' - 1. lambda expressions with free variables need to be beta reduced - 2. let defined functions need to have arguments removed and - occurrences rewritten. - 3. let-rec defined functions need to have arguments removed, but - it is a more complicated process. -```unison +1. lambda expressions with free variables need to be beta reduced +2. let defined functions need to have arguments removed and + occurrences rewritten. +3. let-rec defined functions need to have arguments removed, but + it is a more complicated process. + +``` unison > Any (w x -> let f0 y = match y with 0 -> x @@ -56,7 +57,7 @@ always occur with `x` as the first argument, but if we aren't careful, we might do that, because we find the first occurrence of `f`, and discard its arguments, where `f` also occurs. -```unison +``` unison > Any (x -> let f x y = match y with 0 -> 0 diff --git a/unison-src/transcripts/fix3634.output.md b/unison-src/transcripts/fix3634.output.md index 8648dd1cf..e06cd8fbc 100644 --- a/unison-src/transcripts/fix3634.output.md +++ b/unison-src/transcripts/fix3634.output.md @@ -1,4 +1,4 @@ -```unison +``` unison structural type M a = N | J a d = {{ diff --git a/unison-src/transcripts/fix3678.output.md b/unison-src/transcripts/fix3678.output.md index f99633e64..3b2754bdd 100644 --- a/unison-src/transcripts/fix3678.output.md +++ b/unison-src/transcripts/fix3678.output.md @@ -1,7 +1,6 @@ - Array comparison was indexing out of bounds. -```unison +``` unison arr = Scope.run do ma = Scope.arrayOf "asdf" 0 freeze! ma diff --git a/unison-src/transcripts/fix3752.output.md b/unison-src/transcripts/fix3752.output.md index fd477070b..fb52acd21 100644 --- a/unison-src/transcripts/fix3752.output.md +++ b/unison-src/transcripts/fix3752.output.md @@ -1,7 +1,7 @@ These were failing to type check before, because id was not generalized. -```unison +``` unison foo = do id x = _ = 1 diff --git a/unison-src/transcripts/fix3759.output.md b/unison-src/transcripts/fix3759.output.md index d4f1d9b2a..4f0db3fe5 100644 --- a/unison-src/transcripts/fix3759.output.md +++ b/unison-src/transcripts/fix3759.output.md @@ -1,5 +1,4 @@ - -```unison +``` unison unique type codebase.Foo = Foo Woot.state : Nat @@ -9,7 +8,7 @@ Woot.frobnicate : Nat Woot.frobnicate = 43 ``` -```unison +``` unison unique type Oog.Foo = Foo Text unique ability Blah where diff --git a/unison-src/transcripts/fix3773.output.md b/unison-src/transcripts/fix3773.output.md index 09027c3a1..e7f355fd0 100644 --- a/unison-src/transcripts/fix3773.output.md +++ b/unison-src/transcripts/fix3773.output.md @@ -1,5 +1,4 @@ - -```unison +``` unison foo = _ = 1 _ = 22 diff --git a/unison-src/transcripts/fix4172.output.md b/unison-src/transcripts/fix4172.output.md index da56c3940..436f79715 100644 --- a/unison-src/transcripts/fix4172.output.md +++ b/unison-src/transcripts/fix4172.output.md @@ -1,5 +1,4 @@ - -```unison +``` unison debug a = match Debug.toText a with None -> "" Some (Left a) -> a @@ -56,7 +55,7 @@ scratch/main> test Tip: Use view 1 to view the source of a test. ``` -```unison +``` unison bool = false ``` diff --git a/unison-src/transcripts/fix4280.output.md b/unison-src/transcripts/fix4280.output.md index 8b918418f..4c7fbb2de 100644 --- a/unison-src/transcripts/fix4280.output.md +++ b/unison-src/transcripts/fix4280.output.md @@ -1,4 +1,4 @@ -```unison +``` unison foo.bar._baz = 5 bonk : Nat diff --git a/unison-src/transcripts/fix4397.output.md b/unison-src/transcripts/fix4397.output.md index e80ab21d4..2cb173290 100644 --- a/unison-src/transcripts/fix4397.output.md +++ b/unison-src/transcripts/fix4397.output.md @@ -1,4 +1,4 @@ -```unison +``` unison structural type Foo f = Foo (f ()) unique type Baz = Baz (Foo Bar) diff --git a/unison-src/transcripts/fix4415.output.md b/unison-src/transcripts/fix4415.output.md index b6d881fa2..90d57f289 100644 --- a/unison-src/transcripts/fix4415.output.md +++ b/unison-src/transcripts/fix4415.output.md @@ -1,5 +1,4 @@ - -```unison +``` unison unique type Foo = Foo unique type sub.Foo = ``` diff --git a/unison-src/transcripts/fix4424.output.md b/unison-src/transcripts/fix4424.output.md index dbf505ced..1eb07ab2d 100644 --- a/unison-src/transcripts/fix4424.output.md +++ b/unison-src/transcripts/fix4424.output.md @@ -1,6 +1,6 @@ Some basics: -```unison +``` unison unique type Cat.Dog = Mouse Nat unique type Rat.Dog = Bird @@ -20,7 +20,7 @@ scratch/main> add ``` Now I want to add a constructor. -```unison +``` unison unique type Rat.Dog = Bird | Mouse ``` diff --git a/unison-src/transcripts/fix4482.output.md b/unison-src/transcripts/fix4482.output.md index d61ddd665..26a73068d 100644 --- a/unison-src/transcripts/fix4482.output.md +++ b/unison-src/transcripts/fix4482.output.md @@ -1,4 +1,4 @@ -```unison +``` unison lib.foo0.lib.bonk1.bar = 203 lib.foo0.baz = 1 lib.foo1.zonk = 204 @@ -53,7 +53,7 @@ myproj/main> upgrade foo0 foo1 to delete the temporary branch and switch back to main. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u mybar : Nat mybar = use Nat + diff --git a/unison-src/transcripts/fix4498.output.md b/unison-src/transcripts/fix4498.output.md index fb5bbd771..149d3406f 100644 --- a/unison-src/transcripts/fix4498.output.md +++ b/unison-src/transcripts/fix4498.output.md @@ -1,4 +1,4 @@ -```unison +``` unison lib.dep0.bonk.foo = 5 lib.dep0.zonk.foo = "hi" lib.dep0.lib.dep1.foo = 6 diff --git a/unison-src/transcripts/fix4515.output.md b/unison-src/transcripts/fix4515.output.md index e2f03e9d5..925195662 100644 --- a/unison-src/transcripts/fix4515.output.md +++ b/unison-src/transcripts/fix4515.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Foo1 unique type Bar = X Foo unique type Baz = X Foo @@ -35,7 +35,7 @@ myproject/main> add useBar : Bar -> Nat ``` -```unison +``` unison unique type Foo = Foo1 | Foo2 ``` diff --git a/unison-src/transcripts/fix4528.output.md b/unison-src/transcripts/fix4528.output.md index 4715b6f47..8b2d96fc3 100644 --- a/unison-src/transcripts/fix4528.output.md +++ b/unison-src/transcripts/fix4528.output.md @@ -1,4 +1,4 @@ -```unison +``` unison structural type Foo = MkFoo Nat main : () -> Foo diff --git a/unison-src/transcripts/fix4556.output.md b/unison-src/transcripts/fix4556.output.md index 2b4add6ca..f36c030d2 100644 --- a/unison-src/transcripts/fix4556.output.md +++ b/unison-src/transcripts/fix4556.output.md @@ -1,4 +1,4 @@ -```unison +``` unison thing = 3 foo.hello = 5 + thing bar.hello = 5 + thing @@ -32,7 +32,7 @@ scratch/main> add thing : Nat ``` -```unison +``` unison thing = 2 ``` diff --git a/unison-src/transcripts/fix4592.output.md b/unison-src/transcripts/fix4592.output.md index d1711bb55..1644f6c33 100644 --- a/unison-src/transcripts/fix4592.output.md +++ b/unison-src/transcripts/fix4592.output.md @@ -1,4 +1,4 @@ -```unison +``` unison doc = {{ {{ bug "bug" 52 }} }} ``` diff --git a/unison-src/transcripts/fix4618.output.md b/unison-src/transcripts/fix4618.output.md index 0b6a3921d..144c13a8d 100644 --- a/unison-src/transcripts/fix4618.output.md +++ b/unison-src/transcripts/fix4618.output.md @@ -1,4 +1,4 @@ -```unison +``` unison foo = 5 unique type Bugs.Zonk = Bugs ``` @@ -26,7 +26,7 @@ scratch/main> add foo : Nat ``` -```unison +``` unison foo = 4 unique type Bugs = ``` diff --git a/unison-src/transcripts/fix4722.output.md b/unison-src/transcripts/fix4722.output.md index 85611e9d9..91b071e5f 100644 --- a/unison-src/transcripts/fix4722.output.md +++ b/unison-src/transcripts/fix4722.output.md @@ -1,14 +1,13 @@ - Tests an improvement to type checking related to abilities. -`foo` below typechecks fine as long as all the branches are _checked_ +`foo` below typechecks fine as long as all the branches are *checked* against their expected type. However, it's annoying to have to annotate them. The old code was checking a match by just synthesizing and subtyping, but we can instead check a match by pushing the expected type into each case, allowing top-level annotations to act like annotations on each case. -```unison +``` unison ability X a where yield : {X a} () ability Y where y : () diff --git a/unison-src/transcripts/fix4780.output.md b/unison-src/transcripts/fix4780.output.md index 9338c3966..392060c34 100644 --- a/unison-src/transcripts/fix4780.output.md +++ b/unison-src/transcripts/fix4780.output.md @@ -1,7 +1,7 @@ Just a simple test case to see whether partially applied builtins decompile properly. -```unison +``` unison > (+) 2 ``` diff --git a/unison-src/transcripts/fix4898.output.md b/unison-src/transcripts/fix4898.output.md index c348778f2..62c4d6377 100644 --- a/unison-src/transcripts/fix4898.output.md +++ b/unison-src/transcripts/fix4898.output.md @@ -4,7 +4,7 @@ scratch/main> builtins.merge Done. ``` -```unison +``` unison double : Int -> Int double x = x + x diff --git a/unison-src/transcripts/fix5055.output.md b/unison-src/transcripts/fix5055.output.md index a9fe9ee5d..475edc5bd 100644 --- a/unison-src/transcripts/fix5055.output.md +++ b/unison-src/transcripts/fix5055.output.md @@ -4,7 +4,7 @@ test-5055/main> builtins.merge Done. ``` -```unison +``` unison foo.add x y = x Int.+ y foo.subtract x y = x Int.- y diff --git a/unison-src/transcripts/fix5080.output.md b/unison-src/transcripts/fix5080.output.md index c9d0b7c0c..67468e1b8 100644 --- a/unison-src/transcripts/fix5080.output.md +++ b/unison-src/transcripts/fix5080.output.md @@ -1,4 +1,4 @@ -```unison +``` unison test> fix5080.tests.success = [Ok "success"] test> fix5080.tests.failure = [Fail "fail"] ``` diff --git a/unison-src/transcripts/fix614.output.md b/unison-src/transcripts/fix614.output.md index b679698eb..770489a09 100644 --- a/unison-src/transcripts/fix614.output.md +++ b/unison-src/transcripts/fix614.output.md @@ -2,7 +2,7 @@ This transcript demonstrates that Unison forces actions in blocks to have a retu This works, as expected: -```unison +``` unison structural ability Stream a where emit : a -> () ex1 = do @@ -27,7 +27,7 @@ ex1 = do ``` This does not typecheck, we've accidentally underapplied `Stream.emit`: -```unison +``` unison ex2 = do Stream.emit 42 @@ -49,7 +49,7 @@ ex2 = do ``` We can explicitly ignore an unused result like so: -```unison +``` unison ex3 = do _ = Stream.emit () @@ -70,7 +70,7 @@ ex3 = do ``` Using a helper function like `void` also works fine: -```unison +``` unison void x = () ex4 = @@ -94,7 +94,7 @@ ex4 = ``` One more example: -```unison +``` unison ex4 = [1,2,3] -- no good () diff --git a/unison-src/transcripts/fix689.output.md b/unison-src/transcripts/fix689.output.md index 9bb9dcc06..06689cf64 100644 --- a/unison-src/transcripts/fix689.output.md +++ b/unison-src/transcripts/fix689.output.md @@ -1,6 +1,6 @@ Tests the fix for https://github.com/unisonweb/unison/issues/689 -```unison +``` unison structural ability SystemTime where systemTime : ##Nat diff --git a/unison-src/transcripts/fix693.output.md b/unison-src/transcripts/fix693.output.md index a5d037737..753e434f2 100644 --- a/unison-src/transcripts/fix693.output.md +++ b/unison-src/transcripts/fix693.output.md @@ -1,5 +1,4 @@ - -```unison +``` unison structural ability X t where x : t -> a -> a @@ -35,7 +34,7 @@ skolem variable `a` such that `c : a` and the continuation has type `a ->{X} b`. Thus, `handle c with h : Optional a`, which is not the correct result type. -```unison +``` unison h0 : Request {X t} b -> Optional b h0 req = match req with { X.x _ c -> _ } -> handle c with h0 @@ -63,7 +62,7 @@ h0 req = match req with ``` This code should not check because `t` does not match `b`. -```unison +``` unison h1 : Request {X t} b -> Optional b h1 req = match req with { X.x t _ -> _ } -> handle t with h1 @@ -92,7 +91,7 @@ h1 req = match req with This code should not check for reasons similar to the first example, but with the continuation rather than a parameter. -```unison +``` unison h2 : Request {Abort} r -> r h2 req = match req with { Abort.abort -> k } -> handle k 5 with h2 @@ -114,7 +113,7 @@ h2 req = match req with ``` This should work fine. -```unison +``` unison h3 : Request {X b, Abort} b -> Optional b h3 = cases { r } -> Some r diff --git a/unison-src/transcripts/fix845.output.md b/unison-src/transcripts/fix845.output.md index fbdc9fc73..6b910d67e 100644 --- a/unison-src/transcripts/fix845.output.md +++ b/unison-src/transcripts/fix845.output.md @@ -1,7 +1,6 @@ - Add `List.zonk` to the codebase: -```unison +``` unison List.zonk : [a] -> [a] List.zonk xs = xs @@ -25,7 +24,7 @@ Text.zonk txt = txt ++ "!! " ``` Now, typecheck a file with a reference to `Blah.zonk` (which doesn't exist in the codebase). This should fail: -```unison +``` unison -- should not typecheck as there's no `Blah.zonk` in the codebase > Blah.zonk [1,2,3] ``` @@ -52,7 +51,7 @@ Now, typecheck a file with a reference to `Blah.zonk` (which doesn't exist in th ``` Here's another example, just checking that TDNR works for definitions in the same file: -```unison +``` unison foo.bar.baz = 42 qux.baz = "hello" @@ -86,7 +85,7 @@ ex = baz ++ ", world!" ``` Here's another example, checking that TDNR works when multiple codebase definitions have matching names: -```unison +``` unison ex = zonk "hi" > ex @@ -114,7 +113,7 @@ ex = zonk "hi" ``` Last example, showing that TDNR works when there are multiple matching names in both the file and the codebase: -```unison +``` unison woot.zonk = "woot" woot2.zonk = 9384 diff --git a/unison-src/transcripts/fix849.output.md b/unison-src/transcripts/fix849.output.md index 33720e550..f1775f630 100644 --- a/unison-src/transcripts/fix849.output.md +++ b/unison-src/transcripts/fix849.output.md @@ -1,7 +1,6 @@ - See [this ticket](https://github.com/unisonweb/unison/issues/849). -```unison +``` unison x = 42 > x diff --git a/unison-src/transcripts/fix942.output.md b/unison-src/transcripts/fix942.output.md index 68ec09bba..13d68377a 100644 --- a/unison-src/transcripts/fix942.output.md +++ b/unison-src/transcripts/fix942.output.md @@ -1,6 +1,6 @@ First we add some code: -```unison +``` unison x = 0 y = x + 1 z = y + 2 @@ -33,7 +33,7 @@ scratch/main> add ``` Now we edit `x` to be `7`, which should make `z` equal `10`: -```unison +``` unison x = 7 ``` @@ -79,9 +79,9 @@ scratch/main> view x y z y + 2 ``` -Uh oh! `z` is still referencing the old version. Just to confirm: +Uh oh\! `z` is still referencing the old version. Just to confirm: -```unison +``` unison test> t1 = if z == 3 then [Fail "nooo!!!"] else [Ok "great"] ``` diff --git a/unison-src/transcripts/fix987.output.md b/unison-src/transcripts/fix987.output.md index 50d747862..e816b3808 100644 --- a/unison-src/transcripts/fix987.output.md +++ b/unison-src/transcripts/fix987.output.md @@ -1,7 +1,6 @@ - First we'll add a definition: -```unison +``` unison structural ability DeathStar where attack : Text -> () @@ -38,7 +37,7 @@ scratch/main> add ``` Now we'll try to add a different definition that runs the actions in a different order. This should work fine: -```unison +``` unison spaceAttack2 x = z = attack "neptune" y = attack "saturn" @@ -67,3 +66,4 @@ scratch/main> add ``` Previously, this would fail because the hashing algorithm was being given one big let rec block whose binding order was normalized. + diff --git a/unison-src/transcripts/formatter.output.md b/unison-src/transcripts/formatter.output.md index ce931ed31..1b16b7def 100644 --- a/unison-src/transcripts/formatter.output.md +++ b/unison-src/transcripts/formatter.output.md @@ -1,4 +1,4 @@ -```unison +``` unison {{ # Doc This is a *doc*! @@ -87,7 +87,7 @@ with a strike-through block~ scratch/main> debug.format ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u x.doc = {{ # Doc This is a **doc**! @@ -167,7 +167,7 @@ multilineBold = Formatter should leave things alone if the file doesn't typecheck. -```unison +``` unison brokenDoc = {{ hello }} + 1 ``` diff --git a/unison-src/transcripts/fuzzy-options.output.md b/unison-src/transcripts/fuzzy-options.output.md index 290d07aab..f07d39906 100644 --- a/unison-src/transcripts/fuzzy-options.output.md +++ b/unison-src/transcripts/fuzzy-options.output.md @@ -2,7 +2,6 @@ If an argument is required but doesn't have a fuzzy resolver, the command should just print the help. - ```ucm -- The second argument of move.term is a 'new-name' and doesn't have a fuzzy resolver scratch/main> move.term @@ -21,7 +20,7 @@ scratch/empty> view Sorry, I was expecting an argument for the definition to view, and I couldn't find any to suggest to you. 😅 ``` -```unison +``` unison optionOne = 1 nested.optionTwo = 2 diff --git a/unison-src/transcripts/generic-parse-errors.output.md b/unison-src/transcripts/generic-parse-errors.output.md index 7800cbab4..b0f6d6a5b 100644 --- a/unison-src/transcripts/generic-parse-errors.output.md +++ b/unison-src/transcripts/generic-parse-errors.output.md @@ -1,6 +1,6 @@ Just a bunch of random parse errors to test the error formatting. -```unison +``` unison x = foo.123 ``` @@ -22,7 +22,7 @@ x = * identifier (ex: abba1, snake_case, .foo.bar#xyz, .foo.++#xyz, or 🌻) ``` -```unison +``` unison namespace.blah = 1 ``` @@ -38,7 +38,7 @@ namespace.blah = 1 or wrapping it in backticks (like `namespace` ). ``` -```unison +``` unison x = 1 ] ``` @@ -52,7 +52,7 @@ x = 1 ] ``` -```unison +``` unison x = a.#abc ``` @@ -68,7 +68,7 @@ x = a.#abc I was surprised to find a '.' here. ``` -```unison +``` unison x = "hi ``` @@ -78,7 +78,8 @@ x = "hi I got confused here: - 2 | + 1 | x = "hi + I was surprised to find an end of input here. I was expecting one of these instead: @@ -88,7 +89,7 @@ x = "hi * literal character ``` -```unison +``` unison y : a ``` @@ -98,7 +99,8 @@ y : a I got confused here: - 2 | + 1 | y : a + I was surprised to find an end of section here. I was expecting one of these instead: diff --git a/unison-src/transcripts/hello.output.md b/unison-src/transcripts/hello.output.md index e6d03ea95..3c5d9bc8c 100644 --- a/unison-src/transcripts/hello.output.md +++ b/unison-src/transcripts/hello.output.md @@ -1,29 +1,25 @@ - -# Hello! +# Hello\! This markdown file is also a Unison transcript file. Transcript files are an easy way to create self-documenting Unison programs, libraries, and tutorials. The format is just a regular markdown file with some fenced code blocks that are typechecked and elaborated by `ucm`. For example, you can call this transcript via: -``` -$ ucm transcript hello.md - -``` + $ ucm transcript hello.md This runs it on a freshly generated empty codebase. Alternately `ucm transcript.fork --codebase /path/to/code hello.md` runs the transcript on a freshly generated copy of the provided codebase. Do `ucm help` to learn more about usage. Fenced code blocks of type `unison` and `ucm` are treated specially: -* `ucm` blocks are executed, and the output is interleaved into the output markdown file after each command, replacing the original `ucm` block. -* `unison` blocks are typechecked, and a `ucm` block with the output of typechecking and execution of the file is inserted immediately afterwards. + - `ucm` blocks are executed, and the output is interleaved into the output markdown file after each command, replacing the original `ucm` block. + - `unison` blocks are typechecked, and a `ucm` block with the output of typechecking and execution of the file is inserted immediately afterwards. Take a look at [the elaborated output](hello.output.md) to see what this file looks like after passing through the transcript runner. -## Let's try it out!! +## Let's try it out\!\! In the `unison` fenced block, you can give an (optional) file name (defaults to `scratch.u`), like so: -```unison +``` unison --- title: myfile.u --- @@ -31,7 +27,6 @@ x = 42 ``` - ```ucm Loading changes detected in myfile.u. @@ -66,7 +61,7 @@ If `view` returned no results, the transcript would fail at this point. You may not always want to view the output of typechecking and evaluation every time, in which case, you can add `:hide` to the block. For instance: -```unison +``` unison y = 99 ``` @@ -76,9 +71,9 @@ Doing `unison:hide:all` hides the block altogether, both input and output - this ## Expecting failures -Sometimes, you have a block which you are _expecting_ to fail, perhaps because you're illustrating how something would be a type error. Adding `:error` to the block will check for this. For instance, this program has a type error: +Sometimes, you have a block which you are *expecting* to fail, perhaps because you're illustrating how something would be a type error. Adding `:error` to the block will check for this. For instance, this program has a type error: -```unison +``` unison hmm : .builtin.Nat hmm = "Not, in fact, a number" ``` diff --git a/unison-src/transcripts/help.output.md b/unison-src/transcripts/help.output.md index 27a6d7489..54662d0c9 100644 --- a/unison-src/transcripts/help.output.md +++ b/unison-src/transcripts/help.output.md @@ -966,3 +966,4 @@ scratch/main> help-topic testcache ``` We should add a command to show help for hidden commands also. + diff --git a/unison-src/transcripts/higher-rank.output.md b/unison-src/transcripts/higher-rank.output.md index 2054583f6..f4c2dbf50 100644 --- a/unison-src/transcripts/higher-rank.output.md +++ b/unison-src/transcripts/higher-rank.output.md @@ -1,9 +1,8 @@ - This transcript does some testing of higher-rank types. Regression tests related to higher-rank types can be added here. In this example, a higher-rank function is defined, `f`. No annotation is needed at the call-site of `f`, because the lambda is being checked against the polymorphic type `forall a . a -> a`, rather than inferred: -```unison +``` unison f : (forall a . a -> a) -> (Nat, Text) f id = (id 1, id "hi") @@ -32,7 +31,7 @@ f id = (id 1, id "hi") ``` Another example, involving abilities. Here the ability-polymorphic function is instantiated with two different ability lists, `{}` and `{IO}`: -```unison +``` unison f : (forall a g . '{g} a -> '{g} a) -> () -> () f id _ = _ = (id ('1 : '{} Nat), id ('("hi") : '{IO} Text)) @@ -54,7 +53,7 @@ f id _ = ``` Here's an example, showing that polymorphic functions can be fields of a constructor, and the functions remain polymorphic even when the field is bound to a name during pattern matching: -```unison +``` unison unique type Functor f = Functor (forall a b . (a -> b) -> f a -> f b) Functor.map : Functor f -> (forall a b . (a -> b) -> f a -> f b) @@ -85,7 +84,7 @@ Functor.blah = cases Functor f -> ``` This example is similar, but involves abilities: -```unison +``` unison unique ability Remote t where doRemoteStuff : t () unique type Loc = Loc (forall t a . '{Remote t} a ->{Remote t} t a) @@ -134,7 +133,7 @@ Loc.transform2 nt = cases Loc f -> ``` ## Types with polymorphic fields -```unison +``` unison structural type HigherRanked = HigherRanked (forall a. a -> a) ``` diff --git a/unison-src/transcripts/input-parse-errors.output.md b/unison-src/transcripts/input-parse-errors.output.md index ee1af109d..2e00b284c 100644 --- a/unison-src/transcripts/input-parse-errors.output.md +++ b/unison-src/transcripts/input-parse-errors.output.md @@ -1,10 +1,11 @@ # demonstrating our new input parsing errors -```unison +``` unison x = 55 ``` `handleNameArg` parse error in `add` + ```ucm scratch/main> add . @@ -42,8 +43,8 @@ scratch/main> add 2 ``` todo: -```haskell +``` haskell SA.Name name -> pure name SA.NameWithBranchPrefix (Left _) name -> pure name SA.NameWithBranchPrefix (Right prefix) name -> pure $ Path.prefixNameIfRel (Path.AbsolutePath' prefix) name @@ -56,7 +57,6 @@ todo: SA.SearchResult mpath result -> maybe (Left "can’t find a name from the numbered arg") pure . HQ.toName $ searchResultToHQ mpath result otherNumArg -> Left . I.Formatted $ wrongStructuredArgument "a name" otherNumArg - ``` aliasMany: skipped -- similar to `add` @@ -75,18 +75,17 @@ You can run `help update` for more information on using ``` aliasTerm -```scratch -/main> alias.term ##Nat.+ Nat.+ -``` + scratch/main> alias.term ##Nat.+ Nat.+ aliasTermForce, aliasType, - todo: -```alias -Many, + +``` + +aliasMany, api, authLogin, back, @@ -202,6 +201,5 @@ upgradeCommitInputPattern, view, viewGlobal, viewReflog - ``` diff --git a/unison-src/transcripts/io-test-command.output.md b/unison-src/transcripts/io-test-command.output.md index ec848f23d..65abcdab6 100644 --- a/unison-src/transcripts/io-test-command.output.md +++ b/unison-src/transcripts/io-test-command.output.md @@ -1,6 +1,6 @@ The `io.test` command should run all of the tests within the current namespace, excluding libs. -```unison +``` unison -- We manually specify types so we don't need to pull in base to run IO and such ioAndExceptionTest : '{IO, Exception} [Result] ioAndExceptionTest = do @@ -15,7 +15,7 @@ lib.ioAndExceptionTestInLib = do [Ok "Success"] ``` -Run a IO tests one by one +Run a IO tests one by one ```ucm scratch/main> io.test ioAndExceptionTest diff --git a/unison-src/transcripts/io.output.md b/unison-src/transcripts/io.output.md index cbc177145..2cdaeea0e 100644 --- a/unison-src/transcripts/io.output.md +++ b/unison-src/transcripts/io.output.md @@ -14,12 +14,12 @@ create a scratch directory which will automatically get cleaned up. ### Creating/Deleting/Renaming Directories Tests: createDirectory, - isDirectory, - fileExists, - renameDirectory, - deleteDirectory +isDirectory, +fileExists, +renameDirectory, +deleteDirectory -```unison +``` unison testCreateRename : '{io2.IO} [Result] testCreateRename _ = test = 'let @@ -85,10 +85,10 @@ scratch/main> io.test testCreateRename ### Opening / Closing files Tests: openFile - closeFile - isFileOpen +closeFile +isFileOpen -```unison +``` unison testOpenClose : '{io2.IO} [Result] testOpenClose _ = test = 'let @@ -166,11 +166,11 @@ scratch/main> io.test testOpenClose ### Reading files with getSomeBytes Tests: getSomeBytes - putBytes - isFileOpen - seekHandle +putBytes +isFileOpen +seekHandle -```unison +``` unison testGetSomeBytes : '{io2.IO} [Result] testGetSomeBytes _ = test = 'let @@ -258,15 +258,15 @@ scratch/main> io.test testGetSomeBytes ### Seeking in open files Tests: openFile - putBytes - closeFile - isSeekable - isFileEOF - seekHandle - getBytes - getLine +putBytes +closeFile +isSeekable +isFileEOF +seekHandle +getBytes +getLine -```unison +``` unison testSeek : '{io2.IO} [Result] testSeek _ = test = 'let @@ -374,7 +374,8 @@ scratch/main> io.test testAppend ``` ### SystemTime -```unison + +``` unison testSystemTime : '{io2.IO} [Result] testSystemTime _ = test = 'let @@ -417,7 +418,7 @@ scratch/main> io.test testSystemTime ``` ### Get temp directory -```unison +``` unison testGetTempDirectory : '{io2.IO} [Result] testGetTempDirectory _ = test = 'let @@ -448,7 +449,7 @@ scratch/main> io.test testGetTempDirectory ``` ### Get current directory -```unison +``` unison testGetCurrentDirectory : '{io2.IO} [Result] testGetCurrentDirectory _ = test = 'let @@ -479,7 +480,7 @@ scratch/main> io.test testGetCurrentDirectory ``` ### Get directory contents -```unison +``` unison testDirContents : '{io2.IO} [Result] testDirContents _ = test = 'let @@ -512,7 +513,7 @@ scratch/main> io.test testDirContents ``` ### Read environment variables -```unison +``` unison testGetEnv : '{io2.IO} [Result] testGetEnv _ = test = 'let @@ -548,7 +549,7 @@ scratch/main> io.test testGetEnv `runMeWithNoArgs`, `runMeWithOneArg`, and `runMeWithTwoArgs` raise exceptions unless they called with the right number of arguments. -```unison +``` unison testGetArgs.fail : Text -> Failure testGetArgs.fail descr = Failure (typeLink IOFailure) descr !Any @@ -578,6 +579,7 @@ testGetArgs.runMeWithTwoArgs = 'let ``` Test that they can be run with the right number of args. + ```ucm scratch/main> add @@ -658,7 +660,7 @@ scratch/main> run runMeWithTwoArgs ``` ### Get the time zone -```unison +``` unison testTimeZone = do (offset, summer, name) = Clock.internals.systemTimeZone +0 _ = (offset : Int, summer : Nat, name : Text) @@ -679,7 +681,7 @@ scratch/main> run testTimeZone ``` ### Get some random bytes -```unison +``` unison testRandom : '{io2.IO} [Result] testRandom = do test = do diff --git a/unison-src/transcripts/keyword-identifiers.output.md b/unison-src/transcripts/keyword-identifiers.output.md index 03ed3e919..27a31d6f3 100644 --- a/unison-src/transcripts/keyword-identifiers.output.md +++ b/unison-src/transcripts/keyword-identifiers.output.md @@ -4,34 +4,34 @@ In particular, following a keyword with a `wordyIdChar` should be a valid identi Related issues: -- https://github.com/unisonweb/unison/issues/2091 -- https://github.com/unisonweb/unison/issues/2727 + - https://github.com/unisonweb/unison/issues/2091 + - https://github.com/unisonweb/unison/issues/2727 ## Keyword list Checks the following keywords: -- `type` -- `ability` -- `structural` -- `unique` -- `if` -- `then` -- `else` -- `forall` -- `handle` -- `with` -- `where` -- `use` -- `true` -- `false` -- `alias` -- `typeLink` -- `termLink` -- `let` -- `namespace` -- `match` -- `cases` + - `type` + - `ability` + - `structural` + - `unique` + - `if` + - `then` + - `else` + - `forall` + - `handle` + - `with` + - `where` + - `use` + - `true` + - `false` + - `alias` + - `typeLink` + - `termLink` + - `let` + - `namespace` + - `match` + - `cases` Note that although `∀` is a keyword, it cannot actually appear at the start of identifier. @@ -40,7 +40,7 @@ identifier. `type`: -```unison +``` unison typeFoo = 99 type1 = "I am a variable" type_ = 292 @@ -52,7 +52,7 @@ structural type type! type_ = type' type_ | type'' `ability`: -```unison +``` unison abilityFoo = 99 ability1 = "I am a variable" ability_ = 292 @@ -63,7 +63,7 @@ structural type ability! ability_ = ability' ability_ | ability'' `structural` -```unison +``` unison structuralFoo = 99 structural1 = "I am a variable" structural_ = 292 @@ -74,7 +74,7 @@ structural type structural! structural_ = structural' structural_ | structural'' `unique` -```unison +``` unison uniqueFoo = 99 unique1 = "I am a variable" unique_ = 292 @@ -85,7 +85,7 @@ structural type unique! unique_ = unique' unique_ | unique'' `if` -```unison +``` unison ifFoo = 99 if1 = "I am a variable" if_ = 292 @@ -96,7 +96,7 @@ structural type if! if_ = if' if_ | if'' `then` -```unison +``` unison thenFoo = 99 then1 = "I am a variable" then_ = 292 @@ -107,7 +107,7 @@ structural type then! then_ = then' then_ | then'' `else` -```unison +``` unison elseFoo = 99 else1 = "I am a variable" else_ = 292 @@ -118,7 +118,7 @@ structural type else! else_ = else' else_ | else'' `forall` -```unison +``` unison forallFoo = 99 forall1 = "I am a variable" forall_ = 292 @@ -129,7 +129,7 @@ structural type forall! forall_ = forall' forall_ | forall'' `handle` -```unison +``` unison handleFoo = 99 handle1 = "I am a variable" handle_ = 292 @@ -140,7 +140,7 @@ structural type handle! handle_ = handle' handle_ | handle'' `with` -```unison +``` unison withFoo = 99 with1 = "I am a variable" with_ = 292 @@ -151,7 +151,7 @@ structural type with! with_ = with' with_ | with'' `where` -```unison +``` unison whereFoo = 99 where1 = "I am a variable" where_ = 292 @@ -162,7 +162,7 @@ structural type where! where_ = where' where_ | where'' `use` -```unison +``` unison useFoo = 99 use1 = "I am a variable" use_ = 292 @@ -173,7 +173,7 @@ structural type use! use_ = use' use_ | use'' `true` -```unison +``` unison trueFoo = 99 true1 = "I am a variable" true_ = 292 @@ -184,7 +184,7 @@ structural type true! true_ = true' true_ | true'' `false` -```unison +``` unison falseFoo = 99 false1 = "I am a variable" false_ = 292 @@ -195,7 +195,7 @@ structural type false! false_ = false' false_ | false'' `alias` -```unison +``` unison aliasFoo = 99 alias1 = "I am a variable" alias_ = 292 @@ -206,7 +206,7 @@ structural type alias! alias_ = alias' alias_ | alias'' `typeLink` -```unison +``` unison typeLinkFoo = 99 typeLink1 = "I am a variable" typeLink_ = 292 @@ -217,7 +217,7 @@ structural type typeLink! typeLink_ = typeLink' typeLink_ | typeLink'' `termLink` -```unison +``` unison termLinkFoo = 99 termLink1 = "I am a variable" termLink_ = 292 @@ -228,7 +228,7 @@ structural type termLink! termLink_ = termLink' termLink_ | termLink'' `let` -```unison +``` unison letFoo = 99 let1 = "I am a variable" let_ = 292 @@ -239,7 +239,7 @@ structural type let! let_ = let' let_ | let'' `namespace` -```unison +``` unison namespaceFoo = 99 namespace1 = "I am a variable" namespace_ = 292 @@ -250,7 +250,7 @@ structural type namespace! namespace_ = namespace' namespace_ | namespace'' `match` -```unison +``` unison matchFoo = 99 match1 = "I am a variable" match_ = 292 @@ -261,7 +261,7 @@ structural type match! match_ = match' match_ | match'' `cases` -```unison +``` unison casesFoo = 99 cases1 = "I am a variable" cases_ = 292 diff --git a/unison-src/transcripts/kind-inference.output.md b/unison-src/transcripts/kind-inference.output.md index 73fb41d2d..46a335a20 100644 --- a/unison-src/transcripts/kind-inference.output.md +++ b/unison-src/transcripts/kind-inference.output.md @@ -1,8 +1,8 @@ - ## A type param cannot have conflicting kind constraints within a single decl conflicting constraints on the kind of `a` in a product -```unison + +``` unison unique type T a = T a (a Nat) ``` @@ -17,7 +17,8 @@ unique type T a = T a (a Nat) ``` conflicting constraints on the kind of `a` in a sum -```unison + +``` unison unique type T a = Star a | StarStar (a Nat) @@ -37,7 +38,8 @@ unique type T a Successfully infer `a` in `Ping a` to be of kind `* -> *` by inspecting its component-mate `Pong`. -```unison + +``` unison unique type Ping a = Ping Pong unique type Pong = Pong (Ping Optional) ``` @@ -58,7 +60,8 @@ unique type Pong = Pong (Ping Optional) ``` Catch the conflict on the kind of `a` in `Ping a`. `Ping` restricts `a` to `*`, whereas `Pong` restricts `a` to `* -> *`. -```unison + +``` unison unique type Ping a = Ping a Pong unique type Pong = Pong (Ping Optional) ``` @@ -75,7 +78,8 @@ unique type Pong = Pong (Ping Optional) ``` Successful example between mutually recursive type and ability -```unison + +``` unison unique type Ping a = Ping (a Nat -> {Pong Nat} ()) unique ability Pong a where pong : Ping Optional -> () @@ -96,7 +100,8 @@ unique ability Pong a where ``` Catch conflict between mutually recursive type and ability -```unison + +``` unison unique type Ping a = Ping (a -> {Pong Nat} ()) unique ability Pong a where pong : Ping Optional -> () @@ -114,7 +119,8 @@ unique ability Pong a where ``` Consistent instantiation of `T`'s `a` parameter in `S` -```unison + +``` unison unique type T a = T a unique type S = S (T Nat) @@ -137,7 +143,8 @@ unique type S = S (T Nat) Delay kind defaulting until all components are processed. Here `S` constrains the kind of `T`'s `a` parameter, although `S` is not in the same component as `T`. -```unison + +``` unison unique type T a = T unique type S = S (T Optional) @@ -158,7 +165,8 @@ unique type S = S (T Optional) ``` Catch invalid instantiation of `T`'s `a` parameter in `S` -```unison + +``` unison unique type T a = T a unique type S = S (T Optional) @@ -178,7 +186,8 @@ unique type S = S (T Optional) ## Checking annotations Catch kind error in type annotation -```unison + +``` unison test : Nat Nat test = 0 ``` @@ -195,7 +204,8 @@ test = 0 ``` Catch kind error in annotation example 2 -```unison + +``` unison test : Optional -> () test _ = () ``` @@ -212,7 +222,8 @@ test _ = () ``` Catch kind error in annotation example 3 -```unison + +``` unison unique type T a = T (a Nat) test : T Nat -> () @@ -231,7 +242,8 @@ test _ = () ``` Catch kind error in scoped type variable annotation -```unison + +``` unison unique type StarStar a = StarStar (a Nat) unique type Star a = Star a @@ -256,7 +268,8 @@ test _ = ## Effect/type mismatch Effects appearing where types are expected -```unison + +``` unison unique ability Foo where foo : () @@ -276,7 +289,8 @@ test _ = () ``` Types appearing where effects are expected -```unison + +``` unison test : {Nat} () test _ = () ``` @@ -295,7 +309,7 @@ test _ = () ``` ## Cyclic kinds -```unison +``` unison unique type T a = T (a a) ``` @@ -311,7 +325,7 @@ unique type T a = T (a a) is the kind of a. ``` -```unison +``` unison unique type T a b = T (a b) (b a) ``` @@ -327,7 +341,7 @@ unique type T a b = T (a b) (b a) k = (k -> Type) -> Type where k is the kind of b. ``` -```unison +``` unison unique type Ping a = Ping (a Pong) unique type Pong a = Pong (a Ping) ``` diff --git a/unison-src/transcripts/lambdacase.output.md b/unison-src/transcripts/lambdacase.output.md index 2e55001a9..86fd5b234 100644 --- a/unison-src/transcripts/lambdacase.output.md +++ b/unison-src/transcripts/lambdacase.output.md @@ -2,7 +2,7 @@ This function takes a single argument and immediately pattern matches on it. As we'll see below, it can be written using `cases` syntax: -```unison +``` unison isEmpty x = match x with [] -> true _ -> false @@ -23,7 +23,7 @@ isEmpty x = match x with ``` Here's the same function written using `cases` syntax: -```unison +``` unison isEmpty2 = cases [] -> true _ -> false @@ -60,7 +60,7 @@ it shows the definition using `cases` syntax opportunistically, even though the Functions that take multiple arguments and immediately match on a tuple of arguments can also be rewritten to use `cases`. Here's a version using regular `match` syntax on a tuple: -```unison +``` unison merge : [a] -> [a] -> [a] merge xs ys = match (xs, ys) with ([], ys) -> ys @@ -80,7 +80,7 @@ scratch/main> add ``` And here's a version using `cases`. The patterns are separated by commas: -```unison +``` unison merge2 : [a] -> [a] -> [a] merge2 = cases [], ys -> ys @@ -122,7 +122,7 @@ it again shows the definition using the multi-argument `cases` syntax opportunis Here's another example: -```unison +``` unison structural type B = T | F blah : B -> B -> Text @@ -171,7 +171,7 @@ blorf = cases ``` ## Patterns with multiple guards -```unison +``` unison merge3 : [a] -> [a] -> [a] merge3 = cases [], ys -> ys @@ -213,7 +213,7 @@ scratch/main> view merge3 ``` This is the same definition written with multiple patterns and not using the `cases` syntax; notice it is considered an alias of `merge3` above. -```unison +``` unison merge4 : [a] -> [a] -> [a] merge4 a b = match (a,b) with [], ys -> ys diff --git a/unison-src/transcripts/lsp-fold-ranges.output.md b/unison-src/transcripts/lsp-fold-ranges.output.md index 2b76b3ff4..f2af4461b 100644 --- a/unison-src/transcripts/lsp-fold-ranges.output.md +++ b/unison-src/transcripts/lsp-fold-ranges.output.md @@ -1,4 +1,4 @@ -```unison +``` unison {{ Type doc }} structural type Optional a = None diff --git a/unison-src/transcripts/lsp-name-completion.output.md b/unison-src/transcripts/lsp-name-completion.output.md index 622d415f4..0b57f6a98 100644 --- a/unison-src/transcripts/lsp-name-completion.output.md +++ b/unison-src/transcripts/lsp-name-completion.output.md @@ -1,4 +1,4 @@ -```unison +``` unison foldMap = "top-level" nested.deeply.foldMap = "nested" lib.base.foldMap = "lib" @@ -29,6 +29,7 @@ scratch/main> debug.lsp-name-completion foldMap ``` Should still find the term which has a matching hash to a better name if the better name doesn't match. + ```ucm scratch/main> debug.lsp-name-completion transitive_same_hash.foldMap diff --git a/unison-src/transcripts/merge.output.md b/unison-src/transcripts/merge.output.md index a8a97adb6..d67d0355b 100644 --- a/unison-src/transcripts/merge.output.md +++ b/unison-src/transcripts/merge.output.md @@ -30,18 +30,21 @@ contains both additions. ## Basic merge: two unconflicted adds Alice's adds: -```unison + +``` unison foo : Text foo = "alices foo" ``` Bob's adds: -```unison + +``` unison bar : Text bar = "bobs bar" ``` Merge result: + ```ucm project/alice> merge /bob @@ -61,13 +64,15 @@ project/alice> view foo bar If Alice and Bob also happen to add the same definition, that's not a conflict. Alice's adds: -```unison + +``` unison foo : Text foo = "alice and bobs foo" ``` Bob's adds: -```unison + +``` unison foo : Text foo = "alice and bobs foo" @@ -76,6 +81,7 @@ bar = "bobs bar" ``` Merge result: + ```ucm project/alice> merge /bob @@ -95,19 +101,22 @@ project/alice> view foo bar Updates that occur in one branch are propagated to the other. In this example, Alice updates `foo`, while Bob adds a new dependent `bar` of the original `foo`. When Bob's branch is merged into Alice's, her update to `foo` is propagated to his `bar`. Original branch: -```unison + +``` unison foo : Text foo = "old foo" ``` Alice's updates: -```unison + +``` unison foo : Text foo = "new foo" ``` Bob's adds: -```unison + +``` unison bar : Text bar = foo ++ " - " ++ foo ``` @@ -119,6 +128,7 @@ project/bob> display bar ``` Merge result: + ```ucm project/alice> merge /bob @@ -146,7 +156,8 @@ We classify something as an update if its "syntactic hash"—not its normal Unis Let's see an example. We have `foo`, which depends on `bar` and `baz`. Alice updates `bar` (propagating to `foo`), and Bob updates `baz` (propagating to `foo`). When we merge their updates, both updates will be reflected in the final `foo`. Original branch: -```unison + +``` unison foo : Text foo = "foo" ++ " - " ++ bar ++ " - " ++ baz @@ -158,7 +169,8 @@ baz = "old baz" ``` Alice's updates: -```unison + +``` unison bar : Text bar = "alices bar" ``` @@ -170,7 +182,8 @@ project/alice> display foo ``` Bob's updates: -```unison + +``` unison baz : Text baz = "bobs baz" ``` @@ -182,6 +195,7 @@ project/bob> display foo ``` Merge result: + ```ucm project/alice> merge /bob @@ -210,7 +224,8 @@ project/alice> display foo Of course, it's also possible for Alice's update to propagate to one of Bob's updates. In this example, `foo` depends on `bar` which depends on `baz`. Alice updates `baz`, propagating to `bar` and `foo`, while Bob updates `bar` (to something that still depends on `foo`), propagating to `baz`. The merged result will have Alice's update to `foo` incorporated into Bob's updated `bar`, and both updates will propagate to `baz`. Original branch: -```unison + +``` unison foo : Text foo = "old foo" ++ " - " ++ bar @@ -228,7 +243,8 @@ project/main> display foo ``` Alice's updates: -```unison + +``` unison baz : Text baz = "alices baz" ``` @@ -240,7 +256,8 @@ project/alice> display foo ``` Bob's updates: -```unison + +``` unison bar : Text bar = "bobs bar" ++ " - " ++ baz ``` @@ -252,6 +269,7 @@ project/bob> display foo ``` Merge result: + ```ucm project/alice> merge /bob @@ -282,18 +300,21 @@ project/alice> display foo We don't currently consider "update + delete" a conflict like Git does. In this situation, the delete is just ignored, allowing the update to proceed. Original branch: -```unison + +``` unison foo : Text foo = "old foo" ``` Alice's updates: -```unison + +``` unison foo : Text foo = "alices foo" ``` Bob's changes: + ```ucm project/bob> delete.term foo @@ -301,6 +322,7 @@ project/bob> delete.term foo ``` Merge result: + ```ucm project/alice> merge /bob @@ -319,7 +341,8 @@ In a future version, we'd like to give the user a warning at least. Library dependencies don't cause merge conflicts, the library dependencies are just unioned together. If two library dependencies have the same name but different namespace hashes, then the merge algorithm makes up two fresh names. Alice's adds: -```unison + +``` unison lib.alice.foo : Nat lib.alice.foo = 17 @@ -331,7 +354,8 @@ lib.bothDifferent.baz = 19 ``` Bob's adds: -```unison + +``` unison lib.bob.foo : Nat lib.bob.foo = 20 @@ -343,6 +367,7 @@ lib.bothDifferent.baz = 21 ``` Merge result: + ```ucm project/alice> merge bob @@ -392,7 +417,7 @@ project/alice> merge /bob project/alice was already up-to-date with project/bob. ``` -## No-op merge (Bob < Alice) +## No-op merge (Bob \< Alice) If Bob is behind Alice, then merging Bob into Alice looks like this. @@ -413,7 +438,8 @@ project/main> branch bob ``` Alice's addition: -```unison + +``` unison foo : Text foo = "foo" ``` @@ -432,7 +458,7 @@ project/alice> merge /bob project/alice was already up-to-date with project/bob. ``` -## Fast-forward merge (Bob > Alice) +## Fast-forward merge (Bob \> Alice) If Bob is ahead of Alice, then merging Bob into Alice looks like this. @@ -453,7 +479,8 @@ project/main> branch bob ``` Bob's addition: -```unison + +``` unison foo : Text foo = "foo" ``` @@ -496,12 +523,14 @@ This can cause merge failures due to out-of-scope identifiers, and the user may In this example, Alice deletes `foo`, while Bob adds a new dependent of `foo`. Original branch: -```unison + +``` unison foo : Text foo = "foo" ``` Alice's delete: + ```ucm project/alice> delete.term foo @@ -509,7 +538,8 @@ project/alice> delete.term foo ``` Bob's new code that depends on `foo`: -```unison + +``` unison bar : Text bar = foo ++ " - " ++ foo ``` @@ -540,13 +570,12 @@ project/alice> merge /bob to delete the temporary branch and switch back to alice. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u bar : Text bar = use Text ++ foo ++ " - " ++ foo - ``` ## Merge failure: type error @@ -556,19 +585,22 @@ It may be Alice's and Bob's changes merge together cleanly in the sense that the In this example, Alice updates a `Text` to a `Nat`, while Bob adds a new dependent of the `Text`. Upon merging, propagating Alice's update to Bob's dependent causes a typechecking failure. Original branch: -```unison + +``` unison foo : Text foo = "foo" ``` Alice's update: -```unison + +``` unison foo : Nat foo = 100 ``` Bob's new definition: -```unison + +``` unison bar : Text bar = foo ++ " - " ++ foo ``` @@ -593,13 +625,12 @@ project/alice> merge /bob to delete the temporary branch and switch back to alice. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u bar : Text bar = use Text ++ foo ++ " - " ++ foo - ``` ## Merge failure: simple term conflict @@ -608,7 +639,8 @@ Alice and Bob may disagree about the definition of a term. In this case, the con are presented to the user to resolve. Original branch: -```unison + +``` unison foo : Text foo = "old foo" @@ -617,7 +649,8 @@ bar = "old bar" ``` Alice's changes: -```unison + +``` unison foo : Text foo = "alices foo" @@ -630,7 +663,7 @@ qux = "alices qux depends on alices foo" ++ foo Bob's changes: -```unison +``` unison foo : Text foo = "bobs foo" @@ -658,7 +691,7 @@ project/alice> merge /bob to delete the temporary branch and switch back to alice. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u -- project/alice foo : Text foo = "alices foo" @@ -675,7 +708,6 @@ qux = use Text ++ "alices qux depends on alices foo" ++ foo - ``` ```ucm @@ -693,17 +725,20 @@ project/merge-bob-into-alice> view bar baz Ditto for types; if the hashes don't match, it's a conflict. In this example, Alice and Bob do different things to the same constructor. However, any explicit changes to the same type will result in a conflict, including changes that could concievably be merged (e.g. Alice and Bob both add a new constructor, or edit different constructors). Original branch: -```unison + +``` unison unique type Foo = MkFoo Nat ``` Alice's changes: -```unison + +``` unison unique type Foo = MkFoo Nat Nat ``` Bob's changes: -```unison + +``` unison unique type Foo = MkFoo Nat Text ``` @@ -727,14 +762,13 @@ project/alice> merge /bob to delete the temporary branch and switch back to alice. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u -- project/alice type Foo = MkFoo Nat Nat -- project/bob type Foo = MkFoo Nat Text - ``` ## Merge failure: type-update + constructor-rename conflict @@ -742,17 +776,20 @@ type Foo = MkFoo Nat Text We model the renaming of a type's constructor as an update, so if Alice updates a type and Bob renames one of its constructors (even without changing its structure), we consider it a conflict. Original branch: -```unison + +``` unison unique type Foo = Baz Nat | Qux Text ``` Alice's changes `Baz Nat` to `Baz Nat Nat` -```unison + +``` unison unique type Foo = Baz Nat Nat | Qux Text ``` Bob's renames `Qux` to `BobQux`: -```unison + +``` unison unique type Foo = Baz Nat | BobQux Text ``` @@ -776,14 +813,13 @@ project/alice> merge /bob to delete the temporary branch and switch back to alice. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u -- project/alice type Foo = Baz Nat Nat | Qux Text -- project/bob type Foo = Baz Nat | BobQux Text - ``` ## Merge failure: constructor-rename conflict @@ -791,11 +827,13 @@ type Foo = Baz Nat | BobQux Text Here is another example demonstrating that constructor renames are modeled as updates. Original branch: -```unison + +``` unison unique type Foo = Baz Nat | Qux Text ``` Alice's rename: + ```ucm project/alice> move.term Foo.Baz Foo.Alice @@ -803,6 +841,7 @@ project/alice> move.term Foo.Baz Foo.Alice ``` Bob's rename: + ```ucm project/bob> move.term Foo.Qux Foo.Bob @@ -829,14 +868,13 @@ project/alice> merge bob to delete the temporary branch and switch back to alice. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u -- project/alice type Foo = Qux Text | Alice Nat -- project/bob type Foo = Bob Text | Baz Nat - ``` ## Merge failure: non-constructor/constructor conflict @@ -844,13 +882,15 @@ type Foo = Bob Text | Baz Nat A constructor on one side can conflict with a regular term definition on the other. Alice's additions: -```unison + +``` unison my.cool.thing : Nat my.cool.thing = 17 ``` Bob's additions: -```unison + +``` unison unique ability my.cool where thing : Nat -> Nat ``` @@ -875,7 +915,7 @@ project/alice> merge bob to delete the temporary branch and switch back to alice. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u -- project/alice my.cool.thing : Nat my.cool.thing = 17 @@ -883,7 +923,6 @@ my.cool.thing = 17 -- project/bob ability my.cool where thing : Nat ->{cool} Nat - ``` ## Merge failure: type/type conflict with term/constructor conflict @@ -891,28 +930,32 @@ ability my.cool where thing : Nat ->{cool} Nat Here's a subtle situation where a new type is added on each side of the merge, and an existing term is replaced with a constructor of one of the types. Original branch: -```unison + +``` unison Foo.Bar : Nat Foo.Bar = 17 ``` Alice adds this type `Foo` with constructor `Foo.Alice`: -```unison + +``` unison unique type Foo = Alice Nat ``` Bob adds the type `Foo` with constructor `Foo.Bar`, replacing the original `Foo.Bar` term: + ```ucm project/bob> delete.term Foo.Bar Done. ``` -```unison +``` unison unique type Foo = Bar Nat Nat ``` These won't cleanly merge. + ```ucm project/alice> merge bob @@ -933,7 +976,7 @@ project/alice> merge bob to delete the temporary branch and switch back to alice. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u -- project/alice Foo.Bar : Nat Foo.Bar = 17 @@ -944,14 +987,13 @@ type Foo = Alice Nat -- project/bob type Foo = Bar Nat Nat - ``` Here's a more involved example that demonstrates the same idea. In the LCA, we have a type with two constructors, and some term. -```unison +``` unison unique type Foo = Bar.Baz Nat | Bar.Qux Nat Nat @@ -1007,7 +1049,7 @@ project/alice> merge bob to delete the temporary branch and switch back to alice. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u -- project/alice Foo.Bar.Baz : Nat Foo.Bar.Baz = 100 @@ -1019,7 +1061,6 @@ Foo.Bar.Hello = 18 -- project/bob type Foo.Bar = Baz Nat | Hello Nat Nat - ``` ## Merge algorithm quirk: add/add unique types @@ -1031,7 +1072,8 @@ which is a parse error. We will resolve this situation automatically in a future version. Alice's additions: -```unison + +``` unison unique type Foo = Bar alice : Foo -> Nat @@ -1039,7 +1081,8 @@ alice _ = 18 ``` Bob's additions: -```unison + +``` unison unique type Foo = Bar bob : Foo -> Nat @@ -1066,7 +1109,7 @@ project/alice> merge bob to delete the temporary branch and switch back to alice. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u -- project/alice type Foo = Bar @@ -1084,7 +1127,6 @@ alice _ = 18 bob : Foo -> Nat bob _ = 19 - ``` ## `merge.commit` example (success) @@ -1093,20 +1135,22 @@ After merge conflicts are resolved, you can use `merge.commit` rather than `swit "commit" your changes. Original branch: -```unison + +``` unison foo : Text foo = "old foo" ``` Alice's changes: -```unison + +``` unison foo : Text foo = "alices foo" ``` Bob's changes: -```unison +``` unison foo : Text foo = "bobs foo" ``` @@ -1133,7 +1177,7 @@ project/alice> merge /bob to delete the temporary branch and switch back to alice. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u -- project/alice foo : Text foo = "alices foo" @@ -1142,12 +1186,11 @@ foo = "alices foo" foo : Text foo = "bobs foo" - ``` Resolve conflicts and commit: -```unison +``` unison foo : Text foo = "alice and bobs foo" ``` @@ -1219,7 +1262,8 @@ There are a number of conditions under which we can't perform a merge, and the u If `foo` and `bar` are aliases in the nearest common ancestor, but not in Alice's branch, then we don't know whether to update Bob's dependents to Alice's `foo` or Alice's `bar` (and vice-versa). Original branch: -```unison + +``` unison foo : Nat foo = 100 @@ -1228,7 +1272,8 @@ bar = 100 ``` Alice's updates: -```unison + +``` unison foo : Nat foo = 200 @@ -1237,7 +1282,8 @@ bar = 300 ``` Bob's addition: -```unison + +``` unison baz : Text baz = "baz" ``` @@ -1271,6 +1317,7 @@ conflict involving a builtin, we can't perform a merge. One way to fix this in the future would be to introduce a syntax for defining aliases in the scratch file. Alice's branch: + ```ucm project/alice> alias.type lib.builtins.Nat MyNat @@ -1278,7 +1325,8 @@ project/alice> alias.type lib.builtins.Nat MyNat ``` Bob's branch: -```unison + +``` unison unique type MyNat = MyNat Nat ``` @@ -1301,7 +1349,8 @@ project/alice> merge /bob Each naming of a decl may not have more than one name for each constructor, within the decl's namespace. Alice's branch: -```unison + +``` unison unique type Foo = Bar ``` @@ -1312,7 +1361,8 @@ project/alice> alias.term Foo.Bar Foo.some.other.Alias ``` Bob's branch: -```unison + +``` unison bob : Nat bob = 100 ``` @@ -1337,7 +1387,8 @@ project/alice> merge /bob Each naming of a decl must have a name for each constructor, within the decl's namespace. Alice's branch: -```unison + +``` unison unique type Foo = Bar ``` @@ -1348,7 +1399,8 @@ project/alice> delete.term Foo.Bar ``` Bob's branch: -```unison + +``` unison bob : Nat bob = 100 ``` @@ -1371,7 +1423,8 @@ project/alice> merge /bob A decl cannot be aliased within the namespace of another of its aliased. Alice's branch: -```unison + +``` unison structural type A = B Nat | C Nat Nat structural type A.inner.X = Y Nat | Z Nat Nat ``` @@ -1387,7 +1440,8 @@ project/alice> names A ``` Bob's branch: -```unison + +``` unison bob : Nat bob = 100 ``` @@ -1406,6 +1460,7 @@ project/alice> merge /bob Constructors may only exist within the corresponding decl's namespace. Alice's branch: + ```ucm project/alice> add @@ -1419,6 +1474,7 @@ project/alice> alias.term Foo.Bar AliasOutsideFooNamespace ``` Bob's branch: + ```ucm project/bob> add @@ -1445,13 +1501,15 @@ project/alice> merge bob By convention, `lib` can only namespaces; each of these represents a library dependencies. Individual terms and types are not allowed at the top level of `lib`. Alice's branch: -```unison + +``` unison lib.foo : Nat lib.foo = 1 ``` Bob's branch: -```unison + +``` unison bob : Nat bob = 100 ``` @@ -1470,14 +1528,14 @@ project/alice> merge /bob ``` ## LCA precondition violations -The LCA is not subject to most precondition violations, which is good, because the user can't easily manipulate it! +The LCA is not subject to most precondition violations, which is good, because the user can't easily manipulate it\! Here's an example. We'll delete a constructor name from the LCA and still be able to merge Alice and Bob's stuff together. LCA: -```unison +``` unison structural type Foo = Bar Nat | Baz Nat Nat ``` @@ -1525,7 +1583,7 @@ project/alice> delete.term Foo.Bar Done. ``` -```unison +``` unison alice : Nat alice = 100 ``` @@ -1570,7 +1628,7 @@ project/bob> delete.term Foo.Bar Done. ``` -```unison +``` unison bob : Nat bob = 101 ``` @@ -1608,8 +1666,7 @@ project/alice> merge /bob ### Delete one alias and update the other - -```unison +``` unison foo = 17 bar = 17 ``` @@ -1648,7 +1705,7 @@ project/alice> delete.term bar Done. ``` -```unison +``` unison foo = 18 ``` @@ -1682,7 +1739,7 @@ project/main> branch bob `switch /main` then `merge /bob`. ``` -```unison +``` unison bob = 101 ``` @@ -1715,8 +1772,7 @@ project/alice> merge /bob ``` ### Delete a constructor - -```unison +``` unison type Foo = Bar | Baz ``` @@ -1748,7 +1804,7 @@ project/main> branch topic `switch /main` then `merge /topic`. ``` -```unison +``` unison boop = "boop" ``` @@ -1773,7 +1829,7 @@ project/topic> add boop : Text ``` -```unison +``` unison type Foo = Bar ``` @@ -1814,10 +1870,9 @@ project/main> view Foo This test demonstrates a bug. - In the LCA, we have `foo` with dependent `bar`, and `baz`. -```unison +``` unison foo : Nat foo = 17 @@ -1862,7 +1917,7 @@ project/alice> branch bob ``` On Bob, we update `baz` to "bob". -```unison +``` unison baz : Text baz = "bob" ``` @@ -1892,7 +1947,7 @@ project/bob> update ``` On Alice, we update `baz` to "alice" (conflict), but also update `foo` (unconflicted), which propagates to `bar`. -```unison +``` unison foo : Nat foo = 18 @@ -1951,7 +2006,7 @@ project/alice> merge /bob to delete the temporary branch and switch back to alice. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u -- project/alice baz : Text baz = "alice" @@ -1968,7 +2023,6 @@ bar = use Nat + foo + foo - ``` But `bar` was put into the scratch file instead. @@ -1980,7 +2034,7 @@ history. Let's make three identical namespaces with different histories: -```unison +``` unison a = 1 ``` @@ -2005,7 +2059,7 @@ project/alice> add a : ##Nat ``` -```unison +``` unison b = 2 ``` @@ -2030,7 +2084,7 @@ project/alice> add b : ##Nat ``` -```unison +``` unison b = 2 ``` @@ -2050,7 +2104,7 @@ project/bob> add b : ##Nat ``` -```unison +``` unison a = 1 ``` @@ -2075,7 +2129,7 @@ project/bob> add a : ##Nat ``` -```unison +``` unison a = 1 b = 2 ``` @@ -2126,7 +2180,7 @@ project/carol> history This test demonstrates a change in syntactic hashing that fixed a bug due to auto-generated variable names for ignored results. -```unison +``` unison ignore : a -> () ignore _ = () @@ -2171,7 +2225,7 @@ scratch/alice> branch bob `switch /alice` then `merge /bob`. ``` -```unison +``` unison bar : Nat bar = ignore "hi" @@ -2204,7 +2258,7 @@ scratch/bob> update Previously, this update to `foo` would also cause a "real update" on `bar`, its dependent. Now it doesn't, so the merge will succeed. -```unison +``` unison foo : Nat foo = 19 ``` diff --git a/unison-src/transcripts/move-all.output.md b/unison-src/transcripts/move-all.output.md index d7a7bec85..cd68b319c 100644 --- a/unison-src/transcripts/move-all.output.md +++ b/unison-src/transcripts/move-all.output.md @@ -4,7 +4,7 @@ Create a term, type, and namespace with history -```unison +``` unison Foo = 2 unique type Foo = Foo Foo.termInA = 1 @@ -38,7 +38,7 @@ scratch/main> add Foo.termInA : Nat ``` -```unison +``` unison Foo.termInA = 2 unique type Foo.T = T1 | T2 ``` @@ -109,7 +109,7 @@ scratch/main> history Bar ``` ## Happy Path - Just term -```unison +``` unison bonk = 5 ``` @@ -149,7 +149,7 @@ z/main> ls ``` ## Happy Path - Just namespace -```unison +``` unison bonk.zonk = 5 ``` diff --git a/unison-src/transcripts/move-namespace.output.md b/unison-src/transcripts/move-namespace.output.md index 257365dbd..57b010c0d 100644 --- a/unison-src/transcripts/move-namespace.output.md +++ b/unison-src/transcripts/move-namespace.output.md @@ -1,11 +1,10 @@ # Tests for `move.namespace` - ## Moving the Root I should be able to move the root into a sub-namespace -```unison +``` unison foo = 1 ``` @@ -57,7 +56,7 @@ foo = 1 □ 1. #08a6hgi6s4 (start of history) ``` -I should be able to move a sub namespace _over_ the root. +I should be able to move a sub namespace *over* the root. ```ucm -- Should request confirmation @@ -101,7 +100,7 @@ I should be able to move a sub namespace _over_ the root. Create a namespace and add some history to it -```unison +``` unison a.termInA = 1 unique type a.T = T ``` @@ -129,7 +128,7 @@ scratch/happy> add a.termInA : Nat ``` -```unison +``` unison a.termInA = 2 unique type a.T = T1 | T2 ``` @@ -193,7 +192,7 @@ scratch/happy> history b Create some namespaces and add some history to them -```unison +``` unison a.termInA = 1 b.termInB = 10 ``` @@ -221,7 +220,7 @@ scratch/history> add b.termInB : Nat ``` -```unison +``` unison a.termInA = 2 b.termInB = 11 ``` @@ -287,7 +286,7 @@ scratch/history> history a Create some namespace and add some history to them -```unison +``` unison a.termInA = 1 b.termInB = 10 ``` @@ -315,7 +314,7 @@ scratch/existing> add b.termInB : Nat ``` -```unison +``` unison a.termInA = 2 b.termInB = 11 ``` diff --git a/unison-src/transcripts/name-selection.output.md b/unison-src/transcripts/name-selection.output.md index a9b3d9679..0df0ba3a0 100644 --- a/unison-src/transcripts/name-selection.output.md +++ b/unison-src/transcripts/name-selection.output.md @@ -1,10 +1,10 @@ This transcript shows how the pretty-printer picks names for a hash when multiple are available. The algorithm is: -1. Names that are "name-only" come before names that are hash qualified. So `List.map` comes before `List.map#2384a` and also `aaaa#xyz`. -2. Shorter names (in terms of segment count) come before longer ones, for instance `base.List.map` comes before `somelibrary.external.base.List.map`. -3. Otherwise if there are multiple names with a minimal number of segments, compare the names alphabetically. +1. Names that are "name-only" come before names that are hash qualified. So `List.map` comes before `List.map#2384a` and also `aaaa#xyz`. +2. Shorter names (in terms of segment count) come before longer ones, for instance `base.List.map` comes before `somelibrary.external.base.List.map`. +3. Otherwise if there are multiple names with a minimal number of segments, compare the names alphabetically. -```unison +``` unison a.a = a.b + 1 a.b = 0 + 1 a.aaa.but.more.segments = 0 + 1 @@ -31,7 +31,7 @@ Will add `a` and `b` to the codebase and give `b` a longer (in terms of segment ``` Next let's introduce a conflicting symbol and show that its hash qualified name isn't used when it has an unconflicted name: -```unison +``` unison a2.a = a2.b + 1 a2.b = 0 + 1 a2.aaa.but.more.segments = 0 + 1 @@ -116,7 +116,7 @@ The original `a2` namespace has an unconflicted definition for `c` and `d`, but ``` ## Name biasing -```unison +``` unison deeply.nested.term = a + 1 @@ -162,7 +162,7 @@ a = 10 ``` Add another term with `num` suffix to force longer suffixification of `deeply.nested.num` -```unison +``` unison other.num = 20 ``` diff --git a/unison-src/transcripts/names.output.md b/unison-src/transcripts/names.output.md index 8138b5434..13d62fd7b 100644 --- a/unison-src/transcripts/names.output.md +++ b/unison-src/transcripts/names.output.md @@ -2,7 +2,7 @@ Example uses of the `names` command and output -```unison +``` unison -- Some names with the same value some.place.x = 1 some.otherplace.y = 1 @@ -78,7 +78,6 @@ somewhere.y = 2 ``` `names.global` searches from the root, and absolutely qualifies results - ```ucm -- We can search by suffix and find all definitions in the codebase named 'x', and each of their aliases respectively. .some> names.global x diff --git a/unison-src/transcripts/namespace-dependencies.output.md b/unison-src/transcripts/namespace-dependencies.output.md index 0e7d29826..ae41b9518 100644 --- a/unison-src/transcripts/namespace-dependencies.output.md +++ b/unison-src/transcripts/namespace-dependencies.output.md @@ -1,6 +1,6 @@ # namespace.dependencies command -```unison +``` unison const a b = a external.mynat = 1 mynamespace.dependsOnText = const external.mynat 10 diff --git a/unison-src/transcripts/numbered-args.output.md b/unison-src/transcripts/numbered-args.output.md index 883a319de..ba6016b96 100644 --- a/unison-src/transcripts/numbered-args.output.md +++ b/unison-src/transcripts/numbered-args.output.md @@ -2,7 +2,7 @@ First lets add some contents to our codebase. -```unison +``` unison foo = "foo" bar = "bar" baz = "baz" diff --git a/unison-src/transcripts/old-fold-right.output.md b/unison-src/transcripts/old-fold-right.output.md index 4f210513b..f054ba959 100644 --- a/unison-src/transcripts/old-fold-right.output.md +++ b/unison-src/transcripts/old-fold-right.output.md @@ -1,4 +1,4 @@ -```unison +``` unison oldRight: (b ->{e} a ->{e} b) -> [a] ->{e} [b] oldRight f la = bug "out" diff --git a/unison-src/transcripts/pattern-match-coverage.output.md b/unison-src/transcripts/pattern-match-coverage.output.md index b8d30cb25..ea249e9f7 100644 --- a/unison-src/transcripts/pattern-match-coverage.output.md +++ b/unison-src/transcripts/pattern-match-coverage.output.md @@ -1,6 +1,8 @@ # Basics + ## non-exhaustive patterns -```unison + +``` unison unique type T = A | B | C test : T -> () @@ -23,7 +25,7 @@ test = cases * C ``` -```unison +``` unison unique type T = A | B test : (T, Optional T) -> () @@ -51,7 +53,8 @@ test = cases ``` ## redundant patterns -```unison + +``` unison unique type T = A | B | C test : T -> () @@ -71,7 +74,7 @@ test = cases ``` -```unison +``` unison unique type T = A | B test : (T, Optional T) -> () @@ -95,7 +98,8 @@ test = cases # Uninhabited patterns match is complete without covering uninhabited patterns -```unison + +``` unison unique type V = test : Optional (Optional V) -> () @@ -119,7 +123,8 @@ test = cases ``` uninhabited patterns are reported as redundant -```unison + +``` unison unique type V = test0 : V -> () @@ -136,7 +141,7 @@ test0 = cases ``` -```unison +``` unison unique type V = test : Optional (Optional V) -> () @@ -158,7 +163,8 @@ test = cases # Guards ## Incomplete patterns due to guards should be reported -```unison + +``` unison test : () -> () test = cases () | false -> () @@ -177,7 +183,7 @@ test = cases * () ``` -```unison +``` unison test : Optional Nat -> Nat test = cases None -> 0 @@ -201,7 +207,8 @@ test = cases ``` ## Complete patterns with guards should be accepted -```unison + +``` unison test : Optional Nat -> Nat test = cases None -> 0 @@ -227,7 +234,8 @@ test = cases Uncovered patterns are only instantiated as deeply as necessary to distinguish them from existing patterns. -```unison + +``` unison unique type T = A | B | C test : Optional (Optional T) -> () @@ -250,7 +258,7 @@ test = cases * Some (Some _) ``` -```unison +``` unison unique type T = A | B | C test : Optional (Optional T) -> () @@ -282,7 +290,8 @@ test = cases ## Non-exhaustive Nat -```unison + +``` unison test : Nat -> () test = cases 0 -> () @@ -302,7 +311,8 @@ test = cases ``` Boolean -```unison + +``` unison test : Boolean -> () test = cases true -> () @@ -324,7 +334,8 @@ test = cases ## Exhaustive Nat -```unison + +``` unison test : Nat -> () test = cases 0 -> () @@ -345,7 +356,8 @@ test = cases ``` Boolean -```unison + +``` unison test : Boolean -> () test = cases true -> () @@ -368,7 +380,8 @@ test = cases # Redundant Nat -```unison + +``` unison test : Nat -> () test = cases 0 -> () @@ -386,7 +399,8 @@ test = cases ``` Boolean -```unison + +``` unison test : Boolean -> () test = cases true -> () @@ -406,7 +420,8 @@ test = cases # Sequences ## Exhaustive -```unison + +``` unison test : [()] -> () test = cases [] -> () @@ -427,7 +442,8 @@ test = cases ``` ## Non-exhaustive -```unison + +``` unison test : [()] -> () test = cases [] -> () @@ -446,7 +462,7 @@ test = cases * (() +: _) ``` -```unison +``` unison test : [()] -> () test = cases x +: xs -> () @@ -465,7 +481,7 @@ test = cases * [] ``` -```unison +``` unison test : [()] -> () test = cases xs :+ x -> () @@ -484,7 +500,7 @@ test = cases * [] ``` -```unison +``` unison test : [()] -> () test = cases x0 +: (x1 +: xs) -> () @@ -505,7 +521,7 @@ test = cases * (() +: []) ``` -```unison +``` unison test : [()] -> () test = cases [] -> () @@ -529,7 +545,8 @@ test = cases ## Uninhabited `Cons` is not expected since `V` is uninhabited -```unison + +``` unison unique type V = test : [V] -> () @@ -559,7 +576,8 @@ final element is `false`, while the fourth pattern matches when the first element is `true`. However, the only possible list length at the third or fourth clause is 1, so the first and final element must be equal. Thus, the pattern match is exhaustive. -```unison + +``` unison test : [Boolean] -> () test = cases [a, b] ++ xs -> () @@ -582,7 +600,8 @@ test = cases ``` This is the same idea as above but shows that fourth match is redundant. -```unison + +``` unison test : [Boolean] -> () test = cases [a, b] ++ xs -> () @@ -607,7 +626,8 @@ first and third element are true. The third matches lists of length 4 or greater where the final 4 elements are `true, false, true, false`. The list must be exactly of length 4 to arrive at the second or third clause, so the third pattern is redundant. -```unison + +``` unison test : [Boolean] -> () test = cases [a, b, c, d, f] ++ xs -> () @@ -627,7 +647,7 @@ test = cases ``` # bugfix: Sufficient data decl map -```unison +``` unison unique type T = A unit2t : Unit -> T @@ -665,7 +685,8 @@ transitive type dependencies of references that appear in the expression. This test ensures that we have fetched the `T` type although there is no data decl reference to `T` in `witht`. -```unison + +``` unison witht : Unit witht = match unit2t () with x -> () @@ -684,7 +705,7 @@ witht = match unit2t () with witht : () ``` -```unison +``` unison unique type V = evil : Unit -> V @@ -714,7 +735,7 @@ scratch/main> add evil : 'V ``` -```unison +``` unison withV : Unit withV = match evil () with x -> () @@ -729,7 +750,7 @@ withV = match evil () with ``` -```unison +``` unison unique type SomeType = A ``` @@ -754,7 +775,7 @@ scratch/main> add type SomeType ``` -```unison +``` unison unique type R = R SomeType get x = match x with @@ -775,7 +796,7 @@ get x = match x with get : R -> SomeType ``` -```unison +``` unison unique type R = { someType : SomeType } ``` @@ -799,7 +820,7 @@ unique type R = { someType : SomeType } ## Exhaustive ability handlers are accepted -```unison +``` unison structural ability Abort where abort : {Abort} a @@ -824,7 +845,7 @@ result f = handle !f with cases result : '{e, Abort} a ->{e} a ``` -```unison +``` unison structural ability Abort where abort : {Abort} a @@ -856,7 +877,7 @@ result f = handle !f with cases type T ``` -```unison +``` unison structural ability Abort where abort : {Abort} a @@ -882,7 +903,7 @@ result f = result : '{e, Abort} V ->{e} V ``` -```unison +``` unison structural ability Abort where abort : {Abort} a @@ -915,7 +936,7 @@ handleMulti c = ``` ## Non-exhaustive ability handlers are rejected -```unison +``` unison structural ability Abort where abort : {Abort} a abortWithMessage : Text -> {Abort} a @@ -941,7 +962,7 @@ result f = handle !f with cases * { abortWithMessage _ -> _ } ``` -```unison +``` unison structural ability Abort where abort : {Abort} a @@ -967,7 +988,7 @@ result f = handle !f with cases * { B } ``` -```unison +``` unison unique ability Give a where give : a -> {Give a} Unit @@ -993,7 +1014,7 @@ result f = handle !f with cases * { give B -> _ } ``` -```unison +``` unison structural ability Abort where abort : {Abort} a @@ -1025,7 +1046,7 @@ handleMulti c = ``` ## Redundant handler cases are rejected -```unison +``` unison unique ability Give a where give : a -> {Give a} Unit @@ -1049,7 +1070,7 @@ result f = handle !f with cases ``` ## Exhaustive ability reinterpretations are accepted -```unison +``` unison structural ability Abort where abort : {Abort} a abortWithMessage : Text -> {Abort} a @@ -1076,7 +1097,7 @@ result f = handle !f with cases result : '{e, Abort} a ->{e, Abort} a ``` -```unison +``` unison structural ability Abort a where abort : {Abort a} r abortWithMessage : a -> {Abort a} r @@ -1106,7 +1127,7 @@ result f = ``` ## Non-exhaustive ability reinterpretations are rejected -```unison +``` unison structural ability Abort where abort : {Abort} a abortWithMessage : Text -> {Abort} a @@ -1145,7 +1166,7 @@ they are all uninhabited. The messages here aren't the best, but I don't think uninhabited abilities will come up and get handlers written for them often. -```unison +``` unison unique ability Give a where give : a -> {Give a} Unit give2 : a -> {Give a} Unit @@ -1173,7 +1194,7 @@ result f = * { give2 _ -> _ } ``` -```unison +``` unison unique ability Give a where give : a -> {Give a} Unit give2 : a -> {Give a} Unit @@ -1201,7 +1222,7 @@ result f = result : '{e, Give V} r ->{e} r ``` -```unison +``` unison unique ability Give a where give : a -> {Give a} Unit give2 : a -> {Give a} Unit @@ -1229,7 +1250,7 @@ result f = result : '{e, Give V} r ->{e} r ``` -```unison +``` unison unique ability Give a where give : a -> {Give a} Unit give2 : a -> {Give a} Unit @@ -1253,7 +1274,7 @@ result f = ``` -```unison +``` unison unique ability GiveA a where giveA : a -> {GiveA a} Unit giveA2 : a -> {GiveA a} Unit @@ -1283,7 +1304,7 @@ result f = ``` -```unison +``` unison unique ability GiveA a where giveA : a -> {GiveA a} Unit giveA2 : a -> {GiveA a} Unit diff --git a/unison-src/transcripts/pattern-pretty-print-2345.output.md b/unison-src/transcripts/pattern-pretty-print-2345.output.md index 6157aa8e7..15ebf8740 100644 --- a/unison-src/transcripts/pattern-pretty-print-2345.output.md +++ b/unison-src/transcripts/pattern-pretty-print-2345.output.md @@ -1,7 +1,6 @@ Regression test for https://github.com/unisonweb/unison/pull/2377 - -```unison +``` unison structural ability Ab where a: Nat -> () diff --git a/unison-src/transcripts/patternMatchTls.output.md b/unison-src/transcripts/patternMatchTls.output.md index 65aa5153d..7d207ef37 100644 --- a/unison-src/transcripts/patternMatchTls.output.md +++ b/unison-src/transcripts/patternMatchTls.output.md @@ -1,9 +1,7 @@ We had bugs in the calling conventions for both send and terminate which would cause pattern matching on the resulting (Right ()) would cause a runtime error. - - -```unison +``` unison use builtin.io2.Tls newClient send handshake terminate frank: '{IO} () diff --git a/unison-src/transcripts/patterns.output.md b/unison-src/transcripts/patterns.output.md index 7db153f99..054c9224e 100644 --- a/unison-src/transcripts/patterns.output.md +++ b/unison-src/transcripts/patterns.output.md @@ -1,6 +1,6 @@ Some tests of pattern behavior. -```unison +``` unison p1 = join [literal "blue", literal "frog"] > Pattern.run (many p1) "bluefrogbluegoat" diff --git a/unison-src/transcripts/propagate.output.md b/unison-src/transcripts/propagate.output.md index 5e16983bc..036681f1b 100644 --- a/unison-src/transcripts/propagate.output.md +++ b/unison-src/transcripts/propagate.output.md @@ -2,7 +2,7 @@ We introduce a type `Foo` with a function dependent `fooToInt`. -```unison +``` unison unique type Foo = Foo fooToInt : Foo -> Int @@ -54,7 +54,7 @@ scratch/main> view fooToInt ``` Then if we change the type `Foo`... -```unison +``` unison unique type Foo = Foo | Bar ``` @@ -96,7 +96,7 @@ scratch/main> view fooToInt We make a term that has a dependency on another term and also a non-redundant user-provided type signature. -```unison +``` unison preserve.someTerm : Optional foo -> Optional foo preserve.someTerm x = x @@ -131,7 +131,7 @@ scratch/main> add ``` Let's now edit the dependency: -```unison +``` unison preserve.someTerm : Optional x -> Optional x preserve.someTerm _ = None ``` @@ -189,7 +189,7 @@ Cleaning up a bit... ``` Now, we make two terms, where one depends on the other. -```unison +``` unison one.someTerm : Optional foo -> Optional foo one.someTerm x = x @@ -228,7 +228,7 @@ We'll make two copies of this namespace. ``` Now let's edit one of the terms... -```unison +``` unison someTerm : Optional x -> Optional x someTerm _ = None ``` diff --git a/unison-src/transcripts/records.output.md b/unison-src/transcripts/records.output.md index 315bec4bb..8d2be7417 100644 --- a/unison-src/transcripts/records.output.md +++ b/unison-src/transcripts/records.output.md @@ -2,7 +2,7 @@ Ensure that Records keep their syntax after being added to the codebase ## Record with 1 field -```unison +``` unison unique type Record1 = { a : Text } ``` @@ -14,7 +14,7 @@ scratch/main> view Record1 ``` ## Record with 2 fields -```unison +``` unison unique type Record2 = { a : Text, b : Int } ``` @@ -26,7 +26,7 @@ scratch/main> view Record2 ``` ## Record with 3 fields -```unison +``` unison unique type Record3 = { a : Text, b : Int, c : Nat } ``` @@ -38,7 +38,7 @@ scratch/main> view Record3 ``` ## Record with many fields -```unison +``` unison unique type Record4 = { a : Text , b : Int @@ -65,7 +65,7 @@ scratch/main> view Record4 ``` ## Record with many many fields -```unison +``` unison unique type Record5 = { zero : Nat, one : [Nat], @@ -122,13 +122,13 @@ scratch/main> view Record5 This record type has two fields whose types are user-defined (`Record4` and `UserType`). -```unison +``` unison unique type UserType = UserType Nat unique type RecordWithUserType = { a : Text, b : Record4, c : UserType } ``` -If you `view` or `edit` it, it _should_ be treated as a record type, but it does not (which is a bug) +If you `view` or `edit` it, it *should* be treated as a record type, but it does not (which is a bug) ```ucm scratch/main> view RecordWithUserType @@ -141,7 +141,7 @@ scratch/main> view RecordWithUserType Trailing commas are allowed. -```unison +``` unison unique type Record5 = { a : Text, b : Int, diff --git a/unison-src/transcripts/reflog.output.md b/unison-src/transcripts/reflog.output.md index 96e68114f..a608b04a9 100644 --- a/unison-src/transcripts/reflog.output.md +++ b/unison-src/transcripts/reflog.output.md @@ -1,7 +1,7 @@ First we make two changes to the codebase, so that there's more than one line for the `reflog` command to display: -```unison +``` unison x = 1 ``` @@ -26,7 +26,7 @@ x = 1 x : Nat ``` -```unison +``` unison y = 2 ``` @@ -81,6 +81,7 @@ y = 2 ``` If we `reset-root` to its previous value, `y` disappears. + ```ucm .> reset-root 2 diff --git a/unison-src/transcripts/release-draft-command.output.md b/unison-src/transcripts/release-draft-command.output.md index 0eb667e87..58077a37e 100644 --- a/unison-src/transcripts/release-draft-command.output.md +++ b/unison-src/transcripts/release-draft-command.output.md @@ -2,7 +2,7 @@ The `release.draft` command drafts a release from the current branch. Some setup: -```unison +``` unison someterm = 18 ``` diff --git a/unison-src/transcripts/reset.output.md b/unison-src/transcripts/reset.output.md index 9be437365..1858250ab 100644 --- a/unison-src/transcripts/reset.output.md +++ b/unison-src/transcripts/reset.output.md @@ -1,5 +1,6 @@ # reset loose code -```unison + +``` unison a = 5 ``` @@ -50,7 +51,7 @@ scratch/main> history □ 1. #4bigcpnl7t (start of history) ``` -```unison +``` unison foo.a = 5 ``` @@ -108,7 +109,7 @@ foo/main> history ☝️ The namespace is empty. ``` -```unison +``` unison a = 5 ``` @@ -149,7 +150,7 @@ foo/main> history □ 1. #5l94rduvel (start of history) ``` -```unison +``` unison a = 3 ``` @@ -192,7 +193,8 @@ foo/main> history # ambiguous reset ## ambiguous target -```unison + +``` unison main.a = 3 ``` @@ -244,7 +246,7 @@ foo/main> reset 2 main ``` ## ambiguous hash -```unison +``` unison main.a = 3 ``` diff --git a/unison-src/transcripts/resolution-failures.output.md b/unison-src/transcripts/resolution-failures.output.md index bca703a4e..262f6f744 100644 --- a/unison-src/transcripts/resolution-failures.output.md +++ b/unison-src/transcripts/resolution-failures.output.md @@ -6,7 +6,7 @@ This transcript tests the errors printed to the user when a name cannot be resol First we define differing types with the same name in different namespaces: -```unison +``` unison unique type one.AmbiguousType = one.AmbiguousType unique type two.AmbiguousType = two.AmbiguousType @@ -48,10 +48,10 @@ It is ambiguous which type from which namespace we mean. We expect the output to: -1. Print all ambiguous usage sites separately -2. Print possible disambiguation suggestions for each unique ambiguity +1. Print all ambiguous usage sites separately +2. Print possible disambiguation suggestions for each unique ambiguity -```unison +``` unison -- We intentionally avoid using a constructor to ensure the constructor doesn't -- affect type resolution. useAmbiguousType : AmbiguousType -> () @@ -96,7 +96,7 @@ separateAmbiguousTypeUsage _ = () Currently, ambiguous terms are caught and handled by type directed name resolution, but expect it to eventually be handled by the above machinery. -```unison +``` unison useAmbiguousTerm = ambiguousTerm ``` diff --git a/unison-src/transcripts/rsa.output.md b/unison-src/transcripts/rsa.output.md index b81a16bec..a5994b24b 100644 --- a/unison-src/transcripts/rsa.output.md +++ b/unison-src/transcripts/rsa.output.md @@ -1,5 +1,4 @@ - -```unison +``` unison up = 0xs0123456789abcdef down = 0xsfedcba9876543210 diff --git a/unison-src/transcripts/scope-ref.output.md b/unison-src/transcripts/scope-ref.output.md index ea44a7946..131918662 100644 --- a/unison-src/transcripts/scope-ref.output.md +++ b/unison-src/transcripts/scope-ref.output.md @@ -1,7 +1,6 @@ - A short script to test mutable references with local scope. -```unison +``` unison test = Scope.run 'let r = Scope.ref 0 Ref.write r 1 diff --git a/unison-src/transcripts/suffixes.output.md b/unison-src/transcripts/suffixes.output.md index 411fdebba..5752f2918 100644 --- a/unison-src/transcripts/suffixes.output.md +++ b/unison-src/transcripts/suffixes.output.md @@ -2,7 +2,7 @@ Any unique name suffix can be used to refer to a definition. For instance: -```unison +``` unison -- No imports needed even though FQN is `builtin.{Int,Nat}` foo.bar.a : Int foo.bar.a = +99 @@ -61,7 +61,7 @@ scratch/main> find : Nat -> [a] -> [a] Suffix-based resolution prefers names that are not in an indirect dependency. -```unison +``` unison cool.abra.cadabra = "my project" lib.distributed.abra.cadabra = "direct dependency 1" lib.distributed.baz.qux = "direct dependency 2" @@ -95,7 +95,7 @@ scratch/main> add lib.distributed.lib.baz.qux : Text ``` -```unison +``` unison > abra.cadabra ``` @@ -117,7 +117,7 @@ scratch/main> add distributed.abra.cadabra : Text ``` -```unison +``` unison > baz.qux ``` @@ -173,7 +173,7 @@ scratch/main> names distributed.lib.baz.qux If a definition is given in a scratch file, its suffixes shadow existing definitions that exist in the codebase with the same suffixes. For example: -```unison +``` unison unique type A = Thing1 Nat | thing2 Nat foo.a = 23 @@ -190,7 +190,7 @@ scratch/main> add foo.a : Nat ``` -```unison +``` unison unique type B = Thing1 Text | thing2 Text | Thing3 Text zoink.a = "hi" diff --git a/unison-src/transcripts/sum-type-update-conflicts.output.md b/unison-src/transcripts/sum-type-update-conflicts.output.md index 493a4d940..f28ec5dd4 100644 --- a/unison-src/transcripts/sum-type-update-conflicts.output.md +++ b/unison-src/transcripts/sum-type-update-conflicts.output.md @@ -4,7 +4,7 @@ https://github.com/unisonweb/unison/issues/2786 First we add a sum-type to the codebase. -```unison +``` unison structural type X = x ``` @@ -31,10 +31,10 @@ scratch/main> add (also named lib.builtins.Unit) ``` -Now we update the type, changing the name of the constructors, _but_, we simultaneously +Now we update the type, changing the name of the constructors, *but*, we simultaneously add a new top-level term with the same name as the old constructor. -```unison +``` unison structural type X = y | z X.x : Text diff --git a/unison-src/transcripts/switch-command.output.md b/unison-src/transcripts/switch-command.output.md index e84fefd0a..f00a15723 100644 --- a/unison-src/transcripts/switch-command.output.md +++ b/unison-src/transcripts/switch-command.output.md @@ -2,7 +2,7 @@ The `switch` command switches to an existing project or branch. Setup stuff. -```unison +``` unison someterm = 18 ``` diff --git a/unison-src/transcripts/tab-completion.output.md b/unison-src/transcripts/tab-completion.output.md index c7730c17d..86a7b552e 100644 --- a/unison-src/transcripts/tab-completion.output.md +++ b/unison-src/transcripts/tab-completion.output.md @@ -25,7 +25,7 @@ scratch/main> debug.tab-complete delete. ``` ## Tab complete terms & types -```unison +``` unison subnamespace.someName = 1 subnamespace.someOtherName = 2 subnamespace2.thing = 3 @@ -89,7 +89,7 @@ scratch/main> debug.tab-complete view subnamespace.someOther * subnamespace.someOtherName ``` -```unison +``` unison absolute.term = "absolute" ``` @@ -143,7 +143,7 @@ scratch/main> debug.tab-complete io.test subnamespace. ``` Tab Complete Delete Subcommands -```unison +``` unison unique type Foo = A | B add : a -> a add b = b @@ -202,7 +202,7 @@ myproject/main> debug.tab-complete project.rename my ``` Commands which complete namespaces OR branches should list both -```unison +``` unison mybranchsubnamespace.term = 1 ``` diff --git a/unison-src/transcripts/test-command.output.md b/unison-src/transcripts/test-command.output.md index 4e2d9bafe..4182b223c 100644 --- a/unison-src/transcripts/test-command.output.md +++ b/unison-src/transcripts/test-command.output.md @@ -2,7 +2,7 @@ Merge builtins so we get enough names for the testing stuff. The `test` command should run all of the tests in the current directory. -```unison +``` unison test1 : [Result] test1 = [Ok "test1"] @@ -64,7 +64,7 @@ scratch/main> test ``` `test` won't descend into the `lib` namespace, but `test.all` will. -```unison +``` unison lib.dep.testInLib : [Result] lib.dep.testInLib = [Ok "testInLib"] ``` diff --git a/unison-src/transcripts/text-literals.output.md b/unison-src/transcripts/text-literals.output.md index 1889ec8e7..f9d4311f2 100644 --- a/unison-src/transcripts/text-literals.output.md +++ b/unison-src/transcripts/text-literals.output.md @@ -1,7 +1,6 @@ - This transcript shows some syntax for raw text literals. -```unison +``` unison lit1 = """ This is a raw text literal. It can start with 3 or more ", diff --git a/unison-src/transcripts/todo-bug-builtins.output.md b/unison-src/transcripts/todo-bug-builtins.output.md index 0e3bb72ad..104d6bf86 100644 --- a/unison-src/transcripts/todo-bug-builtins.output.md +++ b/unison-src/transcripts/todo-bug-builtins.output.md @@ -1,7 +1,8 @@ # The `todo` and `bug` builtin `todo` and `bug` have type `a -> b`. They take a message or a value of type `a` and crash during runtime displaying `a` in ucm. -```unison + +``` unison > todo "implement me later" ``` @@ -28,7 +29,7 @@ #qe5e1lcfn8 ``` -```unison +``` unison > bug "there's a bug in my code" ``` @@ -56,8 +57,10 @@ ``` ## Todo + `todo` is useful if you want to come back to a piece of code later but you want your project to compile. -```unison + +``` unison complicatedMathStuff x = todo "Come back and to something with x here" ``` @@ -75,8 +78,10 @@ complicatedMathStuff x = todo "Come back and to something with x here" ``` ## Bug + `bug` is used to indicate that a particular branch is not expected to execute. -```unison + +``` unison test = match true with true -> "Yay" false -> bug "Wow, that's unexpected" diff --git a/unison-src/transcripts/todo.output.md b/unison-src/transcripts/todo.output.md index cfad74ec1..434e7a43d 100644 --- a/unison-src/transcripts/todo.output.md +++ b/unison-src/transcripts/todo.output.md @@ -16,7 +16,7 @@ The todo command shows conflicted names (not demonstrated here yet because it is The `todo` command shows local (outside `lib`) terms that directly call `todo`. -```unison +``` unison foo : Nat foo = todo "implement foo" @@ -58,7 +58,7 @@ project/main> todo The `todo` command shows hashes of direct dependencies of local (outside `lib`) definitions that don't have names in the current namespace. -```unison +``` unison foo.bar = 15 baz = foo.bar + foo.bar ``` diff --git a/unison-src/transcripts/top-level-exceptions.output.md b/unison-src/transcripts/top-level-exceptions.output.md index 6624fbd23..4a889dedc 100644 --- a/unison-src/transcripts/top-level-exceptions.output.md +++ b/unison-src/transcripts/top-level-exceptions.output.md @@ -1,4 +1,3 @@ - A simple transcript to test the use of exceptions that bubble to the top level. FYI, here are the `Exception` and `Failure` types: @@ -15,7 +14,7 @@ scratch/main> view Exception Failure ``` Here's a sample program just to verify that the typechecker allows `run` to throw exceptions: -```unison +``` unison use builtin IO Exception Test.Result main : '{IO, Exception} () @@ -64,7 +63,7 @@ scratch/main> io.test mytest ``` Now a test to show the handling of uncaught exceptions: -```unison +``` unison main2 = '(error "oh noes!" ()) error : Text -> a ->{Exception} x diff --git a/unison-src/transcripts/transcript-parser-commands.output.md b/unison-src/transcripts/transcript-parser-commands.output.md index 15b72bc3b..842ea130c 100644 --- a/unison-src/transcripts/transcript-parser-commands.output.md +++ b/unison-src/transcripts/transcript-parser-commands.output.md @@ -2,7 +2,7 @@ The transcript parser is meant to parse `ucm` and `unison` blocks. -```unison +``` unison x = 1 ``` @@ -27,7 +27,7 @@ x = 1 x : Nat ``` -```unison +``` unison --- title: :scratch.u --- @@ -35,7 +35,6 @@ z ``` - ```ucm .> delete foo @@ -56,21 +55,15 @@ z ``` However handling of blocks of other languages should be supported. -```python - +``` python some python code - ``` -```c_cpp - +``` c_cpp some C++ code - ``` -```c9search - +``` c9search some cloud9 code - ``` diff --git a/unison-src/transcripts/type-deps.output.md b/unison-src/transcripts/type-deps.output.md index ad1205e1e..24ab0e288 100644 --- a/unison-src/transcripts/type-deps.output.md +++ b/unison-src/transcripts/type-deps.output.md @@ -4,13 +4,13 @@ https://github.com/unisonweb/unison/pull/2821 Define a type. -```unison +``` unison structural type Y = Y ``` Now, we update `Y`, and add a new type `Z` which depends on it. -```unison +``` unison structural type Z = Z Y structural type Y = Y Nat ``` @@ -35,6 +35,7 @@ structural type Y = Y Nat ``` Adding should fail for BOTH definitions, `Y` needs an update and `Z` is blocked by `Y`. + ```ucm scratch/main> add diff --git a/unison-src/transcripts/type-modifier-are-optional.output.md b/unison-src/transcripts/type-modifier-are-optional.output.md index 88b784412..34c562d15 100644 --- a/unison-src/transcripts/type-modifier-are-optional.output.md +++ b/unison-src/transcripts/type-modifier-are-optional.output.md @@ -2,7 +2,7 @@ Types and abilities may be prefixed with either `unique` or `structural`. When left unspecified, `unique` is assumed. -```unison +``` unison type Abc = Abc unique type Def = Def structural type Ghi = Ghi diff --git a/unison-src/transcripts/unique-type-churn.output.md b/unison-src/transcripts/unique-type-churn.output.md index 74076d8c6..f633292e8 100644 --- a/unison-src/transcripts/unique-type-churn.output.md +++ b/unison-src/transcripts/unique-type-churn.output.md @@ -1,7 +1,7 @@ This transcript demonstrates that unique types no longer always get a fresh GUID: they share GUIDs with already-saved unique types of the same name. -```unison +``` unison unique type A = A unique type B = B C @@ -33,7 +33,7 @@ scratch/main> add type C ``` -```unison +``` unison unique type A = A unique type B = B C @@ -64,7 +64,7 @@ scratch/main> names A Tip: Use `names.global` to see more results. ``` -```unison +``` unison unique type A = A () ``` @@ -103,7 +103,7 @@ scratch/main> names A Tip: Use `names.global` to see more results. ``` -```unison +``` unison unique type A = A ``` diff --git a/unison-src/transcripts/unitnamespace.output.md b/unison-src/transcripts/unitnamespace.output.md index a3d7b3956..9bc427434 100644 --- a/unison-src/transcripts/unitnamespace.output.md +++ b/unison-src/transcripts/unitnamespace.output.md @@ -1,4 +1,4 @@ -```unison +``` unison `()`.foo = "bar" ``` diff --git a/unison-src/transcripts/universal-cmp.output.md b/unison-src/transcripts/universal-cmp.output.md index b1f07fddf..af4bced3e 100644 --- a/unison-src/transcripts/universal-cmp.output.md +++ b/unison-src/transcripts/universal-cmp.output.md @@ -1,8 +1,7 @@ - File for test cases making sure that universal equality/comparison cases exist for built-in types. Just making sure they don't crash. -```unison +``` unison unique type A = A threadEyeDeez _ = @@ -38,7 +37,7 @@ scratch/main> run threadEyeDeez (false, true) ``` -```unison +``` unison > typeLink A == typeLink A > typeLink Text == typeLink Text > typeLink Text == typeLink A diff --git a/unison-src/transcripts/unsafe-coerce.output.md b/unison-src/transcripts/unsafe-coerce.output.md index 62eb29845..73ed1c625 100644 --- a/unison-src/transcripts/unsafe-coerce.output.md +++ b/unison-src/transcripts/unsafe-coerce.output.md @@ -1,5 +1,4 @@ - -```unison +``` unison f : '{} Nat f _ = 5 diff --git a/unison-src/transcripts/update-ignores-lib-namespace.output.md b/unison-src/transcripts/update-ignores-lib-namespace.output.md index e7026d6f3..ffc4147d0 100644 --- a/unison-src/transcripts/update-ignores-lib-namespace.output.md +++ b/unison-src/transcripts/update-ignores-lib-namespace.output.md @@ -2,7 +2,7 @@ the project organization convention that dependencies are put in "lib"; it's much easier to apply a patch to all of one's own code if the "lib" namespace is simply ignored. -```unison +``` unison foo = 100 lib.foo = 100 ``` @@ -30,7 +30,7 @@ scratch/main> add lib.foo : Nat ``` -```unison +``` unison foo = 200 ``` diff --git a/unison-src/transcripts/update-on-conflict.output.md b/unison-src/transcripts/update-on-conflict.output.md index ce48e5f6c..8d05b394f 100644 --- a/unison-src/transcripts/update-on-conflict.output.md +++ b/unison-src/transcripts/update-on-conflict.output.md @@ -2,7 +2,7 @@ Updating conflicted definitions works fine. -```unison +``` unison x = 1 temp = 2 ``` @@ -38,7 +38,7 @@ scratch/main> delete.term temp Done. ``` -```unison +``` unison x = 3 ``` diff --git a/unison-src/transcripts/update-suffixifies-properly.output.md b/unison-src/transcripts/update-suffixifies-properly.output.md index 812eac20e..a2a938fea 100644 --- a/unison-src/transcripts/update-suffixifies-properly.output.md +++ b/unison-src/transcripts/update-suffixifies-properly.output.md @@ -1,4 +1,4 @@ -```unison +``` unison a.x.x.x.x = 100 b.x.x.x.x = 100 foo = 25 @@ -38,7 +38,7 @@ myproject/main> add foo : Nat ``` -```unison +``` unison foo = +30 ``` @@ -69,7 +69,7 @@ myproject/main> update `update` again. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u bar : Nat bar = use Nat + diff --git a/unison-src/transcripts/update-term-aliases-in-different-ways.output.md b/unison-src/transcripts/update-term-aliases-in-different-ways.output.md index 10e8303ca..3d16a9254 100644 --- a/unison-src/transcripts/update-term-aliases-in-different-ways.output.md +++ b/unison-src/transcripts/update-term-aliases-in-different-ways.output.md @@ -4,7 +4,7 @@ scratch/main> builtins.merge Done. ``` -```unison +``` unison foo : Nat foo = 5 @@ -35,7 +35,7 @@ scratch/main> add foo : Nat ``` -```unison +``` unison foo : Nat foo = 6 diff --git a/unison-src/transcripts/update-term-to-different-type.output.md b/unison-src/transcripts/update-term-to-different-type.output.md index b1cad29f4..a525811da 100644 --- a/unison-src/transcripts/update-term-to-different-type.output.md +++ b/unison-src/transcripts/update-term-to-different-type.output.md @@ -4,7 +4,7 @@ scratch/main> builtins.merge Done. ``` -```unison +``` unison foo : Nat foo = 5 ``` @@ -30,7 +30,7 @@ scratch/main> add foo : Nat ``` -```unison +``` unison foo : Int foo = +5 ``` diff --git a/unison-src/transcripts/update-term-with-alias.output.md b/unison-src/transcripts/update-term-with-alias.output.md index 785a5e0d6..03124e794 100644 --- a/unison-src/transcripts/update-term-with-alias.output.md +++ b/unison-src/transcripts/update-term-with-alias.output.md @@ -4,7 +4,7 @@ scratch/main> builtins.merge Done. ``` -```unison +``` unison foo : Nat foo = 5 @@ -35,7 +35,7 @@ scratch/main> add foo : Nat ``` -```unison +``` unison foo : Nat foo = 6 ``` diff --git a/unison-src/transcripts/update-term-with-dependent-to-different-type.output.md b/unison-src/transcripts/update-term-with-dependent-to-different-type.output.md index c2357e31e..aef8fcb1e 100644 --- a/unison-src/transcripts/update-term-with-dependent-to-different-type.output.md +++ b/unison-src/transcripts/update-term-with-dependent-to-different-type.output.md @@ -4,7 +4,7 @@ scratch/main> builtins.merge Done. ``` -```unison +``` unison foo : Nat foo = 5 @@ -35,7 +35,7 @@ scratch/main> add foo : Nat ``` -```unison +``` unison foo : Int foo = +5 ``` @@ -67,7 +67,7 @@ scratch/main> update `update` again. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u bar : Nat bar = use Nat + diff --git a/unison-src/transcripts/update-term-with-dependent.output.md b/unison-src/transcripts/update-term-with-dependent.output.md index 9acbb2b7b..79aee87f3 100644 --- a/unison-src/transcripts/update-term-with-dependent.output.md +++ b/unison-src/transcripts/update-term-with-dependent.output.md @@ -4,7 +4,7 @@ scratch/main> builtins.merge Done. ``` -```unison +``` unison foo : Nat foo = 5 @@ -35,7 +35,7 @@ scratch/main> add foo : Nat ``` -```unison +``` unison foo : Nat foo = 6 ``` diff --git a/unison-src/transcripts/update-term.output.md b/unison-src/transcripts/update-term.output.md index 26bb87579..982c3b23a 100644 --- a/unison-src/transcripts/update-term.output.md +++ b/unison-src/transcripts/update-term.output.md @@ -4,7 +4,7 @@ scratch/main> builtins.merge Done. ``` -```unison +``` unison foo : Nat foo = 5 ``` @@ -30,7 +30,7 @@ scratch/main> add foo : Nat ``` -```unison +``` unison foo : Nat foo = 6 ``` diff --git a/unison-src/transcripts/update-test-to-non-test.output.md b/unison-src/transcripts/update-test-to-non-test.output.md index f08dd4bb9..fc9363d5a 100644 --- a/unison-src/transcripts/update-test-to-non-test.output.md +++ b/unison-src/transcripts/update-test-to-non-test.output.md @@ -4,7 +4,7 @@ scratch/main> builtins.merge Done. ``` -```unison +``` unison test> foo = [] ``` @@ -42,7 +42,7 @@ scratch/main> view foo foo = [] ``` -```unison +``` unison foo = 1 ``` diff --git a/unison-src/transcripts/update-test-watch-roundtrip.output.md b/unison-src/transcripts/update-test-watch-roundtrip.output.md index 2f1959eb5..5ba534cd3 100644 --- a/unison-src/transcripts/update-test-watch-roundtrip.output.md +++ b/unison-src/transcripts/update-test-watch-roundtrip.output.md @@ -1,7 +1,6 @@ - Given a test that depends on another definition, -```unison +``` unison foo n = n + 1 test> mynamespace.foo.test = @@ -20,7 +19,7 @@ scratch/main> add ``` if we change the type of the dependency, the test should show in the scratch file as a test watch. -```unison +``` unison foo n = "hello, world!" ``` @@ -51,7 +50,7 @@ scratch/main> update `update` again. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u test> mynamespace.foo.test = n = 2 if foo n == 2 then [Ok "passed"] else [Fail "wat"] diff --git a/unison-src/transcripts/update-type-add-constructor.output.md b/unison-src/transcripts/update-type-add-constructor.output.md index 4064cbf3d..5f58f745c 100644 --- a/unison-src/transcripts/update-type-add-constructor.output.md +++ b/unison-src/transcripts/update-type-add-constructor.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Bar Nat ``` @@ -24,7 +24,7 @@ scratch/main> add type Foo ``` -```unison +``` unison unique type Foo = Bar Nat | Baz Nat Nat diff --git a/unison-src/transcripts/update-type-add-field.output.md b/unison-src/transcripts/update-type-add-field.output.md index 6ba047164..b96464e02 100644 --- a/unison-src/transcripts/update-type-add-field.output.md +++ b/unison-src/transcripts/update-type-add-field.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Bar Nat ``` @@ -23,7 +23,7 @@ scratch/main> add type Foo ``` -```unison +``` unison unique type Foo = Bar Nat Nat ``` diff --git a/unison-src/transcripts/update-type-add-new-record.output.md b/unison-src/transcripts/update-type-add-new-record.output.md index 321ac28ec..4e10132bc 100644 --- a/unison-src/transcripts/update-type-add-new-record.output.md +++ b/unison-src/transcripts/update-type-add-new-record.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = { bar : Nat } ``` diff --git a/unison-src/transcripts/update-type-add-record-field.output.md b/unison-src/transcripts/update-type-add-record-field.output.md index d0a7a700e..1997eb2ac 100644 --- a/unison-src/transcripts/update-type-add-record-field.output.md +++ b/unison-src/transcripts/update-type-add-record-field.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = { bar : Nat } ``` @@ -29,7 +29,7 @@ scratch/main> add Foo.bar.set : Nat -> Foo -> Foo ``` -```unison +``` unison unique type Foo = { bar : Nat, baz : Int } ``` diff --git a/unison-src/transcripts/update-type-constructor-alias.output.md b/unison-src/transcripts/update-type-constructor-alias.output.md index 21cea73a9..76291ee05 100644 --- a/unison-src/transcripts/update-type-constructor-alias.output.md +++ b/unison-src/transcripts/update-type-constructor-alias.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Bar Nat ``` @@ -27,7 +27,7 @@ scratch/main> alias.term Foo.Bar Foo.BarAlias Done. ``` -```unison +``` unison unique type Foo = Bar Nat Nat ``` diff --git a/unison-src/transcripts/update-type-delete-constructor-with-dependent.output.md b/unison-src/transcripts/update-type-delete-constructor-with-dependent.output.md index f443c3426..3eca077a5 100644 --- a/unison-src/transcripts/update-type-delete-constructor-with-dependent.output.md +++ b/unison-src/transcripts/update-type-delete-constructor-with-dependent.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Bar Nat | Baz Nat Nat @@ -32,7 +32,7 @@ scratch/main> add foo : Foo -> Nat ``` -```unison +``` unison unique type Foo = Bar Nat ``` @@ -64,7 +64,7 @@ scratch/main> update `update` again. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u foo : Foo -> Nat foo = cases Bar n -> n diff --git a/unison-src/transcripts/update-type-delete-constructor.output.md b/unison-src/transcripts/update-type-delete-constructor.output.md index 1aa01c8a5..05d18c259 100644 --- a/unison-src/transcripts/update-type-delete-constructor.output.md +++ b/unison-src/transcripts/update-type-delete-constructor.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Bar Nat | Baz Nat Nat @@ -25,7 +25,7 @@ scratch/main> add type Foo ``` -```unison +``` unison unique type Foo = Bar Nat ``` diff --git a/unison-src/transcripts/update-type-delete-record-field.output.md b/unison-src/transcripts/update-type-delete-record-field.output.md index e2691b814..dcdfa6d51 100644 --- a/unison-src/transcripts/update-type-delete-record-field.output.md +++ b/unison-src/transcripts/update-type-delete-record-field.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = { bar : Nat, baz : Int } ``` @@ -35,7 +35,7 @@ scratch/main> add Foo.baz.set : Int -> Foo -> Foo ``` -```unison +``` unison unique type Foo = { bar : Nat } ``` @@ -103,7 +103,7 @@ scratch/main> find.verbose ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u Foo.baz : Foo -> Int Foo.baz = cases Foo _ baz -> baz diff --git a/unison-src/transcripts/update-type-missing-constructor.output.md b/unison-src/transcripts/update-type-missing-constructor.output.md index 59df270a5..2344e4319 100644 --- a/unison-src/transcripts/update-type-missing-constructor.output.md +++ b/unison-src/transcripts/update-type-missing-constructor.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Bar Nat ``` @@ -29,7 +29,7 @@ scratch/main> delete.term Foo.Bar ``` Now we've set up a situation where the original constructor missing. -```unison +``` unison unique type Foo = Bar Nat Nat ``` diff --git a/unison-src/transcripts/update-type-nested-decl-aliases.output.md b/unison-src/transcripts/update-type-nested-decl-aliases.output.md index afddbf3de..e67a1c4b1 100644 --- a/unison-src/transcripts/update-type-nested-decl-aliases.output.md +++ b/unison-src/transcripts/update-type-nested-decl-aliases.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Bar Nat structural type A.B = OneAlias Foo @@ -30,7 +30,7 @@ scratch/main> add type Foo ``` -```unison +``` unison unique type Foo = Bar Nat Nat ``` @@ -65,7 +65,7 @@ scratch/main> update `update` again. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u structural type A = B.OneAlias Foo structural type A.B = OneAlias Foo diff --git a/unison-src/transcripts/update-type-no-op-record.output.md b/unison-src/transcripts/update-type-no-op-record.output.md index 8d46e420c..159f9aa86 100644 --- a/unison-src/transcripts/update-type-no-op-record.output.md +++ b/unison-src/transcripts/update-type-no-op-record.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = { bar : Nat } ``` diff --git a/unison-src/transcripts/update-type-stray-constructor-alias.output.md b/unison-src/transcripts/update-type-stray-constructor-alias.output.md index 0e906b70d..54a1e5965 100644 --- a/unison-src/transcripts/update-type-stray-constructor-alias.output.md +++ b/unison-src/transcripts/update-type-stray-constructor-alias.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Bar Nat ``` @@ -27,7 +27,7 @@ scratch/main> alias.term Foo.Bar Stray.BarAlias Done. ``` -```unison +``` unison unique type Foo = Bar Nat Nat ``` diff --git a/unison-src/transcripts/update-type-stray-constructor.output.md b/unison-src/transcripts/update-type-stray-constructor.output.md index a76b034b4..999c57ae4 100644 --- a/unison-src/transcripts/update-type-stray-constructor.output.md +++ b/unison-src/transcripts/update-type-stray-constructor.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Bar Nat ``` @@ -29,7 +29,7 @@ scratch/main> move.term Foo.Bar Stray.Bar ``` Now we've set up a situation where the constructor is not where it's supposed to be; it's somewhere else. -```unison +``` unison unique type Foo = Bar Nat Nat ``` diff --git a/unison-src/transcripts/update-type-turn-constructor-into-smart-constructor.output.md b/unison-src/transcripts/update-type-turn-constructor-into-smart-constructor.output.md index a00b5dde6..cff0653a0 100644 --- a/unison-src/transcripts/update-type-turn-constructor-into-smart-constructor.output.md +++ b/unison-src/transcripts/update-type-turn-constructor-into-smart-constructor.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Bar Nat makeFoo : Nat -> Foo @@ -28,7 +28,7 @@ scratch/main> add makeFoo : Nat -> Foo ``` -```unison +``` unison unique type Foo = internal.Bar Nat Foo.Bar : Nat -> Foo diff --git a/unison-src/transcripts/update-type-turn-non-record-into-record.output.md b/unison-src/transcripts/update-type-turn-non-record-into-record.output.md index fb1f2dd2c..a9a3bf467 100644 --- a/unison-src/transcripts/update-type-turn-non-record-into-record.output.md +++ b/unison-src/transcripts/update-type-turn-non-record-into-record.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Nat ``` @@ -23,7 +23,7 @@ scratch/main> add type Foo ``` -```unison +``` unison unique type Foo = { bar : Nat } ``` diff --git a/unison-src/transcripts/update-type-with-dependent-term.output.md b/unison-src/transcripts/update-type-with-dependent-term.output.md index 1ab2b586b..09d0a63f5 100644 --- a/unison-src/transcripts/update-type-with-dependent-term.output.md +++ b/unison-src/transcripts/update-type-with-dependent-term.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Bar Nat incrFoo : Foo -> Foo @@ -28,7 +28,7 @@ scratch/main> add incrFoo : Foo -> Foo ``` -```unison +``` unison unique type Foo = Bar Nat Nat ``` @@ -59,7 +59,7 @@ scratch/main> update `update` again. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u incrFoo : Foo -> Foo incrFoo = cases Bar n -> Bar (n Nat.+ 1) diff --git a/unison-src/transcripts/update-type-with-dependent-type-to-different-kind.output.md b/unison-src/transcripts/update-type-with-dependent-type-to-different-kind.output.md index edc63c214..ea8d65242 100644 --- a/unison-src/transcripts/update-type-with-dependent-type-to-different-kind.output.md +++ b/unison-src/transcripts/update-type-with-dependent-type-to-different-kind.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Bar Nat unique type Baz = Qux Foo ``` @@ -26,7 +26,7 @@ scratch/main> add type Foo ``` -```unison +``` unison unique type Foo a = Bar Nat a ``` @@ -57,7 +57,7 @@ scratch/main> update `update` again. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u type Baz = Qux Foo type Foo a = Bar Nat a diff --git a/unison-src/transcripts/update-type-with-dependent-type.output.md b/unison-src/transcripts/update-type-with-dependent-type.output.md index 2523eed7d..474a8ceef 100644 --- a/unison-src/transcripts/update-type-with-dependent-type.output.md +++ b/unison-src/transcripts/update-type-with-dependent-type.output.md @@ -1,4 +1,4 @@ -```unison +``` unison unique type Foo = Bar Nat unique type Baz = Qux Foo ``` @@ -26,7 +26,7 @@ scratch/main> add type Foo ``` -```unison +``` unison unique type Foo = Bar Nat Nat ``` diff --git a/unison-src/transcripts/update-watch.output.md b/unison-src/transcripts/update-watch.output.md index c9c951045..36bc89ae2 100644 --- a/unison-src/transcripts/update-watch.output.md +++ b/unison-src/transcripts/update-watch.output.md @@ -1,4 +1,4 @@ -```unison +``` unison > 1 ``` diff --git a/unison-src/transcripts/upgrade-happy-path.output.md b/unison-src/transcripts/upgrade-happy-path.output.md index b2d8bb80a..33c8b6c8d 100644 --- a/unison-src/transcripts/upgrade-happy-path.output.md +++ b/unison-src/transcripts/upgrade-happy-path.output.md @@ -1,4 +1,4 @@ -```unison +``` unison lib.old.foo = 17 lib.new.foo = 18 thingy = lib.old.foo + 10 diff --git a/unison-src/transcripts/upgrade-sad-path.output.md b/unison-src/transcripts/upgrade-sad-path.output.md index f0811cd8e..d25d2f8c4 100644 --- a/unison-src/transcripts/upgrade-sad-path.output.md +++ b/unison-src/transcripts/upgrade-sad-path.output.md @@ -1,4 +1,4 @@ -```unison +``` unison lib.old.foo = 17 lib.new.foo = +18 thingy = lib.old.foo + 10 @@ -49,7 +49,7 @@ proj/main> upgrade old new to delete the temporary branch and switch back to main. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u thingy : Nat thingy = use Nat + @@ -58,7 +58,7 @@ thingy = Resolve the error and commit the upgrade. -```unison +``` unison thingy = foo + +10 ``` diff --git a/unison-src/transcripts/upgrade-suffixifies-properly.output.md b/unison-src/transcripts/upgrade-suffixifies-properly.output.md index 4b7b31319..cacefecf8 100644 --- a/unison-src/transcripts/upgrade-suffixifies-properly.output.md +++ b/unison-src/transcripts/upgrade-suffixifies-properly.output.md @@ -1,4 +1,4 @@ -```unison +``` unison lib.old.foo = 25 lib.new.foo = +30 a.x.x.x.x = 100 @@ -61,7 +61,7 @@ myproject/main> upgrade old new to delete the temporary branch and switch back to main. ``` -```unison:added-by-ucm scratch.u +``` unison:added-by-ucm scratch.u bar : Nat bar = use Nat + diff --git a/unison-src/transcripts/upgrade-with-old-alias.output.md b/unison-src/transcripts/upgrade-with-old-alias.output.md index 9fdea6d7b..46b073616 100644 --- a/unison-src/transcripts/upgrade-with-old-alias.output.md +++ b/unison-src/transcripts/upgrade-with-old-alias.output.md @@ -1,4 +1,4 @@ -```unison +``` unison lib.old.foo = 141 lib.new.foo = 142 bar = 141 diff --git a/unison-src/transcripts/view.output.md b/unison-src/transcripts/view.output.md index 71ebf98da..c300d96d3 100644 --- a/unison-src/transcripts/view.output.md +++ b/unison-src/transcripts/view.output.md @@ -1,6 +1,6 @@ # View commands -```unison +``` unison a.thing = "a" b.thing = "b" ``` diff --git a/unison-src/transcripts/watch-expressions.output.md b/unison-src/transcripts/watch-expressions.output.md index 589b70833..0641ab1a6 100644 --- a/unison-src/transcripts/watch-expressions.output.md +++ b/unison-src/transcripts/watch-expressions.output.md @@ -4,7 +4,7 @@ scratch/main> builtins.mergeio Done. ``` -```unison +``` unison test> pass = [Ok "Passed"] ``` @@ -36,7 +36,7 @@ scratch/main> add pass : [Result] ``` -```unison +``` unison test> pass = [Ok "Passed"] ``` @@ -71,7 +71,7 @@ scratch/main> test Tip: Use view 1 to view the source of a test. ``` -```unison +``` unison > ImmutableArray.fromList [?a, ?b, ?c] > ImmutableByteArray.fromBytes 0xs123456 ``` From 0031542fafa33d05d55e6a66cb3337d931cfdb43 Mon Sep 17 00:00:00 2001 From: Greg Pfeil Date: Wed, 10 Jul 2024 10:17:15 -0600 Subject: [PATCH 12/16] Add a space before code block info strings This is for consistency with the `cmark` style. Now the blocks we still pretty-print ourselves will match the bulk of them that `cmark` produces. --- .../IntegrationTests/transcript.output.md | 4 +- .../src/Unison/Codebase/TranscriptParser.hs | 6 +- .../transcripts-manual/docs.to-html.output.md | 6 +- .../transcripts-manual/rewrites.output.md | 20 +- .../transcripts-round-trip/main.output.md | 10 +- .../transcripts-using-base/_base.output.md | 4 +- .../all-base-hashes.output.md | 2 +- .../binary-encoding-nats.output.md | 4 +- .../transcripts-using-base/codeops.output.md | 16 +- .../transcripts-using-base/doc.output.md | 10 +- .../failure-tests.output.md | 8 +- .../fix2158-1.output.md | 2 +- .../transcripts-using-base/fix2297.output.md | 2 +- .../transcripts-using-base/fix2358.output.md | 4 +- .../transcripts-using-base/fix3166.output.md | 6 +- .../transcripts-using-base/fix3542.output.md | 2 +- .../transcripts-using-base/fix3939.output.md | 4 +- .../transcripts-using-base/fix4746.output.md | 2 +- .../transcripts-using-base/fix5129.output.md | 4 +- .../transcripts-using-base/hashing.output.md | 16 +- .../transcripts-using-base/mvar.output.md | 4 +- .../nat-coersion.output.md | 4 +- .../transcripts-using-base/net.output.md | 8 +- .../random-deserial.output.md | 4 +- .../ref-promise.output.md | 20 +- .../serial-test-00.output.md | 4 +- .../serial-test-01.output.md | 4 +- .../serial-test-02.output.md | 4 +- .../serial-test-03.output.md | 4 +- .../serial-test-04.output.md | 4 +- .../transcripts-using-base/stm.output.md | 8 +- .../test-watch-dependencies.output.md | 8 +- .../transcripts-using-base/thread.output.md | 10 +- .../transcripts-using-base/tls.output.md | 8 +- .../transcripts-using-base/utf8.output.md | 10 +- unison-src/transcripts/abilities.output.md | 4 +- ...ability-order-doesnt-affect-hash.output.md | 4 +- ...ability-term-conflicts-on-update.output.md | 22 +- unison-src/transcripts/add-run.output.md | 40 ++-- .../add-test-watch-roundtrip.output.md | 2 +- .../transcripts/addupdatemessages.output.md | 16 +- unison-src/transcripts/alias-many.output.md | 2 +- unison-src/transcripts/alias-term.output.md | 8 +- unison-src/transcripts/alias-type.output.md | 8 +- unison-src/transcripts/anf-tests.output.md | 4 +- unison-src/transcripts/any-extract.output.md | 4 +- .../transcripts/api-doc-rendering.output.md | 4 +- unison-src/transcripts/api-find.output.md | 6 +- .../transcripts/api-getDefinition.output.md | 6 +- .../api-list-projects-branches.output.md | 2 +- .../api-namespace-details.output.md | 6 +- .../transcripts/api-namespace-list.output.md | 6 +- .../transcripts/api-summaries.output.md | 4 +- .../block-on-required-update.output.md | 8 +- unison-src/transcripts/blocks.output.md | 26 +-- .../boolean-op-pretty-print-2819.output.md | 4 +- .../transcripts/branch-command.output.md | 8 +- .../branch-relative-path.output.md | 8 +- unison-src/transcripts/bug-fix-4354.output.md | 2 +- .../transcripts/bug-strange-closure.output.md | 8 +- .../transcripts/builtins-merge.output.md | 2 +- unison-src/transcripts/builtins.output.md | 12 +- .../transcripts/bytesFromList.output.md | 2 +- unison-src/transcripts/check763.output.md | 4 +- unison-src/transcripts/check873.output.md | 6 +- .../constructor-applied-to-unit.output.md | 2 +- .../transcripts/contrabilities.output.md | 2 +- .../transcripts/create-author.output.md | 2 +- .../transcripts/cycle-update-1.output.md | 8 +- .../transcripts/cycle-update-2.output.md | 8 +- .../transcripts/cycle-update-3.output.md | 8 +- .../transcripts/cycle-update-4.output.md | 8 +- .../transcripts/cycle-update-5.output.md | 8 +- .../transcripts/debug-definitions.output.md | 2 +- .../transcripts/debug-name-diffs.output.md | 4 +- unison-src/transcripts/deep-names.output.md | 8 +- .../transcripts/definition-diff-api.output.md | 14 +- ...elete-namespace-dependents-check.output.md | 4 +- .../transcripts/delete-namespace.output.md | 12 +- .../delete-project-branch.output.md | 8 +- .../transcripts/delete-project.output.md | 2 +- .../transcripts/delete-silent.output.md | 4 +- unison-src/transcripts/delete.output.md | 28 +-- ...ependents-dependencies-debugfile.output.md | 4 +- .../transcripts/destructuring-binds.output.md | 14 +- .../transcripts/diff-namespace.output.md | 32 +-- .../transcripts/doc-formatting.output.md | 54 ++--- .../doc-type-link-keywords.output.md | 2 +- unison-src/transcripts/doc1.output.md | 16 +- unison-src/transcripts/doc2.output.md | 2 +- unison-src/transcripts/doc2markdown.output.md | 4 +- ...t-upgrade-refs-that-exist-in-old.output.md | 4 +- .../transcripts/duplicate-names.output.md | 12 +- .../duplicate-term-detection.output.md | 8 +- unison-src/transcripts/ed25519.output.md | 2 +- unison-src/transcripts/edit-command.output.md | 8 +- .../transcripts/edit-namespace.output.md | 8 +- .../transcripts/empty-namespaces.output.md | 14 +- .../transcripts/emptyCodebase.output.md | 6 +- .../transcripts/error-messages.output.md | 40 ++-- .../transcripts/escape-sequences.output.md | 2 +- unison-src/transcripts/find-by-type.output.md | 4 +- unison-src/transcripts/find-command.output.md | 10 +- .../fix-1381-excess-propagate.output.md | 8 +- .../transcripts/fix-big-list-crash.output.md | 2 +- unison-src/transcripts/fix-ls.output.md | 6 +- unison-src/transcripts/fix1063.output.md | 4 +- unison-src/transcripts/fix1334.output.md | 2 +- unison-src/transcripts/fix1390.output.md | 8 +- unison-src/transcripts/fix1532.output.md | 14 +- unison-src/transcripts/fix1696.output.md | 2 +- unison-src/transcripts/fix1709.output.md | 6 +- unison-src/transcripts/fix1731.output.md | 2 +- unison-src/transcripts/fix1800.output.md | 8 +- unison-src/transcripts/fix1844.output.md | 2 +- unison-src/transcripts/fix1926.output.md | 6 +- unison-src/transcripts/fix2026.output.md | 4 +- unison-src/transcripts/fix2027.output.md | 4 +- unison-src/transcripts/fix2049.output.md | 6 +- unison-src/transcripts/fix2053.output.md | 2 +- unison-src/transcripts/fix2156.output.md | 2 +- unison-src/transcripts/fix2167.output.md | 2 +- unison-src/transcripts/fix2187.output.md | 2 +- unison-src/transcripts/fix2231.output.md | 4 +- unison-src/transcripts/fix2238.output.md | 4 +- unison-src/transcripts/fix2244.output.md | 2 +- unison-src/transcripts/fix2254.output.md | 12 +- unison-src/transcripts/fix2268.output.md | 2 +- unison-src/transcripts/fix2334.output.md | 2 +- unison-src/transcripts/fix2344.output.md | 2 +- unison-src/transcripts/fix2350.output.md | 2 +- unison-src/transcripts/fix2353.output.md | 2 +- unison-src/transcripts/fix2354.output.md | 2 +- unison-src/transcripts/fix2355.output.md | 2 +- unison-src/transcripts/fix2378.output.md | 2 +- unison-src/transcripts/fix2423.output.md | 2 +- unison-src/transcripts/fix2474.output.md | 4 +- unison-src/transcripts/fix2628.output.md | 2 +- unison-src/transcripts/fix2663.output.md | 2 +- unison-src/transcripts/fix2693.output.md | 8 +- unison-src/transcripts/fix2712.output.md | 6 +- unison-src/transcripts/fix2795.output.md | 2 +- unison-src/transcripts/fix2840.output.md | 4 +- unison-src/transcripts/fix2970.output.md | 4 +- unison-src/transcripts/fix3037.output.md | 4 +- unison-src/transcripts/fix3171.output.md | 2 +- unison-src/transcripts/fix3196.output.md | 2 +- unison-src/transcripts/fix3215.output.md | 2 +- unison-src/transcripts/fix3244.output.md | 2 +- unison-src/transcripts/fix3265.output.md | 4 +- unison-src/transcripts/fix3634.output.md | 4 +- unison-src/transcripts/fix3678.output.md | 2 +- unison-src/transcripts/fix3752.output.md | 2 +- unison-src/transcripts/fix3759.output.md | 2 +- unison-src/transcripts/fix3773.output.md | 2 +- unison-src/transcripts/fix4172.output.md | 8 +- unison-src/transcripts/fix4280.output.md | 2 +- unison-src/transcripts/fix4397.output.md | 2 +- unison-src/transcripts/fix4415.output.md | 2 +- unison-src/transcripts/fix4424.output.md | 4 +- unison-src/transcripts/fix4482.output.md | 4 +- unison-src/transcripts/fix4498.output.md | 4 +- unison-src/transcripts/fix4515.output.md | 8 +- unison-src/transcripts/fix4528.output.md | 4 +- unison-src/transcripts/fix4556.output.md | 8 +- unison-src/transcripts/fix4592.output.md | 2 +- unison-src/transcripts/fix4618.output.md | 8 +- unison-src/transcripts/fix4722.output.md | 2 +- unison-src/transcripts/fix4780.output.md | 2 +- unison-src/transcripts/fix4898.output.md | 6 +- unison-src/transcripts/fix5055.output.md | 6 +- unison-src/transcripts/fix5080.output.md | 6 +- unison-src/transcripts/fix614.output.md | 10 +- unison-src/transcripts/fix689.output.md | 2 +- unison-src/transcripts/fix693.output.md | 12 +- unison-src/transcripts/fix845.output.md | 10 +- unison-src/transcripts/fix849.output.md | 2 +- unison-src/transcripts/fix942.output.md | 12 +- unison-src/transcripts/fix987.output.md | 8 +- unison-src/transcripts/formatter.output.md | 6 +- .../transcripts/fuzzy-options.output.md | 10 +- .../generic-parse-errors.output.md | 12 +- unison-src/transcripts/hello.output.md | 6 +- unison-src/transcripts/help.output.md | 2 +- unison-src/transcripts/higher-rank.output.md | 10 +- .../transcripts/input-parse-errors.output.md | 4 +- .../transcripts/io-test-command.output.md | 6 +- unison-src/transcripts/io.output.md | 42 ++-- .../transcripts/kind-inference.output.md | 36 +-- unison-src/transcripts/lambdacase.output.md | 20 +- .../transcripts/lsp-fold-ranges.output.md | 2 +- .../transcripts/lsp-name-completion.output.md | 4 +- unison-src/transcripts/merge.output.md | 206 +++++++++--------- unison-src/transcripts/move-all.output.md | 20 +- .../transcripts/move-namespace.output.md | 36 +-- .../transcripts/name-segment-escape.output.md | 4 +- .../transcripts/name-selection.output.md | 14 +- unison-src/transcripts/names.output.md | 8 +- .../namespace-deletion-regression.output.md | 2 +- .../namespace-dependencies.output.md | 2 +- .../transcripts/numbered-args.output.md | 14 +- .../transcripts/old-fold-right.output.md | 2 +- .../pattern-match-coverage.output.md | 112 +++++----- .../pattern-pretty-print-2345.output.md | 4 +- .../transcripts/patternMatchTls.output.md | 4 +- unison-src/transcripts/patterns.output.md | 2 +- unison-src/transcripts/propagate.output.md | 32 +-- unison-src/transcripts/pull-errors.output.md | 2 +- unison-src/transcripts/records.output.md | 14 +- unison-src/transcripts/reflog.output.md | 14 +- .../release-draft-command.output.md | 8 +- unison-src/transcripts/reset.output.md | 26 +-- .../transcripts/resolution-failures.output.md | 8 +- unison-src/transcripts/rsa.output.md | 2 +- unison-src/transcripts/scope-ref.output.md | 2 +- unison-src/transcripts/suffixes.output.md | 22 +- .../sum-type-update-conflicts.output.md | 8 +- .../transcripts/switch-command.output.md | 14 +- .../transcripts/tab-completion.output.md | 20 +- unison-src/transcripts/test-command.output.md | 14 +- .../transcripts/text-literals.output.md | 4 +- .../transcripts/todo-bug-builtins.output.md | 8 +- unison-src/transcripts/todo.output.md | 10 +- .../top-level-exceptions.output.md | 10 +- .../transcript-parser-commands.output.md | 8 +- unison-src/transcripts/type-deps.output.md | 4 +- .../type-modifier-are-optional.output.md | 2 +- .../transcripts/unique-type-churn.output.md | 16 +- .../transcripts/unitnamespace.output.md | 4 +- .../transcripts/universal-cmp.output.md | 6 +- .../transcripts/unsafe-coerce.output.md | 4 +- .../update-ignores-lib-namespace.output.md | 8 +- .../transcripts/update-on-conflict.output.md | 8 +- .../update-suffixifies-properly.output.md | 8 +- ...e-term-aliases-in-different-ways.output.md | 10 +- .../update-term-to-different-type.output.md | 10 +- .../update-term-with-alias.output.md | 10 +- ...with-dependent-to-different-type.output.md | 10 +- .../update-term-with-dependent.output.md | 10 +- unison-src/transcripts/update-term.output.md | 10 +- .../update-test-to-non-test.output.md | 10 +- .../update-test-watch-roundtrip.output.md | 6 +- .../update-type-add-constructor.output.md | 8 +- .../update-type-add-field.output.md | 8 +- .../update-type-add-new-record.output.md | 4 +- .../update-type-add-record-field.output.md | 8 +- .../update-type-constructor-alias.output.md | 8 +- ...elete-constructor-with-dependent.output.md | 8 +- .../update-type-delete-constructor.output.md | 8 +- .../update-type-delete-record-field.output.md | 8 +- .../update-type-missing-constructor.output.md | 8 +- .../update-type-nested-decl-aliases.output.md | 8 +- .../update-type-no-op-record.output.md | 6 +- ...ate-type-stray-constructor-alias.output.md | 8 +- .../update-type-stray-constructor.output.md | 8 +- ...nstructor-into-smart-constructor.output.md | 8 +- ...type-turn-non-record-into-record.output.md | 8 +- .../update-type-with-dependent-term.output.md | 8 +- ...dependent-type-to-different-kind.output.md | 8 +- .../update-type-with-dependent-type.output.md | 8 +- unison-src/transcripts/update-watch.output.md | 4 +- .../transcripts/upgrade-happy-path.output.md | 8 +- .../transcripts/upgrade-sad-path.output.md | 10 +- .../upgrade-suffixifies-properly.output.md | 6 +- .../upgrade-with-old-alias.output.md | 4 +- unison-src/transcripts/view.output.md | 2 +- .../transcripts/watch-expressions.output.md | 12 +- 267 files changed, 1157 insertions(+), 1157 deletions(-) diff --git a/unison-cli-integration/integration-tests/IntegrationTests/transcript.output.md b/unison-cli-integration/integration-tests/IntegrationTests/transcript.output.md index 09def1616..2cf4f325c 100644 --- a/unison-cli-integration/integration-tests/IntegrationTests/transcript.output.md +++ b/unison-cli-integration/integration-tests/IntegrationTests/transcript.output.md @@ -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: diff --git a/unison-cli/src/Unison/Codebase/TranscriptParser.hs b/unison-cli/src/Unison/Codebase/TranscriptParser.hs index ebabe7b4d..bf71f18a8 100644 --- a/unison-cli/src/Unison/Codebase/TranscriptParser.hs +++ b/unison-cli/src/Unison/Codebase/TranscriptParser.hs @@ -423,14 +423,14 @@ 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 "```") awaitInput @@ -438,7 +438,7 @@ run verbosity dir stanzas codebase runtime sbRuntime nRuntime config ucmVersion 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 diff --git a/unison-src/transcripts-manual/docs.to-html.output.md b/unison-src/transcripts-manual/docs.to-html.output.md index e59537da2..5c938806b 100644 --- a/unison-src/transcripts-manual/docs.to-html.output.md +++ b/unison-src/transcripts-manual/docs.to-html.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm test-html-docs/main> builtins.mergeio lib.builtins Done. @@ -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: diff --git a/unison-src/transcripts-manual/rewrites.output.md b/unison-src/transcripts-manual/rewrites.output.md index 91d1272ec..26cd59b49 100644 --- a/unison-src/transcripts-manual/rewrites.output.md +++ b/unison-src/transcripts-manual/rewrites.output.md @@ -29,7 +29,7 @@ rule2 x = @rewrite signature Optional ==> Optional2 Let's rewrite these: -```ucm +``` ucm scratch/main> rewrite rule1 ☝️ @@ -110,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 @@ -156,7 +156,7 @@ blah2 = 456 Let's apply the rewrite `woot1to2`: -```ucm +``` ucm scratch/main> rewrite woot1to2 ☝️ @@ -192,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 @@ -224,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 @@ -265,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 ☝️ @@ -299,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. @@ -330,7 +330,7 @@ rule a = @rewrite term 233 ==> a ``` -```ucm +``` ucm scratch/main> rewrite rule ☝️ @@ -356,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. @@ -386,7 +386,7 @@ findEitherEx x = @rewrite term Left ("hello", x) ==> Left ("hello" Text.++ x) findEitherFailure = @rewrite signature a . Either Failure a ==> () ``` -```ucm +``` ucm scratch/main> sfind findEitherEx 🔎 diff --git a/unison-src/transcripts-round-trip/main.output.md b/unison-src/transcripts-round-trip/main.output.md index 05d85375e..5230f3495 100644 --- a/unison-src/transcripts-round-trip/main.output.md +++ b/unison-src/transcripts-round-trip/main.output.md @@ -4,7 +4,7 @@ This transcript verifies that the pretty-printer produces code that can be succe 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 ☝️ @@ -770,7 +770,7 @@ 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. @@ -784,7 +784,7 @@ This just makes 'roundtrip.u' the latest scratch file. x = () ``` -```ucm +``` ucm .a3> edit 1-5000 ☝️ @@ -819,7 +819,7 @@ sloppyDocEval = These are currently all expected to have different hashes on round trip. -```ucm +``` ucm .> diff.namespace a3 a3_old Updates: diff --git a/unison-src/transcripts-using-base/_base.output.md b/unison-src/transcripts-using-base/_base.output.md index ef2da4b88..eaad4fb38 100644 --- a/unison-src/transcripts-using-base/_base.output.md +++ b/unison-src/transcripts-using-base/_base.output.md @@ -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: diff --git a/unison-src/transcripts-using-base/all-base-hashes.output.md b/unison-src/transcripts-using-base/all-base-hashes.output.md index 99d4128d0..0b656ef0c 100644 --- a/unison-src/transcripts-using-base/all-base-hashes.output.md +++ b/unison-src/transcripts-using-base/all-base-hashes.output.md @@ -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 diff --git a/unison-src/transcripts-using-base/binary-encoding-nats.output.md b/unison-src/transcripts-using-base/binary-encoding-nats.output.md index 5f4b4c889..da9bc7a95 100644 --- a/unison-src/transcripts-using-base/binary-encoding-nats.output.md +++ b/unison-src/transcripts-using-base/binary-encoding-nats.output.md @@ -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: diff --git a/unison-src/transcripts-using-base/codeops.output.md b/unison-src/transcripts-using-base/codeops.output.md index 4a4671c53..6e51f371d 100644 --- a/unison-src/transcripts-using-base/codeops.output.md +++ b/unison-src/transcripts-using-base/codeops.output.md @@ -151,7 +151,7 @@ swapped name link = rejected ("swapped " ++ name) rco ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -198,7 +198,7 @@ swapped name link = ->{Throw Text} () ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -315,7 +315,7 @@ badLoad _ = Left _ -> [Fail "Exception"] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -342,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: @@ -428,7 +428,7 @@ codeTests = ] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -441,7 +441,7 @@ codeTests = codeTests : '{IO} [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -514,7 +514,7 @@ vtests _ = ] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -528,7 +528,7 @@ vtests _ = vtests : '{IO} [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts-using-base/doc.output.md b/unison-src/transcripts-using-base/doc.output.md index 12a284c07..850929aba 100644 --- a/unison-src/transcripts-using-base/doc.output.md +++ b/unison-src/transcripts-using-base/doc.output.md @@ -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 diff --git a/unison-src/transcripts-using-base/failure-tests.output.md b/unison-src/transcripts-using-base/failure-tests.output.md index adbf9bc53..3a661894d 100644 --- a/unison-src/transcripts-using-base/failure-tests.output.md +++ b/unison-src/transcripts-using-base/failure-tests.output.md @@ -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 💔💥 diff --git a/unison-src/transcripts-using-base/fix2158-1.output.md b/unison-src/transcripts-using-base/fix2158-1.output.md index 2099749bc..9a692bb3d 100644 --- a/unison-src/transcripts-using-base/fix2158-1.output.md +++ b/unison-src/transcripts-using-base/fix2158-1.output.md @@ -11,7 +11,7 @@ Async.parMap f as = List.map await tasks ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts-using-base/fix2297.output.md b/unison-src/transcripts-using-base/fix2297.output.md index 3d8ca7d62..949cdd89e 100644 --- a/unison-src/transcripts-using-base/fix2297.output.md +++ b/unison-src/transcripts-using-base/fix2297.output.md @@ -24,7 +24,7 @@ wat = handleTrivial testAction -- Somehow this completely forgets about Excepti > handleTrivial testAction ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts-using-base/fix2358.output.md b/unison-src/transcripts-using-base/fix2358.output.md index 8c8582c27..7e71541b7 100644 --- a/unison-src/transcripts-using-base/fix2358.output.md +++ b/unison-src/transcripts-using-base/fix2358.output.md @@ -8,7 +8,7 @@ timingApp2 _ = printLine "World" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -21,7 +21,7 @@ timingApp2 _ = timingApp2 : '{IO, Exception} () ``` -```ucm +``` ucm scratch/main> run timingApp2 () diff --git a/unison-src/transcripts-using-base/fix3166.output.md b/unison-src/transcripts-using-base/fix3166.output.md index 35e5815f9..9e33e1456 100644 --- a/unison-src/transcripts-using-base/fix3166.output.md +++ b/unison-src/transcripts-using-base/fix3166.output.md @@ -31,7 +31,7 @@ increment n = 1 + n Stream.toList s2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -82,7 +82,7 @@ foo _ = > h foo 337 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -126,7 +126,7 @@ hmm = > hmm ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts-using-base/fix3542.output.md b/unison-src/transcripts-using-base/fix3542.output.md index 5d6fe4b53..976f1c063 100644 --- a/unison-src/transcripts-using-base/fix3542.output.md +++ b/unison-src/transcripts-using-base/fix3542.output.md @@ -13,7 +13,7 @@ arrayList v n = do > Scope.run '(catch (arrayList 7 8)) ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts-using-base/fix3939.output.md b/unison-src/transcripts-using-base/fix3939.output.md index 75c0dcbea..9240c712f 100644 --- a/unison-src/transcripts-using-base/fix3939.output.md +++ b/unison-src/transcripts-using-base/fix3939.output.md @@ -5,7 +5,7 @@ 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: diff --git a/unison-src/transcripts-using-base/fix4746.output.md b/unison-src/transcripts-using-base/fix4746.output.md index 62f7632c0..8887e3474 100644 --- a/unison-src/transcripts-using-base/fix4746.output.md +++ b/unison-src/transcripts-using-base/fix4746.output.md @@ -35,7 +35,7 @@ run s = () ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts-using-base/fix5129.output.md b/unison-src/transcripts-using-base/fix5129.output.md index 90f205bd4..3d07942a7 100644 --- a/unison-src/transcripts-using-base/fix5129.output.md +++ b/unison-src/transcripts-using-base/fix5129.output.md @@ -22,7 +22,7 @@ go = do foreach forkIt [thunk] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -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. diff --git a/unison-src/transcripts-using-base/hashing.output.md b/unison-src/transcripts-using-base/hashing.output.md index 721c1ec3c..3bede2577 100644 --- a/unison-src/transcripts-using-base/hashing.output.md +++ b/unison-src/transcripts-using-base/hashing.output.md @@ -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) @@ -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 @@ -159,7 +159,7 @@ Note that the universal versions of `hash` and `hmac` are currently unimplemente > hash Sha3_256 (fromHex "3849238492") ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -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) @@ -378,7 +378,7 @@ test> hmac_sha2_512.tests.ex2 = "164b7a7bfcf819e2e395fbe73b56e0a387bd64222e831fd610270cd7ea2505549758bf75c05a994a6d034f65f8f0e6fdcaeab1a34d4a6b4b636e070a38bce737" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -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) diff --git a/unison-src/transcripts-using-base/mvar.output.md b/unison-src/transcripts-using-base/mvar.output.md index 466291ead..c0bfdac99 100644 --- a/unison-src/transcripts-using-base/mvar.output.md +++ b/unison-src/transcripts-using-base/mvar.output.md @@ -50,7 +50,7 @@ testMvars _ = runTest test ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -64,7 +64,7 @@ testMvars _ = testMvars : '{IO} [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts-using-base/nat-coersion.output.md b/unison-src/transcripts-using-base/nat-coersion.output.md index dac858429..14d5c6685 100644 --- a/unison-src/transcripts-using-base/nat-coersion.output.md +++ b/unison-src/transcripts-using-base/nat-coersion.output.md @@ -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: diff --git a/unison-src/transcripts-using-base/net.output.md b/unison-src/transcripts-using-base/net.output.md index 702be91bb..4d95488cb 100644 --- a/unison-src/transcripts-using-base/net.output.md +++ b/unison-src/transcripts-using-base/net.output.md @@ -90,7 +90,7 @@ testDefaultPort _ = runTest test ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -105,7 +105,7 @@ testDefaultPort _ = testExplicitHost : '{IO} [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -177,7 +177,7 @@ testTcpConnect = 'let ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -192,7 +192,7 @@ testTcpConnect = 'let testTcpConnect : '{IO} [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts-using-base/random-deserial.output.md b/unison-src/transcripts-using-base/random-deserial.output.md index 66d6354d5..6c68e978e 100644 --- a/unison-src/transcripts-using-base/random-deserial.output.md +++ b/unison-src/transcripts-using-base/random-deserial.output.md @@ -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: diff --git a/unison-src/transcripts-using-base/ref-promise.output.md b/unison-src/transcripts-using-base/ref-promise.output.md index bcc4487c3..b44e98bb9 100644 --- a/unison-src/transcripts-using-base/ref-promise.output.md +++ b/unison-src/transcripts-using-base/ref-promise.output.md @@ -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: @@ -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: @@ -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: @@ -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: @@ -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: diff --git a/unison-src/transcripts-using-base/serial-test-00.output.md b/unison-src/transcripts-using-base/serial-test-00.output.md index 019289ccd..ce996f93b 100644 --- a/unison-src/transcripts-using-base/serial-test-00.output.md +++ b/unison-src/transcripts-using-base/serial-test-00.output.md @@ -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: diff --git a/unison-src/transcripts-using-base/serial-test-01.output.md b/unison-src/transcripts-using-base/serial-test-01.output.md index a1a9668c1..a6654a254 100644 --- a/unison-src/transcripts-using-base/serial-test-01.output.md +++ b/unison-src/transcripts-using-base/serial-test-01.output.md @@ -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: diff --git a/unison-src/transcripts-using-base/serial-test-02.output.md b/unison-src/transcripts-using-base/serial-test-02.output.md index 3a352b88b..102fea092 100644 --- a/unison-src/transcripts-using-base/serial-test-02.output.md +++ b/unison-src/transcripts-using-base/serial-test-02.output.md @@ -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: diff --git a/unison-src/transcripts-using-base/serial-test-03.output.md b/unison-src/transcripts-using-base/serial-test-03.output.md index a1ca50f90..a20eafe7f 100644 --- a/unison-src/transcripts-using-base/serial-test-03.output.md +++ b/unison-src/transcripts-using-base/serial-test-03.output.md @@ -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: diff --git a/unison-src/transcripts-using-base/serial-test-04.output.md b/unison-src/transcripts-using-base/serial-test-04.output.md index 0b0b6230e..990ce1479 100644 --- a/unison-src/transcripts-using-base/serial-test-04.output.md +++ b/unison-src/transcripts-using-base/serial-test-04.output.md @@ -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: diff --git a/unison-src/transcripts-using-base/stm.output.md b/unison-src/transcripts-using-base/stm.output.md index fd8fb9728..2e7724f9e 100644 --- a/unison-src/transcripts-using-base/stm.output.md +++ b/unison-src/transcripts-using-base/stm.output.md @@ -28,7 +28,7 @@ body k out v = atomically '(TVar.write out (Some n)) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -44,7 +44,7 @@ body k out v = loop : '{IO} Nat -> Nat -> Nat ->{IO} Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -90,7 +90,7 @@ tests : '{io2.IO} [Result] tests = '(map spawn nats) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -106,7 +106,7 @@ tests = '(map spawn nats) tests : '{IO} [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts-using-base/test-watch-dependencies.output.md b/unison-src/transcripts-using-base/test-watch-dependencies.output.md index b38e4373a..a32164356 100644 --- a/unison-src/transcripts-using-base/test-watch-dependencies.output.md +++ b/unison-src/transcripts-using-base/test-watch-dependencies.output.md @@ -15,7 +15,7 @@ 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: @@ -61,7 +61,7 @@ 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: diff --git a/unison-src/transcripts-using-base/thread.output.md b/unison-src/transcripts-using-base/thread.output.md index bab82e7eb..863d74969 100644 --- a/unison-src/transcripts-using-base/thread.output.md +++ b/unison-src/transcripts-using-base/thread.output.md @@ -16,7 +16,7 @@ testBasicFork = 'let ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -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: @@ -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: diff --git a/unison-src/transcripts-using-base/tls.output.md b/unison-src/transcripts-using-base/tls.output.md index fc0362d8c..76b9be278 100644 --- a/unison-src/transcripts-using-base/tls.output.md +++ b/unison-src/transcripts-using-base/tls.output.md @@ -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: @@ -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: diff --git a/unison-src/transcripts-using-base/utf8.output.md b/unison-src/transcripts-using-base/utf8.output.md index 0cd3d4c0d..15c15c027 100644 --- a/unison-src/transcripts-using-base/utf8.output.md +++ b/unison-src/transcripts-using-base/utf8.output.md @@ -2,7 +2,7 @@ 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 @@ -21,7 +21,7 @@ ascii = "ABCDE" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -51,7 +51,7 @@ greek = "ΑΒΓΔΕ" > toUtf8 greek ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -86,7 +86,7 @@ greek = "ΑΒΓΔΕ" test> greekTest = checkRoundTrip greek ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -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. diff --git a/unison-src/transcripts/abilities.output.md b/unison-src/transcripts/abilities.output.md index 52428c98f..aa162e135 100644 --- a/unison-src/transcripts/abilities.output.md +++ b/unison-src/transcripts/abilities.output.md @@ -16,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. @@ -30,7 +30,7 @@ ha = cases ha : Request {A} r -> r ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/ability-order-doesnt-affect-hash.output.md b/unison-src/transcripts/ability-order-doesnt-affect-hash.output.md index 7b98c2065..a61dd0045 100644 --- a/unison-src/transcripts/ability-order-doesnt-affect-hash.output.md +++ b/unison-src/transcripts/ability-order-doesnt-affect-hash.output.md @@ -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: diff --git a/unison-src/transcripts/ability-term-conflicts-on-update.output.md b/unison-src/transcripts/ability-term-conflicts-on-update.output.md index a9bba9dbf..f5580e7b8 100644 --- a/unison-src/transcripts/ability-term-conflicts-on-update.output.md +++ b/unison-src/transcripts/ability-term-conflicts-on-update.output.md @@ -10,7 +10,7 @@ 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: @@ -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: @@ -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 @@ -169,7 +169,7 @@ scratch/main> update.old 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: @@ -195,7 +195,7 @@ 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: diff --git a/unison-src/transcripts/add-run.output.md b/unison-src/transcripts/add-run.output.md index c1802922f..acf50c24d 100644 --- a/unison-src/transcripts/add-run.output.md +++ b/unison-src/transcripts/add-run.output.md @@ -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 @@ -48,7 +48,7 @@ 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 ⚠️ @@ -59,7 +59,7 @@ 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: @@ -67,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 @@ -87,7 +87,7 @@ main : '{IO, Exception} (Nat -> Nat -> Nat) main _ = y ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -102,7 +102,7 @@ main _ = y z : Nat -> Nat ``` -```ucm +``` ucm scratch/main> run main a b -> a Nat.+ b Nat.+ z 10 @@ -122,7 +122,7 @@ inc : Nat -> Nat inc x = x + 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -135,7 +135,7 @@ inc x = x + 1 inc : Nat -> Nat ``` -```ucm +``` ucm scratch/main> add inc ⍟ I've added these definitions: @@ -148,7 +148,7 @@ main : '(Nat -> Nat) main _ x = inc x ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -161,7 +161,7 @@ main _ x = inc x main : '(Nat -> Nat) ``` -```ucm +``` ucm scratch/main> run main inc @@ -186,7 +186,7 @@ y = x + x main = 'y ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -201,7 +201,7 @@ main = 'y y : Nat ``` -```ucm +``` ucm scratch/main> run main 2 @@ -211,7 +211,7 @@ scratch/main> run main x = 50 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -226,7 +226,7 @@ x = 50 ``` this saves 2 to xres, rather than 100 -```ucm +``` ucm scratch/main> add.run xres ⍟ I've added these definitions: @@ -245,7 +245,7 @@ scratch/main> view xres main = '5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -258,7 +258,7 @@ main = '5 main : 'Nat ``` -```ucm +``` ucm scratch/main> run main 5 @@ -279,7 +279,7 @@ scratch/main> add.run xres main = '5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -292,7 +292,7 @@ main = '5 main : 'Nat ``` -```ucm +``` ucm .> run main 5 diff --git a/unison-src/transcripts/add-test-watch-roundtrip.output.md b/unison-src/transcripts/add-test-watch-roundtrip.output.md index e276eba24..5366a4734 100644 --- a/unison-src/transcripts/add-test-watch-roundtrip.output.md +++ b/unison-src/transcripts/add-test-watch-roundtrip.output.md @@ -5,7 +5,7 @@ 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\! -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/addupdatemessages.output.md b/unison-src/transcripts/addupdatemessages.output.md index 813639f58..cbf055271 100644 --- a/unison-src/transcripts/addupdatemessages.output.md +++ b/unison-src/transcripts/addupdatemessages.output.md @@ -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: @@ -47,7 +47,7 @@ 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: @@ -84,7 +84,7 @@ 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 @@ -123,7 +123,7 @@ 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 diff --git a/unison-src/transcripts/alias-many.output.md b/unison-src/transcripts/alias-many.output.md index 942539b62..4a20a354c 100644 --- a/unison-src/transcripts/alias-many.output.md +++ b/unison-src/transcripts/alias-many.output.md @@ -10,7 +10,7 @@ The names that will be used in the target namespace are the names you specify, r 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 : diff --git a/unison-src/transcripts/alias-term.output.md b/unison-src/transcripts/alias-term.output.md index d072506cb..2c120239e 100644 --- a/unison-src/transcripts/alias-term.output.md +++ b/unison-src/transcripts/alias-term.output.md @@ -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. diff --git a/unison-src/transcripts/alias-type.output.md b/unison-src/transcripts/alias-type.output.md index 820c81761..79a2fbcd7 100644 --- a/unison-src/transcripts/alias-type.output.md +++ b/unison-src/transcripts/alias-type.output.md @@ -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. diff --git a/unison-src/transcripts/anf-tests.output.md b/unison-src/transcripts/anf-tests.output.md index b1dc2f599..0a1242dda 100644 --- a/unison-src/transcripts/anf-tests.output.md +++ b/unison-src/transcripts/anf-tests.output.md @@ -23,7 +23,7 @@ foo _ = > !foo ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -43,7 +43,7 @@ foo _ = 5 ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/any-extract.output.md b/unison-src/transcripts/any-extract.output.md index 8f3488cb4..342ef3fbb 100644 --- a/unison-src/transcripts/any-extract.output.md +++ b/unison-src/transcripts/any-extract.output.md @@ -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: diff --git a/unison-src/transcripts/api-doc-rendering.output.md b/unison-src/transcripts/api-doc-rendering.output.md index 8afef59e8..271fac784 100644 --- a/unison-src/transcripts/api-doc-rendering.output.md +++ b/unison-src/transcripts/api-doc-rendering.output.md @@ -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": [], diff --git a/unison-src/transcripts/api-find.output.md b/unison-src/transcripts/api-find.output.md index aecfe603a..24c34c837 100644 --- a/unison-src/transcripts/api-find.output.md +++ b/unison-src/transcripts/api-find.output.md @@ -7,7 +7,7 @@ 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 [ diff --git a/unison-src/transcripts/api-getDefinition.output.md b/unison-src/transcripts/api-getDefinition.output.md index bf244e4a0..6daa80c01 100644 --- a/unison-src/transcripts/api-getDefinition.output.md +++ b/unison-src/transcripts/api-getDefinition.output.md @@ -5,7 +5,7 @@ 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 { @@ -216,7 +216,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": [], @@ -334,7 +334,7 @@ GET /api/projects/scratch/branches/main/getDefinition?names=thing&relativeTo=doc } ```If we request a doc, the api should return the source, but also the rendered doc should appear in the 'termDocs' list. -```api +``` api GET /api/projects/scratch/branches/main/getDefinition?names=thing.doc&relativeTo=doctest { "missingDefinitions": [], diff --git a/unison-src/transcripts/api-list-projects-branches.output.md b/unison-src/transcripts/api-list-projects-branches.output.md index b3c09895d..5768b6454 100644 --- a/unison-src/transcripts/api-list-projects-branches.output.md +++ b/unison-src/transcripts/api-list-projects-branches.output.md @@ -1,6 +1,6 @@ # List Projects And Branches Test -```api +``` api -- Should list all projects GET /api/projects [ diff --git a/unison-src/transcripts/api-namespace-details.output.md b/unison-src/transcripts/api-namespace-details.output.md index 593efac4f..124c28e5d 100644 --- a/unison-src/transcripts/api-namespace-details.output.md +++ b/unison-src/transcripts/api-namespace-details.output.md @@ -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 { diff --git a/unison-src/transcripts/api-namespace-list.output.md b/unison-src/transcripts/api-namespace-list.output.md index 6116dad61..1378a7d36 100644 --- a/unison-src/transcripts/api-namespace-list.output.md +++ b/unison-src/transcripts/api-namespace-list.output.md @@ -7,7 +7,7 @@ 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": [ diff --git a/unison-src/transcripts/api-summaries.output.md b/unison-src/transcripts/api-summaries.output.md index de7e14c3a..115dba15a 100644 --- a/unison-src/transcripts/api-summaries.output.md +++ b/unison-src/transcripts/api-summaries.output.md @@ -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 { @@ -669,7 +669,7 @@ GET /api/projects/scratch/branches/main/definitions/terms/by-hash/@@IO.putBytes. } ```## Type Summary APIs -```api +``` api -- data GET /api/projects/scratch/branches/main/definitions/types/by-hash/@altimqs66j3dh94dpab5pg7j5adjrndq61n803j7fg0v0ohdiut6or66bu1fiongpd45s5euiuo8ru47b928aqv8osln1ikdeg05hq0/summary?name=Thing { diff --git a/unison-src/transcripts/block-on-required-update.output.md b/unison-src/transcripts/block-on-required-update.output.md index 49e133246..20560c94c 100644 --- a/unison-src/transcripts/block-on-required-update.output.md +++ b/unison-src/transcripts/block-on-required-update.output.md @@ -6,7 +6,7 @@ Should block an `add` if it requires an update on an in-file dependency. 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: @@ -34,7 +34,7 @@ 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: diff --git a/unison-src/transcripts/blocks.output.md b/unison-src/transcripts/blocks.output.md index b017e0cfc..f52ca4f25 100644 --- a/unison-src/transcripts/blocks.output.md +++ b/unison-src/transcripts/blocks.output.md @@ -15,7 +15,7 @@ ex thing = > ex "hello" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -48,7 +48,7 @@ ex thing = > ex "hello" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -83,7 +83,7 @@ ex thing = > ex (x -> x * 100) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -115,7 +115,7 @@ ex thing = > ex (x -> x * 100) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -154,7 +154,7 @@ ex n = ping 42 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -181,7 +181,7 @@ ex n = ping 0 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -205,7 +205,7 @@ ex n = pong ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -223,7 +223,7 @@ ex n = loop ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -240,7 +240,7 @@ ex n = !loop ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -269,7 +269,7 @@ ex n = zap1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -293,7 +293,7 @@ ex n = zap1 "pluto" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -322,7 +322,7 @@ ex n = ping 42 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -349,7 +349,7 @@ ex n = ping 42 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/boolean-op-pretty-print-2819.output.md b/unison-src/transcripts/boolean-op-pretty-print-2819.output.md index 7fe8f92cf..b840f4bbc 100644 --- a/unison-src/transcripts/boolean-op-pretty-print-2819.output.md +++ b/unison-src/transcripts/boolean-op-pretty-print-2819.output.md @@ -7,7 +7,7 @@ hangExample = && ("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: diff --git a/unison-src/transcripts/branch-command.output.md b/unison-src/transcripts/branch-command.output.md index 569ab5d76..6a78b8e72 100644 --- a/unison-src/transcripts/branch-command.output.md +++ b/unison-src/transcripts/branch-command.output.md @@ -6,7 +6,7 @@ First, we'll create a term to include in the branches. 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. diff --git a/unison-src/transcripts/branch-relative-path.output.md b/unison-src/transcripts/branch-relative-path.output.md index 591fa64f8..e9e33b5ad 100644 --- a/unison-src/transcripts/branch-relative-path.output.md +++ b/unison-src/transcripts/branch-relative-path.output.md @@ -3,7 +3,7 @@ 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: @@ -31,7 +31,7 @@ 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: diff --git a/unison-src/transcripts/bug-fix-4354.output.md b/unison-src/transcripts/bug-fix-4354.output.md index 8ef9e7370..110aca002 100644 --- a/unison-src/transcripts/bug-fix-4354.output.md +++ b/unison-src/transcripts/bug-fix-4354.output.md @@ -8,7 +8,7 @@ bonk x = x ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/bug-strange-closure.output.md b/unison-src/transcripts/bug-strange-closure.output.md index 91f7ce998..ebd96be4a 100644 --- a/unison-src/transcripts/bug-strange-closure.output.md +++ b/unison-src/transcripts/bug-strange-closure.output.md @@ -1,6 +1,6 @@ We can display the guide before and after adding it to the codebase: -```ucm +``` ucm .> display doc.guide # Unison computable documentation @@ -417,7 +417,7 @@ But we can't display this due to a decompilation problem. rendered = Pretty.get (docFormatConsole doc.guide) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -430,7 +430,7 @@ rendered = Pretty.get (docFormatConsole doc.guide) rendered : Annotated () (Either SpecialForm ConsoleText) ``` -```ucm +``` ucm .> display rendered # Unison computable documentation @@ -850,7 +850,7 @@ rendered = Pretty.get (docFormatConsole doc.guide) > rendered ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/builtins-merge.output.md b/unison-src/transcripts/builtins-merge.output.md index b79bdab58..814737577 100644 --- a/unison-src/transcripts/builtins-merge.output.md +++ b/unison-src/transcripts/builtins-merge.output.md @@ -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. diff --git a/unison-src/transcripts/builtins.output.md b/unison-src/transcripts/builtins.output.md index 5ddc4b765..3a4538f30 100644 --- a/unison-src/transcripts/builtins.output.md +++ b/unison-src/transcripts/builtins.output.md @@ -363,7 +363,7 @@ 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. @@ -415,7 +415,7 @@ test> Sandbox.test3 = checks [validateSandboxed [termLink openFile.impl] openFile] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -468,7 +468,7 @@ openFilesIO = do ] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -481,7 +481,7 @@ openFilesIO = do openFilesIO : '{IO} [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -508,7 +508,7 @@ Just exercises the function test> Universal.murmurHash.tests = checks [Universal.murmurHash [1,2,3] == Universal.murmurHash [1,2,3]] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -536,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) diff --git a/unison-src/transcripts/bytesFromList.output.md b/unison-src/transcripts/bytesFromList.output.md index 099a73cb5..b4a978221 100644 --- a/unison-src/transcripts/bytesFromList.output.md +++ b/unison-src/transcripts/bytesFromList.output.md @@ -4,7 +4,7 @@ This should render as `Bytes.fromList [1,2,3,4]`, not `##Bytes.fromSequence [1,2 > Bytes.fromList [1,2,3,4] ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/check763.output.md b/unison-src/transcripts/check763.output.md index 0d5dcc0ba..7975553f1 100644 --- a/unison-src/transcripts/check763.output.md +++ b/unison-src/transcripts/check763.output.md @@ -5,7 +5,7 @@ Regression test for https://github.com/unisonweb/unison/issues/763 (+-+) 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: diff --git a/unison-src/transcripts/check873.output.md b/unison-src/transcripts/check873.output.md index cc952acca..fa6f046e8 100644 --- a/unison-src/transcripts/check873.output.md +++ b/unison-src/transcripts/check873.output.md @@ -4,7 +4,7 @@ See [this ticket](https://github.com/unisonweb/unison/issues/873); the point bei (-) = 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: @@ -29,7 +29,7 @@ scratch/main> add baz x = x - 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/constructor-applied-to-unit.output.md b/unison-src/transcripts/constructor-applied-to-unit.output.md index 04cc3c417..e12d3f1d4 100644 --- a/unison-src/transcripts/constructor-applied-to-unit.output.md +++ b/unison-src/transcripts/constructor-applied-to-unit.output.md @@ -5,7 +5,7 @@ structural type Zoink a b c = Zoink a b c > [ 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. diff --git a/unison-src/transcripts/contrabilities.output.md b/unison-src/transcripts/contrabilities.output.md index f3b76a8c5..ef0f98dff 100644 --- a/unison-src/transcripts/contrabilities.output.md +++ b/unison-src/transcripts/contrabilities.output.md @@ -3,7 +3,7 @@ f : (() -> a) -> Nat f x = 42 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/create-author.output.md b/unison-src/transcripts/create-author.output.md index a71fca7b1..caa4d2740 100644 --- a/unison-src/transcripts/create-author.output.md +++ b/unison-src/transcripts/create-author.output.md @@ -1,6 +1,6 @@ Demonstrating `create.author`: -```ucm +``` ucm scratch/main> create.author alicecoder "Alice McGee" Added definitions: diff --git a/unison-src/transcripts/cycle-update-1.output.md b/unison-src/transcripts/cycle-update-1.output.md index 3cfeca6fc..b5dd6e69a 100644 --- a/unison-src/transcripts/cycle-update-1.output.md +++ b/unison-src/transcripts/cycle-update-1.output.md @@ -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: @@ -36,7 +36,7 @@ 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 diff --git a/unison-src/transcripts/cycle-update-2.output.md b/unison-src/transcripts/cycle-update-2.output.md index 11b97f14d..b9bdc363f 100644 --- a/unison-src/transcripts/cycle-update-2.output.md +++ b/unison-src/transcripts/cycle-update-2.output.md @@ -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: @@ -36,7 +36,7 @@ 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 diff --git a/unison-src/transcripts/cycle-update-3.output.md b/unison-src/transcripts/cycle-update-3.output.md index cf8c1c72c..15b0e2662 100644 --- a/unison-src/transcripts/cycle-update-3.output.md +++ b/unison-src/transcripts/cycle-update-3.output.md @@ -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: @@ -36,7 +36,7 @@ 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: diff --git a/unison-src/transcripts/cycle-update-4.output.md b/unison-src/transcripts/cycle-update-4.output.md index c3bcccbd1..2fec74ba8 100644 --- a/unison-src/transcripts/cycle-update-4.output.md +++ b/unison-src/transcripts/cycle-update-4.output.md @@ -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: @@ -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: diff --git a/unison-src/transcripts/cycle-update-5.output.md b/unison-src/transcripts/cycle-update-5.output.md index a022fbed6..64f50af57 100644 --- a/unison-src/transcripts/cycle-update-5.output.md +++ b/unison-src/transcripts/cycle-update-5.output.md @@ -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: @@ -39,7 +39,7 @@ 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 diff --git a/unison-src/transcripts/debug-definitions.output.md b/unison-src/transcripts/debug-definitions.output.md index 8689d2d78..9c4bb349c 100644 --- a/unison-src/transcripts/debug-definitions.output.md +++ b/unison-src/transcripts/debug-definitions.output.md @@ -12,7 +12,7 @@ ability Ask a where ask : a ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/debug-name-diffs.output.md b/unison-src/transcripts/debug-name-diffs.output.md index 0333dee6b..beed0b4cc 100644 --- a/unison-src/transcripts/debug-name-diffs.output.md +++ b/unison-src/transcripts/debug-name-diffs.output.md @@ -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: diff --git a/unison-src/transcripts/deep-names.output.md b/unison-src/transcripts/deep-names.output.md index dcaf16dbe..114133d78 100644 --- a/unison-src/transcripts/deep-names.output.md +++ b/unison-src/transcripts/deep-names.output.md @@ -14,7 +14,7 @@ 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. @@ -42,7 +42,7 @@ 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 @@ -63,7 +63,7 @@ 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. @@ -96,7 +96,7 @@ 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 diff --git a/unison-src/transcripts/definition-diff-api.output.md b/unison-src/transcripts/definition-diff-api.output.md index 460e84d80..8d55cc785 100644 --- a/unison-src/transcripts/definition-diff-api.output.md +++ b/unison-src/transcripts/definition-diff-api.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm diffs/main> builtins.merge Done. @@ -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: @@ -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": { @@ -560,7 +560,7 @@ GET /api/projects/diffs/diff/terms?oldBranchRef=main&newBranchRef=new&oldTerm=te } ```Diff types -```api +``` api GET /api/projects/diffs/diff/types?oldBranchRef=main&newBranchRef=new&oldType=Type&newType=Type { "diff": { diff --git a/unison-src/transcripts/delete-namespace-dependents-check.output.md b/unison-src/transcripts/delete-namespace-dependents-check.output.md index ce131fcb7..134373103 100644 --- a/unison-src/transcripts/delete-namespace-dependents-check.output.md +++ b/unison-src/transcripts/delete-namespace-dependents-check.output.md @@ -10,7 +10,7 @@ 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: diff --git a/unison-src/transcripts/delete-namespace.output.md b/unison-src/transcripts/delete-namespace.output.md index a57094d9e..288160895 100644 --- a/unison-src/transcripts/delete-namespace.output.md +++ b/unison-src/transcripts/delete-namespace.output.md @@ -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 diff --git a/unison-src/transcripts/delete-project-branch.output.md b/unison-src/transcripts/delete-project-branch.output.md index 84568c97d..755d5f0c7 100644 --- a/unison-src/transcripts/delete-project-branch.output.md +++ b/unison-src/transcripts/delete-project-branch.output.md @@ -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 ``` diff --git a/unison-src/transcripts/delete-project.output.md b/unison-src/transcripts/delete-project.output.md index e2b974a9c..2ee362e50 100644 --- a/unison-src/transcripts/delete-project.output.md +++ b/unison-src/transcripts/delete-project.output.md @@ -1,6 +1,6 @@ # delete.project -```ucm +``` ucm scratch/main> project.create-empty foo 🎉 I've created the project foo. diff --git a/unison-src/transcripts/delete-silent.output.md b/unison-src/transcripts/delete-silent.output.md index 899a38b3b..49c5a0860 100644 --- a/unison-src/transcripts/delete-silent.output.md +++ b/unison-src/transcripts/delete-silent.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> delete foo ⚠️ @@ -12,7 +12,7 @@ foo = 1 structural type Foo = Foo () ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/delete.output.md b/unison-src/transcripts/delete.output.md index 853f2ee38..178e92797 100644 --- a/unison-src/transcripts/delete.output.md +++ b/unison-src/transcripts/delete.output.md @@ -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 ⚠️ @@ -22,7 +22,7 @@ foo = 1 structural type Foo = Foo () ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -62,7 +62,7 @@ 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: @@ -106,7 +106,7 @@ structural type Foo = Foo () structural type Bar = Bar ``` -```ucm +``` ucm .a> add ⍟ I've added these definitions: @@ -149,7 +149,7 @@ foo = 1 structural type foo = Foo () ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -175,7 +175,7 @@ b = "b" c = "c" ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -204,7 +204,7 @@ b = "b" c = "c" ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -242,7 +242,7 @@ We can delete a type and its constructors structural type Foo = Foo () ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -273,7 +273,7 @@ c = 3 d = a + b + c ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -306,7 +306,7 @@ g = 13 + f h = e + f + g ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -338,7 +338,7 @@ incrementFoo = cases (Foo n) -> n + 1 ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -366,7 +366,7 @@ g = 13 + f h = e + f + g ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -391,7 +391,7 @@ ping _ = 1 Nat.+ !pong pong _ = 4 Nat.+ !ping ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/dependents-dependencies-debugfile.output.md b/unison-src/transcripts/dependents-dependencies-debugfile.output.md index 19b2526d7..a02c49169 100644 --- a/unison-src/transcripts/dependents-dependencies-debugfile.output.md +++ b/unison-src/transcripts/dependents-dependencies-debugfile.output.md @@ -16,7 +16,7 @@ inside.q x = x + p * p inside.r = d ``` -```ucm +``` ucm scratch/main> debug.file type inside.M#h37a56c5ep @@ -35,7 +35,7 @@ This will help me make progress in some situations when UCM is being deficient o 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: diff --git a/unison-src/transcripts/destructuring-binds.output.md b/unison-src/transcripts/destructuring-binds.output.md index ec7f39182..371864ee9 100644 --- a/unison-src/transcripts/destructuring-binds.output.md +++ b/unison-src/transcripts/destructuring-binds.output.md @@ -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: @@ -58,7 +58,7 @@ ex2 tup = match tup with (a, b, (c,d)) -> c + d ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -82,7 +82,7 @@ ex4 = "Doesn't typecheck" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -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: @@ -162,7 +162,7 @@ ex6 x = match x with 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: diff --git a/unison-src/transcripts/diff-namespace.output.md b/unison-src/transcripts/diff-namespace.output.md index 2c327bc83..32cfbb27b 100644 --- a/unison-src/transcripts/diff-namespace.output.md +++ b/unison-src/transcripts/diff-namespace.output.md @@ -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: @@ -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,7 +116,7 @@ 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. @@ -126,7 +126,7 @@ Here's what we've done so far: junk = "asldkfjasldkfj" ``` -```ucm +``` ucm .ns1> add ⍟ I've added these definitions: @@ -151,7 +151,7 @@ f = 6 unique type Y a b = Y a b ``` -```ucm +``` ucm .ns2> update.old ⍟ I've added these definitions: @@ -287,7 +287,7 @@ unique type Y a b = Y a b bdependent = "banana" ``` -```ucm +``` ucm .ns3> update.old ⍟ I've updated these names to your new definition: @@ -321,7 +321,7 @@ a = 333 b = a + 1 ``` -```ucm +``` ucm ☝️ The namespace .nsx is empty. .nsx> add @@ -344,7 +344,7 @@ b = a + 1 a = 444 ``` -```ucm +``` ucm .nsy> update.old ⍟ I've updated these names to your new definition: @@ -356,7 +356,7 @@ a = 444 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: @@ -416,7 +416,7 @@ a = 555 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 @@ -443,7 +443,7 @@ x = 1 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: diff --git a/unison-src/transcripts/doc-formatting.output.md b/unison-src/transcripts/doc-formatting.output.md index a99d2ca4b..9a8d60c8b 100644 --- a/unison-src/transcripts/doc-formatting.output.md +++ b/unison-src/transcripts/doc-formatting.output.md @@ -9,7 +9,7 @@ foo n = 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 @@ -38,7 +38,7 @@ Note that `@` and `:]` must be escaped within docs. 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 @@ -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 @@ -105,7 +105,7 @@ Handling of indenting in docs between the parser and pretty-printer is a bit fid doc1 = [: hi :] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -118,7 +118,7 @@ doc1 = [: hi :] doc1 : Doc ``` -```ucm +``` ucm scratch/main> view doc1 doc1 : Doc @@ -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 @@ -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 @@ -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 @@ -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 @@ -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 @@ -323,7 +323,7 @@ empty = [::] expr = foo 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -337,7 +337,7 @@ expr = foo 1 expr : Nat ``` -```ucm +``` ucm scratch/main> view empty empty : Doc @@ -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 @@ -466,7 +466,7 @@ reg1363 = [: `@List.take foo` bar baz :] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -479,7 +479,7 @@ reg1363 = [: `@List.take foo` bar reg1363 : Doc ``` -```ucm +``` ucm scratch/main> view reg1363 reg1363 : Doc @@ -496,7 +496,7 @@ test2 = [: :] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -511,7 +511,7 @@ test2 = [: ``` View is fine. -```ucm +``` ucm scratch/main> view test2 test2 : Doc @@ -523,7 +523,7 @@ 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: diff --git a/unison-src/transcripts/doc-type-link-keywords.output.md b/unison-src/transcripts/doc-type-link-keywords.output.md index 3229bed19..e1b04a715 100644 --- a/unison-src/transcripts/doc-type-link-keywords.output.md +++ b/unison-src/transcripts/doc-type-link-keywords.output.md @@ -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 diff --git a/unison-src/transcripts/doc1.output.md b/unison-src/transcripts/doc1.output.md index bd5b5b255..3c15677ba 100644 --- a/unison-src/transcripts/doc1.output.md +++ b/unison-src/transcripts/doc1.output.md @@ -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 @@ -26,7 +26,7 @@ Can link to definitions like @List.drop or @List :] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -58,7 +58,7 @@ 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: @@ -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 : diff --git a/unison-src/transcripts/doc2.output.md b/unison-src/transcripts/doc2.output.md index 0d09b5618..dc8330c53 100644 --- a/unison-src/transcripts/doc2.output.md +++ b/unison-src/transcripts/doc2.output.md @@ -109,7 +109,7 @@ 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 ``` diff --git a/unison-src/transcripts/doc2markdown.output.md b/unison-src/transcripts/doc2markdown.output.md index e670bff8c..d8a6b6942 100644 --- a/unison-src/transcripts/doc2markdown.output.md +++ b/unison-src/transcripts/doc2markdown.output.md @@ -81,7 +81,7 @@ Table }} ``` -```ucm +``` ucm scratch/main> debug.doc-to-markdown fulldoc Heres some text with a soft line break @@ -174,7 +174,7 @@ unique type MyUniqueType = MyUniqueType structural type MyStructuralType = MyStructuralType ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/dont-upgrade-refs-that-exist-in-old.output.md b/unison-src/transcripts/dont-upgrade-refs-that-exist-in-old.output.md index 5bbf2fb0b..9e369c57c 100644 --- a/unison-src/transcripts/dont-upgrade-refs-that-exist-in-old.output.md +++ b/unison-src/transcripts/dont-upgrade-refs-that-exist-in-old.output.md @@ -8,7 +8,7 @@ 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: diff --git a/unison-src/transcripts/duplicate-names.output.md b/unison-src/transcripts/duplicate-names.output.md index a9d9f2ad0..7e1e83851 100644 --- a/unison-src/transcripts/duplicate-names.output.md +++ b/unison-src/transcripts/duplicate-names.output.md @@ -10,7 +10,7 @@ Stream.send : a -> () Stream.send _ = () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -33,7 +33,7 @@ X.x : a -> () X.x _ = () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -55,7 +55,7 @@ structural ability X where x : () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -76,7 +76,7 @@ X.x.set = () X.x = () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -109,7 +109,7 @@ 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: diff --git a/unison-src/transcripts/duplicate-term-detection.output.md b/unison-src/transcripts/duplicate-term-detection.output.md index 3751e75f8..b726a6a94 100644 --- a/unison-src/transcripts/duplicate-term-detection.output.md +++ b/unison-src/transcripts/duplicate-term-detection.output.md @@ -7,7 +7,7 @@ x = 1 x = 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -26,7 +26,7 @@ x = 1 x = 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -47,7 +47,7 @@ Record.x.set = 2 Record.x.modify = 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -85,7 +85,7 @@ structural ability AnAbility where AnAbility.thing = 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/ed25519.output.md b/unison-src/transcripts/ed25519.output.md index 2679028d4..0647c3199 100644 --- a/unison-src/transcripts/ed25519.output.md +++ b/unison-src/transcripts/ed25519.output.md @@ -19,7 +19,7 @@ sigOkay = match signature with > sigOkay ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/edit-command.output.md b/unison-src/transcripts/edit-command.output.md index 8470de948..e13d5cea9 100644 --- a/unison-src/transcripts/edit-command.output.md +++ b/unison-src/transcripts/edit-command.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -16,7 +16,7 @@ mytest = [Ok "ok"] ``` -```ucm +``` ucm Loading changes detected in /private/tmp/scratch.u. @@ -31,7 +31,7 @@ mytest = [Ok "ok"] mytest : [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -71,7 +71,7 @@ foo = 123 test> mytest = [Ok "ok"] ``` -```ucm +``` ucm scratch/main> edit missing ⚠️ diff --git a/unison-src/transcripts/edit-namespace.output.md b/unison-src/transcripts/edit-namespace.output.md index 67e24e064..452a5d388 100644 --- a/unison-src/transcripts/edit-namespace.output.md +++ b/unison-src/transcripts/edit-namespace.output.md @@ -17,7 +17,7 @@ lib.project.ignoreMe = 30 unique type Foo = { bar : Nat, baz : Nat } ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -44,7 +44,7 @@ unique type Foo = { bar : Nat, baz : Nat } toplevel : Text ``` -```ucm +``` ucm project/main> add ⍟ I've added these definitions: @@ -68,7 +68,7 @@ project/main> add ``` `edit.namespace` edits the whole namespace (minus the top-level `lib`). -```ucm +``` ucm project/main> edit.namespace ☝️ @@ -110,7 +110,7 @@ toplevel = "hi" `edit.namespace` can also accept explicit paths -```ucm +``` ucm project/main> edit.namespace nested simple ☝️ diff --git a/unison-src/transcripts/empty-namespaces.output.md b/unison-src/transcripts/empty-namespaces.output.md index 4bea6f5b5..409dfcd51 100644 --- a/unison-src/transcripts/empty-namespaces.output.md +++ b/unison-src/transcripts/empty-namespaces.output.md @@ -6,13 +6,13 @@ mynamespace.x = 1 The deleted namespace shouldn't appear in `ls` output. -```ucm +``` ucm scratch/main> ls nothing to show ``` -```ucm +``` ucm scratch/main> find.verbose ☝️ @@ -29,7 +29,7 @@ scratch/main> find.verbose namespace. ``` -```ucm +``` ucm scratch/main> find mynamespace ☝️ @@ -50,7 +50,7 @@ scratch/main> find mynamespace The history of the namespace should be empty. -```ucm +``` ucm scratch/main> history mynamespace ☝️ The namespace mynamespace is empty. @@ -67,7 +67,7 @@ stuff.thing = 2 I should be allowed to fork over a deleted namespace -```ucm +``` ucm scratch/main> fork stuff deleted Done. @@ -75,7 +75,7 @@ scratch/main> fork stuff deleted ``` The history from the `deleted` namespace should have been overwritten by the history from `stuff`. -```ucm +``` ucm scratch/main> history stuff Note: The most recent namespace hash is immediately below this @@ -105,7 +105,7 @@ moveme.y = 2 I should be able to move a namespace over-top of a deleted namespace. The history should be that of the moved namespace. -```ucm +``` ucm scratch/main> delete.namespace moveoverme Done. diff --git a/unison-src/transcripts/emptyCodebase.output.md b/unison-src/transcripts/emptyCodebase.output.md index 4a8b1cff1..86c4b63ff 100644 --- a/unison-src/transcripts/emptyCodebase.output.md +++ b/unison-src/transcripts/emptyCodebase.output.md @@ -6,7 +6,7 @@ Not even `Nat` or `+`\! BEHOLD\!\!\! -```ucm +``` ucm scratch/main> ls nothing to show @@ -14,7 +14,7 @@ scratch/main> ls ``` Technically, the definitions all exist, but they have no names. `builtins.merge` brings them into existence, under the current namespace: -```ucm +``` ucm scratch/main> builtins.merge lib.builtins Done. @@ -26,7 +26,7 @@ scratch/main> ls lib ``` And for a limited time, you can get even more builtin goodies: -```ucm +``` ucm scratch/main> builtins.mergeio lib.builtinsio Done. diff --git a/unison-src/transcripts/error-messages.output.md b/unison-src/transcripts/error-messages.output.md index 694f20f4c..ed5d4c178 100644 --- a/unison-src/transcripts/error-messages.output.md +++ b/unison-src/transcripts/error-messages.output.md @@ -10,7 +10,7 @@ Some basic errors of literals. x = 1. -- missing some digits after the decimal ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -26,7 +26,7 @@ x = 1. -- missing some digits after the decimal x = 1e -- missing an exponent ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -42,7 +42,7 @@ x = 1e -- missing an exponent x = 1e- -- missing an exponent ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -58,7 +58,7 @@ x = 1e- -- missing an exponent x = 1E+ -- missing an exponent ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -76,7 +76,7 @@ x = 1E+ -- missing an exponent x = 0xoogabooga -- invalid hex chars ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -92,7 +92,7 @@ x = 0xoogabooga -- invalid hex chars x = 0o987654321 -- 9 and 8 are not valid octal char ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -108,7 +108,7 @@ x = 0o987654321 -- 9 and 8 are not valid octal char x = 0xsf -- odd number of hex chars in a bytes literal ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -124,7 +124,7 @@ x = 0xsf -- odd number of hex chars in a bytes literal x = 0xsnotvalidhexchars -- invalid hex chars in a bytes literal ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -142,7 +142,7 @@ x = 0xsnotvalidhexchars -- invalid hex chars in a bytes literal foo = else -- not matching if ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -156,7 +156,7 @@ foo = else -- not matching if foo = then -- unclosed ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -170,7 +170,7 @@ foo = then -- unclosed foo = with -- unclosed ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -187,7 +187,7 @@ foo = with -- unclosed foo = match 1 with ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -205,7 +205,7 @@ foo = match 1 with 2 -- no right-hand-side ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -229,7 +229,7 @@ foo = cases 3 -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -252,7 +252,7 @@ x = match Some a with 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -280,7 +280,7 @@ x = match Some a with -> 3 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -302,7 +302,7 @@ x = match Some a with | true -> 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -324,7 +324,7 @@ x = match Some a with > ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -340,7 +340,7 @@ x = match Some a with use.keyword.in.namespace = 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -357,7 +357,7 @@ use.keyword.in.namespace = 1 a ! b = 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/escape-sequences.output.md b/unison-src/transcripts/escape-sequences.output.md index 0834375f1..955b6e8fe 100644 --- a/unison-src/transcripts/escape-sequences.output.md +++ b/unison-src/transcripts/escape-sequences.output.md @@ -4,7 +4,7 @@ > "古池や蛙飛びこむ水の音" ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/find-by-type.output.md b/unison-src/transcripts/find-by-type.output.md index 476f6ff80..c45fcd6a8 100644 --- a/unison-src/transcripts/find-by-type.output.md +++ b/unison-src/transcripts/find-by-type.output.md @@ -12,7 +12,7 @@ baz = cases A t -> t ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -39,7 +39,7 @@ scratch/main> find : A ``` -```ucm +``` ucm scratch/main> find : Text ☝️ diff --git a/unison-src/transcripts/find-command.output.md b/unison-src/transcripts/find-command.output.md index e4c4f6fe7..7abbe26f0 100644 --- a/unison-src/transcripts/find-command.output.md +++ b/unison-src/transcripts/find-command.output.md @@ -8,7 +8,7 @@ cat.lib.bar = 6 somewhere.bar = 7 ``` -```ucm +``` ucm scratch/main> find foo 1. cat.foo : Nat @@ -34,7 +34,7 @@ scratch/main> view 1 cat.foo = 4 ``` -```ucm +``` ucm scratch/main> find-in cat foo 1. foo : Nat @@ -59,7 +59,7 @@ scratch/main> view 1 ``` Finding within a namespace -```ucm +``` ucm scratch/main> find bar 1. somewhere.bar : Nat @@ -73,7 +73,7 @@ scratch/main> find-in somewhere bar ``` -```ucm +``` ucm scratch/main> find baz ☝️ @@ -90,7 +90,7 @@ scratch/main> find baz namespace. ``` -```ucm +``` ucm scratch/main> find.global notHere 😶 diff --git a/unison-src/transcripts/fix-1381-excess-propagate.output.md b/unison-src/transcripts/fix-1381-excess-propagate.output.md index 373289970..edc30e9f2 100644 --- a/unison-src/transcripts/fix-1381-excess-propagate.output.md +++ b/unison-src/transcripts/fix-1381-excess-propagate.output.md @@ -7,7 +7,7 @@ a = "a term" X.foo = "a namespace" ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -22,7 +22,7 @@ Here is an update which should not affect `X`: a = "an update" ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be @@ -33,7 +33,7 @@ scratch/main> update ``` As of the time of this writing, the history for `X` should be a single node, `#4eeuo5bsfr`; -```ucm +``` ucm scratch/main> history X Note: The most recent namespace hash is immediately below this @@ -46,7 +46,7 @@ scratch/main> history X ``` however, as of release/M1i, we saw an extraneous node appear. If your `ucm` is fixed, you won't see it below: -```ucm +``` ucm scratch/main> history #7nl6ppokhg 😶 diff --git a/unison-src/transcripts/fix-big-list-crash.output.md b/unison-src/transcripts/fix-big-list-crash.output.md index 5661b0339..f6db0fb0b 100644 --- a/unison-src/transcripts/fix-big-list-crash.output.md +++ b/unison-src/transcripts/fix-big-list-crash.output.md @@ -8,7 +8,7 @@ unique type Direction = U | D | L | R x = [(R,1005),(U,563),(R,417),(U,509),(L,237),(U,555),(R,397),(U,414),(L,490),(U,336),(L,697),(D,682),(L,180),(U,951),(L,189),(D,547),(R,697),(U,583),(L,172),(D,859),(L,370),(D,114),(L,519),(U,829),(R,389),(U,608),(R,66),(D,634),(L,320),(D,49),(L,931),(U,137),(L,349),(D,689),(L,351),(D,829),(R,819),(D,138),(L,118),(D,849),(R,230),(U,858),(L,509),(D,311),(R,815),(U,217),(R,359),(U,840),(R,77),(U,230),(R,361),(U,322),(R,300),(D,646),(R,348),(U,815),(R,793),(D,752),(R,967),(U,128),(R,948),(D,499),(R,359),(U,572),(L,566),(U,815),(R,630),(D,290),(L,829),(D,736),(R,358),(U,778),(R,891),(U,941),(R,544),(U,889),(L,920),(U,913),(L,447),(D,604),(R,538),(U,818),(L,215),(D,437),(R,447),(U,576),(R,452),(D,794),(R,864),(U,269),(L,325),(D,35),(L,268),(D,639),(L,101),(U,777),(L,776),(U,958),(R,105),(U,517),(R,667),(D,423),(R,603),(U,469),(L,125),(D,919),(R,879),(U,994),(R,665),(D,377),(R,456),(D,570),(L,685),(U,291),(R,261),(U,846),(R,840),(U,418),(L,974),(D,270),(L,312),(D,426),(R,621),(D,334),(L,855),(D,378),(R,694),(U,845),(R,481),(U,895),(L,362),(D,840),(L,712),(U,57),(R,276),(D,643),(R,566),(U,348),(R,361),(D,144),(L,287),(D,864),(L,556),(U,610),(L,927),(U,322),(R,271),(D,90),(L,741),(U,446),(R,181),(D,527),(R,56),(U,805),(L,907),(D,406),(L,286),(U,873),(L,79),(D,280),(L,153),(D,377),(R,253),(D,61),(R,475),(D,804),(R,788),(U,393),(L,660),(U,314),(R,489),(D,491),(L,234),(D,712),(L,253),(U,651),(L,777),(D,726),(R,146),(U,47),(R,630),(U,517),(R,226),(U,624),(L,834),(D,153),(L,513),(U,799),(R,287),(D,868),(R,982),(U,390),(L,296),(D,373),(R,9),(U,994),(R,105),(D,673),(L,657),(D,868),(R,738),(D,277),(R,374),(U,828),(R,860),(U,247),(R,484),(U,986),(L,723),(D,847),(L,578),(U,487),(L,51),(D,865),(L,328),(D,199),(R,812),(D,726),(R,355),(D,463),(R,761),(U,69),(R,508),(D,753),(L,81),(D,50),(L,345),(D,66),(L,764),(D,466),(L,975),(U,619),(R,59),(D,788),(L,737),(D,360),(R,14),(D,253),(L,512),(D,417),(R,828),(D,188),(L,394),(U,212),(R,658),(U,369),(R,920),(U,927),(L,339),(U,552),(R,856),(D,458),(R,407),(U,41),(L,930),(D,460),(R,809),(U,467),(L,410),(D,800),(L,135),(D,596),(R,678),(D,4),(L,771),(D,637),(L,876),(U,192),(L,406),(D,136),(R,666),(U,730),(R,711),(D,291),(L,586),(U,845),(R,606),(U,2),(L,228),(D,759),(R,244),(U,946),(R,948),(U,160),(R,397),(U,134),(R,188),(U,850),(R,623),(D,315),(L,219),(D,450),(R,489),(U,374),(R,299),(D,474),(L,767),(D,679),(L,160),(D,403),(L,708)] ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix-ls.output.md b/unison-src/transcripts/fix-ls.output.md index abf280b23..b99f0f587 100644 --- a/unison-src/transcripts/fix-ls.output.md +++ b/unison-src/transcripts/fix-ls.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm test-ls/main> builtins.merge Done. @@ -10,7 +10,7 @@ foo.bar.add x y = x Int.+ y foo.bar.subtract x y = x Int.- y ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -24,7 +24,7 @@ foo.bar.subtract x y = x Int.- y foo.bar.subtract : Int -> Int -> Int ``` -```ucm +``` ucm test-ls/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/fix1063.output.md b/unison-src/transcripts/fix1063.output.md index ca9f0ad57..57ab0b23d 100644 --- a/unison-src/transcripts/fix1063.output.md +++ b/unison-src/transcripts/fix1063.output.md @@ -8,7 +8,7 @@ use Boolean not noop = not `.` not ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -22,7 +22,7 @@ noop = not `.` not noop : Boolean -> Boolean ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/fix1334.output.md b/unison-src/transcripts/fix1334.output.md index b9b6f6a89..dfadcbe0a 100644 --- a/unison-src/transcripts/fix1334.output.md +++ b/unison-src/transcripts/fix1334.output.md @@ -4,7 +4,7 @@ With this PR, the source of an alias can be a short hash (even of a definition t Let's make some hash-only aliases, now that we can. :mad-with-power-emoji: -```ucm +``` ucm scratch/main> alias.type ##Nat Cat Done. diff --git a/unison-src/transcripts/fix1390.output.md b/unison-src/transcripts/fix1390.output.md index 4d50e86af..340a34e2c 100644 --- a/unison-src/transcripts/fix1390.output.md +++ b/unison-src/transcripts/fix1390.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -13,7 +13,7 @@ List.map f = go [] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -26,7 +26,7 @@ List.map f = List.map : (i ->{g} o) -> [i] ->{g} [o] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -53,7 +53,7 @@ List.map2 f = go [] ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix1532.output.md b/unison-src/transcripts/fix1532.output.md index 41ea7b2b9..0412312d8 100644 --- a/unison-src/transcripts/fix1532.output.md +++ b/unison-src/transcripts/fix1532.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -12,7 +12,7 @@ foo.y = 100 bar.z = x + y ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -27,7 +27,7 @@ bar.z = x + y foo.y : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -39,7 +39,7 @@ scratch/main> add ``` Let's see what we have created... -```ucm +``` ucm scratch/main> ls 1. bar/ (1 term) @@ -49,7 +49,7 @@ scratch/main> ls ``` Now, if we try deleting the namespace `foo`, we get an error, as expected. -```ucm +``` ucm scratch/main> delete.namespace foo ⚠️ @@ -68,7 +68,7 @@ scratch/main> delete.namespace foo ``` Any numbered arguments should refer to `bar.z`. -```ucm +``` ucm scratch/main> debug.numberedArgs 1. bar.z @@ -77,7 +77,7 @@ scratch/main> debug.numberedArgs ``` We can then delete the dependent term, and then delete `foo`. -```ucm +``` ucm scratch/main> delete.term 1 Done. diff --git a/unison-src/transcripts/fix1696.output.md b/unison-src/transcripts/fix1696.output.md index 47c1159a3..772f10e6c 100644 --- a/unison-src/transcripts/fix1696.output.md +++ b/unison-src/transcripts/fix1696.output.md @@ -16,7 +16,7 @@ dialog = Ask.provide 'zoot '("Awesome number: " ++ Nat.toText Ask.ask ++ "!") > dialog ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix1709.output.md b/unison-src/transcripts/fix1709.output.md index 3aacb9753..7159b5b54 100644 --- a/unison-src/transcripts/fix1709.output.md +++ b/unison-src/transcripts/fix1709.output.md @@ -6,7 +6,7 @@ id2 x = id x ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -20,7 +20,7 @@ id2 x = id2 : x -> x ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -33,7 +33,7 @@ scratch/main> add > id2 "hi" ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix1731.output.md b/unison-src/transcripts/fix1731.output.md index 8c8a7610a..be55bbb4b 100644 --- a/unison-src/transcripts/fix1731.output.md +++ b/unison-src/transcripts/fix1731.output.md @@ -12,7 +12,7 @@ repro = cases input -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix1800.output.md b/unison-src/transcripts/fix1800.output.md index 8fb9e9297..97f93ed40 100644 --- a/unison-src/transcripts/fix1800.output.md +++ b/unison-src/transcripts/fix1800.output.md @@ -20,7 +20,7 @@ Testing a few variations here: - Should be able to run annotated and unannotated main functions in the current file. - Should be able to run annotated and unannotated main functions from the codebase. -```ucm +``` ucm scratch/main> run main1 () @@ -57,7 +57,7 @@ scratch/main> rename.term main3 code.main3 ``` The renaming just ensures that when running `code.main1`, it has to get that main from the codebase rather than the scratch file: -```ucm +``` ucm scratch/main> run code.main1 () @@ -83,7 +83,7 @@ main5 _ = () This shouldn't work since `main4` and `main5` don't have the right type. -```ucm +``` ucm scratch/main> run main4 😶 @@ -97,7 +97,7 @@ scratch/main> run main4 main4 : '{IO, Exception} result ``` -```ucm +``` ucm scratch/main> run main5 😶 diff --git a/unison-src/transcripts/fix1844.output.md b/unison-src/transcripts/fix1844.output.md index bbc28208c..0f6f42817 100644 --- a/unison-src/transcripts/fix1844.output.md +++ b/unison-src/transcripts/fix1844.output.md @@ -9,7 +9,7 @@ snoc k aN = match k with > snoc (One 1) 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix1926.output.md b/unison-src/transcripts/fix1926.output.md index 6326666d2..1c940cc22 100644 --- a/unison-src/transcripts/fix1926.output.md +++ b/unison-src/transcripts/fix1926.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -10,7 +10,7 @@ scratch/main> builtins.merge sq = 2934892384 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -36,7 +36,7 @@ sq = 2934892384 sq = 2934892384 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2026.output.md b/unison-src/transcripts/fix2026.output.md index 5718d9516..254fcb72c 100644 --- a/unison-src/transcripts/fix2026.output.md +++ b/unison-src/transcripts/fix2026.output.md @@ -35,7 +35,7 @@ Exception.unsafeRun! e _ = handle !e with h ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -63,7 +63,7 @@ Exception.unsafeRun! e _ = toException : Either Failure a ->{Exception} a ``` -```ucm +``` ucm scratch/main> run ex () diff --git a/unison-src/transcripts/fix2027.output.md b/unison-src/transcripts/fix2027.output.md index cb959dcc5..3d224d644 100644 --- a/unison-src/transcripts/fix2027.output.md +++ b/unison-src/transcripts/fix2027.output.md @@ -44,7 +44,7 @@ myServer = unsafeRun! '(hello "127.0.0.1" "0") ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -77,7 +77,7 @@ myServer = unsafeRun! '(hello "127.0.0.1" "0") toException : Either Failure a ->{Exception} a ``` -```ucm +``` ucm scratch/main> run myServer 💔💥 diff --git a/unison-src/transcripts/fix2049.output.md b/unison-src/transcripts/fix2049.output.md index 492729b03..a9354446f 100644 --- a/unison-src/transcripts/fix2049.output.md +++ b/unison-src/transcripts/fix2049.output.md @@ -48,7 +48,7 @@ Fold.Stream.fold = !res Universal.== false ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -106,7 +106,7 @@ tests _ = ] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -120,7 +120,7 @@ tests _ = tests : ∀ _. _ ->{IO} [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/fix2053.output.md b/unison-src/transcripts/fix2053.output.md index 39766e272..ae97366df 100644 --- a/unison-src/transcripts/fix2053.output.md +++ b/unison-src/transcripts/fix2053.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> display List.map f a -> diff --git a/unison-src/transcripts/fix2156.output.md b/unison-src/transcripts/fix2156.output.md index acad8adb9..4a15b1acc 100644 --- a/unison-src/transcripts/fix2156.output.md +++ b/unison-src/transcripts/fix2156.output.md @@ -8,7 +8,7 @@ sqr n = n * n > sqr ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2167.output.md b/unison-src/transcripts/fix2167.output.md index 0a5c34eb1..d4e630f59 100644 --- a/unison-src/transcripts/fix2167.output.md +++ b/unison-src/transcripts/fix2167.output.md @@ -15,7 +15,7 @@ R.near1 region loc = match R.near 42 with ls -> R.die () ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2187.output.md b/unison-src/transcripts/fix2187.output.md index 45fb5de8b..12a1aab7f 100644 --- a/unison-src/transcripts/fix2187.output.md +++ b/unison-src/transcripts/fix2187.output.md @@ -13,7 +13,7 @@ lexicalScopeEx = ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2231.output.md b/unison-src/transcripts/fix2231.output.md index 5dfb0b791..d0e410477 100644 --- a/unison-src/transcripts/fix2231.output.md +++ b/unison-src/transcripts/fix2231.output.md @@ -20,7 +20,7 @@ foldl f a = cases txt = foldl (Text.++) "" ["a", "b", "c"] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -36,7 +36,7 @@ txt = foldl (Text.++) "" ["a", "b", "c"] txt : Text ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/fix2238.output.md b/unison-src/transcripts/fix2238.output.md index 0133809e1..0958d7182 100644 --- a/unison-src/transcripts/fix2238.output.md +++ b/unison-src/transcripts/fix2238.output.md @@ -6,7 +6,7 @@ structural ability Abort where abort : x ex = {{ @eval{abort} }} ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -18,7 +18,7 @@ ex = {{ @eval{abort} }} ``` This file should also not typecheck - it has a triple backticks block that uses abilities. -```ucm +``` ucm scratch/main> load unison-src/transcripts/fix2238.u Loading changes detected in unison-src/transcripts/fix2238.u. diff --git a/unison-src/transcripts/fix2244.output.md b/unison-src/transcripts/fix2244.output.md index 63ac780c2..2341d1a26 100644 --- a/unison-src/transcripts/fix2244.output.md +++ b/unison-src/transcripts/fix2244.output.md @@ -1,6 +1,6 @@ Ensure closing token is emitted by closing brace in doc eval block. -```ucm +``` ucm scratch/main> load ./unison-src/transcripts/fix2244.u Loading changes detected in diff --git a/unison-src/transcripts/fix2254.output.md b/unison-src/transcripts/fix2254.output.md index 7abb35233..0c60b4dc7 100644 --- a/unison-src/transcripts/fix2254.output.md +++ b/unison-src/transcripts/fix2254.output.md @@ -32,7 +32,7 @@ g = cases We'll make our edits in a new branch. -```ucm +``` ucm scratch/a> add ⍟ I've added these definitions: @@ -65,7 +65,7 @@ unique type A a b c d Let's do the update now, and verify that the definitions all look good and there's nothing `todo`: -```ucm +``` ucm scratch/a2> update.old ⍟ I've updated these names to your new definition: @@ -121,7 +121,7 @@ structural type Rec = { uno : Nat, dos : Nat } combine r = uno r + dos r ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -141,7 +141,7 @@ combine r = uno r + dos r combine : Rec -> Nat ``` -```ucm +``` ucm scratch/r1> add ⍟ I've added these definitions: @@ -167,7 +167,7 @@ scratch/r1> branch r2 structural type Rec = { uno : Nat, dos : Nat, tres : Text } ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -195,7 +195,7 @@ structural type Rec = { uno : Nat, dos : Nat, tres : Text } ``` And checking that after updating this record, there's nothing `todo`: -```ucm +``` ucm scratch/r2> update.old ⍟ I've added these definitions: diff --git a/unison-src/transcripts/fix2268.output.md b/unison-src/transcripts/fix2268.output.md index 1c170dd54..79da65596 100644 --- a/unison-src/transcripts/fix2268.output.md +++ b/unison-src/transcripts/fix2268.output.md @@ -15,7 +15,7 @@ test _ = toNat x ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2334.output.md b/unison-src/transcripts/fix2334.output.md index 03e65bdcd..ab20adb8e 100644 --- a/unison-src/transcripts/fix2334.output.md +++ b/unison-src/transcripts/fix2334.output.md @@ -14,7 +14,7 @@ f = cases > f 1 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2344.output.md b/unison-src/transcripts/fix2344.output.md index 4c35e7211..1d5707614 100644 --- a/unison-src/transcripts/fix2344.output.md +++ b/unison-src/transcripts/fix2344.output.md @@ -16,7 +16,7 @@ sneezy dee _ = dee 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2350.output.md b/unison-src/transcripts/fix2350.output.md index 4fcf50790..5f6f273c3 100644 --- a/unison-src/transcripts/fix2350.output.md +++ b/unison-src/transcripts/fix2350.output.md @@ -24,7 +24,7 @@ save : a ->{Storage d g, g} (d a) save a = !(save.impl a) ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2353.output.md b/unison-src/transcripts/fix2353.output.md index 72d0c465e..a6a8be6b6 100644 --- a/unison-src/transcripts/fix2353.output.md +++ b/unison-src/transcripts/fix2353.output.md @@ -11,7 +11,7 @@ pure.run a0 a = Scope.run a' ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2354.output.md b/unison-src/transcripts/fix2354.output.md index 4dab20348..226d20bc5 100644 --- a/unison-src/transcripts/fix2354.output.md +++ b/unison-src/transcripts/fix2354.output.md @@ -8,7 +8,7 @@ f id = id 0 x = 'f ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2355.output.md b/unison-src/transcripts/fix2355.output.md index 27337dbd6..b162860a9 100644 --- a/unison-src/transcripts/fix2355.output.md +++ b/unison-src/transcripts/fix2355.output.md @@ -19,7 +19,7 @@ example = 'let A.await r ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2378.output.md b/unison-src/transcripts/fix2378.output.md index 73c63de73..0c63239cc 100644 --- a/unison-src/transcripts/fix2378.output.md +++ b/unison-src/transcripts/fix2378.output.md @@ -38,7 +38,7 @@ x : '{} (Either () Nat) x _ = Ex.catch '(C.pure.run '(A.pure.run ex)) ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2423.output.md b/unison-src/transcripts/fix2423.output.md index cc17ad15c..40d2fa650 100644 --- a/unison-src/transcripts/fix2423.output.md +++ b/unison-src/transcripts/fix2423.output.md @@ -26,7 +26,7 @@ Split.zipSame sa sb _ = handle !sa with go sb ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2474.output.md b/unison-src/transcripts/fix2474.output.md index 4a0d8a08e..0daf2d3ba 100644 --- a/unison-src/transcripts/fix2474.output.md +++ b/unison-src/transcripts/fix2474.output.md @@ -16,7 +16,7 @@ should be typed in the following way: Previously this was being checked as `o ->{E0} r`, where `E0` is the ability that contains `e`. -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -35,7 +35,7 @@ Stream.uncons s = handle !s with go ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2628.output.md b/unison-src/transcripts/fix2628.output.md index cb51cf0d7..87aa68a67 100644 --- a/unison-src/transcripts/fix2628.output.md +++ b/unison-src/transcripts/fix2628.output.md @@ -4,7 +4,7 @@ unique type foo.bar.baz.MyRecord = { } ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/fix2663.output.md b/unison-src/transcripts/fix2663.output.md index fcb73c75d..6153dc042 100644 --- a/unison-src/transcripts/fix2663.output.md +++ b/unison-src/transcripts/fix2663.output.md @@ -18,7 +18,7 @@ bad x = match Some (Some x) with > bad 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2693.output.md b/unison-src/transcripts/fix2693.output.md index 94961fc9e..e5414c32a 100644 --- a/unison-src/transcripts/fix2693.output.md +++ b/unison-src/transcripts/fix2693.output.md @@ -8,7 +8,7 @@ range : Nat -> List Nat range = loop [] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -22,7 +22,7 @@ range = loop [] range : Nat -> [Nat] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -35,7 +35,7 @@ scratch/main> add > range 2000 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -2057,7 +2057,7 @@ Should be cached: > range 2000 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2712.output.md b/unison-src/transcripts/fix2712.output.md index 04c8c46e3..418123510 100644 --- a/unison-src/transcripts/fix2712.output.md +++ b/unison-src/transcripts/fix2712.output.md @@ -5,7 +5,7 @@ mapWithKey : (k ->{e} a ->{e} b) -> Map k a ->{e} Map k b mapWithKey f m = Tip ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -19,7 +19,7 @@ mapWithKey f m = Tip mapWithKey : (k ->{e} a ->{e} b) -> Map k a ->{e} Map k b ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -40,7 +40,7 @@ naiomi = ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix2795.output.md b/unison-src/transcripts/fix2795.output.md index 09ae558fc..39da527ba 100644 --- a/unison-src/transcripts/fix2795.output.md +++ b/unison-src/transcripts/fix2795.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.mergeio Done. diff --git a/unison-src/transcripts/fix2840.output.md b/unison-src/transcripts/fix2840.output.md index a84e33e4d..d6e9c3eef 100644 --- a/unison-src/transcripts/fix2840.output.md +++ b/unison-src/transcripts/fix2840.output.md @@ -2,7 +2,7 @@ This bugfix addresses an issue where embedded Unison code in UCM was expected to First, a few \[hidden\] definitions necessary for typechecking a simple Doc2. -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -25,7 +25,7 @@ Hi }} ``` -```ucm +``` ucm scratch/main> display README Hi diff --git a/unison-src/transcripts/fix2970.output.md b/unison-src/transcripts/fix2970.output.md index 2d4915f4a..7f5bddca1 100644 --- a/unison-src/transcripts/fix2970.output.md +++ b/unison-src/transcripts/fix2970.output.md @@ -1,6 +1,6 @@ Also fixes \#1519 (it's the same issue). -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -11,7 +11,7 @@ foo.+.doc : Nat foo.+.doc = 10 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix3037.output.md b/unison-src/transcripts/fix3037.output.md index be813afc7..aebd61c50 100644 --- a/unison-src/transcripts/fix3037.output.md +++ b/unison-src/transcripts/fix3037.output.md @@ -13,7 +13,7 @@ runner : Runner {IO} runner = pureRunner ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -47,7 +47,7 @@ h _ = () > h anA ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix3171.output.md b/unison-src/transcripts/fix3171.output.md index 0fdaf8377..8778f0442 100644 --- a/unison-src/transcripts/fix3171.output.md +++ b/unison-src/transcripts/fix3171.output.md @@ -9,7 +9,7 @@ f x y z _ = x + y * z > f 1 2 3 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix3196.output.md b/unison-src/transcripts/fix3196.output.md index 95f0764c0..3b8f04647 100644 --- a/unison-src/transcripts/fix3196.output.md +++ b/unison-src/transcripts/fix3196.output.md @@ -26,7 +26,7 @@ w2 = cases W -> W > w2 w1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix3215.output.md b/unison-src/transcripts/fix3215.output.md index 492d69016..2f5128ffb 100644 --- a/unison-src/transcripts/fix3215.output.md +++ b/unison-src/transcripts/fix3215.output.md @@ -16,7 +16,7 @@ f = cases {x} -> 5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix3244.output.md b/unison-src/transcripts/fix3244.output.md index 5eca2f4f7..00899d4c5 100644 --- a/unison-src/transcripts/fix3244.output.md +++ b/unison-src/transcripts/fix3244.output.md @@ -15,7 +15,7 @@ foo t = > foo (10,20) ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix3265.output.md b/unison-src/transcripts/fix3265.output.md index 2db3893b8..1f70863dc 100644 --- a/unison-src/transcripts/fix3265.output.md +++ b/unison-src/transcripts/fix3265.output.md @@ -21,7 +21,7 @@ are three cases that need to be 'fixed up.' g (z -> x + f0 z)) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -66,7 +66,7 @@ discard its arguments, where `f` also occurs. f x 20) ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix3634.output.md b/unison-src/transcripts/fix3634.output.md index e06cd8fbc..ac92ec60c 100644 --- a/unison-src/transcripts/fix3634.output.md +++ b/unison-src/transcripts/fix3634.output.md @@ -10,7 +10,7 @@ d = {{ }} ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -25,7 +25,7 @@ d = {{ d : Doc2 ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/fix3678.output.md b/unison-src/transcripts/fix3678.output.md index 3b2754bdd..321c493f2 100644 --- a/unison-src/transcripts/fix3678.output.md +++ b/unison-src/transcripts/fix3678.output.md @@ -8,7 +8,7 @@ arr = Scope.run do > compare arr arr ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix3752.output.md b/unison-src/transcripts/fix3752.output.md index fb52acd21..b22b33408 100644 --- a/unison-src/transcripts/fix3752.output.md +++ b/unison-src/transcripts/fix3752.output.md @@ -15,7 +15,7 @@ bar = do id "hello" ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix3759.output.md b/unison-src/transcripts/fix3759.output.md index 4f0db3fe5..1102f4535 100644 --- a/unison-src/transcripts/fix3759.output.md +++ b/unison-src/transcripts/fix3759.output.md @@ -47,7 +47,7 @@ blah.frobnicate = "Yay!" > blah.frobnicate Text.++ " 🎉" ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix3773.output.md b/unison-src/transcripts/fix3773.output.md index e7f355fd0..360dd2578 100644 --- a/unison-src/transcripts/fix3773.output.md +++ b/unison-src/transcripts/fix3773.output.md @@ -7,7 +7,7 @@ foo = > foo + 20 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix4172.output.md b/unison-src/transcripts/fix4172.output.md index 436f79715..b94add30a 100644 --- a/unison-src/transcripts/fix4172.output.md +++ b/unison-src/transcripts/fix4172.output.md @@ -11,7 +11,7 @@ bool = true allowDebug = debug [1,2,3] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -34,7 +34,7 @@ allowDebug = debug [1,2,3] ✅ Passed Yay ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -59,7 +59,7 @@ scratch/main> test bool = false ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -73,7 +73,7 @@ bool = false bool : Boolean ``` -```ucm +``` ucm scratch/main> update.old ⍟ I've updated these names to your new definition: diff --git a/unison-src/transcripts/fix4280.output.md b/unison-src/transcripts/fix4280.output.md index 4c7fbb2de..65561ba2a 100644 --- a/unison-src/transcripts/fix4280.output.md +++ b/unison-src/transcripts/fix4280.output.md @@ -7,7 +7,7 @@ bonk = _baz ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix4397.output.md b/unison-src/transcripts/fix4397.output.md index 2cb173290..5d62c1227 100644 --- a/unison-src/transcripts/fix4397.output.md +++ b/unison-src/transcripts/fix4397.output.md @@ -7,7 +7,7 @@ unique type Bar = Bar Baz ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix4415.output.md b/unison-src/transcripts/fix4415.output.md index 90d57f289..b17f16ddc 100644 --- a/unison-src/transcripts/fix4415.output.md +++ b/unison-src/transcripts/fix4415.output.md @@ -3,7 +3,7 @@ unique type Foo = Foo unique type sub.Foo = ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix4424.output.md b/unison-src/transcripts/fix4424.output.md index 1eb07ab2d..2c7c4b4b6 100644 --- a/unison-src/transcripts/fix4424.output.md +++ b/unison-src/transcripts/fix4424.output.md @@ -8,7 +8,7 @@ countCat = cases Cat.Dog.Mouse x -> Bird ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -24,7 +24,7 @@ Now I want to add a constructor. unique type Rat.Dog = Bird | Mouse ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/fix4482.output.md b/unison-src/transcripts/fix4482.output.md index 26a73068d..5f641c204 100644 --- a/unison-src/transcripts/fix4482.output.md +++ b/unison-src/transcripts/fix4482.output.md @@ -6,7 +6,7 @@ lib.foo1.lib.bonk2.qux = 1 mybar = bar + bar ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -23,7 +23,7 @@ mybar = bar + bar mybar : Nat ``` -```ucm +``` ucm myproj/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/fix4498.output.md b/unison-src/transcripts/fix4498.output.md index 149d3406f..49cc9735f 100644 --- a/unison-src/transcripts/fix4498.output.md +++ b/unison-src/transcripts/fix4498.output.md @@ -5,7 +5,7 @@ lib.dep0.lib.dep1.foo = 6 myterm = foo + 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -21,7 +21,7 @@ myterm = foo + 2 myterm : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/fix4515.output.md b/unison-src/transcripts/fix4515.output.md index 925195662..9e4b3ee65 100644 --- a/unison-src/transcripts/fix4515.output.md +++ b/unison-src/transcripts/fix4515.output.md @@ -8,7 +8,7 @@ useBar = cases Bar.X _ -> 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -24,7 +24,7 @@ useBar = cases useBar : Bar -> Nat ``` -```ucm +``` ucm myproject/main> add ⍟ I've added these definitions: @@ -39,7 +39,7 @@ myproject/main> add unique type Foo = Foo1 | Foo2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -53,7 +53,7 @@ unique type Foo = Foo1 | Foo2 type Foo ``` -```ucm +``` ucm myproject/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/fix4528.output.md b/unison-src/transcripts/fix4528.output.md index 8b2d96fc3..0266eef0a 100644 --- a/unison-src/transcripts/fix4528.output.md +++ b/unison-src/transcripts/fix4528.output.md @@ -5,7 +5,7 @@ main : () -> Foo main _ = MkFoo 5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -19,7 +19,7 @@ main _ = MkFoo 5 main : 'Foo ``` -```ucm +``` ucm foo/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/fix4556.output.md b/unison-src/transcripts/fix4556.output.md index f36c030d2..23bdc3a9f 100644 --- a/unison-src/transcripts/fix4556.output.md +++ b/unison-src/transcripts/fix4556.output.md @@ -5,7 +5,7 @@ bar.hello = 5 + thing hey = foo.hello ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -21,7 +21,7 @@ hey = foo.hello thing : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -36,7 +36,7 @@ scratch/main> add thing = 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -50,7 +50,7 @@ thing = 2 thing : Nat ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/fix4592.output.md b/unison-src/transcripts/fix4592.output.md index 1644f6c33..a6a05b76d 100644 --- a/unison-src/transcripts/fix4592.output.md +++ b/unison-src/transcripts/fix4592.output.md @@ -3,7 +3,7 @@ doc = {{ {{ bug "bug" 52 }} }} ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix4618.output.md b/unison-src/transcripts/fix4618.output.md index 144c13a8d..a364ddc8f 100644 --- a/unison-src/transcripts/fix4618.output.md +++ b/unison-src/transcripts/fix4618.output.md @@ -3,7 +3,7 @@ foo = 5 unique type Bugs.Zonk = Bugs ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -17,7 +17,7 @@ unique type Bugs.Zonk = Bugs foo : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -31,7 +31,7 @@ foo = 4 unique type Bugs = ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -49,7 +49,7 @@ unique type Bugs = foo : Nat ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/fix4722.output.md b/unison-src/transcripts/fix4722.output.md index 91b071e5f..faa963b19 100644 --- a/unison-src/transcripts/fix4722.output.md +++ b/unison-src/transcripts/fix4722.output.md @@ -34,7 +34,7 @@ foo = cases f (_ -> ()) (foo l) (foo r) ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix4780.output.md b/unison-src/transcripts/fix4780.output.md index 392060c34..5fefbd4cc 100644 --- a/unison-src/transcripts/fix4780.output.md +++ b/unison-src/transcripts/fix4780.output.md @@ -5,7 +5,7 @@ builtins decompile properly. > (+) 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix4898.output.md b/unison-src/transcripts/fix4898.output.md index 62c4d6377..9bacabb90 100644 --- a/unison-src/transcripts/fix4898.output.md +++ b/unison-src/transcripts/fix4898.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -12,7 +12,7 @@ redouble : Int -> Int redouble x = double x + double x ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -26,7 +26,7 @@ redouble x = double x + double x redouble : Int -> Int ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/fix5055.output.md b/unison-src/transcripts/fix5055.output.md index 475edc5bd..005e47585 100644 --- a/unison-src/transcripts/fix5055.output.md +++ b/unison-src/transcripts/fix5055.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm test-5055/main> builtins.merge Done. @@ -10,7 +10,7 @@ foo.add x y = x Int.+ y foo.subtract x y = x Int.- y ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -24,7 +24,7 @@ foo.subtract x y = x Int.- y foo.subtract : Int -> Int -> Int ``` -```ucm +``` ucm test-5055/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/fix5080.output.md b/unison-src/transcripts/fix5080.output.md index 67468e1b8..f64f9c84f 100644 --- a/unison-src/transcripts/fix5080.output.md +++ b/unison-src/transcripts/fix5080.output.md @@ -3,7 +3,7 @@ test> fix5080.tests.success = [Ok "success"] test> fix5080.tests.failure = [Fail "fail"] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -28,7 +28,7 @@ test> fix5080.tests.failure = [Fail "fail"] 🚫 FAILED fail ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -49,7 +49,7 @@ scratch/main> test Tip: Use view 1 to view the source of a test. ``` -```ucm +``` ucm scratch/main> delete.term 2 Done. diff --git a/unison-src/transcripts/fix614.output.md b/unison-src/transcripts/fix614.output.md index 770489a09..97ec65e00 100644 --- a/unison-src/transcripts/fix614.output.md +++ b/unison-src/transcripts/fix614.output.md @@ -11,7 +11,7 @@ ex1 = do 42 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -33,7 +33,7 @@ ex2 = do 42 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -55,7 +55,7 @@ ex3 = do () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -78,7 +78,7 @@ ex4 = () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -100,7 +100,7 @@ ex4 = () ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix689.output.md b/unison-src/transcripts/fix689.output.md index 06689cf64..ed8ea0410 100644 --- a/unison-src/transcripts/fix689.output.md +++ b/unison-src/transcripts/fix689.output.md @@ -7,7 +7,7 @@ structural ability SystemTime where tomorrow = '(SystemTime.systemTime + 24 * 60 * 60) ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix693.output.md b/unison-src/transcripts/fix693.output.md index 753e434f2..35e07bec5 100644 --- a/unison-src/transcripts/fix693.output.md +++ b/unison-src/transcripts/fix693.output.md @@ -6,7 +6,7 @@ structural ability Abort where abort : a ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -20,7 +20,7 @@ structural ability Abort where structural ability X t ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -41,7 +41,7 @@ h0 req = match req with { d } -> Some d ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -69,7 +69,7 @@ h1 req = match req with { d } -> Some d ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -98,7 +98,7 @@ h2 req = match req with { r } -> r ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -121,7 +121,7 @@ h3 = cases { X.x b _ -> _ } -> Some b ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix845.output.md b/unison-src/transcripts/fix845.output.md index 6b910d67e..c192583c6 100644 --- a/unison-src/transcripts/fix845.output.md +++ b/unison-src/transcripts/fix845.output.md @@ -8,7 +8,7 @@ Text.zonk : Text -> Text Text.zonk txt = txt ++ "!! " ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -29,7 +29,7 @@ Now, typecheck a file with a reference to `Blah.zonk` (which doesn't exist in th > Blah.zonk [1,2,3] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -61,7 +61,7 @@ ex = baz ++ ", world!" > ex ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -91,7 +91,7 @@ ex = zonk "hi" > ex ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -123,7 +123,7 @@ ex = zonk "hi" -- should resolve to Text.zonk, from the codebase > ex ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix849.output.md b/unison-src/transcripts/fix849.output.md index f1775f630..c6c5c1390 100644 --- a/unison-src/transcripts/fix849.output.md +++ b/unison-src/transcripts/fix849.output.md @@ -6,7 +6,7 @@ x = 42 > x ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/fix942.output.md b/unison-src/transcripts/fix942.output.md index 13d68377a..13dd97532 100644 --- a/unison-src/transcripts/fix942.output.md +++ b/unison-src/transcripts/fix942.output.md @@ -6,7 +6,7 @@ y = x + 1 z = y + 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -21,7 +21,7 @@ z = y + 2 z : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -37,7 +37,7 @@ Now we edit `x` to be `7`, which should make `z` equal `10`: x = 7 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -51,7 +51,7 @@ x = 7 x : Nat ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be @@ -85,7 +85,7 @@ Uh oh\! `z` is still referencing the old version. Just to confirm: test> t1 = if z == 3 then [Fail "nooo!!!"] else [Ok "great"] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -105,7 +105,7 @@ test> t1 = if z == 3 then [Fail "nooo!!!"] else [Ok "great"] ✅ Passed great ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/fix987.output.md b/unison-src/transcripts/fix987.output.md index e816b3808..a128fa6c0 100644 --- a/unison-src/transcripts/fix987.output.md +++ b/unison-src/transcripts/fix987.output.md @@ -10,7 +10,7 @@ spaceAttack1 x = "All done" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -26,7 +26,7 @@ spaceAttack1 x = ``` Add it to the codebase: -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -44,7 +44,7 @@ spaceAttack2 x = "All done" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -57,7 +57,7 @@ spaceAttack2 x = spaceAttack2 : x ->{DeathStar} Text ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/formatter.output.md b/unison-src/transcripts/formatter.output.md index 1b16b7def..54c9a1232 100644 --- a/unison-src/transcripts/formatter.output.md +++ b/unison-src/transcripts/formatter.output.md @@ -83,7 +83,7 @@ with a strike-through block~ }} ``` -```ucm +``` ucm scratch/main> debug.format ``` @@ -171,7 +171,7 @@ Formatter should leave things alone if the file doesn't typecheck. brokenDoc = {{ hello }} + 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -199,7 +199,7 @@ brokenDoc = {{ hello }} + 1 (Nat.+) : Nat -> Nat -> Nat ``` -```ucm +``` ucm scratch/main> debug.format ``` diff --git a/unison-src/transcripts/fuzzy-options.output.md b/unison-src/transcripts/fuzzy-options.output.md index f07d39906..d83fd4341 100644 --- a/unison-src/transcripts/fuzzy-options.output.md +++ b/unison-src/transcripts/fuzzy-options.output.md @@ -2,7 +2,7 @@ If an argument is required but doesn't have a fuzzy resolver, the command should just print the help. -```ucm +``` ucm -- The second argument of move.term is a 'new-name' and doesn't have a fuzzy resolver scratch/main> move.term @@ -12,7 +12,7 @@ scratch/main> move.term If a fuzzy resolver doesn't have any options available it should print a message instead of opening an empty fuzzy-select. -```ucm +``` ucm scratch/empty> view ⚠️ @@ -28,7 +28,7 @@ nested.optionTwo = 2 Definition args -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -45,7 +45,7 @@ scratch/main> debug.fuzzy-options view _ ``` Namespace args -```ucm +``` ucm scratch/main> add ⊡ Ignored previously added definitions: nested.optionTwo @@ -59,7 +59,7 @@ scratch/main> debug.fuzzy-options find-in _ ``` Project Branch args -```ucm +``` ucm myproject/main> branch mybranch Done. I've created the mybranch branch based off of main. diff --git a/unison-src/transcripts/generic-parse-errors.output.md b/unison-src/transcripts/generic-parse-errors.output.md index b0f6d6a5b..c66d0c594 100644 --- a/unison-src/transcripts/generic-parse-errors.output.md +++ b/unison-src/transcripts/generic-parse-errors.output.md @@ -5,7 +5,7 @@ x = foo.123 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -26,7 +26,7 @@ x = namespace.blah = 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -42,7 +42,7 @@ namespace.blah = 1 x = 1 ] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -56,7 +56,7 @@ x = 1 ] x = a.#abc ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -72,7 +72,7 @@ x = a.#abc x = "hi ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -93,7 +93,7 @@ x = "hi y : a ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/hello.output.md b/unison-src/transcripts/hello.output.md index 3c5d9bc8c..720cd6d3f 100644 --- a/unison-src/transcripts/hello.output.md +++ b/unison-src/transcripts/hello.output.md @@ -27,7 +27,7 @@ x = 42 ``` -```ucm +``` ucm Loading changes detected in myfile.u. @@ -42,7 +42,7 @@ x = 42 ``` Let's go ahead and add that to the codebase, then make sure it's there: -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -78,7 +78,7 @@ hmm : .builtin.Nat hmm = "Not, in fact, a number" ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/help.output.md b/unison-src/transcripts/help.output.md index 54662d0c9..019bc3092 100644 --- a/unison-src/transcripts/help.output.md +++ b/unison-src/transcripts/help.output.md @@ -1,6 +1,6 @@ # Shows `help` output -```ucm +``` ucm scratch/main> help add diff --git a/unison-src/transcripts/higher-rank.output.md b/unison-src/transcripts/higher-rank.output.md index f4c2dbf50..449617d84 100644 --- a/unison-src/transcripts/higher-rank.output.md +++ b/unison-src/transcripts/higher-rank.output.md @@ -9,7 +9,7 @@ f id = (id 1, id "hi") > f (x -> x) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -38,7 +38,7 @@ f id _ = () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -66,7 +66,7 @@ Functor.blah = cases Functor f -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -110,7 +110,7 @@ Loc.transform2 nt = cases Loc f -> Loc f' ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -139,7 +139,7 @@ structural type HigherRanked = HigherRanked (forall a. a -> a) We should be able to add and view records with higher-rank fields. -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/input-parse-errors.output.md b/unison-src/transcripts/input-parse-errors.output.md index 2e00b284c..f349b8a88 100644 --- a/unison-src/transcripts/input-parse-errors.output.md +++ b/unison-src/transcripts/input-parse-errors.output.md @@ -6,7 +6,7 @@ x = 55 `handleNameArg` parse error in `add` -```ucm +``` ucm scratch/main> add . ⚠️ @@ -61,7 +61,7 @@ todo: aliasMany: skipped -- similar to `add` -```ucm +``` ucm scratch/main> update arg ⚠️ diff --git a/unison-src/transcripts/io-test-command.output.md b/unison-src/transcripts/io-test-command.output.md index 65abcdab6..0e1d8cbbd 100644 --- a/unison-src/transcripts/io-test-command.output.md +++ b/unison-src/transcripts/io-test-command.output.md @@ -17,7 +17,7 @@ lib.ioAndExceptionTestInLib = do Run a IO tests one by one -```ucm +``` ucm scratch/main> io.test ioAndExceptionTest New test results: @@ -41,7 +41,7 @@ scratch/main> io.test ioTest ``` `io.test` doesn't cache results -```ucm +``` ucm scratch/main> io.test ioAndExceptionTest New test results: @@ -55,7 +55,7 @@ scratch/main> io.test ioAndExceptionTest ``` `io.test.all` will run all matching tests except those in the `lib` namespace. -```ucm +``` ucm scratch/main> io.test.all diff --git a/unison-src/transcripts/io.output.md b/unison-src/transcripts/io.output.md index 2cdaeea0e..ef385d897 100644 --- a/unison-src/transcripts/io.output.md +++ b/unison-src/transcripts/io.output.md @@ -45,7 +45,7 @@ testCreateRename _ = runTest test ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -58,7 +58,7 @@ testCreateRename _ = testCreateRename : '{IO} [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -127,7 +127,7 @@ testOpenClose _ = runTest test ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -140,7 +140,7 @@ testOpenClose _ = testOpenClose : '{IO} [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -217,7 +217,7 @@ testGetSomeBytes _ = runTest test ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -230,7 +230,7 @@ testGetSomeBytes _ = testGetSomeBytes : '{IO} [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -324,7 +324,7 @@ testAppend _ = runTest test ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -338,7 +338,7 @@ testAppend _ = testSeek : '{IO} [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -385,7 +385,7 @@ testSystemTime _ = runTest test ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -398,7 +398,7 @@ testSystemTime _ = testSystemTime : '{IO} [Result] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -428,7 +428,7 @@ testGetTempDirectory _ = runTest test ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -459,7 +459,7 @@ testGetCurrentDirectory _ = runTest test ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -492,7 +492,7 @@ testDirContents _ = runTest test ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -525,7 +525,7 @@ testGetEnv _ = runTest test ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -580,7 +580,7 @@ testGetArgs.runMeWithTwoArgs = 'let Test that they can be run with the right number of args. -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -605,7 +605,7 @@ scratch/main> run runMeWithTwoArgs foo bar ``` Calling our examples with the wrong number of args will error. -```ucm +``` ucm scratch/main> run runMeWithNoArgs foo 💔💥 @@ -618,7 +618,7 @@ scratch/main> run runMeWithNoArgs foo ##raise ``` -```ucm +``` ucm scratch/main> run runMeWithOneArg 💔💥 @@ -631,7 +631,7 @@ scratch/main> run runMeWithOneArg ##raise ``` -```ucm +``` ucm scratch/main> run runMeWithOneArg foo bar 💔💥 @@ -645,7 +645,7 @@ scratch/main> run runMeWithOneArg foo bar ##raise ``` -```ucm +``` ucm scratch/main> run runMeWithTwoArgs 💔💥 @@ -667,7 +667,7 @@ testTimeZone = do () ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -690,7 +690,7 @@ testRandom = do runTest test ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/kind-inference.output.md b/unison-src/transcripts/kind-inference.output.md index 46a335a20..c40961bc7 100644 --- a/unison-src/transcripts/kind-inference.output.md +++ b/unison-src/transcripts/kind-inference.output.md @@ -6,7 +6,7 @@ conflicting constraints on the kind of `a` in a product unique type T a = T a (a Nat) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -24,7 +24,7 @@ unique type T a | StarStar (a Nat) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -44,7 +44,7 @@ unique type Ping a = Ping Pong unique type Pong = Pong (Ping Optional) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -66,7 +66,7 @@ unique type Ping a = Ping a Pong unique type Pong = Pong (Ping Optional) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -85,7 +85,7 @@ unique ability Pong a where pong : Ping Optional -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -107,7 +107,7 @@ unique ability Pong a where pong : Ping Optional -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -126,7 +126,7 @@ unique type T a = T a unique type S = S (T Nat) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -150,7 +150,7 @@ unique type T a = T unique type S = S (T Optional) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -172,7 +172,7 @@ unique type T a = T a unique type S = S (T Optional) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -192,7 +192,7 @@ test : Nat Nat test = 0 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -210,7 +210,7 @@ test : Optional -> () test _ = () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -230,7 +230,7 @@ test : T Nat -> () test _ = () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -254,7 +254,7 @@ test _ = () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -277,7 +277,7 @@ test : Foo -> () test _ = () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -295,7 +295,7 @@ test : {Nat} () test _ = () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -313,7 +313,7 @@ test _ = () unique type T a = T (a a) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -329,7 +329,7 @@ unique type T a = T (a a) unique type T a b = T (a b) (b a) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -346,7 +346,7 @@ unique type Ping a = Ping (a Pong) unique type Pong a = Pong (a Ping) ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/lambdacase.output.md b/unison-src/transcripts/lambdacase.output.md index 86fd5b234..c7c6e01c2 100644 --- a/unison-src/transcripts/lambdacase.output.md +++ b/unison-src/transcripts/lambdacase.output.md @@ -8,7 +8,7 @@ isEmpty x = match x with _ -> false ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -29,7 +29,7 @@ isEmpty2 = cases _ -> false ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -45,7 +45,7 @@ isEmpty2 = cases ``` Notice that Unison detects this as an alias of `isEmpty`, and if we view `isEmpty` -```ucm +``` ucm scratch/main> view isEmpty isEmpty : [t] -> Boolean @@ -70,7 +70,7 @@ merge xs ys = match (xs, ys) with else h2 +: merge (h +: t) t2 ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -90,7 +90,7 @@ merge2 = cases else h2 +: merge2 (h +: t) t2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -106,7 +106,7 @@ merge2 = cases ``` Notice that Unison detects this as an alias of `merge`, and if we view `merge` -```ucm +``` ucm scratch/main> view merge merge : [a] -> [a] -> [a] @@ -139,7 +139,7 @@ blorf = cases > blorf T F ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -180,7 +180,7 @@ merge3 = cases | otherwise -> h2 +: merge3 (h +: t) t2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -193,7 +193,7 @@ merge3 = cases merge3 : [a] -> [a] -> [a] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -222,7 +222,7 @@ merge4 a b = match (a,b) with h +: t, h2 +: t2 | otherwise -> h2 +: merge4 (h +: t) t2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/lsp-fold-ranges.output.md b/unison-src/transcripts/lsp-fold-ranges.output.md index f2af4461b..46e0a9c76 100644 --- a/unison-src/transcripts/lsp-fold-ranges.output.md +++ b/unison-src/transcripts/lsp-fold-ranges.output.md @@ -23,7 +23,7 @@ test> z = let [Ok (x ++ y)] ``` -```ucm +``` ucm scratch/main> debug.lsp.fold-ranges 《{{ Type doc }}》 diff --git a/unison-src/transcripts/lsp-name-completion.output.md b/unison-src/transcripts/lsp-name-completion.output.md index 0b57f6a98..9c310ea87 100644 --- a/unison-src/transcripts/lsp-name-completion.output.md +++ b/unison-src/transcripts/lsp-name-completion.output.md @@ -17,7 +17,7 @@ sorted by number of name segments, shortest first. Individual LSP clients may still handle sorting differently, e.g. doing a fuzzy match over returned results, or prioritizing exact matches over partial matches. We don't have any control over that. -```ucm +``` ucm scratch/main> debug.lsp-name-completion foldMap Matching Path Name Hash @@ -30,7 +30,7 @@ scratch/main> debug.lsp-name-completion foldMap ``` Should still find the term which has a matching hash to a better name if the better name doesn't match. -```ucm +``` ucm scratch/main> debug.lsp-name-completion transitive_same_hash.foldMap Matching Path Name Hash diff --git a/unison-src/transcripts/merge.output.md b/unison-src/transcripts/merge.output.md index d67d0355b..77350b113 100644 --- a/unison-src/transcripts/merge.output.md +++ b/unison-src/transcripts/merge.output.md @@ -3,7 +3,7 @@ The `merge` command merges together two branches in the same project: the current branch (unspecificed), and the target branch. For example, to merge `topic` into `main`, switch to `main` and run `merge topic`: -```ucm +``` ucm scratch/main> help merge merge @@ -45,7 +45,7 @@ bar = "bobs bar" Merge result: -```ucm +``` ucm project/alice> merge /bob I merged project/bob into project/alice. @@ -82,7 +82,7 @@ bar = "bobs bar" Merge result: -```ucm +``` ucm project/alice> merge /bob I merged project/bob into project/alice. @@ -121,7 +121,7 @@ bar : Text bar = foo ++ " - " ++ foo ``` -```ucm +``` ucm project/bob> display bar "old foo - old foo" @@ -129,7 +129,7 @@ project/bob> display bar ``` Merge result: -```ucm +``` ucm project/alice> merge /bob I merged project/bob into project/alice. @@ -175,7 +175,7 @@ bar : Text bar = "alices bar" ``` -```ucm +``` ucm project/alice> display foo "foo - alices bar - old baz" @@ -188,7 +188,7 @@ baz : Text baz = "bobs baz" ``` -```ucm +``` ucm project/bob> display foo "foo - old bar - bobs baz" @@ -196,7 +196,7 @@ project/bob> display foo ``` Merge result: -```ucm +``` ucm project/alice> merge /bob I merged project/bob into project/alice. @@ -236,7 +236,7 @@ baz : Text baz = "old baz" ``` -```ucm +``` ucm project/main> display foo "old foo - old bar - old baz" @@ -249,7 +249,7 @@ baz : Text baz = "alices baz" ``` -```ucm +``` ucm project/alice> display foo "old foo - old bar - alices baz" @@ -262,7 +262,7 @@ bar : Text bar = "bobs bar" ++ " - " ++ baz ``` -```ucm +``` ucm project/bob> display foo "old foo - bobs bar - old baz" @@ -270,7 +270,7 @@ project/bob> display foo ``` Merge result: -```ucm +``` ucm project/alice> merge /bob I merged project/bob into project/alice. @@ -315,7 +315,7 @@ foo = "alices foo" Bob's changes: -```ucm +``` ucm project/bob> delete.term foo Done. @@ -323,7 +323,7 @@ project/bob> delete.term foo ``` Merge result: -```ucm +``` ucm project/alice> merge /bob I merged project/bob into project/alice. @@ -368,7 +368,7 @@ lib.bothDifferent.baz = 21 Merge result: -```ucm +``` ucm project/alice> merge bob I merged project/bob into project/alice. @@ -395,7 +395,7 @@ project/alice> view foo bar baz If Bob is equals Alice, then merging Bob into Alice looks like this. -```ucm +``` ucm project/main> branch alice Done. I've created the alice branch based off of main. @@ -421,7 +421,7 @@ project/alice> merge /bob If Bob is behind Alice, then merging Bob into Alice looks like this. -```ucm +``` ucm project/main> branch alice Done. I've created the alice branch based off of main. @@ -444,7 +444,7 @@ foo : Text foo = "foo" ``` -```ucm +``` ucm project/alice> add ⍟ I've added these definitions: @@ -462,7 +462,7 @@ project/alice> merge /bob If Bob is ahead of Alice, then merging Bob into Alice looks like this. -```ucm +``` ucm project/main> branch alice Done. I've created the alice branch based off of main. @@ -485,7 +485,7 @@ foo : Text foo = "foo" ``` -```ucm +``` ucm project/bob> add ⍟ I've added these definitions: @@ -499,7 +499,7 @@ project/alice> merge /bob ``` ## No-op merge: merge empty namespace into empty namespace -```ucm +``` ucm project/main> branch topic Done. I've created the topic branch based off of main. @@ -531,7 +531,7 @@ foo = "foo" Alice's delete: -```ucm +``` ucm project/alice> delete.term foo Done. @@ -544,7 +544,7 @@ bar : Text bar = foo ++ " - " ++ foo ``` -```ucm +``` ucm project/bob> add ⍟ I've added these definitions: @@ -605,7 +605,7 @@ bar : Text bar = foo ++ " - " ++ foo ``` -```ucm +``` ucm project/alice> merge /bob I couldn't automatically merge project/bob into project/alice. @@ -671,7 +671,7 @@ baz : Text baz = "bobs baz" ``` -```ucm +``` ucm project/alice> merge /bob I couldn't automatically merge project/bob into project/alice. @@ -710,7 +710,7 @@ qux = ``` -```ucm +``` ucm project/merge-bob-into-alice> view bar baz bar : Text @@ -742,7 +742,7 @@ Bob's changes: unique type Foo = MkFoo Nat Text ``` -```ucm +``` ucm project/alice> merge /bob I couldn't automatically merge project/bob into project/alice. @@ -793,7 +793,7 @@ Bob's renames `Qux` to `BobQux`: unique type Foo = Baz Nat | BobQux Text ``` -```ucm +``` ucm project/alice> merge /bob I couldn't automatically merge project/bob into project/alice. @@ -834,7 +834,7 @@ unique type Foo = Baz Nat | Qux Text Alice's rename: -```ucm +``` ucm project/alice> move.term Foo.Baz Foo.Alice Done. @@ -842,13 +842,13 @@ project/alice> move.term Foo.Baz Foo.Alice ``` Bob's rename: -```ucm +``` ucm project/bob> move.term Foo.Qux Foo.Bob Done. ``` -```ucm +``` ucm project/alice> merge bob I couldn't automatically merge project/bob into project/alice. @@ -895,7 +895,7 @@ unique ability my.cool where thing : Nat -> Nat ``` -```ucm +``` ucm project/alice> merge bob I couldn't automatically merge project/bob into project/alice. @@ -944,7 +944,7 @@ unique type Foo = Alice Nat Bob adds the type `Foo` with constructor `Foo.Bar`, replacing the original `Foo.Bar` term: -```ucm +``` ucm project/bob> delete.term Foo.Bar Done. @@ -956,7 +956,7 @@ unique type Foo = Bar Nat Nat These won't cleanly merge. -```ucm +``` ucm project/alice> merge bob I couldn't automatically merge project/bob into project/alice. @@ -1004,7 +1004,7 @@ Foo.Bar.Hello = 17 Alice deletes this type entirely, and repurposes its constructor names for other terms. She also updates the term. -```ucm +``` ucm project/alice> view Foo.Bar.Baz Foo.Bar.Qux Foo.Bar.Hello Foo.Bar.Baz : Nat @@ -1019,7 +1019,7 @@ project/alice> view Foo.Bar.Baz Foo.Bar.Qux Foo.Bar.Hello ``` Bob, meanwhile, first deletes the term, then sort of deletes the type and re-adds it under another name, but one constructor's fully qualified names doesn't actually change. The other constructor reuses the name of the deleted term. -```ucm +``` ucm project/bob> view Foo.Bar type Foo.Bar = Baz Nat | Hello Nat Nat @@ -1029,7 +1029,7 @@ At this point, Bob and alice have both updated the name `Foo.Bar.Hello` in diffe Notably, Alice's "unconflicted" update on the name "Foo.Bar.Baz" (because she changed its hash and Bob didn't touch it) is nonetheless considered conflicted with Bob's "Foo.Bar.Baz". -```ucm +``` ucm project/alice> merge bob I couldn't automatically merge project/bob into project/alice. @@ -1089,7 +1089,7 @@ bob : Foo -> Nat bob _ = 19 ``` -```ucm +``` ucm project/alice> merge bob I couldn't automatically merge project/bob into project/alice. @@ -1157,7 +1157,7 @@ foo = "bobs foo" Attempt to merge: -```ucm +``` ucm project/alice> merge /bob I couldn't automatically merge project/bob into project/alice. @@ -1195,7 +1195,7 @@ foo : Text foo = "alice and bobs foo" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1208,7 +1208,7 @@ foo = "alice and bobs foo" foo : Text ``` -```ucm +``` ucm project/merge-bob-into-alice> update Okay, I'm searching the branch for code that needs to be @@ -1238,7 +1238,7 @@ project/alice> branches `merge.commit` can only be run on a "merge branch". -```ucm +``` ucm project/main> branch topic Done. I've created the topic branch based off of main. @@ -1247,7 +1247,7 @@ project/main> branch topic `switch /main` then `merge /topic`. ``` -```ucm +``` ucm project/topic> merge.commit It doesn't look like there's a merge in progress. @@ -1288,7 +1288,7 @@ baz : Text baz = "baz" ``` -```ucm +``` ucm project/alice> merge /bob Sorry, I wasn't able to perform the merge: @@ -1318,7 +1318,7 @@ One way to fix this in the future would be to introduce a syntax for defining al Alice's branch: -```ucm +``` ucm project/alice> alias.type lib.builtins.Nat MyNat Done. @@ -1330,7 +1330,7 @@ Bob's branch: unique type MyNat = MyNat Nat ``` -```ucm +``` ucm project/alice> merge /bob Sorry, I wasn't able to perform the merge: @@ -1354,7 +1354,7 @@ Alice's branch: unique type Foo = Bar ``` -```ucm +``` ucm project/alice> alias.term Foo.Bar Foo.some.other.Alias Done. @@ -1367,7 +1367,7 @@ bob : Nat bob = 100 ``` -```ucm +``` ucm project/alice> merge /bob Sorry, I wasn't able to perform the merge: @@ -1392,7 +1392,7 @@ Alice's branch: unique type Foo = Bar ``` -```ucm +``` ucm project/alice> delete.term Foo.Bar Done. @@ -1405,7 +1405,7 @@ bob : Nat bob = 100 ``` -```ucm +``` ucm project/alice> merge /bob Sorry, I wasn't able to perform the merge: @@ -1429,7 +1429,7 @@ structural type A = B Nat | C Nat Nat structural type A.inner.X = Y Nat | Z Nat Nat ``` -```ucm +``` ucm project/alice> names A Type @@ -1446,7 +1446,7 @@ bob : Nat bob = 100 ``` -```ucm +``` ucm project/alice> merge /bob On project/alice, the type A.inner.X is an alias of A. I'm not @@ -1461,7 +1461,7 @@ Constructors may only exist within the corresponding decl's namespace. Alice's branch: -```ucm +``` ucm project/alice> add ⍟ I've added these definitions: @@ -1475,7 +1475,7 @@ project/alice> alias.term Foo.Bar AliasOutsideFooNamespace ``` Bob's branch: -```ucm +``` ucm project/bob> add ⍟ I've added these definitions: @@ -1483,7 +1483,7 @@ project/bob> add bob : Nat ``` -```ucm +``` ucm project/alice> merge bob Sorry, I wasn't able to perform the merge, because I need all @@ -1514,7 +1514,7 @@ bob : Nat bob = 100 ``` -```ucm +``` ucm project/alice> merge /bob Sorry, I wasn't able to perform the merge: @@ -1539,7 +1539,7 @@ LCA: structural type Foo = Bar Nat | Baz Nat Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1552,7 +1552,7 @@ structural type Foo = Bar Nat | Baz Nat Nat structural type Foo ``` -```ucm +``` ucm project/main> add ⍟ I've added these definitions: @@ -1566,7 +1566,7 @@ project/main> delete.term Foo.Baz ``` Alice's branch: -```ucm +``` ucm project/main> branch alice Done. I've created the alice branch based off of main. @@ -1588,7 +1588,7 @@ alice : Nat alice = 100 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1601,7 +1601,7 @@ alice = 100 alice : Nat ``` -```ucm +``` ucm project/alice> add ⍟ I've added these definitions: @@ -1611,7 +1611,7 @@ project/alice> add ``` Bob's branch: -```ucm +``` ucm project/main> branch bob Done. I've created the bob branch based off of main. @@ -1633,7 +1633,7 @@ bob : Nat bob = 101 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1646,7 +1646,7 @@ bob = 101 bob : Nat ``` -```ucm +``` ucm project/bob> add ⍟ I've added these definitions: @@ -1656,7 +1656,7 @@ project/bob> add ``` Now we merge: -```ucm +``` ucm project/alice> merge /bob I merged project/bob into project/alice. @@ -1671,7 +1671,7 @@ foo = 17 bar = 17 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1685,7 +1685,7 @@ bar = 17 foo : Nat ``` -```ucm +``` ucm project/main> add ⍟ I've added these definitions: @@ -1709,7 +1709,7 @@ project/alice> delete.term bar foo = 18 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1723,7 +1723,7 @@ foo = 18 foo : Nat ``` -```ucm +``` ucm project/alice> update Okay, I'm searching the branch for code that needs to be @@ -1743,7 +1743,7 @@ project/main> branch bob bob = 101 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1756,7 +1756,7 @@ bob = 101 bob : Nat ``` -```ucm +``` ucm project/bob> add ⍟ I've added these definitions: @@ -1764,7 +1764,7 @@ project/bob> add bob : Nat ``` -```ucm +``` ucm project/alice> merge /bob I merged project/bob into project/alice. @@ -1776,7 +1776,7 @@ project/alice> merge /bob type Foo = Bar | Baz ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1789,7 +1789,7 @@ type Foo = Bar | Baz type Foo ``` -```ucm +``` ucm project/main> add ⍟ I've added these definitions: @@ -1808,7 +1808,7 @@ project/main> branch topic boop = "boop" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1821,7 +1821,7 @@ boop = "boop" boop : Text ``` -```ucm +``` ucm project/topic> add ⍟ I've added these definitions: @@ -1833,7 +1833,7 @@ project/topic> add type Foo = Bar ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1847,7 +1847,7 @@ type Foo = Bar type Foo ``` -```ucm +``` ucm project/main> update Okay, I'm searching the branch for code that needs to be @@ -1856,7 +1856,7 @@ project/main> update Done. ``` -```ucm +``` ucm project/main> merge topic I merged project/topic into project/main. @@ -1883,7 +1883,7 @@ baz : Text baz = "lca" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1898,7 +1898,7 @@ baz = "lca" foo : Nat ``` -```ucm +``` ucm project/alice> add ⍟ I've added these definitions: @@ -1922,7 +1922,7 @@ baz : Text baz = "bob" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1936,7 +1936,7 @@ baz = "bob" baz : Text ``` -```ucm +``` ucm project/bob> update Okay, I'm searching the branch for code that needs to be @@ -1955,7 +1955,7 @@ baz : Text baz = "alice" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1970,7 +1970,7 @@ baz = "alice" foo : Nat ``` -```ucm +``` ucm project/alice> update Okay, I'm searching the branch for code that needs to be @@ -1986,7 +1986,7 @@ project/alice> update When we try to merge Bob into Alice, we should see both versions of `baz`, with Alice's unconflicted `foo` and `bar` in the underlying namespace. -```ucm +``` ucm project/alice> merge /bob I couldn't automatically merge project/bob into project/alice. @@ -2038,7 +2038,7 @@ Let's make three identical namespaces with different histories: a = 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -2051,7 +2051,7 @@ a = 1 a : ##Nat ``` -```ucm +``` ucm project/alice> add ⍟ I've added these definitions: @@ -2063,7 +2063,7 @@ project/alice> add b = 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -2076,7 +2076,7 @@ b = 2 b : ##Nat ``` -```ucm +``` ucm project/alice> add ⍟ I've added these definitions: @@ -2088,7 +2088,7 @@ project/alice> add b = 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -2096,7 +2096,7 @@ b = 2 file has been previously added to the codebase. ``` -```ucm +``` ucm project/bob> add ⍟ I've added these definitions: @@ -2108,7 +2108,7 @@ project/bob> add a = 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -2121,7 +2121,7 @@ a = 1 a : ##Nat ``` -```ucm +``` ucm project/bob> add ⍟ I've added these definitions: @@ -2134,7 +2134,7 @@ a = 1 b = 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -2142,7 +2142,7 @@ b = 2 file has been previously added to the codebase. ``` -```ucm +``` ucm project/carol> add ⍟ I've added these definitions: @@ -2193,7 +2193,7 @@ bar = foo + foo ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -2208,7 +2208,7 @@ bar = ignore : a -> () ``` -```ucm +``` ucm scratch/alice> add ⍟ I've added these definitions: @@ -2232,7 +2232,7 @@ bar = foo + foo + foo ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -2246,7 +2246,7 @@ bar = bar : Nat ``` -```ucm +``` ucm scratch/bob> update Okay, I'm searching the branch for code that needs to be @@ -2263,7 +2263,7 @@ foo : Nat foo = 19 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -2277,7 +2277,7 @@ foo = 19 foo : Nat ``` -```ucm +``` ucm scratch/alice> update Okay, I'm searching the branch for code that needs to be @@ -2290,7 +2290,7 @@ scratch/alice> update Done. ``` -```ucm +``` ucm scratch/alice> merge /bob I merged scratch/bob into scratch/alice. diff --git a/unison-src/transcripts/move-all.output.md b/unison-src/transcripts/move-all.output.md index cd68b319c..36116ad2b 100644 --- a/unison-src/transcripts/move-all.output.md +++ b/unison-src/transcripts/move-all.output.md @@ -11,7 +11,7 @@ Foo.termInA = 1 unique type Foo.T = T ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -27,7 +27,7 @@ unique type Foo.T = T Foo.termInA : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -43,7 +43,7 @@ Foo.termInA = 2 unique type Foo.T = T1 | T2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -59,7 +59,7 @@ unique type Foo.T = T1 | T2 (also named Foo) ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be @@ -70,7 +70,7 @@ scratch/main> update ``` Should be able to move the term, type, and namespace, including its types, terms, and sub-namespaces. -```ucm +``` ucm scratch/main> move Foo Bar Done. @@ -113,7 +113,7 @@ scratch/main> history Bar bonk = 5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -126,7 +126,7 @@ bonk = 5 bonk : Nat ``` -```ucm +``` ucm z/main> builtins.merge Done. @@ -153,7 +153,7 @@ z/main> ls bonk.zonk = 5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -167,7 +167,7 @@ bonk.zonk = 5 (also named zonk) ``` -```ucm +``` ucm a/main> builtins.merge Done. @@ -195,7 +195,7 @@ a/main> view zonk.zonk ``` ## Sad Path - No term, type, or namespace named src -```ucm +``` ucm scratch/main> move doesntexist foo ⚠️ diff --git a/unison-src/transcripts/move-namespace.output.md b/unison-src/transcripts/move-namespace.output.md index 57b010c0d..627edf4a9 100644 --- a/unison-src/transcripts/move-namespace.output.md +++ b/unison-src/transcripts/move-namespace.output.md @@ -8,7 +8,7 @@ I should be able to move the root into a sub-namespace foo = 1 ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -41,7 +41,7 @@ foo = 1 □ 1. #g97lh1m2v7 (start of history) ``` -```ucm +``` ucm .> ls .root.at.path 1. foo (##Nat) @@ -58,7 +58,7 @@ foo = 1 ``` I should be able to move a sub namespace *over* the root. -```ucm +``` ucm -- Should request confirmation .> move.namespace .root.at.path . @@ -85,7 +85,7 @@ I should be able to move a sub namespace *over* the root. □ 1. #08a6hgi6s4 (start of history) ``` -```ucm +``` ucm -- should be empty .> ls .root.at.path @@ -105,7 +105,7 @@ a.termInA = 1 unique type a.T = T ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -119,7 +119,7 @@ unique type a.T = T a.termInA : Nat ``` -```ucm +``` ucm scratch/happy> add ⍟ I've added these definitions: @@ -133,7 +133,7 @@ a.termInA = 2 unique type a.T = T1 | T2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -148,7 +148,7 @@ unique type a.T = T1 | T2 a.termInA : Nat ``` -```ucm +``` ucm scratch/happy> update Okay, I'm searching the branch for code that needs to be @@ -159,7 +159,7 @@ scratch/happy> update ``` Should be able to move the namespace, including its types, terms, and sub-namespaces. -```ucm +``` ucm scratch/happy> move.namespace a b Done. @@ -197,7 +197,7 @@ a.termInA = 1 b.termInB = 10 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -211,7 +211,7 @@ b.termInB = 10 b.termInB : Nat ``` -```ucm +``` ucm scratch/history> add ⍟ I've added these definitions: @@ -225,7 +225,7 @@ a.termInA = 2 b.termInB = 11 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -240,7 +240,7 @@ b.termInB = 11 b.termInB : Nat ``` -```ucm +``` ucm scratch/history> update Okay, I'm searching the branch for code that needs to be @@ -253,7 +253,7 @@ Deleting a namespace should not leave behind any history, if we move another to that location we expect the history to simply be the history of the moved namespace. -```ucm +``` ucm scratch/history> delete.namespace b Done. @@ -291,7 +291,7 @@ a.termInA = 1 b.termInB = 10 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -305,7 +305,7 @@ b.termInB = 10 b.termInB : Nat ``` -```ucm +``` ucm scratch/existing> add ⍟ I've added these definitions: @@ -319,7 +319,7 @@ a.termInA = 2 b.termInB = 11 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -334,7 +334,7 @@ b.termInB = 11 b.termInB : Nat ``` -```ucm +``` ucm scratch/existing> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/name-segment-escape.output.md b/unison-src/transcripts/name-segment-escape.output.md index f324018ff..4a5842274 100644 --- a/unison-src/transcripts/name-segment-escape.output.md +++ b/unison-src/transcripts/name-segment-escape.output.md @@ -1,6 +1,6 @@ You can use a keyword or reserved operator as a name segment if you surround it with backticks. -```ucm +``` ucm scratch/main> view `match` ⚠️ @@ -20,7 +20,7 @@ You can also use backticks to expand the set of valid symbols in a symboly name This allows you to spell `.` or `()` as name segments (which historically have appeared in the namespace). -```ucm +``` ucm scratch/main> view `.` ⚠️ diff --git a/unison-src/transcripts/name-selection.output.md b/unison-src/transcripts/name-selection.output.md index 0df0ba3a0..f76c6796f 100644 --- a/unison-src/transcripts/name-selection.output.md +++ b/unison-src/transcripts/name-selection.output.md @@ -12,7 +12,7 @@ a.aaa.but.more.segments = 0 + 1 Will add `a` and `b` to the codebase and give `b` a longer (in terms of segment length alias), and show that it isn't used when viewing `a`: -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -47,7 +47,7 @@ a3.d = a3.c + 10 a3.long.name.but.shortest.suffixification = 1 ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -84,7 +84,7 @@ At this point, `a3` is conflicted for symbols `c` and `d`, so those are depriori The original `a2` namespace has an unconflicted definition for `c` and `d`, but since there are multiple 'c's in scope, `a2.c` is chosen because although the suffixified version has fewer segments, its fully-qualified name has the fewest segments. -```ucm +``` ucm .> view a b c d a.a : Nat @@ -125,7 +125,7 @@ deeply.nested.num = 10 a = 10 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -140,7 +140,7 @@ a = 10 deeply.nested.term : Nat ``` -```ucm +``` ucm .biasing> add ⍟ I've added these definitions: @@ -166,7 +166,7 @@ Add another term with `num` suffix to force longer suffixification of `deeply.ne other.num = 20 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -179,7 +179,7 @@ other.num = 20 other.num : Nat ``` -```ucm +``` ucm .biasing> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/names.output.md b/unison-src/transcripts/names.output.md index 13d62fd7b..287782fa2 100644 --- a/unison-src/transcripts/names.output.md +++ b/unison-src/transcripts/names.output.md @@ -12,7 +12,7 @@ somewhere.z = 1 somewhere.y = 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -29,7 +29,7 @@ somewhere.y = 2 somewhere.z : ##Nat ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -43,7 +43,7 @@ somewhere.y = 2 ``` `names` searches relative to the current path. -```ucm +``` ucm -- We can search by suffix and find all definitions named 'x', and each of their aliases respectively. -- But we don't see somewhere.z which is has the same value but is out of our namespace .some> names x @@ -78,7 +78,7 @@ somewhere.y = 2 ``` `names.global` searches from the root, and absolutely qualifies results -```ucm +``` ucm -- We can search by suffix and find all definitions in the codebase named 'x', and each of their aliases respectively. .some> names.global x diff --git a/unison-src/transcripts/namespace-deletion-regression.output.md b/unison-src/transcripts/namespace-deletion-regression.output.md index 21e0866f7..1730897d3 100644 --- a/unison-src/transcripts/namespace-deletion-regression.output.md +++ b/unison-src/transcripts/namespace-deletion-regression.output.md @@ -7,7 +7,7 @@ If branch operations aren't performed in the correct order it's possible to end Previously the following sequence delete the current namespace unexpectedly 😬. -```ucm +``` ucm scratch/main> alias.term ##Nat.+ Nat.+ Done. diff --git a/unison-src/transcripts/namespace-dependencies.output.md b/unison-src/transcripts/namespace-dependencies.output.md index ae41b9518..80ea30e39 100644 --- a/unison-src/transcripts/namespace-dependencies.output.md +++ b/unison-src/transcripts/namespace-dependencies.output.md @@ -6,7 +6,7 @@ external.mynat = 1 mynamespace.dependsOnText = const external.mynat 10 ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/numbered-args.output.md b/unison-src/transcripts/numbered-args.output.md index ba6016b96..0567bcac3 100644 --- a/unison-src/transcripts/numbered-args.output.md +++ b/unison-src/transcripts/numbered-args.output.md @@ -11,7 +11,7 @@ quux = "quux" corge = "corge" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -29,7 +29,7 @@ corge = "corge" qux : Text ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -45,7 +45,7 @@ scratch/main> add We can get the list of things in the namespace, and UCM will give us a numbered list: -```ucm +``` ucm scratch/main> find 1. bar : Text @@ -60,7 +60,7 @@ scratch/main> find ``` We can ask to `view` the second element of this list: -```ucm +``` ucm scratch/main> find 1. bar : Text @@ -80,7 +80,7 @@ scratch/main> view 2 ``` And we can `view` multiple elements by separating with spaces: -```ucm +``` ucm scratch/main> find 1. bar : Text @@ -106,7 +106,7 @@ scratch/main> view 2 3 5 ``` We can also ask for a range: -```ucm +``` ucm scratch/main> find 1. bar : Text @@ -132,7 +132,7 @@ scratch/main> view 2-4 ``` And we can ask for multiple ranges and use mix of ranges and numbers: -```ucm +``` ucm scratch/main> find 1. bar : Text diff --git a/unison-src/transcripts/old-fold-right.output.md b/unison-src/transcripts/old-fold-right.output.md index f054ba959..a74a317a4 100644 --- a/unison-src/transcripts/old-fold-right.output.md +++ b/unison-src/transcripts/old-fold-right.output.md @@ -11,7 +11,7 @@ pecan = 'let oldRight f la ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/pattern-match-coverage.output.md b/unison-src/transcripts/pattern-match-coverage.output.md index ea249e9f7..575c35cab 100644 --- a/unison-src/transcripts/pattern-match-coverage.output.md +++ b/unison-src/transcripts/pattern-match-coverage.output.md @@ -10,7 +10,7 @@ test = cases A -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -36,7 +36,7 @@ test = cases (B, None) -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -65,7 +65,7 @@ test = cases _ -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -86,7 +86,7 @@ test = cases (A, Some A) -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -108,7 +108,7 @@ test = cases Some None -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -132,7 +132,7 @@ test0 = cases _ -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -151,7 +151,7 @@ test = cases Some _ -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -170,7 +170,7 @@ test = cases () | false -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -191,7 +191,7 @@ test = cases | isEven x -> x ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -217,7 +217,7 @@ test = cases | otherwise -> 0 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -244,7 +244,7 @@ test = cases Some None -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -268,7 +268,7 @@ test = cases Some (Some A) -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -297,7 +297,7 @@ test = cases 0 -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -318,7 +318,7 @@ test = cases true -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -342,7 +342,7 @@ test = cases _ -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -364,7 +364,7 @@ test = cases false -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -389,7 +389,7 @@ test = cases _ -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -408,7 +408,7 @@ test = cases _ -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -428,7 +428,7 @@ test = cases x +: xs -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -449,7 +449,7 @@ test = cases [] -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -468,7 +468,7 @@ test = cases x +: xs -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -487,7 +487,7 @@ test = cases xs :+ x -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -507,7 +507,7 @@ test = cases [] -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -528,7 +528,7 @@ test = cases x0 +: [] -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -554,7 +554,7 @@ test = cases [] -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -586,7 +586,7 @@ test = cases true +: xs -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -611,7 +611,7 @@ test = cases _ -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -636,7 +636,7 @@ test = cases _ -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -655,7 +655,7 @@ unit2t = cases () -> A ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -669,7 +669,7 @@ unit2t = cases unit2t : 'T ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -692,7 +692,7 @@ witht = match unit2t () with x -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -712,7 +712,7 @@ evil : Unit -> V evil = bug "" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -726,7 +726,7 @@ evil = bug "" evil : 'V ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -741,7 +741,7 @@ withV = match evil () with x -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -754,7 +754,7 @@ withV = match evil () with unique type SomeType = A ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -767,7 +767,7 @@ unique type SomeType = A type SomeType ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -782,7 +782,7 @@ get x = match x with R y -> y ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -800,7 +800,7 @@ get x = match x with unique type R = { someType : SomeType } ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -831,7 +831,7 @@ result f = handle !f with cases { abort -> _ } -> bug "aborted" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -858,7 +858,7 @@ result f = handle !f with cases { abort -> _ } -> bug "aborted" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -889,7 +889,7 @@ result f = handle !f with impl ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -919,7 +919,7 @@ handleMulti c = handle !c with impl [] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -947,7 +947,7 @@ result f = handle !f with cases { abort -> _ } -> bug "aborted" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -974,7 +974,7 @@ result f = handle !f with cases { abort -> _ } -> bug "aborted" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1000,7 +1000,7 @@ result f = handle !f with cases { give A -> resume } -> result resume ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1030,7 +1030,7 @@ handleMulti c = handle !c with impl [] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1059,7 +1059,7 @@ result f = handle !f with cases { give A -> resume } -> result resume ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1083,7 +1083,7 @@ result f = handle !f with cases { abortWithMessage msg -> _ } -> abortWithMessage ("aborting: " ++ msg) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1111,7 +1111,7 @@ result f = handle !f with impl ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1139,7 +1139,7 @@ result f = handle !f with cases { abortWithMessage msg -> _ } -> abortWithMessage ("aborting: " ++ msg) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1179,7 +1179,7 @@ result f = handle !f with impl ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1208,7 +1208,7 @@ result f = handle !f with impl ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1236,7 +1236,7 @@ result f = handle !f with impl ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1265,7 +1265,7 @@ result f = handle !f with impl ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1295,7 +1295,7 @@ result f = handle !f with impl ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -1323,7 +1323,7 @@ result f = handle !f with impl ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/pattern-pretty-print-2345.output.md b/unison-src/transcripts/pattern-pretty-print-2345.output.md index 15ebf8740..711297412 100644 --- a/unison-src/transcripts/pattern-pretty-print-2345.output.md +++ b/unison-src/transcripts/pattern-pretty-print-2345.output.md @@ -59,7 +59,7 @@ doc = cases _ -> () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -86,7 +86,7 @@ doc = cases tremulous : (Nat, Nat) -> () ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/patternMatchTls.output.md b/unison-src/transcripts/patternMatchTls.output.md index 7d207ef37..1e6e9ced2 100644 --- a/unison-src/transcripts/patternMatchTls.output.md +++ b/unison-src/transcripts/patternMatchTls.output.md @@ -20,7 +20,7 @@ assertRight = cases Left _ -> bug "expected a right but got a left" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -34,7 +34,7 @@ assertRight = cases frank : '{IO} () ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/patterns.output.md b/unison-src/transcripts/patterns.output.md index 054c9224e..f68423848 100644 --- a/unison-src/transcripts/patterns.output.md +++ b/unison-src/transcripts/patterns.output.md @@ -7,7 +7,7 @@ p1 = join [literal "blue", literal "frog"] > Pattern.run (many.corrected p1) "bluefrogbluegoat" ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/propagate.output.md b/unison-src/transcripts/propagate.output.md index 036681f1b..14da5ae23 100644 --- a/unison-src/transcripts/propagate.output.md +++ b/unison-src/transcripts/propagate.output.md @@ -9,7 +9,7 @@ fooToInt : Foo -> Int fooToInt _ = +42 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -25,7 +25,7 @@ fooToInt _ = +42 ``` And then we add it. -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -58,7 +58,7 @@ Then if we change the type `Foo`... unique type Foo = Foo | Bar ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -74,7 +74,7 @@ unique type Foo = Foo | Bar ``` and update the codebase to use the new type `Foo`... -```ucm +``` ucm scratch/main> update.old ⍟ I've updated these names to your new definition: @@ -84,7 +84,7 @@ scratch/main> update.old ``` ... it should automatically propagate the type to `fooToInt`. -```ucm +``` ucm scratch/main> view fooToInt fooToInt : Foo -> Int @@ -104,7 +104,7 @@ preserve.otherTerm : Optional baz -> Optional baz preserve.otherTerm y = someTerm y ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -120,7 +120,7 @@ preserve.otherTerm y = someTerm y ``` Add that to the codebase: -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -136,7 +136,7 @@ preserve.someTerm : Optional x -> Optional x preserve.someTerm _ = None ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -152,7 +152,7 @@ preserve.someTerm _ = None ``` Update... -```ucm +``` ucm scratch/main> update.old ⍟ I've updated these names to your new definition: @@ -163,7 +163,7 @@ scratch/main> update.old Now the type of `someTerm` should be `Optional x -> Optional x` and the type of `otherTerm` should remain the same. -```ucm +``` ucm scratch/main> view preserve.someTerm preserve.someTerm : Optional x -> Optional x @@ -179,7 +179,7 @@ scratch/main> view preserve.otherTerm Cleaning up a bit... -```ucm +``` ucm ☝️ The namespace .subpath.lib is empty. .subpath.lib> builtins.merge @@ -197,7 +197,7 @@ one.otherTerm : Optional baz -> Optional baz one.otherTerm y = someTerm y ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -213,7 +213,7 @@ one.otherTerm y = someTerm y ``` We'll make two copies of this namespace. -```ucm +``` ucm .subpath> add ⍟ I've added these definitions: @@ -233,7 +233,7 @@ someTerm : Optional x -> Optional x someTerm _ = None ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -248,7 +248,7 @@ someTerm _ = None ``` ... in one of the namespaces... -```ucm +``` ucm .subpath.one> update.old ⍟ I've updated these names to your new definition: @@ -258,7 +258,7 @@ someTerm _ = None ``` The other namespace should be left alone. -```ucm +``` ucm .subpath> view two.someTerm two.someTerm : Optional foo -> Optional foo diff --git a/unison-src/transcripts/pull-errors.output.md b/unison-src/transcripts/pull-errors.output.md index 063c439dd..38afde71c 100644 --- a/unison-src/transcripts/pull-errors.output.md +++ b/unison-src/transcripts/pull-errors.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm test/main> pull @aryairani/test-almost-empty/main lib.base_latest The use of `pull` to install libraries is now deprecated. diff --git a/unison-src/transcripts/records.output.md b/unison-src/transcripts/records.output.md index 8d2be7417..3e3d66245 100644 --- a/unison-src/transcripts/records.output.md +++ b/unison-src/transcripts/records.output.md @@ -6,7 +6,7 @@ Ensure that Records keep their syntax after being added to the codebase unique type Record1 = { a : Text } ``` -```ucm +``` ucm scratch/main> view Record1 type Record1 = { a : Text } @@ -18,7 +18,7 @@ scratch/main> view Record1 unique type Record2 = { a : Text, b : Int } ``` -```ucm +``` ucm scratch/main> view Record2 type Record2 = { a : Text, b : Int } @@ -30,7 +30,7 @@ scratch/main> view Record2 unique type Record3 = { a : Text, b : Int, c : Nat } ``` -```ucm +``` ucm scratch/main> view Record3 type Record3 = { a : Text, b : Int, c : Nat } @@ -50,7 +50,7 @@ unique type Record4 = } ``` -```ucm +``` ucm scratch/main> view Record4 type Record4 @@ -91,7 +91,7 @@ unique type Record5 = { } ``` -```ucm +``` ucm scratch/main> view Record5 type Record5 @@ -130,7 +130,7 @@ unique type RecordWithUserType = { a : Text, b : Record4, c : UserType } If you `view` or `edit` it, it *should* be treated as a record type, but it does not (which is a bug) -```ucm +``` ucm scratch/main> view RecordWithUserType type RecordWithUserType @@ -148,7 +148,7 @@ unique type Record5 = } ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/reflog.output.md b/unison-src/transcripts/reflog.output.md index a608b04a9..c78f00a83 100644 --- a/unison-src/transcripts/reflog.output.md +++ b/unison-src/transcripts/reflog.output.md @@ -5,7 +5,7 @@ for the `reflog` command to display: x = 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -18,7 +18,7 @@ x = 1 x : Nat ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -30,7 +30,7 @@ x = 1 y = 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -43,7 +43,7 @@ y = 2 y : Nat ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -56,7 +56,7 @@ y = 2 y = 2 ``` -```ucm +``` ucm .> reflog Here is a log of the root namespace hashes, starting with the @@ -82,13 +82,13 @@ y = 2 ``` If we `reset-root` to its previous value, `y` disappears. -```ucm +``` ucm .> reset-root 2 Done. ``` -```ucm +``` ucm .> view y ⚠️ diff --git a/unison-src/transcripts/release-draft-command.output.md b/unison-src/transcripts/release-draft-command.output.md index 58077a37e..3354e764f 100644 --- a/unison-src/transcripts/release-draft-command.output.md +++ b/unison-src/transcripts/release-draft-command.output.md @@ -6,7 +6,7 @@ Some setup: someterm = 18 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -19,7 +19,7 @@ someterm = 18 someterm : Nat ``` -```ucm +``` ucm foo/main> add ⍟ I've added these definitions: @@ -31,7 +31,7 @@ Now, the `release.draft` demo: `release.draft` accepts a single semver argument. -```ucm +``` ucm foo/main> release.draft 1.2.3 😎 Great! I've created a draft release for you at @@ -51,7 +51,7 @@ foo/main> release.draft 1.2.3 ``` It's an error to try to create a `releases/drafts/x.y.z` branch that already exists. -```ucm +``` ucm foo/main> release.draft 1.2.3 foo/releases/drafts/1.2.3 already exists. You can switch to it diff --git a/unison-src/transcripts/reset.output.md b/unison-src/transcripts/reset.output.md index 1858250ab..8fa6362a9 100644 --- a/unison-src/transcripts/reset.output.md +++ b/unison-src/transcripts/reset.output.md @@ -4,7 +4,7 @@ a = 5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -17,7 +17,7 @@ a = 5 a : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -55,7 +55,7 @@ scratch/main> history foo.a = 5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -68,7 +68,7 @@ foo.a = 5 foo.a : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -103,7 +103,7 @@ scratch/main> ls foo.foo ``` # reset branch -```ucm +``` ucm foo/main> history ☝️ The namespace is empty. @@ -113,7 +113,7 @@ foo/main> history a = 5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -126,7 +126,7 @@ a = 5 a : ##Nat ``` -```ucm +``` ucm foo/main> add ⍟ I've added these definitions: @@ -154,7 +154,7 @@ foo/main> history a = 3 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -168,7 +168,7 @@ a = 3 a : ##Nat ``` -```ucm +``` ucm foo/main> update Okay, I'm searching the branch for code that needs to be @@ -198,7 +198,7 @@ foo/main> history main.a = 3 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -211,7 +211,7 @@ main.a = 3 main.a : ##Nat ``` -```ucm +``` ucm foo/main> add ⍟ I've added these definitions: @@ -250,7 +250,7 @@ foo/main> reset 2 main main.a = 3 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -258,7 +258,7 @@ main.a = 3 file has been previously added to the codebase. ``` -```ucm +``` ucm foo/main> switch /topic foo/topic> add diff --git a/unison-src/transcripts/resolution-failures.output.md b/unison-src/transcripts/resolution-failures.output.md index 262f6f744..d30deb424 100644 --- a/unison-src/transcripts/resolution-failures.output.md +++ b/unison-src/transcripts/resolution-failures.output.md @@ -14,7 +14,7 @@ one.ambiguousTerm = "term one" two.ambiguousTerm = "term two" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -30,7 +30,7 @@ two.ambiguousTerm = "term two" two.ambiguousTerm : ##Text ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -65,7 +65,7 @@ separateAmbiguousTypeUsage : AmbiguousType -> () separateAmbiguousTypeUsage _ = () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -100,7 +100,7 @@ but expect it to eventually be handled by the above machinery. useAmbiguousTerm = ambiguousTerm ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/rsa.output.md b/unison-src/transcripts/rsa.output.md index a5994b24b..98e735c2e 100644 --- a/unison-src/transcripts/rsa.output.md +++ b/unison-src/transcripts/rsa.output.md @@ -30,7 +30,7 @@ sigKo = match signature with > sigKo ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/scope-ref.output.md b/unison-src/transcripts/scope-ref.output.md index 131918662..c356bc531 100644 --- a/unison-src/transcripts/scope-ref.output.md +++ b/unison-src/transcripts/scope-ref.output.md @@ -13,7 +13,7 @@ test = Scope.run 'let > test ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/suffixes.output.md b/unison-src/transcripts/suffixes.output.md index 5752f2918..43aa678ef 100644 --- a/unison-src/transcripts/suffixes.output.md +++ b/unison-src/transcripts/suffixes.output.md @@ -15,7 +15,7 @@ optional.isNone = cases This also affects commands like find. Notice lack of qualified names in output: -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -35,7 +35,7 @@ scratch/main> find take ``` The `view` and `display` commands also benefit from this: -```ucm +``` ucm scratch/main> view List.drop builtin builtin.List.drop : builtin.Nat -> [a] -> [a] @@ -49,7 +49,7 @@ In the signature, we don't see `base.Nat`, just `Nat`. The full declaration name Type-based search also benefits from this, we can just say `Nat` rather than `.base.Nat`: -```ucm +``` ucm scratch/main> find : Nat -> [a] -> [a] 1. builtin.List.drop : Nat -> [a] -> [a] @@ -68,7 +68,7 @@ lib.distributed.baz.qux = "direct dependency 2" lib.distributed.lib.baz.qux = "indirect dependency" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -84,7 +84,7 @@ lib.distributed.lib.baz.qux = "indirect dependency" lib.distributed.lib.baz.qux : Text ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -99,7 +99,7 @@ scratch/main> add > abra.cadabra ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -121,7 +121,7 @@ scratch/main> add > baz.qux ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -137,7 +137,7 @@ scratch/main> add "direct dependency 2" ``` -```ucm +``` ucm scratch/main> view abra.cadabra cool.abra.cadabra : Text @@ -154,7 +154,7 @@ scratch/main> view baz.qux ``` Note that we can always still view indirect dependencies by using more name segments: -```ucm +``` ucm scratch/main> view distributed.abra.cadabra lib.distributed.abra.cadabra : Text @@ -180,7 +180,7 @@ foo.a = 23 bar = 100 ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -207,7 +207,7 @@ fn = cases _ -> todo "hmm" ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/sum-type-update-conflicts.output.md b/unison-src/transcripts/sum-type-update-conflicts.output.md index f28ec5dd4..ba70632b8 100644 --- a/unison-src/transcripts/sum-type-update-conflicts.output.md +++ b/unison-src/transcripts/sum-type-update-conflicts.output.md @@ -8,7 +8,7 @@ First we add a sum-type to the codebase. structural type X = x ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -22,7 +22,7 @@ structural type X = x (also named lib.builtins.Unit) ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -43,7 +43,7 @@ X.x = "some text that's not in the codebase" dependsOnX = Text.size X.x ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -66,7 +66,7 @@ dependsOnX = Text.size X.x This update should succeed since the conflicted constructor is removed in the same update that the new term is being added. -```ucm +``` ucm scratch/main> update.old ⍟ I've added these definitions: diff --git a/unison-src/transcripts/switch-command.output.md b/unison-src/transcripts/switch-command.output.md index f00a15723..96778f99d 100644 --- a/unison-src/transcripts/switch-command.output.md +++ b/unison-src/transcripts/switch-command.output.md @@ -6,7 +6,7 @@ Setup stuff. someterm = 18 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -19,7 +19,7 @@ someterm = 18 someterm : Nat ``` -```ucm +``` ucm foo/main> add ⍟ I've added these definitions: @@ -45,7 +45,7 @@ Now, the demo. When unambiguous, `switch` switches to either a project or a bran the current project can be preceded by a forward slash (which makes it unambiguous). A project can be followed by a forward slash (which makes it unambiguous). -```ucm +``` ucm scratch/main> switch foo scratch/main> switch foo/topic @@ -59,7 +59,7 @@ foo/main> switch bar/ ``` It's an error to try to switch to something ambiguous. -```ucm +``` ucm foo/main> switch bar I'm not sure if you wanted to switch to the branch foo/bar or @@ -73,20 +73,20 @@ foo/main> switch bar ``` It's an error to try to switch to something that doesn't exist, of course. -```ucm +``` ucm scratch/main> switch foo/no-such-branch foo/no-such-branch does not exist. ``` -```ucm +``` ucm scratch/main> switch no-such-project Neither project no-such-project nor branch /no-such-project exists. ``` -```ucm +``` ucm foo/main> switch no-such-project-or-branch Neither project no-such-project-or-branch nor branch diff --git a/unison-src/transcripts/tab-completion.output.md b/unison-src/transcripts/tab-completion.output.md index 86a7b552e..98c26e77f 100644 --- a/unison-src/transcripts/tab-completion.output.md +++ b/unison-src/transcripts/tab-completion.output.md @@ -4,7 +4,7 @@ Test that tab completion works as expected. ## Tab Complete Command Names -```ucm +``` ucm scratch/main> debug.tab-complete vi view @@ -34,7 +34,7 @@ othernamespace.someName = 4 unique type subnamespace.AType = A | B ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -51,7 +51,7 @@ unique type subnamespace.AType = A | B subnamespace2.thing : ##Nat ``` -```ucm +``` ucm -- Should tab complete namespaces since they may contain terms/types scratch/main> debug.tab-complete view sub @@ -93,7 +93,7 @@ scratch/main> debug.tab-complete view subnamespace.someOther absolute.term = "absolute" ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -108,7 +108,7 @@ absolute.term = "absolute" ``` ## Tab complete namespaces -```ucm +``` ucm -- Should tab complete namespaces scratch/main> debug.tab-complete find-in sub @@ -149,7 +149,7 @@ add : a -> a add b = b ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -163,7 +163,7 @@ add b = b add : a -> a ``` -```ucm +``` ucm scratch/main> update.old ⍟ I've added these definitions: @@ -183,7 +183,7 @@ scratch/main> debug.tab-complete delete.term add ``` ## Tab complete projects and branches -```ucm +``` ucm myproject/main> branch mybranch Done. I've created the mybranch branch based off of main. @@ -206,7 +206,7 @@ Commands which complete namespaces OR branches should list both mybranchsubnamespace.term = 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -219,7 +219,7 @@ mybranchsubnamespace.term = 1 mybranchsubnamespace.term : ##Nat ``` -```ucm +``` ucm myproject/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/test-command.output.md b/unison-src/transcripts/test-command.output.md index 4182b223c..f603bc3f1 100644 --- a/unison-src/transcripts/test-command.output.md +++ b/unison-src/transcripts/test-command.output.md @@ -10,7 +10,7 @@ foo.test2 : [Result] foo.test2 = [Ok "test2"] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -24,7 +24,7 @@ foo.test2 = [Ok "test2"] test1 : [Result] ``` -```ucm +``` ucm scratch/main> test ✅ @@ -49,7 +49,7 @@ scratch/main> test ``` Tests should be cached if unchanged. -```ucm +``` ucm scratch/main> test Cached test results (`help testcache` to learn more) @@ -69,7 +69,7 @@ lib.dep.testInLib : [Result] lib.dep.testInLib = [Ok "testInLib"] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -82,7 +82,7 @@ lib.dep.testInLib = [Ok "testInLib"] lib.dep.testInLib : [Result] ``` -```ucm +``` ucm scratch/main> test Cached test results (`help testcache` to learn more) @@ -121,7 +121,7 @@ scratch/main> test.all ``` `test` WILL run tests within `lib` if specified explicitly. -```ucm +``` ucm scratch/main> test lib.dep Cached test results (`help testcache` to learn more) @@ -135,7 +135,7 @@ scratch/main> test lib.dep ``` `test` can be given a relative path, in which case it will only run tests found somewhere in that namespace. -```ucm +``` ucm scratch/main> test foo Cached test results (`help testcache` to learn more) diff --git a/unison-src/transcripts/text-literals.output.md b/unison-src/transcripts/text-literals.output.md index f9d4311f2..b023a3d06 100644 --- a/unison-src/transcripts/text-literals.output.md +++ b/unison-src/transcripts/text-literals.output.md @@ -31,7 +31,7 @@ lit2 = """" > Some lit2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -85,7 +85,7 @@ lit2 = """" "This is a raw text literal, indented.\nIt can start with 3 or more \",\nand is terminated by the same number of quotes.\nNothing is escaped. \\n\n\nThis doesn't terminate the literal - \"\"\"" ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/todo-bug-builtins.output.md b/unison-src/transcripts/todo-bug-builtins.output.md index 104d6bf86..932353888 100644 --- a/unison-src/transcripts/todo-bug-builtins.output.md +++ b/unison-src/transcripts/todo-bug-builtins.output.md @@ -6,7 +6,7 @@ > todo "implement me later" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -33,7 +33,7 @@ > bug "there's a bug in my code" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -64,7 +64,7 @@ complicatedMathStuff x = todo "Come back and to something with x here" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -87,7 +87,7 @@ test = match true with false -> bug "Wow, that's unexpected" ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/todo.output.md b/unison-src/transcripts/todo.output.md index 434e7a43d..c29c70e12 100644 --- a/unison-src/transcripts/todo.output.md +++ b/unison-src/transcripts/todo.output.md @@ -2,7 +2,7 @@ When there's nothing to do, `todo` says this: -```ucm +``` ucm project/main> todo You have no pending todo items. Good work! ✅ @@ -24,7 +24,7 @@ bar : Nat bar = foo + foo ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -38,7 +38,7 @@ bar = foo + foo foo : Nat ``` -```ucm +``` ucm project/main> add ⍟ I've added these definitions: @@ -63,7 +63,7 @@ foo.bar = 15 baz = foo.bar + foo.bar ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -77,7 +77,7 @@ baz = foo.bar + foo.bar foo.bar : Nat ``` -```ucm +``` ucm project/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/top-level-exceptions.output.md b/unison-src/transcripts/top-level-exceptions.output.md index 4a889dedc..ded6bdda0 100644 --- a/unison-src/transcripts/top-level-exceptions.output.md +++ b/unison-src/transcripts/top-level-exceptions.output.md @@ -2,7 +2,7 @@ A simple transcript to test the use of exceptions that bubble to the top level. FYI, here are the `Exception` and `Failure` types: -```ucm +``` ucm scratch/main> view Exception Failure structural ability builtin.Exception where @@ -24,7 +24,7 @@ mytest : '{IO, Exception} [Test.Result] mytest _ = [Ok "Great"] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -38,7 +38,7 @@ mytest _ = [Ok "Great"] mytest : '{IO, Exception} [Result] ``` -```ucm +``` ucm scratch/main> run main () @@ -73,7 +73,7 @@ error msg a = unique type RuntimeError = ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -88,7 +88,7 @@ unique type RuntimeError = main2 : '{Exception} r ``` -```ucm +``` ucm scratch/main> run main2 💔💥 diff --git a/unison-src/transcripts/transcript-parser-commands.output.md b/unison-src/transcripts/transcript-parser-commands.output.md index 842ea130c..f6971c59e 100644 --- a/unison-src/transcripts/transcript-parser-commands.output.md +++ b/unison-src/transcripts/transcript-parser-commands.output.md @@ -6,7 +6,7 @@ The transcript parser is meant to parse `ucm` and `unison` blocks. x = 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -19,7 +19,7 @@ x = 1 x : Nat ``` -```ucm +``` ucm .> add ⍟ I've added these definitions: @@ -35,7 +35,7 @@ z ``` -```ucm +``` ucm .> delete foo ⚠️ @@ -44,7 +44,7 @@ z foo ``` -```ucm +``` ucm .> delete lineToken.call ⚠️ diff --git a/unison-src/transcripts/type-deps.output.md b/unison-src/transcripts/type-deps.output.md index 24ab0e288..fb04cc34c 100644 --- a/unison-src/transcripts/type-deps.output.md +++ b/unison-src/transcripts/type-deps.output.md @@ -15,7 +15,7 @@ structural type Z = Z Y structural type Y = Y Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -36,7 +36,7 @@ structural type Y = Y Nat ``` Adding should fail for BOTH definitions, `Y` needs an update and `Z` is blocked by `Y`. -```ucm +``` ucm scratch/main> add x These definitions failed: diff --git a/unison-src/transcripts/type-modifier-are-optional.output.md b/unison-src/transcripts/type-modifier-are-optional.output.md index 34c562d15..6cd6812da 100644 --- a/unison-src/transcripts/type-modifier-are-optional.output.md +++ b/unison-src/transcripts/type-modifier-are-optional.output.md @@ -12,7 +12,7 @@ unique ability MyAbilityU where const : a structural ability MyAbilityS where const : a ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/unique-type-churn.output.md b/unison-src/transcripts/unique-type-churn.output.md index f633292e8..ea0058643 100644 --- a/unison-src/transcripts/unique-type-churn.output.md +++ b/unison-src/transcripts/unique-type-churn.output.md @@ -8,7 +8,7 @@ unique type B = B C unique type C = C B ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -23,7 +23,7 @@ unique type C = C B type C ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -40,7 +40,7 @@ unique type B = B C unique type C = C B ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -50,7 +50,7 @@ unique type C = C B ``` If the name stays the same, the churn is even prevented if the type is updated and then reverted to the original form. -```ucm +``` ucm scratch/main> names A Type @@ -68,7 +68,7 @@ scratch/main> names A unique type A = A () ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -82,7 +82,7 @@ unique type A = A () type A ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be @@ -107,7 +107,7 @@ scratch/main> names A unique type A = A ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -123,7 +123,7 @@ unique type A = A ``` Note that `A` is back to its original hash. -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/unitnamespace.output.md b/unison-src/transcripts/unitnamespace.output.md index 9bc427434..0a4833afe 100644 --- a/unison-src/transcripts/unitnamespace.output.md +++ b/unison-src/transcripts/unitnamespace.output.md @@ -2,7 +2,7 @@ `()`.foo = "bar" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -15,7 +15,7 @@ `()`.foo : ##Text ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: diff --git a/unison-src/transcripts/universal-cmp.output.md b/unison-src/transcripts/universal-cmp.output.md index af4bced3e..5b8913fff 100644 --- a/unison-src/transcripts/universal-cmp.output.md +++ b/unison-src/transcripts/universal-cmp.output.md @@ -10,7 +10,7 @@ threadEyeDeez _ = (t1 == t2, t1 < t2) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -24,7 +24,7 @@ threadEyeDeez _ = threadEyeDeez : ∀ _. _ ->{IO} (Boolean, Boolean) ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -44,7 +44,7 @@ scratch/main> run threadEyeDeez > termLink threadEyeDeez == termLink threadEyeDeez ``` -```ucm +``` ucm Loading changes detected in scratch.u. diff --git a/unison-src/transcripts/unsafe-coerce.output.md b/unison-src/transcripts/unsafe-coerce.output.md index 73ed1c625..20380cb69 100644 --- a/unison-src/transcripts/unsafe-coerce.output.md +++ b/unison-src/transcripts/unsafe-coerce.output.md @@ -11,7 +11,7 @@ main _ = if n == 5 then [Ok ""] else [Fail ""] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -26,7 +26,7 @@ main _ = main : '{IO, Exception} [Result] ``` -```ucm +``` ucm scratch/main> find unsafe.coerceAbilities 1. builtin.unsafe.coerceAbilities : (a ->{e1} b) -> a -> b diff --git a/unison-src/transcripts/update-ignores-lib-namespace.output.md b/unison-src/transcripts/update-ignores-lib-namespace.output.md index ffc4147d0..dc03596d0 100644 --- a/unison-src/transcripts/update-ignores-lib-namespace.output.md +++ b/unison-src/transcripts/update-ignores-lib-namespace.output.md @@ -7,7 +7,7 @@ foo = 100 lib.foo = 100 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -21,7 +21,7 @@ lib.foo = 100 lib.foo : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -34,7 +34,7 @@ scratch/main> add foo = 200 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -49,7 +49,7 @@ foo = 200 (The old definition is also named lib.foo.) ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-on-conflict.output.md b/unison-src/transcripts/update-on-conflict.output.md index 8d05b394f..373d3ac22 100644 --- a/unison-src/transcripts/update-on-conflict.output.md +++ b/unison-src/transcripts/update-on-conflict.output.md @@ -7,7 +7,7 @@ x = 1 temp = 2 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -21,7 +21,7 @@ temp = 2 x : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -42,7 +42,7 @@ scratch/main> delete.term temp x = 3 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -56,7 +56,7 @@ x = 3 x : Nat ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-suffixifies-properly.output.md b/unison-src/transcripts/update-suffixifies-properly.output.md index a2a938fea..b76176388 100644 --- a/unison-src/transcripts/update-suffixifies-properly.output.md +++ b/unison-src/transcripts/update-suffixifies-properly.output.md @@ -7,7 +7,7 @@ d.y.y.y.y = foo + 10 bar = a.x.x.x.x + c.y.y.y.y ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -25,7 +25,7 @@ bar = a.x.x.x.x + c.y.y.y.y foo : Nat ``` -```ucm +``` ucm myproject/main> add ⍟ I've added these definitions: @@ -42,7 +42,7 @@ myproject/main> add foo = +30 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -56,7 +56,7 @@ foo = +30 foo : Int ``` -```ucm +``` ucm myproject/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-term-aliases-in-different-ways.output.md b/unison-src/transcripts/update-term-aliases-in-different-ways.output.md index 3d16a9254..5b0e7bf65 100644 --- a/unison-src/transcripts/update-term-aliases-in-different-ways.output.md +++ b/unison-src/transcripts/update-term-aliases-in-different-ways.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -12,7 +12,7 @@ bar : Nat bar = 5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -26,7 +26,7 @@ bar = 5 foo : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -43,7 +43,7 @@ bar : Nat bar = 7 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -60,7 +60,7 @@ bar = 7 (The old definition is also named bar.) ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-term-to-different-type.output.md b/unison-src/transcripts/update-term-to-different-type.output.md index a525811da..c1f65aaca 100644 --- a/unison-src/transcripts/update-term-to-different-type.output.md +++ b/unison-src/transcripts/update-term-to-different-type.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -9,7 +9,7 @@ foo : Nat foo = 5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -22,7 +22,7 @@ foo = 5 foo : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -35,7 +35,7 @@ foo : Int foo = +5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -49,7 +49,7 @@ foo = +5 foo : Int ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-term-with-alias.output.md b/unison-src/transcripts/update-term-with-alias.output.md index 03124e794..b0fbeab2a 100644 --- a/unison-src/transcripts/update-term-with-alias.output.md +++ b/unison-src/transcripts/update-term-with-alias.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -12,7 +12,7 @@ bar : Nat bar = 5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -26,7 +26,7 @@ bar = 5 foo : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -40,7 +40,7 @@ foo : Nat foo = 6 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -55,7 +55,7 @@ foo = 6 (The old definition is also named bar.) ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-term-with-dependent-to-different-type.output.md b/unison-src/transcripts/update-term-with-dependent-to-different-type.output.md index aef8fcb1e..02eeabcfc 100644 --- a/unison-src/transcripts/update-term-with-dependent-to-different-type.output.md +++ b/unison-src/transcripts/update-term-with-dependent-to-different-type.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -12,7 +12,7 @@ bar : Nat bar = foo + 10 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -26,7 +26,7 @@ bar = foo + 10 foo : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -40,7 +40,7 @@ foo : Int foo = +5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -54,7 +54,7 @@ foo = +5 foo : Int ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-term-with-dependent.output.md b/unison-src/transcripts/update-term-with-dependent.output.md index 79aee87f3..42ae8158f 100644 --- a/unison-src/transcripts/update-term-with-dependent.output.md +++ b/unison-src/transcripts/update-term-with-dependent.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -12,7 +12,7 @@ bar : Nat bar = foo + 10 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -26,7 +26,7 @@ bar = foo + 10 foo : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -40,7 +40,7 @@ foo : Nat foo = 6 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -54,7 +54,7 @@ foo = 6 foo : Nat ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-term.output.md b/unison-src/transcripts/update-term.output.md index 982c3b23a..54abb8e06 100644 --- a/unison-src/transcripts/update-term.output.md +++ b/unison-src/transcripts/update-term.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -9,7 +9,7 @@ foo : Nat foo = 5 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -22,7 +22,7 @@ foo = 5 foo : Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -35,7 +35,7 @@ foo : Nat foo = 6 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -49,7 +49,7 @@ foo = 6 foo : Nat ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-test-to-non-test.output.md b/unison-src/transcripts/update-test-to-non-test.output.md index fc9363d5a..5275b97eb 100644 --- a/unison-src/transcripts/update-test-to-non-test.output.md +++ b/unison-src/transcripts/update-test-to-non-test.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.merge Done. @@ -8,7 +8,7 @@ scratch/main> builtins.merge test> foo = [] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -29,7 +29,7 @@ test> foo = [] ``` After adding the test `foo`, we expect `view` to render it like a test. (Bug: It doesn't.) -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -46,7 +46,7 @@ scratch/main> view foo foo = 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -62,7 +62,7 @@ foo = 1 ``` After updating `foo` to not be a test, we expect `view` to not render it like a test. -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-test-watch-roundtrip.output.md b/unison-src/transcripts/update-test-watch-roundtrip.output.md index 5ba534cd3..31aa18ea2 100644 --- a/unison-src/transcripts/update-test-watch-roundtrip.output.md +++ b/unison-src/transcripts/update-test-watch-roundtrip.output.md @@ -8,7 +8,7 @@ test> mynamespace.foo.test = if (foo n) == 2 then [ Ok "passed" ] else [ Fail "wat" ] ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -23,7 +23,7 @@ if we change the type of the dependency, the test should show in the scratch fil foo n = "hello, world!" ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -37,7 +37,7 @@ foo n = "hello, world!" foo : n -> Text ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-add-constructor.output.md b/unison-src/transcripts/update-type-add-constructor.output.md index 5f58f745c..c87b1b7cd 100644 --- a/unison-src/transcripts/update-type-add-constructor.output.md +++ b/unison-src/transcripts/update-type-add-constructor.output.md @@ -3,7 +3,7 @@ unique type Foo = Bar Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -16,7 +16,7 @@ unique type Foo type Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -30,7 +30,7 @@ unique type Foo | Baz Nat Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -44,7 +44,7 @@ unique type Foo type Foo ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-add-field.output.md b/unison-src/transcripts/update-type-add-field.output.md index b96464e02..6741c27a0 100644 --- a/unison-src/transcripts/update-type-add-field.output.md +++ b/unison-src/transcripts/update-type-add-field.output.md @@ -2,7 +2,7 @@ unique type Foo = Bar Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -15,7 +15,7 @@ unique type Foo = Bar Nat type Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -27,7 +27,7 @@ scratch/main> add unique type Foo = Bar Nat Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -41,7 +41,7 @@ unique type Foo = Bar Nat Nat type Foo ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-add-new-record.output.md b/unison-src/transcripts/update-type-add-new-record.output.md index 4e10132bc..a96ce90c2 100644 --- a/unison-src/transcripts/update-type-add-new-record.output.md +++ b/unison-src/transcripts/update-type-add-new-record.output.md @@ -2,7 +2,7 @@ unique type Foo = { bar : Nat } ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -18,7 +18,7 @@ unique type Foo = { bar : Nat } Foo.bar.set : Nat -> Foo -> Foo ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-add-record-field.output.md b/unison-src/transcripts/update-type-add-record-field.output.md index 1997eb2ac..23365f09b 100644 --- a/unison-src/transcripts/update-type-add-record-field.output.md +++ b/unison-src/transcripts/update-type-add-record-field.output.md @@ -2,7 +2,7 @@ unique type Foo = { bar : Nat } ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -18,7 +18,7 @@ unique type Foo = { bar : Nat } Foo.bar.set : Nat -> Foo -> Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -33,7 +33,7 @@ scratch/main> add unique type Foo = { bar : Nat, baz : Int } ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -56,7 +56,7 @@ unique type Foo = { bar : Nat, baz : Int } Foo.bar.set : Nat -> Foo -> Foo ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-constructor-alias.output.md b/unison-src/transcripts/update-type-constructor-alias.output.md index 76291ee05..e8d95fafe 100644 --- a/unison-src/transcripts/update-type-constructor-alias.output.md +++ b/unison-src/transcripts/update-type-constructor-alias.output.md @@ -2,7 +2,7 @@ unique type Foo = Bar Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -15,7 +15,7 @@ unique type Foo = Bar Nat type Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -31,7 +31,7 @@ scratch/main> alias.term Foo.Bar Foo.BarAlias unique type Foo = Bar Nat Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -47,7 +47,7 @@ unique type Foo = Bar Nat Nat ``` Bug: we leave `Foo.BarAlias` in the namespace with a nameless decl. -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-delete-constructor-with-dependent.output.md b/unison-src/transcripts/update-type-delete-constructor-with-dependent.output.md index 3eca077a5..977866e32 100644 --- a/unison-src/transcripts/update-type-delete-constructor-with-dependent.output.md +++ b/unison-src/transcripts/update-type-delete-constructor-with-dependent.output.md @@ -9,7 +9,7 @@ foo = cases Baz n m -> n + m ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -23,7 +23,7 @@ foo = cases foo : Foo -> Nat ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -37,7 +37,7 @@ unique type Foo = Bar Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -51,7 +51,7 @@ unique type Foo type Foo ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-delete-constructor.output.md b/unison-src/transcripts/update-type-delete-constructor.output.md index 05d18c259..31afdb7d4 100644 --- a/unison-src/transcripts/update-type-delete-constructor.output.md +++ b/unison-src/transcripts/update-type-delete-constructor.output.md @@ -4,7 +4,7 @@ unique type Foo | Baz Nat Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -17,7 +17,7 @@ unique type Foo type Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -30,7 +30,7 @@ unique type Foo = Bar Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -44,7 +44,7 @@ unique type Foo type Foo ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-delete-record-field.output.md b/unison-src/transcripts/update-type-delete-record-field.output.md index dcdfa6d51..876edca30 100644 --- a/unison-src/transcripts/update-type-delete-record-field.output.md +++ b/unison-src/transcripts/update-type-delete-record-field.output.md @@ -2,7 +2,7 @@ unique type Foo = { bar : Nat, baz : Int } ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -21,7 +21,7 @@ unique type Foo = { bar : Nat, baz : Int } Foo.baz.set : Int -> Foo -> Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -39,7 +39,7 @@ scratch/main> add unique type Foo = { bar : Nat } ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -58,7 +58,7 @@ unique type Foo = { bar : Nat } ``` We want the field accessors to go away; but for now they are here, causing the update to fail. -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-missing-constructor.output.md b/unison-src/transcripts/update-type-missing-constructor.output.md index 2344e4319..c9c8bc2ec 100644 --- a/unison-src/transcripts/update-type-missing-constructor.output.md +++ b/unison-src/transcripts/update-type-missing-constructor.output.md @@ -2,7 +2,7 @@ unique type Foo = Bar Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -15,7 +15,7 @@ unique type Foo = Bar Nat type Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -33,7 +33,7 @@ Now we've set up a situation where the original constructor missing. unique type Foo = Bar Nat Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -47,7 +47,7 @@ unique type Foo = Bar Nat Nat type Foo ``` -```ucm +``` ucm scratch/main> view Foo type Foo = #b509v3eg4k#0 Nat diff --git a/unison-src/transcripts/update-type-nested-decl-aliases.output.md b/unison-src/transcripts/update-type-nested-decl-aliases.output.md index e67a1c4b1..706efd641 100644 --- a/unison-src/transcripts/update-type-nested-decl-aliases.output.md +++ b/unison-src/transcripts/update-type-nested-decl-aliases.output.md @@ -5,7 +5,7 @@ structural type A.B = OneAlias Foo structural type A = B.TheOtherAlias Foo ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -20,7 +20,7 @@ structural type A = B.TheOtherAlias Foo type Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -34,7 +34,7 @@ scratch/main> add unique type Foo = Bar Nat Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -52,7 +52,7 @@ Bug: we want this update to be rejected earlier, because it violates the "decl c only one name for each constructor. We instead get too far in the update process, and are delivered a bogus scratch.u file to stare at. -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-no-op-record.output.md b/unison-src/transcripts/update-type-no-op-record.output.md index 159f9aa86..763a1aba5 100644 --- a/unison-src/transcripts/update-type-no-op-record.output.md +++ b/unison-src/transcripts/update-type-no-op-record.output.md @@ -2,7 +2,7 @@ unique type Foo = { bar : Nat } ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -18,7 +18,7 @@ unique type Foo = { bar : Nat } Foo.bar.set : Nat -> Foo -> Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -31,7 +31,7 @@ scratch/main> add ``` Bug: this no-op update should (of course) succeed. -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-stray-constructor-alias.output.md b/unison-src/transcripts/update-type-stray-constructor-alias.output.md index 54a1e5965..c6f65667b 100644 --- a/unison-src/transcripts/update-type-stray-constructor-alias.output.md +++ b/unison-src/transcripts/update-type-stray-constructor-alias.output.md @@ -2,7 +2,7 @@ unique type Foo = Bar Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -15,7 +15,7 @@ unique type Foo = Bar Nat type Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -31,7 +31,7 @@ scratch/main> alias.term Foo.Bar Stray.BarAlias unique type Foo = Bar Nat Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -47,7 +47,7 @@ unique type Foo = Bar Nat Nat ``` Bug: we leave `Stray.BarAlias` in the namespace with a nameless decl. -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-stray-constructor.output.md b/unison-src/transcripts/update-type-stray-constructor.output.md index 999c57ae4..4554fd53d 100644 --- a/unison-src/transcripts/update-type-stray-constructor.output.md +++ b/unison-src/transcripts/update-type-stray-constructor.output.md @@ -2,7 +2,7 @@ unique type Foo = Bar Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -15,7 +15,7 @@ unique type Foo = Bar Nat type Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -33,7 +33,7 @@ Now we've set up a situation where the constructor is not where it's supposed to unique type Foo = Bar Nat Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -49,7 +49,7 @@ unique type Foo = Bar Nat Nat ``` Note that the constructor name shown here (implied to be called `Foo.Stray.Bar`) doesn't really exist, it's just showing up due to a pretty-printer bug. -```ucm +``` ucm scratch/main> view Foo type Foo = Stray.Bar Nat diff --git a/unison-src/transcripts/update-type-turn-constructor-into-smart-constructor.output.md b/unison-src/transcripts/update-type-turn-constructor-into-smart-constructor.output.md index cff0653a0..b6daa8302 100644 --- a/unison-src/transcripts/update-type-turn-constructor-into-smart-constructor.output.md +++ b/unison-src/transcripts/update-type-turn-constructor-into-smart-constructor.output.md @@ -5,7 +5,7 @@ makeFoo : Nat -> Foo makeFoo n = Bar (n+10) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -19,7 +19,7 @@ makeFoo n = Bar (n+10) makeFoo : Nat -> Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -35,7 +35,7 @@ Foo.Bar : Nat -> Foo Foo.Bar n = internal.Bar n ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -50,7 +50,7 @@ Foo.Bar n = internal.Bar n Foo.Bar : Nat -> Foo ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-turn-non-record-into-record.output.md b/unison-src/transcripts/update-type-turn-non-record-into-record.output.md index a9a3bf467..edeb85642 100644 --- a/unison-src/transcripts/update-type-turn-non-record-into-record.output.md +++ b/unison-src/transcripts/update-type-turn-non-record-into-record.output.md @@ -2,7 +2,7 @@ unique type Foo = Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -15,7 +15,7 @@ unique type Foo = Nat type Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -27,7 +27,7 @@ scratch/main> add unique type Foo = { bar : Nat } ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -47,7 +47,7 @@ unique type Foo = { bar : Nat } type Foo ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-with-dependent-term.output.md b/unison-src/transcripts/update-type-with-dependent-term.output.md index 09d0a63f5..b5db3f264 100644 --- a/unison-src/transcripts/update-type-with-dependent-term.output.md +++ b/unison-src/transcripts/update-type-with-dependent-term.output.md @@ -5,7 +5,7 @@ incrFoo : Foo -> Foo incrFoo = cases Bar n -> Bar (n+1) ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -19,7 +19,7 @@ incrFoo = cases Bar n -> Bar (n+1) incrFoo : Foo -> Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -32,7 +32,7 @@ scratch/main> add unique type Foo = Bar Nat Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -46,7 +46,7 @@ unique type Foo = Bar Nat Nat type Foo ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-with-dependent-type-to-different-kind.output.md b/unison-src/transcripts/update-type-with-dependent-type-to-different-kind.output.md index ea8d65242..8ffbf3b88 100644 --- a/unison-src/transcripts/update-type-with-dependent-type-to-different-kind.output.md +++ b/unison-src/transcripts/update-type-with-dependent-type-to-different-kind.output.md @@ -3,7 +3,7 @@ unique type Foo = Bar Nat unique type Baz = Qux Foo ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -17,7 +17,7 @@ unique type Baz = Qux Foo type Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -30,7 +30,7 @@ scratch/main> add unique type Foo a = Bar Nat a ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -44,7 +44,7 @@ unique type Foo a = Bar Nat a type Foo a ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-type-with-dependent-type.output.md b/unison-src/transcripts/update-type-with-dependent-type.output.md index 474a8ceef..6effd150c 100644 --- a/unison-src/transcripts/update-type-with-dependent-type.output.md +++ b/unison-src/transcripts/update-type-with-dependent-type.output.md @@ -3,7 +3,7 @@ unique type Foo = Bar Nat unique type Baz = Qux Foo ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -17,7 +17,7 @@ unique type Baz = Qux Foo type Foo ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -30,7 +30,7 @@ scratch/main> add unique type Foo = Bar Nat Nat ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -44,7 +44,7 @@ unique type Foo = Bar Nat Nat type Foo ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/update-watch.output.md b/unison-src/transcripts/update-watch.output.md index 36bc89ae2..feb53dc17 100644 --- a/unison-src/transcripts/update-watch.output.md +++ b/unison-src/transcripts/update-watch.output.md @@ -2,7 +2,7 @@ > 1 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -18,7 +18,7 @@ 1 ``` -```ucm +``` ucm scratch/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/upgrade-happy-path.output.md b/unison-src/transcripts/upgrade-happy-path.output.md index 33c8b6c8d..127b0c489 100644 --- a/unison-src/transcripts/upgrade-happy-path.output.md +++ b/unison-src/transcripts/upgrade-happy-path.output.md @@ -4,7 +4,7 @@ lib.new.foo = 18 thingy = lib.old.foo + 10 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -19,7 +19,7 @@ thingy = lib.old.foo + 10 thingy : Nat ``` -```ucm +``` ucm proj/main> add ⍟ I've added these definitions: @@ -31,7 +31,7 @@ proj/main> add ``` Test tab completion and fzf options of upgrade command. -```ucm +``` ucm proj/main> debug.tab-complete upgrade ol old @@ -51,7 +51,7 @@ proj/main> debug.fuzzy-options upgrade old _ * old ``` -```ucm +``` ucm proj/main> upgrade old new I upgraded old to new, and removed old. diff --git a/unison-src/transcripts/upgrade-sad-path.output.md b/unison-src/transcripts/upgrade-sad-path.output.md index d25d2f8c4..54c7b546c 100644 --- a/unison-src/transcripts/upgrade-sad-path.output.md +++ b/unison-src/transcripts/upgrade-sad-path.output.md @@ -4,7 +4,7 @@ lib.new.foo = +18 thingy = lib.old.foo + 10 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -19,7 +19,7 @@ thingy = lib.old.foo + 10 thingy : Nat ``` -```ucm +``` ucm proj/main> add ⍟ I've added these definitions: @@ -29,7 +29,7 @@ proj/main> add thingy : Nat ``` -```ucm +``` ucm proj/main> upgrade old new I couldn't automatically upgrade old to new. However, I've @@ -62,7 +62,7 @@ Resolve the error and commit the upgrade. thingy = foo + +10 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -76,7 +76,7 @@ thingy = foo + +10 thingy : Int ``` -```ucm +``` ucm proj/upgrade-old-to-new> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/upgrade-suffixifies-properly.output.md b/unison-src/transcripts/upgrade-suffixifies-properly.output.md index cacefecf8..0440acc2a 100644 --- a/unison-src/transcripts/upgrade-suffixifies-properly.output.md +++ b/unison-src/transcripts/upgrade-suffixifies-properly.output.md @@ -8,7 +8,7 @@ d.y.y.y.y = lib.old.foo + 10 bar = a.x.x.x.x + c.y.y.y.y ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -27,7 +27,7 @@ bar = a.x.x.x.x + c.y.y.y.y lib.old.foo : Nat ``` -```ucm +``` ucm myproject/main> add ⍟ I've added these definitions: @@ -41,7 +41,7 @@ myproject/main> add lib.old.foo : Nat ``` -```ucm +``` ucm myproject/main> upgrade old new I couldn't automatically upgrade old to new. However, I've diff --git a/unison-src/transcripts/upgrade-with-old-alias.output.md b/unison-src/transcripts/upgrade-with-old-alias.output.md index 46b073616..9afef6c22 100644 --- a/unison-src/transcripts/upgrade-with-old-alias.output.md +++ b/unison-src/transcripts/upgrade-with-old-alias.output.md @@ -5,7 +5,7 @@ bar = 141 mything = lib.old.foo + 100 ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -21,7 +21,7 @@ mything = lib.old.foo + 100 mything : Nat ``` -```ucm +``` ucm myproject/main> update Okay, I'm searching the branch for code that needs to be diff --git a/unison-src/transcripts/view.output.md b/unison-src/transcripts/view.output.md index c300d96d3..b5cc5149d 100644 --- a/unison-src/transcripts/view.output.md +++ b/unison-src/transcripts/view.output.md @@ -5,7 +5,7 @@ a.thing = "a" b.thing = "b" ``` -```ucm +``` ucm -- Should suffix-search and find values in sub-namespaces .> view thing diff --git a/unison-src/transcripts/watch-expressions.output.md b/unison-src/transcripts/watch-expressions.output.md index 0641ab1a6..096f08e7a 100644 --- a/unison-src/transcripts/watch-expressions.output.md +++ b/unison-src/transcripts/watch-expressions.output.md @@ -1,4 +1,4 @@ -```ucm +``` ucm scratch/main> builtins.mergeio Done. @@ -8,7 +8,7 @@ scratch/main> builtins.mergeio test> pass = [Ok "Passed"] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -28,7 +28,7 @@ test> pass = [Ok "Passed"] ✅ Passed Passed ``` -```ucm +``` ucm scratch/main> add ⍟ I've added these definitions: @@ -40,7 +40,7 @@ scratch/main> add test> pass = [Ok "Passed"] ``` -```ucm +``` ucm Loading changes detected in scratch.u. @@ -55,7 +55,7 @@ test> pass = [Ok "Passed"] ✅ Passed Passed (cached) ``` -```ucm +``` ucm scratch/main> add ⊡ Ignored previously added definitions: pass @@ -76,7 +76,7 @@ scratch/main> test > ImmutableByteArray.fromBytes 0xs123456 ``` -```ucm +``` ucm Loading changes detected in scratch.u. From b657d0dd5091b042c0c79ab9ff7c4172204e9c05 Mon Sep 17 00:00:00 2001 From: Greg Pfeil Date: Wed, 10 Jul 2024 10:27:02 -0600 Subject: [PATCH 13/16] Fix a few transcripts with incorrect Markdown MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit These weren’t errors in any way, but the `cmark`-produced outputs made it clear that some of our transcripts weren’t formatted the way we intended. --- unison-src/transcripts/fix2474.md | 3 +- unison-src/transcripts/fix2474.output.md | 2 +- unison-src/transcripts/fix2663.md | 3 +- unison-src/transcripts/fix2663.output.md | 2 +- unison-src/transcripts/io.md | 44 ++++++++++++---------- unison-src/transcripts/io.output.md | 48 ++++++++++++++---------- 6 files changed, 56 insertions(+), 46 deletions(-) diff --git a/unison-src/transcripts/fix2474.md b/unison-src/transcripts/fix2474.md index 3d48be95b..e84cd4a9e 100644 --- a/unison-src/transcripts/fix2474.md +++ b/unison-src/transcripts/fix2474.md @@ -1,9 +1,8 @@ - Tests an issue with a lack of generality of handlers. In general, a set of cases: - { e ... -> k } + { e ... -> k } should be typed in the following way: diff --git a/unison-src/transcripts/fix2474.output.md b/unison-src/transcripts/fix2474.output.md index 0daf2d3ba..d5863ee87 100644 --- a/unison-src/transcripts/fix2474.output.md +++ b/unison-src/transcripts/fix2474.output.md @@ -2,7 +2,7 @@ Tests an issue with a lack of generality of handlers. In general, a set of cases: -{ e ... -\> k } + { e ... -> k } should be typed in the following way: diff --git a/unison-src/transcripts/fix2663.md b/unison-src/transcripts/fix2663.md index e3b88b062..ee6a5b749 100644 --- a/unison-src/transcripts/fix2663.md +++ b/unison-src/transcripts/fix2663.md @@ -1,9 +1,8 @@ - Tests a variable capture problem. After pattern compilation, the match would end up: - T p1 p3 p3 + T p1 p3 p3 and z would end up referring to the first p3 rather than the second. diff --git a/unison-src/transcripts/fix2663.output.md b/unison-src/transcripts/fix2663.output.md index 6153dc042..d1b0575e1 100644 --- a/unison-src/transcripts/fix2663.output.md +++ b/unison-src/transcripts/fix2663.output.md @@ -2,7 +2,7 @@ Tests a variable capture problem. After pattern compilation, the match would end up: -T p1 p3 p3 + T p1 p3 p3 and z would end up referring to the first p3 rather than the second. diff --git a/unison-src/transcripts/io.md b/unison-src/transcripts/io.md index 0051c7aa6..7db903ebb 100644 --- a/unison-src/transcripts/io.md +++ b/unison-src/transcripts/io.md @@ -24,11 +24,12 @@ scratch/main> add ### Creating/Deleting/Renaming Directories -Tests: createDirectory, - isDirectory, - fileExists, - renameDirectory, - deleteDirectory +Tests: +- createDirectory, +- isDirectory, +- fileExists, +- renameDirectory, +- deleteDirectory ```unison testCreateRename : '{io2.IO} [Result] @@ -63,9 +64,10 @@ scratch/main> io.test testCreateRename ### Opening / Closing files -Tests: openFile - closeFile - isFileOpen +Tests: +- openFile +- closeFile +- isFileOpen ```unison testOpenClose : '{io2.IO} [Result] @@ -113,10 +115,11 @@ scratch/main> io.test testOpenClose ### Reading files with getSomeBytes -Tests: getSomeBytes - putBytes - isFileOpen - seekHandle +Tests: +- getSomeBytes +- putBytes +- isFileOpen +- seekHandle ```unison testGetSomeBytes : '{io2.IO} [Result] @@ -172,14 +175,15 @@ scratch/main> io.test testGetSomeBytes ### Seeking in open files -Tests: openFile - putBytes - closeFile - isSeekable - isFileEOF - seekHandle - getBytes - getLine +Tests: +- openFile +- putBytes +- closeFile +- isSeekable +- isFileEOF +- seekHandle +- getBytes +- getLine ```unison testSeek : '{io2.IO} [Result] diff --git a/unison-src/transcripts/io.output.md b/unison-src/transcripts/io.output.md index ef385d897..4ac673c76 100644 --- a/unison-src/transcripts/io.output.md +++ b/unison-src/transcripts/io.output.md @@ -13,11 +13,13 @@ create a scratch directory which will automatically get cleaned up. ### Creating/Deleting/Renaming Directories -Tests: createDirectory, -isDirectory, -fileExists, -renameDirectory, -deleteDirectory +Tests: + + - createDirectory, + - isDirectory, + - fileExists, + - renameDirectory, + - deleteDirectory ``` unison testCreateRename : '{io2.IO} [Result] @@ -84,9 +86,11 @@ scratch/main> io.test testCreateRename ``` ### Opening / Closing files -Tests: openFile -closeFile -isFileOpen +Tests: + + - openFile + - closeFile + - isFileOpen ``` unison testOpenClose : '{io2.IO} [Result] @@ -165,10 +169,12 @@ scratch/main> io.test testOpenClose ``` ### Reading files with getSomeBytes -Tests: getSomeBytes -putBytes -isFileOpen -seekHandle +Tests: + + - getSomeBytes + - putBytes + - isFileOpen + - seekHandle ``` unison testGetSomeBytes : '{io2.IO} [Result] @@ -257,14 +263,16 @@ scratch/main> io.test testGetSomeBytes ``` ### Seeking in open files -Tests: openFile -putBytes -closeFile -isSeekable -isFileEOF -seekHandle -getBytes -getLine +Tests: + + - openFile + - putBytes + - closeFile + - isSeekable + - isFileEOF + - seekHandle + - getBytes + - getLine ``` unison testSeek : '{io2.IO} [Result] From 8416708a29287cc03542e2aa4b3ec42d7417cf49 Mon Sep 17 00:00:00 2001 From: Greg Pfeil Date: Wed, 10 Jul 2024 10:57:36 -0600 Subject: [PATCH 14/16] Add transcripts for fixed issues This shows that this change fixes #1421, #2826, #5141, and #5168. --- unison-src/transcripts/fix1421.md | 8 +++ unison-src/transcripts/fix1421.output.md | 29 +++++++++++ unison-src/transcripts/fix2826.md | 23 +++++++++ unison-src/transcripts/fix2826.output.md | 66 ++++++++++++++++++++++++ unison-src/transcripts/fix5141.md | 5 ++ unison-src/transcripts/fix5141.output.md | 6 +++ unison-src/transcripts/fix5168.md | 4 ++ unison-src/transcripts/fix5168.output.md | 19 +++++++ 8 files changed, 160 insertions(+) create mode 100644 unison-src/transcripts/fix1421.md create mode 100644 unison-src/transcripts/fix1421.output.md create mode 100644 unison-src/transcripts/fix2826.md create mode 100644 unison-src/transcripts/fix2826.output.md create mode 100644 unison-src/transcripts/fix5141.md create mode 100644 unison-src/transcripts/fix5141.output.md create mode 100644 unison-src/transcripts/fix5168.md create mode 100644 unison-src/transcripts/fix5168.output.md diff --git a/unison-src/transcripts/fix1421.md b/unison-src/transcripts/fix1421.md new file mode 100644 index 000000000..8117928aa --- /dev/null +++ b/unison-src/transcripts/fix1421.md @@ -0,0 +1,8 @@ + ```ucm + scratch/main> alias.type ##Nat Nat + scratch/main> alias.term ##Nat.+ Nat.+ + ``` + ```unison + unique type A = A Nat + unique type B = B Nat Nat + ``` diff --git a/unison-src/transcripts/fix1421.output.md b/unison-src/transcripts/fix1421.output.md new file mode 100644 index 000000000..0f52e9a36 --- /dev/null +++ b/unison-src/transcripts/fix1421.output.md @@ -0,0 +1,29 @@ +``` ucm +scratch/main> alias.type ##Nat Nat + + Done. + +scratch/main> alias.term ##Nat.+ Nat.+ + + Done. + +``` +``` unison +unique type A = A Nat +unique type B = B Nat Nat +``` + +``` 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`: + + type A + type B + +``` diff --git a/unison-src/transcripts/fix2826.md b/unison-src/transcripts/fix2826.md new file mode 100644 index 000000000..d2ad94cd5 --- /dev/null +++ b/unison-src/transcripts/fix2826.md @@ -0,0 +1,23 @@ +```ucm +scratch/main> builtins.mergeio +``` + +Supports fences that are longer than three backticks. + +````unison + +doc = {{ + @typecheck ``` + x = 3 + ``` +}} + +```` + +And round-trips properly. + +```ucm +scratch/main> add +scratch/main> edit doc +scratch/main> load scratch.u +``` diff --git a/unison-src/transcripts/fix2826.output.md b/unison-src/transcripts/fix2826.output.md new file mode 100644 index 000000000..cf691c1b6 --- /dev/null +++ b/unison-src/transcripts/fix2826.output.md @@ -0,0 +1,66 @@ +``` ucm +scratch/main> builtins.mergeio + + Done. + +``` +Supports fences that are longer than three backticks. + +```` unison +doc = {{ + @typecheck ``` + x = 3 + ``` +}} + +```` + +``` 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`: + + doc : Doc2 + +``` +And round-trips properly. + +``` ucm +scratch/main> add + + ⍟ I've added these definitions: + + doc : Doc2 + +scratch/main> edit doc + + ☝️ + + I added 1 definitions to the top of scratch.u + + You can edit them there, then run `update` to replace the + definitions currently in this namespace. + +scratch/main> load scratch.u + + Loading changes detected in scratch.u. + + I found and typechecked the definitions in scratch.u. This + file has been previously added to the codebase. + +``` +```` unison:added-by-ucm scratch.u +doc : Doc2 +doc = + {{ + @typecheck ``` + x = 3 + ``` + }} +```` + diff --git a/unison-src/transcripts/fix5141.md b/unison-src/transcripts/fix5141.md new file mode 100644 index 000000000..0536b6e0a --- /dev/null +++ b/unison-src/transcripts/fix5141.md @@ -0,0 +1,5 @@ + diff --git a/unison-src/transcripts/fix5141.output.md b/unison-src/transcripts/fix5141.output.md new file mode 100644 index 000000000..ab031fee0 --- /dev/null +++ b/unison-src/transcripts/fix5141.output.md @@ -0,0 +1,6 @@ + + diff --git a/unison-src/transcripts/fix5168.md b/unison-src/transcripts/fix5168.md new file mode 100644 index 000000000..2eda5f021 --- /dev/null +++ b/unison-src/transcripts/fix5168.md @@ -0,0 +1,4 @@ +The `edit` seems to suppress a following ```` ```unison ```` block: +```unison +b = 2 +``` diff --git a/unison-src/transcripts/fix5168.output.md b/unison-src/transcripts/fix5168.output.md new file mode 100644 index 000000000..5a7c35e33 --- /dev/null +++ b/unison-src/transcripts/fix5168.output.md @@ -0,0 +1,19 @@ +The `edit` seems to suppress a following ` ```unison ` block: + +``` unison +b = 2 +``` + +``` 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`: + + b : ##Nat + +``` From 179b8d1bb7bbbabe9581e4e7187cb9f9bef42aeb Mon Sep 17 00:00:00 2001 From: Greg Pfeil Date: Wed, 10 Jul 2024 13:15:33 -0600 Subject: [PATCH 15/16] Terminate API code blocks correctly They were missing trailing newlines, so as you can see in the diff, some transcripts had invalid output. --- unison-cli/src/Unison/Codebase/TranscriptParser.hs | 2 +- unison-src/transcripts/api-doc-rendering.output.md | 3 ++- unison-src/transcripts/api-find.output.md | 3 ++- unison-src/transcripts/api-getDefinition.output.md | 11 ++++++++--- .../transcripts/api-list-projects-branches.output.md | 3 ++- .../transcripts/api-namespace-details.output.md | 3 ++- unison-src/transcripts/api-namespace-list.output.md | 3 ++- unison-src/transcripts/api-summaries.output.md | 7 +++++-- unison-src/transcripts/definition-diff-api.output.md | 7 +++++-- 9 files changed, 29 insertions(+), 13 deletions(-) diff --git a/unison-cli/src/Unison/Codebase/TranscriptParser.hs b/unison-cli/src/Unison/Codebase/TranscriptParser.hs index bf71f18a8..988a1e55c 100644 --- a/unison-cli/src/Unison/Codebase/TranscriptParser.hs +++ b/unison-cli/src/Unison/Codebase/TranscriptParser.hs @@ -432,7 +432,7 @@ run verbosity dir stanzas codebase runtime sbRuntime nRuntime config ucmVersion API apiRequests -> do liftIO (output "``` api\n") liftIO (for_ apiRequests apiRequest) - liftIO (output "```") + liftIO (output "```\n\n") awaitInput Ucm hide errOk cmds -> do liftIO (writeIORef hidden hide) diff --git a/unison-src/transcripts/api-doc-rendering.output.md b/unison-src/transcripts/api-doc-rendering.output.md index 271fac784..1ecf4f86a 100644 --- a/unison-src/transcripts/api-doc-rendering.output.md +++ b/unison-src/transcripts/api-doc-rendering.output.md @@ -940,4 +940,5 @@ GET /api/projects/scratch/branches/main/getDefinition?names=term }, "typeDefinitions": {} } -``` \ No newline at end of file +``` + diff --git a/unison-src/transcripts/api-find.output.md b/unison-src/transcripts/api-find.output.md index 24c34c837..2d062550b 100644 --- a/unison-src/transcripts/api-find.output.md +++ b/unison-src/transcripts/api-find.output.md @@ -252,4 +252,5 @@ GET /api/projects/scratch/branches/main/find?query=joey.http } ] ] -``` \ No newline at end of file +``` + diff --git a/unison-src/transcripts/api-getDefinition.output.md b/unison-src/transcripts/api-getDefinition.output.md index 6daa80c01..edf49323c 100644 --- a/unison-src/transcripts/api-getDefinition.output.md +++ b/unison-src/transcripts/api-getDefinition.output.md @@ -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 }} @@ -332,7 +334,9 @@ 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. +``` + +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 @@ -507,4 +511,5 @@ GET /api/projects/scratch/branches/main/getDefinition?names=thing.doc&relativeTo }, "typeDefinitions": {} } -``` \ No newline at end of file +``` + diff --git a/unison-src/transcripts/api-list-projects-branches.output.md b/unison-src/transcripts/api-list-projects-branches.output.md index 5768b6454..0971ab5fc 100644 --- a/unison-src/transcripts/api-list-projects-branches.output.md +++ b/unison-src/transcripts/api-list-projects-branches.output.md @@ -53,4 +53,5 @@ GET /api/projects/project-one/branches?prefix=branch-t "branchName": "branch-two" } ] -``` \ No newline at end of file +``` + diff --git a/unison-src/transcripts/api-namespace-details.output.md b/unison-src/transcripts/api-namespace-details.output.md index 124c28e5d..3ba09740f 100644 --- a/unison-src/transcripts/api-namespace-details.output.md +++ b/unison-src/transcripts/api-namespace-details.output.md @@ -78,4 +78,5 @@ GET /api/projects/scratch/branches/main/namespaces/nested.names "tag": "Paragraph" } } -``` \ No newline at end of file +``` + diff --git a/unison-src/transcripts/api-namespace-list.output.md b/unison-src/transcripts/api-namespace-list.output.md index 1378a7d36..56a6e0949 100644 --- a/unison-src/transcripts/api-namespace-list.output.md +++ b/unison-src/transcripts/api-namespace-list.output.md @@ -131,4 +131,5 @@ GET /api/projects/scratch/branches/main/list?namespace=names&relativeTo=nested "namespaceListingFQN": "nested.names", "namespaceListingHash": "#oms19b4f9s3c8tb5skeb8jii95ij35n3hdg038pu6rv5b0fikqe4gd7lnu6a1i6aq5tdh2opdo4s0sfrupvk6vfkr9lf0n752gbl8o0" } -``` \ No newline at end of file +``` + diff --git a/unison-src/transcripts/api-summaries.output.md b/unison-src/transcripts/api-summaries.output.md index 115dba15a..7ea0a5d19 100644 --- a/unison-src/transcripts/api-summaries.output.md +++ b/unison-src/transcripts/api-summaries.output.md @@ -667,7 +667,9 @@ GET /api/projects/scratch/branches/main/definitions/terms/by-hash/@@IO.putBytes. }, "tag": "Plain" } -```## Type Summary APIs +``` + +## Type Summary APIs ``` api -- data @@ -823,4 +825,5 @@ GET /api/projects/scratch/branches/main/definitions/types/by-hash/@@Nat/summary? }, "tag": "Data" } -``` \ No newline at end of file +``` + diff --git a/unison-src/transcripts/definition-diff-api.output.md b/unison-src/transcripts/definition-diff-api.output.md index 8d55cc785..1670f2b05 100644 --- a/unison-src/transcripts/definition-diff-api.output.md +++ b/unison-src/transcripts/definition-diff-api.output.md @@ -558,7 +558,9 @@ GET /api/projects/diffs/diff/terms?oldBranchRef=main&newBranchRef=new&oldTerm=te }, "project": "diffs" } -```Diff types +``` + +Diff types ``` api GET /api/projects/diffs/diff/types?oldBranchRef=main&newBranchRef=new&oldType=Type&newType=Type @@ -804,4 +806,5 @@ GET /api/projects/diffs/diff/types?oldBranchRef=main&newBranchRef=new&oldType=Ty }, "project": "diffs" } -``` \ No newline at end of file +``` + From cbd533e40f07027c5552e47b8a8d656be78fca52 Mon Sep 17 00:00:00 2001 From: Greg Pfeil Date: Wed, 10 Jul 2024 16:04:21 -0600 Subject: [PATCH 16/16] Update a couple transcripts to the new formatting MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit These aren‘t run as part of ./scripts/check.sh, so they got missed in the initial pass. --- .../builtin-tests/interpreter-tests.output.md | 2 +- unison-src/builtin-tests/jit-tests.output.md | 19 ++++++++++--------- 2 files changed, 11 insertions(+), 10 deletions(-) diff --git a/unison-src/builtin-tests/interpreter-tests.output.md b/unison-src/builtin-tests/interpreter-tests.output.md index 9257063d7..7ba9ed8bb 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 +``` ucm runtime-tests/selected> run tests () diff --git a/unison-src/builtin-tests/jit-tests.output.md b/unison-src/builtin-tests/jit-tests.output.md index 36da40929..4bdb6cc29 100644 --- a/unison-src/builtin-tests/jit-tests.output.md +++ b/unison-src/builtin-tests/jit-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 +``` 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" ```