Merge remote-tracking branch 'origin/trunk' into cp/scratch-file-transcript-block

This commit is contained in:
Chris Penner 2024-01-09 13:55:12 -08:00
commit 7b7c07d9a1
136 changed files with 1068 additions and 3136 deletions

View File

@ -15,6 +15,8 @@ on:
- trunk
tags:
- release/*
workflow_dispatch:
jobs:

View File

@ -0,0 +1,92 @@
name: update-transcripts
on:
workflow_dispatch:
jobs:
update_transcripts:
runs-on: ${{ matrix.os }}
defaults:
run:
shell: bash
strategy:
matrix:
os:
- macOS-12
steps:
- uses: actions/checkout@v4
- id: stackage-resolver
name: record stackage resolver
# https://docs.github.com/en/actions/using-workflows/workflow-commands-for-github-actions#environment-files
# looks for `resolver: nightly-yyyy-mm-dd` or `resolver: lts-xx.yy` in `stack.yaml` and splits it into
# `nightly` or `lts-xx`. the whole resolver string is put into resolver_long as a backup cache key
# ${{ steps.stackage-resolver.outputs.resolver_short }}
# ${{ steps.stackage-resolver.outputs.resolver_long }}
run: |
grep resolver stack.yaml | awk '{ x="resolver_short="; if (split($2,a,"-") > 2) print x a[1]; else {split($2,b,"."); print x b[1]}}' >> "$GITHUB_OUTPUT"
grep resolver stack.yaml | awk '{print "resolver_long="$2}' >> "$GITHUB_OUTPUT"
# Cache ~/.stack, keyed by the contents of 'stack.yaml'.
- uses: actions/cache@v3
name: cache ~/.stack (unix)
if: runner.os != 'Windows'
with:
path: ~/.stack
key: stack-1_${{matrix.os}}-${{ steps.stackage-resolver.outputs.resolver_long }}-${{hashFiles('**/stack.yaml')}}-${{github.sha}}
# Fall-back to use the most recent cache for the stack.yaml, or failing that the OS
restore-keys: |
stack-1_${{matrix.os}}-${{ steps.stackage-resolver.outputs.resolver_long }}-${{hashFiles('**/stack.yaml')}}-
stack-1_${{matrix.os}}-${{ steps.stackage-resolver.outputs.resolver_long }}-
stack-1_${{matrix.os}}-${{ steps.stackage-resolver.outputs.resolver_short }}-
stack-1_${{matrix.os}}-${{ steps.stackage-resolver.outputs.resolver_short }}.
stack-1_${{matrix.os}}-
# Cache each local package's ~/.stack-work for fast incremental builds in CI.
- uses: actions/cache@v3
name: cache .stack-work
with:
path: |
**/.stack-work
# Main cache key: commit hash. This should always result in a cache miss...
# So when loading a cache we'll always fall back to the restore-keys,
# which should load the most recent cache via a prefix search on the most
# recent branch cache.
# Then it will save a new cache at this commit sha, which should be used by
# the next build on this branch.
key: stack-work-4_${{matrix.os}}-${{ steps.stackage-resolver.outputs.resolver_short }}-${{hashFiles('**/stack.yaml')}}-${{github.sha}}
restore-keys: |
stack-work-4_${{matrix.os}}-${{ steps.stackage-resolver.outputs.resolver_long }}-${{hashFiles('**/stack.yaml')}}-
stack-work-4_${{matrix.os}}-${{ steps.stackage-resolver.outputs.resolver_long }}-
stack-work-4_${{matrix.os}}-${{ steps.stackage-resolver.outputs.resolver_short }}-
stack-work-4_${{matrix.os}}-${{ steps.stackage-resolver.outputs.resolver_short }}.
stack-work-4_${{matrix.os}}-
# Install stack by downloading the binary from GitHub.
# The installation process differs by OS.
- name: install stack (Linux)
if: runner.os == 'Linux'
working-directory: ${{ runner.temp }}
run: |
mkdir stack && cd stack
curl -L https://github.com/commercialhaskell/stack/releases/download/v2.9.1/stack-2.9.1-linux-x86_64.tar.gz | tar -xz
echo "$PWD/stack-"* >> $GITHUB_PATH
# One of the transcripts fails if the user's git name hasn't been set.
- name: set git user info
run: |
git config --global user.name "GitHub Actions"
git config --global user.email "actions@github.com"
- name: build
run: stack --no-terminal build --fast --no-run-tests --test
- name: round-trip-tests
run: |
mkdir -p /private/tmp
touch /private/tmp/roundtrip.u
touch /private/tmp/rewrite-tmp.u
stack --no-terminal exec unison transcript unison-src/transcripts-round-trip/main.md
stack --no-terminal exec unison transcript unison-src/transcripts-manual/rewrites.md
- name: transcripts
run: stack --no-terminal exec transcripts
- name: save transcript changes
uses: stefanzweifel/git-auto-commit-action@v4
with:
commit_message: rerun transcripts and round-trip tests

View File

@ -1,5 +1,3 @@
{-# LANGUAGE RecordWildCards #-}
module U.Codebase.Branch.Type
( Branch (..),
CausalBranch,
@ -12,8 +10,6 @@ module U.Codebase.Branch.Type
childAt,
hoist,
hoistCausalBranch,
termMetadata,
typeMetadata,
U.Codebase.Branch.Type.empty,
)
where
@ -105,26 +101,3 @@ hoistCausalBranch f cb =
cb
& Causal.hoist f
& Causal.emap (hoist f) (hoist f)
-- | Returns all the metadata value references that are attached to a term with the provided name in the
-- provided branch.
--
-- If only name is specified, metadata will be returned for all terms at that name.
termMetadata :: (Monad m) => Branch m -> NameSegment -> Maybe Referent -> m [Map MetadataValue MetadataType]
termMetadata Branch {terms} = metadataHelper terms
-- | Returns all the metadata value references that are attached to a type with the provided name in the
-- provided branch.
--
-- If only name is specified, metadata will be returned for all types at that name.
typeMetadata :: (Monad m) => Branch m -> NameSegment -> Maybe Reference -> m [Map MetadataValue MetadataType]
typeMetadata Branch {types} = metadataHelper types
metadataHelper :: (Monad m, Ord ref) => Map NameSegment (Map ref (m MdValues)) -> NameSegment -> Maybe ref -> m [Map MetadataValue MetadataType]
metadataHelper t ns mayQualifier = do
case Map.lookup ns t of
Nothing -> pure []
Just allRefsAtName -> do
case mayQualifier of
Nothing -> (fmap . fmap) unMdValues . sequenceA $ Map.elems allRefsAtName
Just qualifier -> (fmap . fmap) unMdValues . sequenceA . maybeToList $ Map.lookup qualifier allRefsAtName

View File

@ -45,12 +45,10 @@ data Diff a = Diff
-- | Represents the changes to definitions at a given path, not including child paths.
--
-- Note: doesn't yet include any info on metadata or patch diffs. Feel free to add it.
-- Note: doesn't yet include any info on patch diffs. Feel free to add it.
data DefinitionDiffs = DefinitionDiffs
{ termDiffs :: Map NameSegment (Diff Referent),
typeDiffs :: Map NameSegment (Diff Reference)
-- termMetadataDiffs :: Map (NameSegment, Referent) (Diff Reference),
-- typeMetadataDiffs :: Map (NameSegment, Reference) (Diff Reference)
-- patchDiffs :: Map NameSegment (Diff ())
}
deriving stock (Show, Eq, Ord)

View File

@ -1,6 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module Unison.Builtin.Terms
( builtinTermsRef,
builtinTermsSrc,

View File

@ -13,7 +13,6 @@ module Unison.Codebase
isTerm,
putTerm,
putTermComponent,
termMetadata,
-- ** Referents (sorta-termlike)
getTypeOfReferent,
@ -123,7 +122,6 @@ import U.Codebase.Branch qualified as V2
import U.Codebase.Branch qualified as V2Branch
import U.Codebase.Causal qualified as V2Causal
import U.Codebase.HashTags (CausalHash)
import U.Codebase.Referent qualified as V2
import U.Codebase.Sqlite.Operations qualified as Operations
import U.Codebase.Sqlite.Queries qualified as Queries
import Unison.Builtin qualified as Builtin
@ -153,7 +151,6 @@ import Unison.DataDeclaration (Decl)
import Unison.DataDeclaration qualified as DD
import Unison.Hash (Hash)
import Unison.Hashing.V2.Convert qualified as Hashing
import Unison.NameSegment qualified as NameSegment
import Unison.Parser.Ann (Ann)
import Unison.Parser.Ann qualified as Parser
import Unison.Prelude
@ -270,19 +267,6 @@ expectBranchForHash codebase hash =
Just branch -> pure branch
Nothing -> error $ reportBug "E412939" ("expectBranchForHash: " ++ show hash ++ " not found in codebase")
-- | Get the metadata attached to the term at a given path and name relative to the given branch.
termMetadata ::
-- | The branch to search inside. Use the current root if 'Nothing'.
Maybe (V2Branch.Branch Sqlite.Transaction) ->
Split ->
-- | There may be multiple terms at the given name. You can specify a Referent to
-- disambiguate if desired.
Maybe V2.Referent ->
Sqlite.Transaction [Map V2Branch.MetadataValue V2Branch.MetadataType]
termMetadata mayBranch (path, nameSeg) ref = do
b <- getShallowBranchAtPath path mayBranch
V2Branch.termMetadata b (coerce @NameSegment.NameSegment nameSeg) ref
-- | Get the lowest common ancestor of two branches, i.e. the most recent branch that is an ancestor of both branches.
lca :: (MonadIO m) => Codebase m v a -> Branch m -> Branch m -> m (Maybe (Branch m))
lca code b1@(Branch.headHash -> h1) b2@(Branch.headHash -> h2) = do

View File

@ -1,7 +1,4 @@
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Unison.Codebase.Branch
@ -131,7 +128,6 @@ import Unison.Util.List qualified as List
import Unison.Util.Monoid qualified as Monoid
import Unison.Util.Relation qualified as R
import Unison.Util.Relation qualified as Relation
import Unison.Util.Relation4 qualified as R4
import Unison.Util.Set qualified as Set
import Unison.Util.Star3 qualified as Star3
import Witherable (FilterableWithIndex (imapMaybe))
@ -192,7 +188,6 @@ terms =
\branch terms ->
branch {_terms = terms}
& deriveDeepTerms
& deriveDeepTermMetadata
types :: Lens' (Branch0 m) (Star TypeReference NameSegment)
types =
@ -201,7 +196,6 @@ types =
\branch types ->
branch {_types = types}
& deriveDeepTypes
& deriveDeepTypeMetadata
children :: Lens' (Branch0 m) (Map NameSegment (Branch m))
children = lens _children (\Branch0 {..} x -> branch0 _terms _types x _edits)
@ -242,15 +236,11 @@ branch0 terms types children edits =
-- These are all overwritten immediately
deepTerms = R.empty,
deepTypes = R.empty,
deepTermMetadata = R4.empty,
deepTypeMetadata = R4.empty,
deepPaths = Set.empty,
deepEdits = Map.empty
}
& deriveDeepTerms
& deriveDeepTypes
& deriveDeepTermMetadata
& deriveDeepTypeMetadata
& deriveDeepPaths
& deriveDeepEdits
@ -299,50 +289,6 @@ deriveDeepTypes branch =
children <- deepChildrenHelper e
go (work <> children) (types <> acc)
-- | Derive the 'deepTermMetadata' field of a branch.
deriveDeepTermMetadata :: forall m. Branch0 m -> Branch0 m
deriveDeepTermMetadata branch =
branch {deepTermMetadata = R4.fromList (makeDeepTermMetadata branch)}
where
makeDeepTermMetadata :: Branch0 m -> [(Referent, Name, Metadata.Type, Metadata.Value)]
makeDeepTermMetadata branch = State.evalState (go (Seq.singleton ([], 0, branch)) mempty) Set.empty
where
go ::
Seq (DeepChildAcc m) ->
[(Referent, Name, Metadata.Type, Metadata.Value)] ->
DeepState m [(Referent, Name, Metadata.Type, Metadata.Value)]
go Seq.Empty acc = pure acc
go (e@(reversePrefix, _, b0) Seq.:<| work) acc = do
let termMetadata :: [(Referent, Name, Metadata.Type, Metadata.Value)]
termMetadata =
map
(\(r, n, t, v) -> (r, Name.fromReverseSegments (n NonEmpty.:| reversePrefix), t, v))
(Metadata.starToR4List (_terms b0))
children <- deepChildrenHelper e
go (work <> children) (termMetadata <> acc)
-- | Derive the 'deepTypeMetadata' field of a branch.
deriveDeepTypeMetadata :: forall m. Branch0 m -> Branch0 m
deriveDeepTypeMetadata branch =
branch {deepTypeMetadata = R4.fromList (makeDeepTypeMetadata branch)}
where
makeDeepTypeMetadata :: Branch0 m -> [(TypeReference, Name, Metadata.Type, Metadata.Value)]
makeDeepTypeMetadata branch = State.evalState (go (Seq.singleton ([], 0, branch)) mempty) Set.empty
where
go ::
Seq (DeepChildAcc m) ->
[(TypeReference, Name, Metadata.Type, Metadata.Value)] ->
DeepState m [(TypeReference, Name, Metadata.Type, Metadata.Value)]
go Seq.Empty acc = pure acc
go (e@(reversePrefix, _, b0) Seq.:<| work) acc = do
let typeMetadata :: [(TypeReference, Name, Metadata.Type, Metadata.Value)]
typeMetadata =
map
(\(r, n, t, v) -> (r, Name.fromReverseSegments (n NonEmpty.:| reversePrefix), t, v))
(Metadata.starToR4List (_types b0))
children <- deepChildrenHelper e
go (work <> children) (typeMetadata <> acc)
-- | Derive the 'deepPaths' field of a branch.
deriveDeepPaths :: forall m. Branch0 m -> Branch0 m
deriveDeepPaths branch =
@ -483,7 +429,17 @@ one = Branch . Causal.one
empty0 :: Branch0 m
empty0 =
Branch0 mempty mempty mempty mempty True mempty mempty mempty mempty mempty mempty
Branch0
{ _terms = mempty,
_types = mempty,
_children = Map.empty,
_edits = Map.empty,
isEmpty0 = True,
deepTerms = Relation.empty,
deepTypes = Relation.empty,
deepPaths = Set.empty,
deepEdits = Map.empty
}
-- | Checks whether a branch is empty AND has no history.
isEmpty :: Branch m -> Bool
@ -718,15 +674,13 @@ batchUpdatesM (toList -> actions) curBranch = foldM execActions curBranch (group
pathLocation _ = ChildActions
-- todo: consider inlining these into Actions2
addTermName ::
Referent -> NameSegment -> Metadata.Metadata -> Branch0 m -> Branch0 m
addTermName r new md =
over terms (Metadata.insertWithMetadata (r, md) . Star3.insertD1 (r, new))
addTermName :: Referent -> NameSegment -> Branch0 m -> Branch0 m
addTermName r new =
over terms (Star3.insertD1 (r, new))
addTypeName ::
TypeReference -> NameSegment -> Metadata.Metadata -> Branch0 m -> Branch0 m
addTypeName r new md =
over types (Metadata.insertWithMetadata (r, md) . Star3.insertD1 (r, new))
addTypeName :: TypeReference -> NameSegment -> Branch0 m -> Branch0 m
addTypeName r new =
over types (Star3.insertD1 (r, new))
deleteTermName :: Referent -> NameSegment -> Branch0 m -> Branch0 m
deleteTermName r n b

View File

@ -70,12 +70,9 @@ data Branch0 m = Branch0
-- | True if a branch and its children have no definitions or edits in them.
-- (Computed recursively, and small enough to justify storing here to avoid computing more than once.)
isEmpty0 :: Bool,
-- names and metadata for this branch and its children
-- (ref, (name, value)) iff ref has metadata `value` at name `name`
-- names for this branch and its children
deepTerms :: Relation Referent Name,
deepTypes :: Relation Reference Name,
deepTermMetadata :: Metadata.R4 Referent Name,
deepTypeMetadata :: Metadata.R4 Reference Name,
deepPaths :: Set Path,
deepEdits :: Map Name PatchHash
}

View File

@ -5,37 +5,23 @@ import Data.Set qualified as Set
import U.Codebase.HashTags (PatchHash)
import Unison.Codebase.Branch (Branch0 (..))
import Unison.Codebase.Branch qualified as Branch
import Unison.Codebase.Metadata qualified as Metadata
import Unison.Codebase.Patch (Patch, PatchDiff)
import Unison.Codebase.Patch qualified as Patch
import Unison.Name (Name)
import Unison.Prelude
import Unison.Reference (Reference)
import Unison.Referent (Referent)
import Unison.Runtime.IOSource (isPropagatedValue)
import Unison.Util.Relation (Relation)
import Unison.Util.Relation qualified as R
import Unison.Util.Relation3 (Relation3)
import Unison.Util.Relation3 qualified as R3
import Unison.Util.Relation4 qualified as R4
data DiffType a = Create a | Delete a | Modify a deriving (Show)
-- todo: maybe simplify this file using Relation3?
data NamespaceSlice r = NamespaceSlice
{ names :: Relation r Name,
metadata :: Relation3 r Name Metadata.Value
}
deriving (Show)
data DiffSlice r = DiffSlice
{ -- tpatchUpdates :: Relation r r, -- old new
tallnamespaceUpdates :: Map Name (Set r, Set r),
talladds :: Relation r Name,
tallremoves :: Relation r Name,
trenames :: Map r (Set Name, Set Name), -- ref (old, new)
taddedMetadata :: Relation3 r Name Metadata.Value,
tremovedMetadata :: Relation3 r Name Metadata.Value
trenames :: Map r (Set Name, Set Name)
}
deriving stock (Generic, Show)
@ -51,10 +37,10 @@ diff0 old new = BranchDiff terms types <$> patchDiff old new
where
(terms, types) =
computeSlices
(deepr4ToSlice (Branch.deepTerms old) (Branch.deepTermMetadata old))
(deepr4ToSlice (Branch.deepTerms new) (Branch.deepTermMetadata new))
(deepr4ToSlice (Branch.deepTypes old) (Branch.deepTypeMetadata old))
(deepr4ToSlice (Branch.deepTypes new) (Branch.deepTypeMetadata new))
(Branch.deepTerms old)
(Branch.deepTerms new)
(Branch.deepTypes old)
(Branch.deepTypes new)
patchDiff :: forall m. (Monad m) => Branch0 m -> Branch0 m -> m (Map Name (DiffType PatchDiff))
patchDiff old new = do
@ -79,48 +65,33 @@ patchDiff old new = do
modified <- foldM f mempty (Set.intersection (Map.keysSet oldDeepEdits) (Map.keysSet newDeepEdits))
pure $ added <> removed <> modified
deepr4ToSlice ::
(Ord r) =>
R.Relation r Name ->
Metadata.R4 r Name ->
NamespaceSlice r
deepr4ToSlice deepNames deepMetadata =
NamespaceSlice deepNames (R4.d124 deepMetadata)
computeSlices ::
NamespaceSlice Referent ->
NamespaceSlice Referent ->
NamespaceSlice Reference ->
NamespaceSlice Reference ->
Relation Referent Name ->
Relation Referent Name ->
Relation Reference Name ->
Relation Reference Name ->
(DiffSlice Referent, DiffSlice Reference)
computeSlices oldTerms newTerms oldTypes newTypes = (termsOut, typesOut)
where
termsOut =
let nc = allNames oldTerms newTerms
let nc = R.outerJoinDomMultimaps oldTerms newTerms
nu = allNamespaceUpdates oldTerms newTerms
in DiffSlice
{ tallnamespaceUpdates = nu,
talladds = allAdds nc nu,
tallremoves = allRemoves nc nu,
trenames = remainingNameChanges nc,
taddedMetadata = addedMetadata oldTerms newTerms,
tremovedMetadata = removedMetadata oldTerms newTerms
trenames = remainingNameChanges nc
}
typesOut =
let nc = allNames oldTypes newTypes
let nc = R.outerJoinDomMultimaps oldTypes newTypes
nu = allNamespaceUpdates oldTypes newTypes
in DiffSlice
{ tallnamespaceUpdates = nu,
talladds = allAdds nc nu,
tallremoves = allRemoves nc nu,
trenames = remainingNameChanges nc,
taddedMetadata = addedMetadata oldTypes newTypes,
tremovedMetadata = removedMetadata oldTypes newTypes
trenames = remainingNameChanges nc
}
allNames :: (Ord r) => NamespaceSlice r -> NamespaceSlice r -> Map r (Set Name, Set Name)
allNames old new = R.outerJoinDomMultimaps (names old) (names new)
allAdds,
allRemoves ::
forall r.
@ -153,33 +124,14 @@ computeSlices oldTerms newTerms oldTypes newTypes = (termsOut, typesOut)
remainingNameChanges =
Map.filter (\(old, new) -> not (null old) && not (null new) && old /= new)
allNamespaceUpdates :: (Ord r) => NamespaceSlice r -> NamespaceSlice r -> Map Name (Set r, Set r)
allNamespaceUpdates :: (Ord r) => Relation r Name -> Relation r Name -> Map Name (Set r, Set r)
allNamespaceUpdates old new =
Map.filter f $ R.innerJoinRanMultimaps (names old) (names new)
Map.filter f $ R.innerJoinRanMultimaps old new
where
f (old, new) = old /= new
addedMetadata :: (Ord r) => NamespaceSlice r -> NamespaceSlice r -> Relation3 r Name Metadata.Value
addedMetadata old new = metadata new `R3.difference` metadata old
removedMetadata :: (Ord r) => NamespaceSlice r -> NamespaceSlice r -> Relation3 r Name Metadata.Value
removedMetadata old new = metadata old `R3.difference` metadata new
-- the namespace updates that aren't propagated
namespaceUpdates :: (Ord r) => DiffSlice r -> Map Name (Set r, Set r)
namespaceUpdates s = Map.mapMaybeWithKey f (tallnamespaceUpdates s)
namespaceUpdates s = Map.mapMaybe f (tallnamespaceUpdates s)
where
f name (olds, news) =
let news' = Set.difference news (Map.findWithDefault mempty name propagated)
in if null news' then Nothing else Just (olds, news')
propagated = propagatedUpdates s
propagatedUpdates :: (Ord r) => DiffSlice r -> Map Name (Set r)
propagatedUpdates s =
Map.fromList
[ (name, news)
| (name, (_olds0, news0)) <- Map.toList $ tallnamespaceUpdates s,
let news = Set.filter propagated news0
propagated rnew = R3.member rnew name isPropagatedValue (taddedMetadata s),
not (null news)
]
f (olds, news) =
if null news then Nothing else Just (olds, news)

View File

@ -6,10 +6,6 @@ module Unison.Codebase.BranchUtil
getBranch,
getTerm,
getType,
getTermMetadataAt,
getTypeMetadataAt,
getTermMetadataHQNamed,
getTypeMetadataHQNamed,
-- * Branch modifications
makeSetBranch,
@ -28,14 +24,10 @@ import Data.Map qualified as Map
import Data.Set qualified as Set
import Unison.Codebase.Branch (Branch, Branch0)
import Unison.Codebase.Branch qualified as Branch
import Unison.Codebase.Metadata (Metadata)
import Unison.Codebase.Metadata qualified as Metadata
import Unison.Codebase.Patch (Patch)
import Unison.Codebase.Path (Path)
import Unison.Codebase.Path qualified as Path
import Unison.HashQualified' (HashQualified (HashQualified, NameOnly))
import Unison.HashQualified' qualified as HQ'
import Unison.NameSegment (NameSegment)
import Unison.Names (Names)
import Unison.Names qualified as Names
import Unison.Prelude
@ -44,9 +36,7 @@ import Unison.Reference qualified as Reference
import Unison.Referent (Referent)
import Unison.Referent qualified as Referent
import Unison.ShortHash qualified as SH
import Unison.Util.List qualified as List
import Unison.Util.Relation qualified as R
import Unison.Util.Relation4 qualified as R4
import Unison.Util.Star3 qualified as Star3
-- | Creates a branch containing all of the given names, with a single history node.
@ -55,10 +45,8 @@ fromNames names0 = Branch.stepManyAt (typeActions <> termActions) Branch.empty
where
typeActions = map doType . R.toList $ Names.types names0
termActions = map doTerm . R.toList $ Names.terms names0
-- doTerm :: (Name, Referent) -> (Path, Branch0 m -> Branch0 m)
doTerm (n, r) = makeAddTermName (Path.splitFromName n) r mempty -- no metadata
-- doType :: (Name, Reference) -> (Path, Branch0 m -> Branch0 m)
doType (n, r) = makeAddTypeName (Path.splitFromName n) r mempty -- no metadata
doTerm (n, r) = makeAddTermName (Path.splitFromName n) r
doType (n, r) = makeAddTypeName (Path.splitFromName n) r
getTerm :: Path.HQSplit -> Branch0 m -> Set Referent
getTerm (p, hq) b = case hq of
@ -68,31 +56,6 @@ getTerm (p, hq) b = case hq of
filter sh = Set.filter (SH.isPrefixOf sh . Referent.toShortHash)
terms = Branch._terms (Branch.getAt0 p b)
getTermMetadataHQNamed ::
(Path.Path, HQ'.HQSegment) -> Branch0 m -> Metadata.R4 Referent NameSegment
getTermMetadataHQNamed (path, hqseg) b =
R4.filter (\(r, n, _t, _v) -> HQ'.matchesNamedReferent n r hqseg) terms
where
terms = Metadata.starToR4 . Branch._terms $ Branch.getAt0 path b
getTypeMetadataHQNamed ::
(Path.Path, HQ'.HQSegment) ->
Branch0 m ->
Metadata.R4 Reference NameSegment
getTypeMetadataHQNamed (path, hqseg) b =
R4.filter (\(r, n, _t, _v) -> HQ'.matchesNamedReference n r hqseg) types
where
types = Metadata.starToR4 . Branch._types $ Branch.getAt0 path b
-- todo: audit usages and maybe eliminate!
-- Only returns metadata for the term at the exact level given
getTermMetadataAt :: (Path.Path, a) -> Referent -> Branch0 m -> Metadata
getTermMetadataAt (path, _) r b = Set.fromList <$> List.multimap mdList
where
mdList :: [(Metadata.Type, Metadata.Value)]
mdList = Set.toList . R.ran . Star3.d3 . Star3.selectFact (Set.singleton r) $ terms
terms = Branch._terms $ Branch.getAt0 path b
getType :: Path.HQSplit -> Branch0 m -> Set Reference.TypeReference
getType (p, hq) b = case hq of
NameOnly n -> Star3.lookupD1 n types
@ -101,13 +64,6 @@ getType (p, hq) b = case hq of
filter sh = Set.filter (SH.isPrefixOf sh . Reference.toShortHash)
types = Branch._types (Branch.getAt0 p b)
getTypeMetadataAt :: (Path.Path, a) -> Reference -> Branch0 m -> Metadata
getTypeMetadataAt (path, _) r b = Set.fromList <$> List.multimap mdList
where
mdList :: [(Metadata.Type, Metadata.Value)]
mdList = Set.toList . R.ran . Star3.d3 . Star3.selectFact (Set.singleton r) $ types
types = Branch._types $ Branch.getAt0 path b
getBranch :: Path.Split -> Branch0 m -> Maybe (Branch m)
getBranch (p, seg) b = case Path.toList p of
[] -> Map.lookup seg (Branch._children b)
@ -115,8 +71,8 @@ getBranch (p, seg) b = case Path.toList p of
(Branch.head <$> Map.lookup h (Branch._children b))
>>= getBranch (Path.fromList p, seg)
makeAddTermName :: Path.Split -> Referent -> Metadata -> (Path, Branch0 m -> Branch0 m)
makeAddTermName (p, name) r md = (p, Branch.addTermName r name md)
makeAddTermName :: Path.Split -> Referent -> (Path, Branch0 m -> Branch0 m)
makeAddTermName (p, name) r = (p, Branch.addTermName r name)
makeDeleteTermName :: Path.Split -> Referent -> (Path, Branch0 m -> Branch0 m)
makeDeleteTermName (p, name) r = (p, Branch.deleteTermName r name)
@ -133,12 +89,11 @@ makeReplacePatch (p, name) patch = (p, Branch.replacePatch name patch)
makeDeletePatch :: Path.Split -> (Path, Branch0 m -> Branch0 m)
makeDeletePatch (p, name) = (p, Branch.deletePatch name)
makeAddTypeName :: Path.Split -> Reference -> Metadata -> (Path, Branch0 m -> Branch0 m)
makeAddTypeName (p, name) r md = (p, Branch.addTypeName r name md)
makeAddTypeName :: Path.Split -> Reference -> (Path, Branch0 m -> Branch0 m)
makeAddTypeName (p, name) r = (p, Branch.addTypeName r name)
makeDeleteTypeName :: Path.Split -> Reference -> (Path, Branch0 m -> Branch0 m)
makeDeleteTypeName (p, name) r = (p, Branch.deleteTypeName r name)
makeSetBranch ::
Path.Split -> Branch m -> (Path, Branch0 m -> Branch0 m)
makeSetBranch :: Path.Split -> Branch m -> (Path, Branch0 m -> Branch0 m)
makeSetBranch (p, name) b = (p, Branch.setChildBranch name b)

View File

@ -52,11 +52,6 @@ hasMetadataWithType a t = Set.member t . R.lookupDom a . Star3.d2
inserts :: (Ord a, Ord n) => [(a, Type, Value)] -> Star a n -> Star a n
inserts tups s = foldl' (flip insert) s tups
insertWithMetadata ::
(Ord a, Ord n) => (a, Metadata) -> Star a n -> Star a n
insertWithMetadata (a, md) =
inserts [(a, ty, v) | (ty, vs) <- Map.toList md, v <- toList vs]
insert :: (Ord a, Ord n) => (a, Type, Value) -> Star a n -> Star a n
insert (a, ty, v) = Star3.insertD23 (a, ty, (ty, v))

View File

@ -10,12 +10,12 @@ import Data.Set qualified as Set
import Unison.HashQualified' qualified as HQ'
import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.Names (Names)
import Unison.Names qualified as Names
import Unison.NamesWithHistory qualified as Names
import Unison.Prelude
import Unison.PrettyPrintEnv (PrettyPrintEnv (PrettyPrintEnv))
import Unison.Util.Relation qualified as Rel
import Unison.Names (Names)
fromNames :: Int -> Names -> PrettyPrintEnv
fromNames len names = PrettyPrintEnv terms' types'

View File

@ -93,9 +93,18 @@ resolveUnresolvedModifier unresolvedModifier var =
UnresolvedModifier'Structural -> pure (DD.Structural <$ unresolvedModifier)
UnresolvedModifier'UniqueWithGuid guid -> pure (DD.Unique guid <$ unresolvedModifier)
UnresolvedModifier'UniqueWithoutGuid guid0 -> do
ParsingEnv {uniqueTypeGuid} <- ask
guid <- fromMaybe guid0 <$> lift (lift (uniqueTypeGuid (Name.unsafeFromVar var)))
pure (DD.Unique guid <$ unresolvedModifier)
unique <- resolveUniqueModifier var guid0
pure $ unique <$ unresolvedModifier
resolveUniqueModifier :: (Monad m, Var v) => v -> Text -> P v m DD.Modifier
resolveUniqueModifier var guid0 = do
ParsingEnv {uniqueTypeGuid} <- ask
guid <- fromMaybe guid0 <$> lift (lift (uniqueTypeGuid (Name.unsafeFromVar var)))
pure $ DD.Unique guid
defaultUniqueModifier :: (Monad m, Var v) => v -> P v m DD.Modifier
defaultUniqueModifier var =
uniqueName 32 >>= resolveUniqueModifier var
-- unique[someguid] type Blah = ...
modifier :: (Monad m, Var v) => P v m (Maybe (L.Token UnresolvedModifier))
@ -132,7 +141,7 @@ dataDeclaration ::
Maybe (L.Token UnresolvedModifier) ->
P v m (v, DataDeclaration v Ann, Accessors v)
dataDeclaration maybeUnresolvedModifier = do
keywordTok <- fmap void (reserved "type") <|> openBlockWith "type"
_ <- fmap void (reserved "type") <|> openBlockWith "type"
(name, typeArgs) <-
(,)
<$> TermParser.verifyRelativeVarName prefixDefinitionName
@ -181,7 +190,13 @@ dataDeclaration maybeUnresolvedModifier = do
closingAnn :: Ann
closingAnn = last (ann eq : ((\(_, _, t) -> ann t) <$> constructors))
case maybeUnresolvedModifier of
Nothing -> P.customFailure $ MissingTypeModifier ("type" <$ keywordTok) name
Nothing -> do
modifier <- defaultUniqueModifier (L.payload name)
pure
( L.payload name,
DD.mkDataDecl' modifier closingAnn typeArgVs constructors,
accessors
)
Just unresolvedModifier -> do
modifier <- resolveUnresolvedModifier unresolvedModifier (L.payload name)
pure
@ -196,7 +211,7 @@ effectDeclaration ::
Maybe (L.Token UnresolvedModifier) ->
P v m (v, EffectDeclaration v Ann)
effectDeclaration maybeUnresolvedModifier = do
keywordTok <- fmap void (reserved "ability") <|> openBlockWith "ability"
_ <- fmap void (reserved "ability") <|> openBlockWith "ability"
name <- TermParser.verifyRelativeVarName prefixDefinitionName
typeArgs <- many (TermParser.verifyRelativeVarName prefixDefinitionName)
let typeArgVs = L.payload <$> typeArgs
@ -208,7 +223,12 @@ effectDeclaration maybeUnresolvedModifier = do
last $ ann blockStart : ((\(_, _, t) -> ann t) <$> constructors)
case maybeUnresolvedModifier of
Nothing -> P.customFailure $ MissingTypeModifier ("ability" <$ keywordTok) name
Nothing -> do
modifier <- defaultUniqueModifier (L.payload name)
pure
( L.payload name,
DD.mkEffectDecl' modifier closingAnn typeArgVs constructors
)
Just unresolvedModifier -> do
modifier <- resolveUnresolvedModifier unresolvedModifier (L.payload name)
pure

View File

@ -199,8 +199,9 @@ fieldNames env r name dd = do
prettyModifier :: DD.Modifier -> Pretty SyntaxText
prettyModifier DD.Structural = fmt S.DataTypeModifier "structural"
prettyModifier (DD.Unique _uid) =
fmt S.DataTypeModifier "unique" -- <> ("[" <> P.text uid <> "] ")
prettyModifier (DD.Unique _uid) = mempty -- don't print anything since 'unique' is the default
-- leaving this comment for the historical record so the syntax for uid is not forgotten
-- fmt S.DataTypeModifier "unique" -- <> ("[" <> P.text uid <> "] ")
prettyDataHeader ::
(Var v) => HQ.HashQualified Name -> DD.DataDeclaration v a -> Pretty SyntaxText

View File

@ -47,10 +47,10 @@ file = do
Left es -> resolutionFailures (toList es)
let accessors :: [[(v, Ann, Term v Ann)]]
accessors =
[ DD.generateRecordAccessors (toPair <$> fields) (L.payload typ) r
| (typ, fields) <- parsedAccessors,
Just (r, _) <- [Map.lookup (L.payload typ) (UF.datas env)]
]
[ DD.generateRecordAccessors (toPair <$> fields) (L.payload typ) r
| (typ, fields) <- parsedAccessors,
Just (r, _) <- [Map.lookup (L.payload typ) (UF.datas env)]
]
toPair (tok, typ) = (L.payload tok, ann tok <> ann typ)
let importNames = [(Name.unsafeFromVar v, Name.unsafeFromVar v2) | (v, v2) <- imports]
let locals = Names.importing importNames (UF.names env)
@ -97,7 +97,7 @@ file = do
-- A function to replace unique local term suffixes with their
-- fully qualified name
replacements = [ (v, Term.var () v2) | (v,v2) <- Map.toList canonicalVars, v /= v2 ]
replacements = [(v, Term.var () v2) | (v, v2) <- Map.toList canonicalVars, v /= v2]
resolveLocals = ABT.substsInheritAnnotation replacements
let bindNames = Term.bindSomeNames Name.unsafeFromVar (Set.fromList fqLocalTerms) curNames . resolveLocals
terms <- case List.validate (traverseOf _3 bindNames) terms of

View File

@ -18,7 +18,7 @@ usage() {
echo "E.g."
echo "$0 M4a"
echo ""
echo "The latest release is: $(git tag --list 'release/*' | sort -r | head -n 1 | sed 's/release\///')"
echo "I think the latest release is: $(git tag --list 'release/*' | grep -v M | sort -rV | head -n 1 | sed 's/release\///')"
}
if [[ -z "$1" ]] ; then

View File

@ -1,7 +1,6 @@
-- | @.unisonConfig@ file utilities
module Unison.Cli.UnisonConfigUtils
( defaultMetadataKey,
gitUrlKey,
( gitUrlKey,
remoteMappingKey,
resolveConfiguredUrl,
)
@ -34,9 +33,6 @@ configKey k p =
NameSegment.toText
(Path.toSeq $ Path.unabsolute p)
defaultMetadataKey :: Path.Absolute -> Text
defaultMetadataKey = configKey "DefaultMetadata"
gitUrlKey :: Path.Absolute -> Text
gitUrlKey = configKey "GitUrl"

View File

@ -72,7 +72,6 @@ import Unison.Codebase.Editor.HandleInput.DeleteBranch (handleDeleteBranch)
import Unison.Codebase.Editor.HandleInput.DeleteProject (handleDeleteProject)
import Unison.Codebase.Editor.HandleInput.FindAndReplace (handleStructuredFindI, handleStructuredFindReplaceI)
import Unison.Codebase.Editor.HandleInput.Load (EvalMode (Sandboxed), evalUnisonFile, handleLoad, loadUnisonFile)
import Unison.Codebase.Editor.HandleInput.MetadataUtils (addDefaultMetadata, manageLinks)
import Unison.Codebase.Editor.HandleInput.MoveAll (handleMoveAll)
import Unison.Codebase.Editor.HandleInput.MoveBranch (doMoveBranch)
import Unison.Codebase.Editor.HandleInput.MoveTerm (doMoveTerm)
@ -134,7 +133,6 @@ import Unison.Hash qualified as Hash
import Unison.HashQualified qualified as HQ
import Unison.HashQualified' qualified as HQ'
import Unison.HashQualified' qualified as HashQualified
import Unison.Hashing.V2.Convert qualified as Hashing
import Unison.JitInfo qualified as JitInfo
import Unison.LabeledDependency (LabeledDependency)
import Unison.LabeledDependency qualified as LD
@ -197,7 +195,6 @@ import Unison.Util.Pretty qualified as P
import Unison.Util.Pretty qualified as Pretty
import Unison.Util.Relation qualified as R
import Unison.Util.Relation qualified as Relation
import Unison.Util.Relation4 qualified as R4
import Unison.Util.Set qualified as Set
import Unison.Util.Star3 qualified as Star3
import Unison.Util.TransitiveClosure (transitiveClosure)
@ -585,15 +582,7 @@ loop e = do
when (not (Set.null destTerms)) do
Cli.returnEarly (TermAlreadyExists dest' destTerms)
description <- inputDescription input
srcMetadata <-
case src of
Left _ -> pure Metadata.empty
Right (path, _) -> do
root0 <- Cli.getRootBranch0
pure (BranchUtil.getTermMetadataAt (Path.convert path, ()) srcTerm root0)
Cli.stepAt
description
(BranchUtil.makeAddTermName (Path.convert dest) srcTerm srcMetadata)
Cli.stepAt description (BranchUtil.makeAddTermName (Path.convert dest) srcTerm)
Cli.respond Success
AliasTypeI src' dest' -> do
src <- traverseOf _Right Cli.resolveSplit' src'
@ -616,15 +605,7 @@ loop e = do
when (not (Set.null destTypes)) do
Cli.returnEarly (TypeAlreadyExists dest' destTypes)
description <- inputDescription input
srcMetadata <-
case src of
Left _ -> pure Metadata.empty
Right (path, _) -> do
root0 <- Cli.getRootBranch0
pure (BranchUtil.getTypeMetadataAt (Path.convert path, ()) srcType root0)
Cli.stepAt
description
(BranchUtil.makeAddTypeName (Path.convert dest) srcType srcMetadata)
Cli.stepAt description (BranchUtil.makeAddTypeName (Path.convert dest) srcType)
Cli.respond Success
-- this implementation will happily produce name conflicts,
@ -652,9 +633,7 @@ loop e = do
Path.HQSplit ->
([Path.HQSplit], [(Path, Branch0 m -> Branch0 m)])
go root0 currentBranch0 dest (missingSrcs, actions) hqsrc =
let src :: Path.Split
src = second HQ'.toName hqsrc
proposedDest :: Path.Split
let proposedDest :: Path.Split
proposedDest = second HQ'.toName hqProposedDest
hqProposedDest :: Path.HQSplit
hqProposedDest = first Path.unabsolute $ Path.resolve dest hqsrc
@ -668,8 +647,7 @@ loop e = do
-- happy path
Just . map addAlias . toList $ Set.difference rsrcs existing
where
addAlias r = BranchUtil.makeAddTypeName proposedDest r (oldMD r)
oldMD r = BranchUtil.getTypeMetadataAt src r currentBranch0
addAlias r = BranchUtil.makeAddTypeName proposedDest r
doTerm :: Maybe [(Path, Branch0 m -> Branch0 m)]
doTerm = case ( BranchUtil.getTerm hqsrc currentBranch0,
BranchUtil.getTerm hqProposedDest root0
@ -678,8 +656,7 @@ loop e = do
(rsrcs, existing) ->
Just . map addAlias . toList $ Set.difference rsrcs existing
where
addAlias r = BranchUtil.makeAddTermName proposedDest r (oldMD r)
oldMD r = BranchUtil.getTermMetadataAt src r currentBranch0
addAlias r = BranchUtil.makeAddTermName proposedDest r
in case (doType, doTerm) of
(Nothing, Nothing) -> (missingSrcs :> hqsrc, actions)
(Just as, Nothing) -> (missingSrcs, actions ++ as)
@ -714,26 +691,10 @@ loop e = do
types' :: [(Reference, [HQ'.HashQualified Name])]
types' = map (\r -> (r, PPE.allTypeNames unsuffixifiedPPE r)) (Set.toList types)
Cli.respond $ ListNames global hqLength types' terms'
LinkI mdValue srcs -> do
description <- inputDescription input
manageLinks False srcs [mdValue] Metadata.insert
Cli.syncRoot description
UnlinkI mdValue srcs -> do
description <- inputDescription input
manageLinks False srcs [mdValue] Metadata.delete
Cli.syncRoot description
-- > links List.map (.Docs .English)
-- > links List.map -- give me all the
-- > links Optional License
LinksI src mdTypeStr -> do
(ppe, out) <- getLinks (show input) src (Right mdTypeStr)
#numberedArgs .= fmap (HQ.toString . view _1) out
let biasedPPE = (PPE.biasTo (maybeToList . Path.toName' . HQ'.toName $ Path.unsplitHQ' src) ppe)
Cli.respond $ ListOfLinks biasedPPE out
DocsI srcs -> do
basicPrettyPrintNames <- getBasicPrettyPrintNames
for_ srcs (docsI (show input) basicPrettyPrintNames)
for_ srcs (docsI basicPrettyPrintNames)
CreateAuthorI authorNameSegment authorFullName -> do
Cli.Env {codebase} <- ask
initialBranch <- Cli.getCurrentBranch
@ -750,9 +711,9 @@ loop e = do
guidPath <- Cli.resolveSplit' (authorPath' |> "guid")
Cli.stepManyAt
description
[ BranchUtil.makeAddTermName (Path.convert authorPath) (d authorRef) mempty,
BranchUtil.makeAddTermName (Path.convert copyrightHolderPath) (d copyrightHolderRef) mempty,
BranchUtil.makeAddTermName (Path.convert guidPath) (d guidRef) mempty
[ BranchUtil.makeAddTermName (Path.convert authorPath) (d authorRef),
BranchUtil.makeAddTermName (Path.convert copyrightHolderPath) (d copyrightHolderRef),
BranchUtil.makeAddTermName (Path.convert guidPath) (d guidRef)
]
currentPath <- Cli.getCurrentPath
finalBranch <- Cli.getCurrentBranch0
@ -979,7 +940,6 @@ loop e = do
Cli.runTransaction . Codebase.addDefsToCodebase codebase . SlurpResult.filterUnisonFile sr $ uf
ppe <- prettyPrintEnvDecl =<< displayNames uf
Cli.respond $ SlurpOutput input (PPE.suffixifiedPPE ppe) sr
addDefaultMetadata adds
Cli.syncRoot description
SaveExecuteResultI resultName -> handleAddRun input resultName
PreviewAddI requestedNames -> do
@ -1098,12 +1058,12 @@ loop e = do
currentBranch <- Branch.withoutTransitiveLibs <$> Cli.getCurrentBranch0
let projCtx = projectContextFromPath currentPath
case Map.lookup command InputPatterns.patternMap of
Just (IP.InputPattern {argTypes}) -> do
Just (IP.InputPattern {args = argTypes}) -> do
zip argTypes args & Monoid.foldMapM \case
((_, IP.ArgumentType {fzfResolver = Just IP.FZFResolver {argDescription, getOptions}}), "_") -> do
((argName, _, IP.ArgumentType {fzfResolver = Just IP.FZFResolver {getOptions}}), "_") -> do
results <- liftIO $ getOptions codebase projCtx currentBranch
Cli.respond (DebugDisplayFuzzyOptions (Text.unpack argDescription) (Text.unpack <$> results))
((_, IP.ArgumentType {fzfResolver = Nothing}), "_") -> do
Cli.respond (DebugDisplayFuzzyOptions argName (Text.unpack <$> results))
((_, _, IP.ArgumentType {fzfResolver = Nothing}), "_") -> do
Cli.respond DebugFuzzyOptionsNoResolver
_ -> pure ()
Nothing -> do
@ -1122,12 +1082,12 @@ loop e = do
Causal.Merge h _bh b (Map.toList -> tails) -> goBranch h b (map fst tails) (tails ++ queue)
goBranch :: forall m. (Monad m) => CausalHash -> Branch0 m -> [CausalHash] -> [(CausalHash, m (Branch.UnwrappedBranch m))] -> StateT (Set CausalHash) m ()
goBranch h b (Set.fromList -> causalParents) queue = case b of
Branch0 terms0 types0 children0 patches0 _ _ _ _ _ _ _ ->
let wrangleMetadata :: (Ord r, Ord n) => Metadata.Star r n -> r -> (r, (Set n, Set Metadata.Value))
wrangleMetadata s r =
(r, (R.lookupDom r $ Star3.d1 s, Set.map snd . R.lookupDom r $ Star3.d3 s))
terms = Map.fromList . map (wrangleMetadata terms0) . Foldable.toList $ Star3.fact terms0
types = Map.fromList . map (wrangleMetadata types0) . Foldable.toList $ Star3.fact types0
Branch0 terms0 types0 children0 patches0 _ _ _ _ _ ->
let ignoreMetadata :: (Ord r, Ord n) => Metadata.Star r n -> r -> (r, Set n)
ignoreMetadata s r =
(r, R.lookupDom r $ Star3.d1 s)
terms = Map.fromList . map (ignoreMetadata terms0) . Foldable.toList $ Star3.fact terms0
types = Map.fromList . map (ignoreMetadata types0) . Foldable.toList $ Star3.fact types0
patches = fmap fst patches0
children = fmap Branch.headHash children0
in do
@ -1150,10 +1110,9 @@ loop e = do
]
)
where
prettyLinks renderR r [] = P.indentN 2 $ P.text (renderR r)
prettyLinks renderR r links = P.indentN 2 (P.lines (P.text (renderR r) : (links <&> \r -> "+ " <> P.text (Reference.toText r))))
prettyDefn renderR (r, (Foldable.toList -> names, Foldable.toList -> links)) =
P.lines (P.text . NameSegment.toText <$> if null names then [NameSegment "<unnamed>"] else names) <> P.newline <> prettyLinks renderR r links
prettyRef renderR r = P.indentN 2 $ P.text (renderR r)
prettyDefn renderR (r, Foldable.toList -> names) =
P.lines (P.text . NameSegment.toText <$> if null names then [NameSegment "<unnamed>"] else names) <> P.newline <> prettyRef renderR r
rootBranch <- Cli.getRootBranch
void . liftIO . flip State.execStateT mempty $ goCausal [getCausal rootBranch]
DebugDumpNamespaceSimpleI -> do
@ -1336,12 +1295,6 @@ inputDescription input =
ExecuteI s args -> pure ("execute " <> Text.unwords (fmap Text.pack (s : args)))
IOTestI hq -> pure ("io.test " <> HQ.toText hq)
IOTestAllI -> pure "io.test.all"
LinkI md defs0 -> do
defs <- traverse hqs' defs0
pure ("link " <> HQ.toText md <> " " <> Text.intercalate " " defs)
UnlinkI md defs0 -> do
defs <- traverse hqs' defs0
pure ("unlink " <> HQ.toText md <> " " <> Text.intercalate " " defs)
UpdateBuiltinsI -> pure "builtins.update"
MergeBuiltinsI -> pure "builtins.merge"
MergeIOBuiltinsI -> pure "builtins.mergeio"
@ -1399,7 +1352,6 @@ inputDescription input =
StructuredFindReplaceI {} -> wat
GistI {} -> wat
HistoryI {} -> wat
LinksI {} -> wat
ListDependenciesI {} -> wat
ListDependentsI {} -> wat
ListEditsI {} -> wat
@ -1812,49 +1764,6 @@ doDisplay outputLoc names tm = do
else do
writeUtf8 filePath txt
getLinks ::
SrcLoc ->
Path.HQSplit' ->
Either (Set Reference) (Maybe String) ->
Cli
( PPE.PrettyPrintEnv,
-- e.g. ("Foo.doc", #foodoc, Just (#builtin.Doc)
[(HQ.HashQualified Name, Reference, Maybe (Type Symbol Ann))]
)
getLinks srcLoc src =
getLinks' src <=< \case
Left s -> pure (Just s)
Right Nothing -> pure Nothing
Right (Just mdTypeStr) -> do
typ <- parseType srcLoc mdTypeStr
pure (Just (Set.singleton (Hashing.typeToReference typ)))
getLinks' ::
Path.HQSplit' -> -- definition to print metadata of
Maybe (Set Reference) -> -- return all metadata if empty
Cli
( PPE.PrettyPrintEnv,
-- e.g. ("Foo.doc", #foodoc, Just (#builtin.Doc)
[(HQ.HashQualified Name, Reference, Maybe (Type Symbol Ann))]
)
getLinks' src selection0 = do
Cli.Env {codebase} <- ask
root0 <- Cli.getRootBranch0
p <- Path.convert <$> Cli.resolveSplit' src -- ex: the (parent,hqsegment) of `List.map` - `List`
let -- all metadata (type+value) associated with name `src`
allMd =
R4.d34 (BranchUtil.getTermMetadataHQNamed p root0)
<> R4.d34 (BranchUtil.getTypeMetadataHQNamed p root0)
allMd' = maybe allMd (`R.restrictDom` allMd) selection0
-- then list the values after filtering by type
allRefs :: Set Reference = R.ran allMd'
sigs <- Cli.runTransaction (for (toList allRefs) (Codebase.getTypeOfReferent codebase . Referent.Ref))
ppe <- prettyPrintEnvDecl =<< makePrintNamesFromLabeled'
let ppeDecl = PPE.unsuffixifiedPPE ppe
let sortedSigs = sortOn snd (toList allRefs `zip` sigs)
let out = [(PPE.termName ppeDecl (Referent.Ref r), r, t) | (r, t) <- sortedSigs]
pure (PPE.suffixifiedPPE ppe, out)
-- | Show todo output if there are any conflicts or edits.
doShowTodoOutput :: Patch -> Path.Absolute -> Cli ()
doShowTodoOutput patch scopePath = do
@ -2392,13 +2301,12 @@ displayI names outputLoc hq = do
ns <- displayNames unisonFile
doDisplay outputLoc ns tm
docsI :: SrcLoc -> Names -> Path.HQSplit' -> Cli ()
docsI srcLoc names src =
docsI :: Names -> Path.HQSplit' -> Cli ()
docsI prettyPrintNames src =
fileByName
where
{- Given `docs foo`, we look for docs in 3 places, in this order:
(fileByName) First check the file for `foo.doc`, and if found do `display foo.doc`
(codebaseByMetadata) Next check for doc metadata linked to `foo` in the codebase
(codebaseByName) Lastly check for `foo.doc` in the codebase and if found do `display foo.doc`
-}
hq :: HQ.HashQualified Name
@ -2414,35 +2322,11 @@ docsI srcLoc names src =
fileByName = do
ns <- maybe mempty UF.typecheckedToNames <$> Cli.getLatestTypecheckedFile
case Names.lookupHQTerm Names.IncludeSuffixes dotDoc ns of
s | Set.size s == 1 -> do
s | Set.size s == 1 ->
-- the displayI command expects full term names, so we resolve
-- the hash back to its full name in the file
displayI names ConsoleLocation $ Names.longestTermName 10 (Set.findMin s) ns
_ -> codebaseByMetadata
codebaseByMetadata :: Cli ()
codebaseByMetadata = do
(ppe, out) <- getLinks srcLoc src (Left $ Set.fromList [DD.docRef, IOSource.doc2Ref])
case out of
[] -> codebaseByName
[(_name, ref, _tm)] -> do
len <- Cli.runTransaction Codebase.branchHashLength
let tm = Term.ref External ref
tm <- RuntimeUtils.evalUnisonTerm True (PPE.fromNames len names) True tm
doDisplay ConsoleLocation names (Term.unannotate tm)
out -> do
#numberedArgs .= fmap (HQ.toString . view _1) out
Cli.respond $ ListOfLinks ppe out
codebaseByName :: Cli ()
codebaseByName = do
parseNames <- basicParseNames
case Names.lookupHQTerm Names.IncludeSuffixes dotDoc parseNames of
s
| Set.size s == 1 -> displayI names ConsoleLocation dotDoc
| Set.size s == 0 -> Cli.respond $ ListOfLinks PPE.empty []
-- todo: return a list of links here too
| otherwise -> Cli.respond $ ListOfLinks PPE.empty []
displayI prettyPrintNames ConsoleLocation (Names.longestTermName 10 (Set.findMin s) ns)
_ -> displayI prettyPrintNames ConsoleLocation dotDoc
loadDisplayInfo ::
Codebase m Symbol Ann ->

View File

@ -1,176 +0,0 @@
-- | Helpers/utils that have to do with term/type metadata.
module Unison.Codebase.Editor.HandleInput.MetadataUtils
( addDefaultMetadata,
manageLinks,
)
where
import Control.Lens
import Control.Monad.Except
import Control.Monad.Reader (ask)
import Data.Set qualified as Set
import Unison.Cli.Monad (Cli)
import Unison.Cli.Monad qualified as Cli
import Unison.Cli.MonadUtils qualified as Cli
import Unison.Cli.UnisonConfigUtils (defaultMetadataKey)
import Unison.Codebase qualified as Codebase
import Unison.Codebase.Branch qualified as Branch
import Unison.Codebase.Editor.HandleInput.NamespaceDiffUtils (diffHelper)
import Unison.Codebase.Editor.Output
import Unison.Codebase.Editor.Output.BranchDiff qualified as OBranchDiff
import Unison.Codebase.Editor.SlurpComponent (SlurpComponent (..))
import Unison.Codebase.Editor.SlurpComponent qualified as SC
import Unison.Codebase.Metadata qualified as Metadata
import Unison.Codebase.Path qualified as Path
import Unison.CommandLine.InputPatterns qualified as InputPatterns
import Unison.HashQualified qualified as HQ
import Unison.Hashing.V2.Convert qualified as Hashing
import Unison.Name (Name)
import Unison.NameSegment (NameSegment (..))
import Unison.Prelude
import Unison.PrettyPrintEnv qualified as PPE
import Unison.Referent (Referent)
import Unison.Referent qualified as Referent
import Unison.Server.Backend qualified as Backend
import Unison.Syntax.Name qualified as Name (unsafeFromVar)
import Unison.Util.Monoid qualified as Monoid
import Unison.Util.Relation qualified as R
import Unison.Util.Set qualified as Set
-- Add default metadata to all added types and terms in a slurp component.
--
-- No-op if the slurp component is empty.
addDefaultMetadata :: SlurpComponent -> Cli ()
addDefaultMetadata adds =
when (not (SC.isEmpty adds)) do
Cli.time "add-default-metadata" do
currentPath' <- Cli.getCurrentPath
let addedVs = Set.toList $ SC.types adds <> SC.terms adds
addedNs = traverse (Path.hqSplitFromName' . Name.unsafeFromVar) addedVs
case addedNs of
Nothing ->
error $
"I couldn't parse a name I just added to the codebase! "
<> "-- Added names: "
<> show addedVs
Just addedNames ->
resolveDefaultMetadata currentPath' >>= \case
[] -> pure ()
dm -> do
traverse InputPatterns.parseHashQualifiedName dm & \case
Left err -> do
Cli.respond $
ConfiguredMetadataParseError
(Path.absoluteToPath' currentPath')
(show dm)
err
Right defaultMeta -> do
manageLinks True addedNames defaultMeta Metadata.insert
-- | Add/remove links between definitions and metadata.
-- `silent` controls whether this produces any output to the user.
-- `srcs` is (names of the) definitions to pass to `op`
-- `mdValues` is (names of the) metadata to pass to `op`
-- `op` is the operation to add/remove/alter metadata mappings.
-- e.g. `Metadata.insert` is passed to add metadata links.
manageLinks ::
Bool ->
[Path.HQSplit'] ->
[HQ.HashQualified Name] ->
( forall r.
(Ord r) =>
(r, Metadata.Type, Metadata.Value) ->
Branch.Star r NameSegment ->
Branch.Star r NameSegment
) ->
Cli ()
manageLinks silent srcs' metadataNames op = do
metadatas <- traverse resolveMetadata metadataNames
before <- Cli.getRootBranch0
srcs <- traverse Cli.resolveSplit' srcs'
srcle <- Monoid.foldMapM Cli.getTermsAt srcs
srclt <- Monoid.foldMapM Cli.getTypesAt srcs
for_ metadatas \case
Left errOutput -> Cli.respond errOutput
Right (mdType, mdValue) -> do
let step =
let tmUpdates terms = foldl' go terms srcle
where
go terms src = op (src, mdType, mdValue) terms
tyUpdates types = foldl' go types srclt
where
go types src = op (src, mdType, mdValue) types
in over Branch.terms tmUpdates . over Branch.types tyUpdates
let steps = map (\(path, _hq) -> (Path.unabsolute path, step)) srcs
Cli.stepManyAtNoSync steps
if silent
then Cli.respond DefaultMetadataNotification
else do
after <- Cli.getRootBranch0
(ppe, diff) <- diffHelper before after
if OBranchDiff.isEmpty diff
then Cli.respond NoOp
else
Cli.respondNumbered $
ShowDiffNamespace
(Right Path.absoluteEmpty)
(Right Path.absoluteEmpty)
ppe
diff
-- | Resolve a metadata name to its type/value, or fail if it's missing or ambiguous.
resolveMetadata :: HQ.HashQualified Name -> Cli (Either Output (Metadata.Type, Metadata.Value))
resolveMetadata name = do
Cli.Env {codebase} <- ask
root' <- Cli.getRootBranch
currentPath' <- Cli.getCurrentPath
schLength <- Cli.runTransaction Codebase.branchHashLength
let ppe :: PPE.PrettyPrintEnv
ppe =
Backend.basicSuffixifiedNames schLength root' (Backend.Within $ Path.unabsolute currentPath')
terms <- getHQTerms name
runExceptT $ do
ref <-
case Set.asSingleton terms of
Just (Referent.Ref ref) -> pure ref
-- FIXME: we want a different error message if the given name is associated with a data constructor (`Con`).
_ -> throwError (MetadataAmbiguous name ppe (Set.toList terms))
lift (Cli.runTransaction ((Codebase.getTypeOfTerm codebase ref))) >>= \case
Just ty -> pure (Hashing.typeToReference ty, ref)
Nothing -> throwError (MetadataMissingType ppe (Referent.Ref ref))
resolveDefaultMetadata :: Path.Absolute -> Cli [String]
resolveDefaultMetadata path = do
let superpaths = Path.ancestors path
xs <-
for
superpaths
( \path -> do
mayNames <- Cli.getConfig @[String] (defaultMetadataKey path)
pure . join $ toList mayNames
)
pure . join $ toList xs
-- | Get the set of terms related to a hash-qualified name.
getHQTerms :: HQ.HashQualified Name -> Cli (Set Referent)
getHQTerms = \case
HQ.NameOnly n -> do
root0 <- Cli.getRootBranch0
currentPath' <- Cli.getCurrentPath
-- absolute-ify the name, then lookup in deepTerms of root
let path =
n
& Path.fromName'
& Path.resolve currentPath'
& Path.unabsolute
& Path.unsafeToName
pure $ R.lookupRan path (Branch.deepTerms root0)
HQ.HashOnly sh -> hashOnly sh
HQ.HashQualified _ sh -> hashOnly sh
where
hashOnly sh = do
Cli.Env {codebase} <- ask
Cli.runTransaction (Backend.termReferentsByShortHash codebase sh)

View File

@ -30,13 +30,10 @@ moveTermSteps src' dest' = do
when (not (Set.null destTerms)) do
Cli.returnEarly (Output.TermAlreadyExists dest' destTerms)
let p = Path.convert src
srcMetadata <- do
root0 <- Cli.getRootBranch0
pure (BranchUtil.getTermMetadataAt p srcTerm root0)
pure
[ -- Mitchell: throwing away any hash-qualification here seems wrong!
BranchUtil.makeDeleteTermName (over _2 HQ'.toName p) srcTerm,
BranchUtil.makeAddTermName (Path.convert dest) srcTerm srcMetadata
BranchUtil.makeAddTermName (Path.convert dest) srcTerm
]
doMoveTerm :: (Path', HQ'.HQSegment) -> (Path', NameSegment) -> Text -> Cli ()

View File

@ -30,13 +30,10 @@ moveTypeSteps src' dest' = do
when (not (Set.null destTypes)) do
Cli.returnEarly (Output.TypeAlreadyExists dest' destTypes)
let p = Path.convert src
srcMetadata <- do
root0 <- Cli.getRootBranch0
pure (BranchUtil.getTypeMetadataAt p srcType root0)
pure
[ -- Mitchell: throwing away any hash-qualification here seems wrong!
BranchUtil.makeDeleteTypeName (over _2 HQ'.toName p) srcType,
BranchUtil.makeAddTypeName (Path.convert dest) srcType srcMetadata
BranchUtil.makeAddTypeName (Path.convert dest) srcType
]
doMoveType :: (Path', HQ'.HQSegment) -> (Path', NameSegment) -> Text -> Cli ()

View File

@ -44,7 +44,7 @@ handleNamespaceDependencies namespacePath' = do
ppe <- PPED.unsuffixifiedPPE <$> currentPrettyPrintEnvDecl Backend.Within
Cli.respondNumbered $ Output.ListNamespaceDependencies ppe path externalDependencies
-- | Check the dependencies of all types, terms, and metadata in the current namespace,
-- | Check the dependencies of all types and terms in the current namespace,
-- returns a map of dependencies which do not have a name within the current namespace,
-- alongside the names of all of that thing's dependents.
--

View File

@ -49,7 +49,6 @@ diffHelper before after =
hqLength
(Branch.toNames before)
(Branch.toNames after)
ppe
diff
declOrBuiltin :: Codebase m Symbol Ann -> Reference -> Sqlite.Transaction (Maybe (DD.DeclOrBuiltin Symbol Ann))

View File

@ -24,7 +24,6 @@ import Unison.Codebase.Branch (Branch0 (..))
import Unison.Codebase.Branch qualified as Branch
import Unison.Codebase.Branch.Names qualified as Branch
import Unison.Codebase.BranchUtil qualified as BranchUtil
import Unison.Codebase.Editor.HandleInput.MetadataUtils (addDefaultMetadata)
import Unison.Codebase.Editor.Input
import Unison.Codebase.Editor.Output
import Unison.Codebase.Editor.Propagate qualified as Propagate
@ -33,7 +32,6 @@ import Unison.Codebase.Editor.SlurpComponent (SlurpComponent (..))
import Unison.Codebase.Editor.SlurpComponent qualified as SC
import Unison.Codebase.Editor.SlurpResult (SlurpResult (..))
import Unison.Codebase.Editor.SlurpResult qualified as Slurp
import Unison.Codebase.Metadata qualified as Metadata
import Unison.Codebase.Patch (Patch (..))
import Unison.Codebase.Patch qualified as Patch
import Unison.Codebase.Path (Path)
@ -54,7 +52,6 @@ import Unison.Reference qualified as Reference
import Unison.Referent (Referent)
import Unison.Referent qualified as Referent
import Unison.Result qualified as Result
import Unison.Runtime.IOSource qualified as IOSource
import Unison.Sqlite qualified as Sqlite
import Unison.Symbol (Symbol)
import Unison.Syntax.Name qualified as Name (toVar, unsafeFromVar)
@ -73,7 +70,6 @@ import Unison.Util.Relation qualified as R
import Unison.Util.Set qualified as Set
import Unison.Var qualified as Var
import Unison.WatchKind (WatchKind)
import Unison.WatchKind qualified as WK
-- | Handle an @update@ command.
handleUpdate :: Input -> OptionalPatch -> Set Name -> Cli ()
@ -199,7 +195,6 @@ handleUpdate input optionalPatch requestedNames = do
Cli.respond $ SlurpOutput input (PPE.suffixifiedPPE ppe) sr
whenJust patchOps \(updatedPatch, _, _) ->
void $ propagatePatchNoSync updatedPatch currentPath'
addDefaultMetadata addsAndUpdates
Cli.syncRoot case patchPath of
Nothing -> "update.nopatch"
Just p ->
@ -596,18 +591,12 @@ doSlurpAdds slurp uf = Branch.batchUpdates (typeActions <> termActions)
map doTerm . toList $
SC.terms slurp <> UF.constructorsForDecls (SC.types slurp) uf
names = UF.typecheckedToNames uf
tests = Set.fromList $ view _1 <$> UF.watchesOfKind WK.TestWatch (UF.discardTypes uf)
(isTestType, isTestValue) = IOSource.isTest
md v =
if Set.member v tests
then Metadata.singleton isTestType isTestValue
else Metadata.empty
doTerm :: Symbol -> (Path, Branch0 m -> Branch0 m)
doTerm v = case toList (Names.termsNamed names (Name.unsafeFromVar v)) of
[] -> errorMissingVar v
[r] ->
let split = Path.splitFromName (Name.unsafeFromVar v)
in BranchUtil.makeAddTermName split r (md v)
in BranchUtil.makeAddTermName split r
wha ->
error $
"Unison bug, typechecked file w/ multiple terms named "
@ -619,7 +608,7 @@ doSlurpAdds slurp uf = Branch.batchUpdates (typeActions <> termActions)
[] -> errorMissingVar v
[r] ->
let split = Path.splitFromName (Name.unsafeFromVar v)
in BranchUtil.makeAddTypeName split r Metadata.empty
in BranchUtil.makeAddTypeName split r
wha ->
error $
"Unison bug, typechecked file w/ multiple types named "
@ -643,26 +632,19 @@ doSlurpUpdates typeEdits termEdits deprecated b0 =
where
doDeprecate (n, r) = [BranchUtil.makeDeleteTermName (Path.splitFromName n) r]
-- we copy over the metadata on the old thing
-- todo: if the thing being updated, m, is metadata for something x in b0
-- update x's md to reference `m`
doType :: (Name, TypeReference, TypeReference) -> [(Path, Branch0 m -> Branch0 m)]
doType (n, old, new) =
let split = Path.splitFromName n
oldMd = BranchUtil.getTypeMetadataAt split old b0
in [ BranchUtil.makeDeleteTypeName split old,
BranchUtil.makeAddTypeName split new oldMd
BranchUtil.makeAddTypeName split new
]
doTerm :: (Name, TermReference, TermReference) -> [(Path, Branch0 m -> Branch0 m)]
doTerm (n, old, new) =
[ BranchUtil.makeDeleteTermName split (Referent.Ref old),
BranchUtil.makeAddTermName split (Referent.Ref new) oldMd
BranchUtil.makeAddTermName split (Referent.Ref new)
]
where
split = Path.splitFromName n
-- oldMd is the metadata linked to the old definition
-- we relink it to the new definition
oldMd = BranchUtil.getTermMetadataAt split (Referent.Ref old) b0
-- Returns True if the operation changed the namespace, False otherwise.
propagatePatchNoSync :: Patch -> Path.Absolute -> Cli Bool

View File

@ -234,13 +234,13 @@ typecheckedUnisonFileToBranchUpdates abort getConstructors tuf = do
Right actions -> pure actions
let deleteTypeAction = BranchUtil.makeAnnihilateTypeName split
split = splitVar symbol
insertTypeAction = BranchUtil.makeAddTypeName split (Reference.fromId typeRefId) Map.empty
insertTypeAction = BranchUtil.makeAddTypeName split (Reference.fromId typeRefId)
insertTypeConstructorActions =
let referentIdsWithNames = zip (Decl.constructorVars (Decl.asDataDecl decl)) (Decl.declConstructorReferents typeRefId decl)
in map
( \(sym, rid) ->
let splitConName = splitVar sym
in BranchUtil.makeAddTermName splitConName (Reference.fromId <$> rid) Map.empty
in BranchUtil.makeAddTermName splitConName (Reference.fromId <$> rid)
)
referentIdsWithNames
deleteStuff = deleteTypeAction : deleteConstructorActions
@ -257,7 +257,7 @@ typecheckedUnisonFileToBranchUpdates abort getConstructors tuf = do
then
let split = splitVar var
in [ BranchUtil.makeAnnihilateTermName split,
BranchUtil.makeAddTermName split (Referent.fromTermReferenceId ref) Map.empty
BranchUtil.makeAddTermName split (Referent.fromTermReferenceId ref)
]
else []

View File

@ -192,13 +192,13 @@ handleUpgrade oldDepName newDepName = do
maybePath <-
if isTranscript
then pure Nothing
else do
else fmap Just do
maybeLatestFile <- Cli.getLatestFile
case maybeLatestFile of
Nothing -> pure (Just "scratch.u")
Just (file, _) -> pure (Just file)
pure case maybeLatestFile of
Nothing -> "scratch.u"
Just (file, _) -> file
Cli.respond (Output.DisplayDefinitionsString maybePath prettyUnisonFile)
Cli.respond (Output.UpgradeFailure oldDepName newDepName)
Cli.respond (Output.UpgradeFailure (fromMaybe "scratch.u" maybePath) oldDepName newDepName)
Cli.returnEarlyWithoutOutput
branchUpdates <-

View File

@ -182,13 +182,6 @@ data Input
| -- fetch scheme compiler from a given username and branch
FetchSchemeCompilerI String String
| TestI TestInput
| -- metadata
-- `link metadata definitions` (adds metadata to all of `definitions`)
LinkI (HQ.HashQualified Name) [Path.HQSplit']
| -- `unlink metadata definitions` (removes metadata from all of `definitions`)
UnlinkI (HQ.HashQualified Name) [Path.HQSplit']
| -- links from <type>
LinksI Path.HQSplit' (Maybe String)
| CreateAuthorI NameSegment {- identifier -} Text {- name -}
| -- Display provided definitions.
DisplayI OutputLocation (NonEmpty (HQ.HashQualified Name))

View File

@ -228,7 +228,6 @@ data Output
[(Referent, [HQ'.HashQualified Name])] -- term match, term names
-- list of all the definitions within this branch
| ListOfDefinitions FindScope PPE.PrettyPrintEnv ListDetailed [SearchResult' Symbol Ann]
| ListOfLinks PPE.PrettyPrintEnv [(HQ.HashQualified Name, Reference, Maybe (Type Symbol Ann))]
| ListShallow (IO PPE.PrettyPrintEnv) [ShallowListEntry Symbol Ann]
| ListOfPatches (Set Name)
| ListStructuredFind [HQ.HashQualified Name]
@ -272,12 +271,9 @@ data Output
| GitError GitError
| ShareError ShareError
| ViewOnShare (Either WriteShareRemoteNamespace (URI, ProjectName, ProjectBranchName))
| ConfiguredMetadataParseError Path' String (P.Pretty P.ColorText)
| NoConfiguredRemoteMapping PushPull Path.Absolute
| ConfiguredRemoteMappingParseError PushPull Path.Absolute Text String
| MetadataMissingType PPE.PrettyPrintEnv Referent
| TermMissingType Reference
| MetadataAmbiguous (HQ.HashQualified Name) PPE.PrettyPrintEnv [Referent]
| AboutToPropagatePatch
| -- todo: tell the user to run `todo` on the same patch they just used
NothingToPatch PatchPath Path'
@ -312,7 +308,6 @@ data Output
| DumpBitBooster CausalHash (Map CausalHash [CausalHash])
| DumpUnisonFileHashes Int [(Name, Reference.Id)] [(Name, Reference.Id)] [(Name, Reference.Id)]
| BadName String
| DefaultMetadataNotification
| CouldntLoadBranch CausalHash
| HelpMessage Input.InputPattern
| NamespaceEmpty (NonEmpty AbsBranchId)
@ -329,7 +324,7 @@ data Output
| IntegrityCheck IntegrityResult
| DisplayDebugNameDiff NameChanges
| DisplayDebugCompletions [Completion.Completion]
| DebugDisplayFuzzyOptions String [String {- arg description, options -}]
| DebugDisplayFuzzyOptions Text [String {- arg description, options -}]
| DebugFuzzyOptionsNoResolver
| ClearScreen
| PulledEmptyBranch (ReadRemoteNamespace Share.RemoteProjectBranch)
@ -394,7 +389,7 @@ data Output
| UpdateTypecheckingFailure
| UpdateTypecheckingSuccess
| UpdateIncompleteConstructorSet UpdateOrUpgrade Name (Map ConstructorId Name) (Maybe Int)
| UpgradeFailure !NameSegment !NameSegment
| UpgradeFailure !FilePath !NameSegment !NameSegment
| UpgradeSuccess !NameSegment !NameSegment
data UpdateOrUpgrade = UOUUpdate | UOUUpgrade
@ -509,7 +504,6 @@ isFailure o = case o of
MovedOverExistingBranch {} -> False
DeletedEverything -> False
ListNames _ _ tys tms -> null tms && null tys
ListOfLinks _ ds -> null ds
ListOfDefinitions _ _ _ ds -> null ds
ListOfPatches s -> Set.null s
ListStructuredFind tms -> null tms
@ -532,11 +526,8 @@ isFailure o = case o of
CantUndo {} -> True
GitError {} -> True
BustedBuiltins {} -> True
ConfiguredMetadataParseError {} -> True
NoConfiguredRemoteMapping {} -> True
ConfiguredRemoteMappingParseError {} -> True
MetadataMissingType {} -> True
MetadataAmbiguous {} -> True
PatchNeedsToBeConflictFree {} -> True
PatchInvolvesExternalDependents {} -> True
AboutToPropagatePatch {} -> False
@ -558,7 +549,6 @@ isFailure o = case o of
HashAmbiguous {} -> True
ShowReflog {} -> False
LoadPullRequest {} -> False
DefaultMetadataNotification -> False
HelpMessage {} -> True
NoOp -> False
ListDependencies {} -> False

View File

@ -6,43 +6,21 @@ import Control.Lens
import Data.List qualified as List
import Data.Map qualified as Map
import Data.Set qualified as Set
import Unison.Codebase.BranchDiff (BranchDiff (BranchDiff), DiffSlice)
import Unison.Codebase.BranchDiff (BranchDiff (BranchDiff))
import Unison.Codebase.BranchDiff qualified as BranchDiff
import Unison.Codebase.Metadata qualified as Metadata
import Unison.Codebase.Patch qualified as P
import Unison.DataDeclaration (DeclOrBuiltin)
import Unison.HashQualified qualified as HQ
import Unison.HashQualified' (HashQualified)
import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.Names (Names)
import Unison.Names qualified as Names
import Unison.Prelude
import Unison.PrettyPrintEnv qualified as PPE
import Unison.Reference (Reference)
import Unison.Referent (Referent)
import Unison.Referent qualified as Referent
import Unison.Runtime.IOSource (isPropagatedValue)
import Unison.Syntax.Name ()
import Unison.Type (Type)
import Unison.Util.Relation qualified as R
import Unison.Util.Relation3 qualified as R3
import Unison.Util.Set (symmetricDifference)
data MetadataDiff tm = MetadataDiff
{ addedMetadata :: [tm],
removedMetadata :: [tm]
}
deriving (Ord, Eq, Functor, Foldable, Traversable, Show)
instance Semigroup (MetadataDiff tm) where
a <> b =
MetadataDiff
(addedMetadata a <> addedMetadata b)
(removedMetadata a <> removedMetadata b)
instance Monoid (MetadataDiff tm) where
mempty = MetadataDiff mempty mempty
data BranchDiffOutput v a = BranchDiffOutput
{ updatedTypes :: [UpdateTypeDisplay v a],
@ -51,7 +29,6 @@ data BranchDiffOutput v a = BranchDiffOutput
newTermConflicts :: [UpdateTermDisplay v a],
resolvedTypeConflicts :: [UpdateTypeDisplay v a],
resolvedTermConflicts :: [UpdateTermDisplay v a],
propagatedUpdates :: Int,
updatedPatches :: [PatchDisplay],
addedTypes :: [AddedTypeDisplay v a],
addedTerms :: [AddedTermDisplay v a],
@ -81,7 +58,6 @@ isEmpty BranchDiffOutput {..} =
&& null renamedTypes
&& null renamedTerms
&& null updatedPatches
&& propagatedUpdates == 0
-- Need to be able to turn a (Name,Reference) into a HashQualified relative to... what.
-- the new namespace?
@ -89,8 +65,7 @@ isEmpty BranchDiffOutput {..} =
data TermDisplay v a = TermDisplay
{ name :: HashQualified Name,
ref :: Referent,
type_ :: Maybe (Type v a),
metadata :: MetadataDiff (MetadataDisplay v a)
type_ :: Maybe (Type v a)
}
deriving stock (Generic, Show)
@ -106,8 +81,7 @@ instance Ord (TermDisplay v a) where
data TypeDisplay v a = TypeDisplay
{ name :: HashQualified Name,
ref :: Reference,
decl :: Maybe (DeclOrBuiltin v a),
metadata :: MetadataDiff (MetadataDisplay v a)
decl :: Maybe (DeclOrBuiltin v a)
}
deriving stock (Generic, Show)
@ -120,9 +94,9 @@ instance Ord (TypeDisplay v a) where
compare t0 t1 =
Name.compareAlphabetical (t0 ^. #name) (t1 ^. #name) <> compare (t0 ^. #ref) (t1 ^. #ref)
type AddedTermDisplay v a = ([(HashQualified Name, [MetadataDisplay v a])], Referent, Maybe (Type v a))
type AddedTermDisplay v a = ([HashQualified Name], Referent, Maybe (Type v a))
type AddedTypeDisplay v a = ([(HashQualified Name, [MetadataDisplay v a])], Reference, Maybe (DeclOrBuiltin v a))
type AddedTypeDisplay v a = ([HashQualified Name], Reference, Maybe (DeclOrBuiltin v a))
type RemovedTermDisplay v a = ([HashQualified Name], Referent, Maybe (Type v a))
@ -162,8 +136,6 @@ instance Ord (UpdateTypeDisplay v a) where
(t0 : _, t1 : _) -> compare t0 t1
(ts0, ts1) -> compare (null ts0) (null ts1)
type MetadataDisplay v a = (HQ.HashQualified Name, Referent, Maybe (Type v a))
type RenameTermDisplay v a = (Referent, Maybe (Type v a), Set (HashQualified Name), Set (HashQualified Name))
type RenameTypeDisplay v a = (Reference, Maybe (DeclOrBuiltin v a), Set (HashQualified Name), Set (HashQualified Name))
@ -178,7 +150,6 @@ toOutput ::
Int ->
Names ->
Names ->
PPE.PrettyPrintEnv ->
BranchDiff.BranchDiff ->
m (BranchDiffOutput v a)
toOutput
@ -187,56 +158,7 @@ toOutput
hqLen
names1
names2
ppe
(BranchDiff termsDiff typesDiff patchesDiff) = do
let -- This calculates the new reference's metadata as:
-- adds: now-attached metadata that was missing from
-- any of the old references associated with the name
-- removes: not-attached metadata that had been attached to any of
-- the old references associated with the name
getNewMetadataDiff :: (Ord r) => Bool -> DiffSlice r -> Name -> Set r -> r -> MetadataDiff Metadata.Value
getNewMetadataDiff hidePropagatedMd s n rs_old r_new =
let old_metadatas :: [Set Metadata.Value] =
toList . R.toMultimap . R.restrictDom rs_old . R3.lookupD2 n $
BranchDiff.tremovedMetadata s
old_intersection :: Set Metadata.Value =
foldl' Set.intersection mempty old_metadatas
old_union :: Set Metadata.Value =
foldl' Set.union mempty old_metadatas
new_metadata :: Set Metadata.Value =
R.lookupDom n . R3.lookupD1 r_new $ BranchDiff.taddedMetadata s
toDelete = if hidePropagatedMd then Set.singleton isPropagatedValue else mempty
in MetadataDiff
{ addedMetadata = toList $ new_metadata `Set.difference` old_intersection `Set.difference` toDelete,
removedMetadata = toList $ old_union `Set.difference` new_metadata `Set.difference` toDelete
}
-- For the metadata on a definition to have changed, the name
-- and the reference must have existed before and the reference
-- must not have been removed and the name must not have been removed or added
-- or updated 😅
-- "getMetadataUpdates" = a defn has been updated via change of metadata
getMetadataUpdates :: (Ord r) => DiffSlice r -> Map Name (Set r, Set r)
getMetadataUpdates s =
Map.fromList
[ (n, (Set.singleton r, Set.singleton r)) -- the reference is unchanged
| (r, n, v) <-
R3.toList $
BranchDiff.taddedMetadata s
<> BranchDiff.tremovedMetadata s,
R.notMember r n (BranchDiff.talladds s),
R.notMember r n (BranchDiff.tallremoves s),
-- don't count it as a metadata update if it already's already a regular update
let (oldRefs, newRefs) =
Map.findWithDefault mempty n (BranchDiff.tallnamespaceUpdates s)
in Set.notMember r oldRefs && Set.notMember r newRefs,
-- trenames :: Map r (Set Name, Set Name), -- ref (old, new)
case Map.lookup r (BranchDiff.trenames s) of
Nothing -> True
Just (olds, news) ->
Set.notMember n (symmetricDifference olds news),
v /= isPropagatedValue
]
let isSimpleUpdate, isNewConflict, isResolvedConflict :: (Eq r) => (Set r, Set r) -> Bool
isSimpleUpdate (old, new) = Set.size old == 1 && Set.size new == 1
isNewConflict (_old, new) = Set.size new > 1 -- should already be the case that old /= new
@ -249,9 +171,6 @@ toOutput
let -- things where what the name pointed to changed
nsUpdates :: Map Name (Set Reference, Set Reference) =
BranchDiff.namespaceUpdates typesDiff
-- things where the metadata changed (`uniqueBy` below removes these
-- if they were already included in `nsUpdates)
metadataUpdates = getMetadataUpdates typesDiff
loadOld :: Bool -> Name -> Reference -> m (SimpleTypeDisplay v a)
loadOld forceHQ n r_old =
(,,)
@ -262,10 +181,9 @@ toOutput
)
<*> pure r_old
<*> declOrBuiltin r_old
loadNew :: Bool -> Bool -> Name -> Set Reference -> Reference -> m (TypeDisplay v a)
loadNew hidePropagatedMd forceHQ n rs_old r_new = do
loadNew :: Bool -> Name -> Reference -> m (TypeDisplay v a)
loadNew forceHQ n r_new = do
decl <- declOrBuiltin r_new
metadata <- fillMetadata ppe (getNewMetadataDiff hidePropagatedMd typesDiff n rs_old r_new)
pure
TypeDisplay
{ name =
@ -273,33 +191,27 @@ toOutput
then Names.hqTypeName' hqLen n r_new
else Names.hqTypeName hqLen names2 n r_new,
ref = r_new,
decl,
metadata
decl
}
loadEntry :: Bool -> (Name, (Set Reference, Set Reference)) -> m (UpdateTypeDisplay v a)
loadEntry hidePropagatedMd (n, (Set.toList -> [rold], Set.toList -> [rnew]))
loadEntry :: (Name, (Set Reference, Set Reference)) -> m (UpdateTypeDisplay v a)
loadEntry (n, (Set.toList -> [rold], Set.toList -> [rnew]))
| rold == rnew = do
new <- for [rnew] (loadNew hidePropagatedMd False n (Set.singleton rold))
new <- for [rnew] (loadNew False n)
pure
UpdateTypeDisplay
{ old = Nothing,
new
}
loadEntry hidePropagatedMd (n, (rs_old, rs_new)) = do
loadEntry (n, (rs_old, rs_new)) = do
let forceHQ = Set.size rs_old > 1 || Set.size rs_new > 1
old <- Just <$> for (toList rs_old) (loadOld forceHQ n)
new <- for (toList rs_new) (loadNew hidePropagatedMd forceHQ n rs_old)
new <- for (toList rs_new) (loadNew forceHQ n)
pure UpdateTypeDisplay {old, new}
in liftA3
(,,)
( List.sort
<$> liftA2
(<>)
(for (Map.toList $ Map.filter isSimpleUpdate nsUpdates) (loadEntry True))
(for (Map.toList metadataUpdates) (loadEntry False))
)
(List.sort <$> for (Map.toList $ Map.filter isNewConflict nsUpdates) (loadEntry True))
(List.sort <$> for (Map.toList $ Map.filter isResolvedConflict nsUpdates) (loadEntry True))
(List.sort <$> for (Map.toList $ Map.filter isSimpleUpdate nsUpdates) loadEntry)
(List.sort <$> for (Map.toList $ Map.filter isNewConflict nsUpdates) loadEntry)
(List.sort <$> for (Map.toList $ Map.filter isResolvedConflict nsUpdates) loadEntry)
( updatedTerms :: [UpdateTermDisplay v a],
newTermConflicts :: [UpdateTermDisplay v a],
@ -307,9 +219,6 @@ toOutput
) <-
let -- things where what the name pointed to changed
nsUpdates = BranchDiff.namespaceUpdates termsDiff
-- things where the metadata changed (`uniqueBy` below removes these
-- if they were already included in `nsUpdates)
metadataUpdates = getMetadataUpdates termsDiff
loadOld forceHQ n r_old =
(,,)
<$> pure
@ -319,10 +228,9 @@ toOutput
)
<*> pure r_old
<*> typeOf r_old
loadNew :: Bool -> Bool -> Name -> Set Referent -> Referent -> m (TermDisplay v a)
loadNew hidePropagatedMd forceHQ n rs_old r_new = do
loadNew :: Bool -> Name -> Referent -> m (TermDisplay v a)
loadNew forceHQ n r_new = do
type_ <- typeOf r_new
metadata <- fillMetadata ppe (getNewMetadataDiff hidePropagatedMd termsDiff n rs_old r_new)
pure
TermDisplay
{ name =
@ -330,15 +238,14 @@ toOutput
then Names.hqTermName' hqLen n r_new
else Names.hqTermName hqLen names2 n r_new,
ref = r_new,
type_,
metadata
type_
}
loadEntry :: Bool -> (Name, (Set Referent, Set Referent)) -> m (UpdateTermDisplay v a)
loadEntry hidePropagatedMd (n, (rs_old, rs_new))
loadEntry :: (Name, (Set Referent, Set Referent)) -> m (UpdateTermDisplay v a)
loadEntry (n, (rs_old, rs_new))
-- if the references haven't changed, it's code for: only the metadata has changed
-- and we can ignore the old references in the output.
| rs_old == rs_new = do
new <- for (toList rs_new) (loadNew hidePropagatedMd False n rs_old)
new <- for (toList rs_new) (loadNew False n)
pure
UpdateTermDisplay
{ old = Nothing,
@ -347,65 +254,36 @@ toOutput
| otherwise = do
let forceHQ = Set.size rs_old > 1 || Set.size rs_new > 1
old <- Just <$> for (toList rs_old) (loadOld forceHQ n)
new <- for (toList rs_new) (loadNew hidePropagatedMd forceHQ n rs_old)
new <- for (toList rs_new) (loadNew forceHQ n)
pure UpdateTermDisplay {old, new}
in liftA3
(,,)
-- this is sorting the Update section back into alphabetical Name order
-- after calling loadEntry on the two halves.
( List.sort
<$> liftA2
(<>)
(for (Map.toList $ Map.filter isSimpleUpdate nsUpdates) (loadEntry True))
(for (Map.toList metadataUpdates) (loadEntry False))
)
(List.sort <$> for (Map.toList $ Map.filter isNewConflict nsUpdates) (loadEntry True))
(List.sort <$> for (Map.toList $ Map.filter isResolvedConflict nsUpdates) (loadEntry True))
let propagatedUpdates :: Int =
-- counting the number of named auto-propagated definitions
(Set.size . Set.unions . toList . BranchDiff.propagatedUpdates) typesDiff
+ (Set.size . Set.unions . toList . BranchDiff.propagatedUpdates) termsDiff
(List.sort <$> for (Map.toList $ Map.filter isSimpleUpdate nsUpdates) loadEntry)
(List.sort <$> for (Map.toList $ Map.filter isNewConflict nsUpdates) loadEntry)
(List.sort <$> for (Map.toList $ Map.filter isResolvedConflict nsUpdates) loadEntry)
let updatedPatches :: [PatchDisplay] =
[(name, diff) | (name, BranchDiff.Modify diff) <- Map.toList patchesDiff]
addedTypes :: [AddedTypeDisplay v a] <- do
let typeAdds :: [(Reference, [(Name, [Metadata.Value])])] =
let typeAdds :: [(Reference, Set Name)] =
sortOn
snd
[ (r, nsmd)
| (r, ns) <- Map.toList . R.toMultimap . BranchDiff.talladds $ typesDiff,
let nsmd =
[ (n, toList $ getAddedMetadata r n typesDiff)
| n <- toList ns
]
]
for typeAdds $ \(r, nsmd) -> do
hqmds :: [(HashQualified Name, [MetadataDisplay v a])] <-
for nsmd $ \(n, mdRefs) ->
(,)
<$> pure (Names.hqTypeName hqLen names2 n r)
<*> fillMetadata ppe mdRefs
(hqmds,r,) <$> declOrBuiltin r
(Map.toList . R.toMultimap . BranchDiff.talladds $ typesDiff)
for typeAdds \(r, ns) -> do
let hqs = map (\n -> Names.hqTypeName hqLen names2 n r) (Set.toList ns)
(hqs,r,) <$> declOrBuiltin r
addedTerms :: [AddedTermDisplay v a] <- do
let termAdds :: [(Referent, [(Name, [Metadata.Value])])] =
let termAdds :: [(Referent, Set Name)] =
sortOn
snd
[ (r, nsmd)
| (r, ns) <- Map.toList . R.toMultimap . BranchDiff.talladds $ termsDiff,
let nsmd =
[ (n, toList $ getAddedMetadata r n termsDiff)
| n <- toList ns
]
]
for termAdds $ \(r, nsmd) -> do
hqmds <- for nsmd $ \(n, mdRefs) ->
(,)
<$> pure (Names.hqTermName hqLen names2 n r)
<*> fillMetadata ppe mdRefs
(hqmds,r,) <$> typeOf r
(Map.toList . R.toMultimap . BranchDiff.talladds $ termsDiff)
for termAdds \(r, ns) -> do
let hqs = map (\n -> Names.hqTermName hqLen names2 n r) (Set.toList ns)
(hqs,r,) <$> typeOf r
let addedPatches :: [PatchDisplay] =
[ (name, diff)
@ -468,7 +346,6 @@ toOutput
newTermConflicts,
resolvedTypeConflicts,
resolvedTermConflicts,
propagatedUpdates,
updatedPatches,
addedTypes,
addedTerms,
@ -479,14 +356,3 @@ toOutput
renamedTypes,
renamedTerms
}
where
fillMetadata :: (Traversable t) => PPE.PrettyPrintEnv -> t Metadata.Value -> m (t (MetadataDisplay v a))
fillMetadata ppe = traverse $ -- metadata values are all terms
\(Referent.Ref -> mdRef) ->
let name = PPE.termName ppe mdRef
in (name,mdRef,) <$> typeOf mdRef
getMetadata :: (Ord r) => r -> Name -> R3.Relation3 r Name Metadata.Value -> Set Metadata.Value
getMetadata r n = R.lookupDom n . R3.lookupD1 r
getAddedMetadata :: (Ord r) => r -> Name -> BranchDiff.DiffSlice r -> Set Metadata.Value
getAddedMetadata r n slice = getMetadata r n $ BranchDiff.taddedMetadata slice

View File

@ -7,8 +7,8 @@ import Unison.Reference (Reference)
import Unison.Referent (Referent)
data DumpNamespace = DumpNamespace
{ terms :: Map Referent (Set NameSegment, Set Reference),
types :: Map Reference (Set NameSegment, Set Reference),
{ terms :: Map Referent (Set NameSegment),
types :: Map Reference (Set NameSegment),
patches :: Map NameSegment PatchHash,
children :: Map NameSegment CausalHash,
causalParents :: Set CausalHash

View File

@ -371,7 +371,14 @@ run verbosity dir stanzas codebase runtime sbRuntime nRuntime config ucmVersion
let getRoot = fmap Branch.head . atomically $ readTMVar rootVar
liftIO (parseInput codebase getRoot curPath numberedArgs patternMap args) >>= \case
-- invalid command is treated as a failure
Left msg -> liftIO (dieWithMsg $ Pretty.toPlain terminalWidth msg)
Left msg -> do
liftIO $ writeIORef hasErrors True
liftIO (readIORef allowErrors) >>= \case
True -> do
liftIO (output . Pretty.toPlain terminalWidth $ ("\n" <> msg <> "\n"))
awaitInput
False -> do
liftIO (dieWithMsg $ Pretty.toPlain terminalWidth msg)
-- No input received from this line, try again.
Right Nothing -> awaitInput
Right (Just (_expandedArgs, input)) -> pure $ Right input

View File

@ -26,7 +26,7 @@ module Unison.CommandLine
where
import Control.Concurrent (forkIO, killThread)
import Control.Lens (ifor)
import Control.Monad.Except
import Control.Monad.Trans.Except
import Data.Configurator (autoConfig, autoReload)
import Data.Configurator qualified as Config
@ -47,8 +47,8 @@ import Unison.Codebase.Branch qualified as Branch
import Unison.Codebase.Editor.Input (Event (..), Input (..))
import Unison.Codebase.Path qualified as Path
import Unison.Codebase.Watch qualified as Watch
import Unison.CommandLine.FZFResolvers qualified as FZFResolvers
import Unison.CommandLine.FuzzySelect qualified as Fuzzy
import Unison.CommandLine.Globbing qualified as Globbing
import Unison.CommandLine.InputPattern (InputPattern (..))
import Unison.CommandLine.InputPattern qualified as InputPattern
import Unison.Parser.Ann (Ann)
@ -120,7 +120,7 @@ nothingTodo = emojiNote "😶"
parseInput ::
Codebase IO Symbol Ann ->
IO (Branch0 IO) ->
-- | Current path from root, used to expand globs
-- | Current path from root
Path.Absolute ->
-- | Numbered arguments
[String] ->
@ -141,26 +141,15 @@ parseInput codebase getRoot currentPath numberedArgs patterns segments = runExce
case segments of
[] -> throwE ""
command : args -> case Map.lookup command patterns of
Just pat@(InputPattern {parse}) -> do
Just pat@(InputPattern {parse, help}) -> do
let expandedNumbers :: [String]
expandedNumbers =
foldMap (expandNumber numberedArgs) args
expandedGlobs <- ifor expandedNumbers $ \i arg -> do
if Globbing.containsGlob arg
then do
rootBranch <- liftIO getRoot
let targets = case InputPattern.argType pat i of
Just argT -> InputPattern.globTargets argT
Nothing -> mempty
case Globbing.expandGlobs targets rootBranch currentPath arg of
-- No globs encountered
Nothing -> pure [arg]
Just [] -> throwE $ "No matches for: " <> fromString arg
Just matches -> pure matches
else pure [arg]
lift (fzfResolve codebase projCtx getCurrentBranch0 pat (concat expandedGlobs)) >>= \case
Nothing -> pure Nothing
Just resolvedArgs -> do
lift (fzfResolve codebase projCtx getCurrentBranch0 pat expandedNumbers) >>= \case
Left (NoFZFResolverForArgumentType _argDesc) -> throwError help
Left (NoFZFOptions argDesc) -> throwError (noCompletionsMessage argDesc)
Left FZFCancelled -> pure Nothing
Right resolvedArgs -> do
parsedInput <- except . parse $ resolvedArgs
pure $ Just (command : resolvedArgs, parsedInput)
Nothing ->
@ -170,6 +159,15 @@ parseInput codebase getRoot currentPath numberedArgs patterns segments = runExce
$ "I don't know how to "
<> P.group (fromString command <> ".")
<> "Type `help` or `?` to get help."
where
noCompletionsMessage argDesc =
P.callout "⚠️" $
P.lines
[ ( "Sorry, I was expecting an argument for the "
<> P.text argDesc
<> ", and I couldn't find any to suggest to you. 😅"
)
]
-- Expand a numeric argument like `1` or a range like `3-9`
expandNumber :: [String] -> String -> [String]
@ -192,29 +190,43 @@ expandNumber numberedArgs s = case expandedNumber of
(\x y -> [x .. y]) <$> readMay from <*> readMay to
_ -> Nothing
fzfResolve :: Codebase IO Symbol Ann -> ProjectContext -> (IO (Branch0 IO)) -> InputPattern -> [String] -> IO (Maybe [String])
fzfResolve codebase projCtx getCurrentBranch pat args = runMaybeT do
(Align.align (argTypes pat) args) & foldMapM \case
This argDesc@(opt, _)
| opt == InputPattern.Required || opt == InputPattern.OnePlus ->
MaybeT $ fuzzyFillArg argDesc
| otherwise -> pure []
That arg -> pure [arg]
These _ arg -> pure [arg]
data FZFResolveFailure
= NoFZFResolverForArgumentType InputPattern.ArgumentDescription
| NoFZFOptions Text {- argument description -}
| FZFCancelled
fzfResolve :: Codebase IO Symbol Ann -> ProjectContext -> (IO (Branch0 IO)) -> InputPattern -> [String] -> IO (Either FZFResolveFailure [String])
fzfResolve codebase projCtx getCurrentBranch pat args = runExceptT do
-- We resolve args in two steps, first we check that all arguments that will require a fzf
-- resolver have one, and only if so do we prompt the user to actually do a fuzzy search.
-- Otherwise, we might ask the user to perform a search only to realize we don't have a resolver
-- for a later arg.
argumentResolvers :: [ExceptT FZFResolveFailure IO [String]] <-
(Align.align (InputPattern.args pat) args)
& traverse \case
This (argName, opt, InputPattern.ArgumentType {fzfResolver})
| opt == InputPattern.Required || opt == InputPattern.OnePlus ->
case fzfResolver of
Nothing -> throwError $ NoFZFResolverForArgumentType argName
Just fzfResolver -> pure $ fuzzyFillArg opt argName fzfResolver
| otherwise -> pure $ pure []
That arg -> pure $ pure [arg]
These _ arg -> pure $ pure [arg]
argumentResolvers & foldMapM id
where
fuzzyFillArg :: (InputPattern.IsOptional, InputPattern.ArgumentType) -> (IO (Maybe [String]))
fuzzyFillArg (opt, argType) =
runMaybeT do
InputPattern.FZFResolver {argDescription, getOptions} <- hoistMaybe $ InputPattern.fzfResolver argType
liftIO $ Text.putStrLn $ argDescription
currentBranch <- Branch.withoutTransitiveLibs <$> liftIO getCurrentBranch
options <- liftIO $ getOptions codebase projCtx currentBranch
guard . not . null $ options
results <- MaybeT (Fuzzy.fuzzySelect Fuzzy.defaultOptions {Fuzzy.allowMultiSelect = multiSelectForOptional opt} id options)
-- If the user triggered the fuzzy finder, but selected nothing, abort the command rather than continuing execution
-- with no arguments.
guard . not . null $ results
pure (Text.unpack <$> results)
fuzzyFillArg :: InputPattern.IsOptional -> Text -> InputPattern.FZFResolver -> ExceptT FZFResolveFailure IO [String]
fuzzyFillArg opt argDesc InputPattern.FZFResolver {getOptions} = do
currentBranch <- Branch.withoutTransitiveLibs <$> liftIO getCurrentBranch
options <- liftIO $ getOptions codebase projCtx currentBranch
when (null options) $ throwError $ NoFZFOptions argDesc
liftIO $ Text.putStrLn (FZFResolvers.fuzzySelectHeader argDesc)
results <-
liftIO (Fuzzy.fuzzySelect Fuzzy.defaultOptions {Fuzzy.allowMultiSelect = multiSelectForOptional opt} id options)
`whenNothingM` throwError FZFCancelled
-- If the user triggered the fuzzy finder, but selected nothing, abort the command rather than continuing execution
-- with no arguments.
when (null results) $ throwError FZFCancelled
pure (Text.unpack <$> results)
multiSelectForOptional :: InputPattern.IsOptional -> Bool
multiSelectForOptional = \case

View File

@ -203,12 +203,9 @@ completeWithinNamespace compTypes query currentPath = do
where
-- Qualify any conflicted definitions. If the query has a "#" in it, then qualify ALL
-- completions.
qualifyRefs :: NameSegment -> (Map r metadata) -> [HQ'.HashQualified NameSegment]
qualifyRefs :: NameSegment -> Map r metadata -> [HQ'.HashQualified NameSegment]
qualifyRefs n refs
| ((Text.isInfixOf "#" . NameSegment.toText) querySuffix) || length refs > 1 =
refs
& Map.keys
<&> qualify n
| ((Text.isInfixOf "#" . NameSegment.toText) querySuffix) || length refs > 1 = refs & Map.keys <&> qualify n
| otherwise = [HQ'.NameOnly n]
-- If we're not completing namespaces, then all namespace completions should automatically

View File

@ -9,12 +9,23 @@ module Unison.CommandLine.FZFResolvers
projectBranchOptionsWithinCurrentProject,
fuzzySelectFromList,
multiResolver,
definitionResolver,
typeDefinitionResolver,
termDefinitionResolver,
namespaceResolver,
namespaceOrDefinitionResolver,
projectAndOrBranchArg,
projectOrBranchResolver,
projectBranchResolver,
projectNameResolver,
fuzzySelectHeader,
)
where
import Control.Lens
import Data.List.Extra qualified as List
import Data.Set qualified as Set
import Data.Text qualified as Text
import U.Codebase.Sqlite.Project as SqliteProject
import U.Codebase.Sqlite.Queries qualified as Q
import Unison.Codebase (Codebase)
@ -26,7 +37,7 @@ import Unison.Codebase.Path qualified as Path
import Unison.Name qualified as Name
import Unison.Names qualified as Names
import Unison.Parser.Ann (Ann)
import Unison.Position (Position (..))
import Unison.Position qualified as Position
import Unison.Prelude
import Unison.Project.Util (ProjectContext (..))
import Unison.Symbol (Symbol)
@ -38,8 +49,7 @@ import Unison.Util.Relation qualified as Relation
type OptionFetcher = Codebase IO Symbol Ann -> ProjectContext -> Branch0 IO -> IO [Text]
data FZFResolver = FZFResolver
{ argDescription :: Text,
getOptions :: OptionFetcher
{ getOptions :: OptionFetcher
}
instance Show FZFResolver where
@ -47,39 +57,36 @@ instance Show FZFResolver where
-- | Select a definition from the given branch.
-- Returned names will match the provided 'Position' type.
genericDefinitionOptions :: Bool -> Bool -> Position -> OptionFetcher
genericDefinitionOptions includeTerms includeTypes pos _codebase _projCtx searchBranch0 = liftIO do
genericDefinitionOptions :: Bool -> Bool -> OptionFetcher
genericDefinitionOptions includeTerms includeTypes _codebase _projCtx searchBranch0 = liftIO do
let termsAndTypes =
Monoid.whenM includeTerms Relation.dom (Names.hashQualifyTermsRelation (Relation.swap $ Branch.deepTerms searchBranch0))
<> Monoid.whenM includeTypes Relation.dom (Names.hashQualifyTypesRelation (Relation.swap $ Branch.deepTypes searchBranch0))
termsAndTypes
& Set.toList
& map (HQ.toText . fmap (Name.setPosition pos))
& map (HQ.toText . fmap (Name.setPosition Position.Relative))
& pure
-- | Select a definition from the given branch.
-- Returned names will match the provided 'Position' type.
definitionOptions :: Position -> OptionFetcher
definitionOptions :: OptionFetcher
definitionOptions = genericDefinitionOptions True True
-- | Select a term definition from the given branch.
-- Returned names will match the provided 'Position' type.
termDefinitionOptions :: Position -> OptionFetcher
termDefinitionOptions :: OptionFetcher
termDefinitionOptions = genericDefinitionOptions True False
-- | Select a type definition from the given branch.
-- Returned names will match the provided 'Position' type.
typeDefinitionOptions :: Position -> OptionFetcher
typeDefinitionOptions :: OptionFetcher
typeDefinitionOptions = genericDefinitionOptions False True
-- | Select a namespace from the given branch.
-- Returned Path's will match the provided 'Position' type.
namespaceOptions :: Position -> OptionFetcher
namespaceOptions pos _codebase _projCtx searchBranch0 = do
namespaceOptions :: OptionFetcher
namespaceOptions _codebase _projCtx searchBranch0 = do
let intoPath' :: Path -> Path'
intoPath' = case pos of
Relative -> Path' . Right . Path.Relative
Absolute -> Path' . Left . Path.Absolute
intoPath' = Path' . Right . Path.Relative
searchBranch0
& Branch.deepPaths
& Set.delete (Path.empty {- The current path just renders as an empty string which isn't a valid arg -})
@ -89,17 +96,45 @@ namespaceOptions pos _codebase _projCtx searchBranch0 = do
-- | Select a namespace from the given branch.
-- Returned Path's will match the provided 'Position' type.
fuzzySelectFromList :: Text -> [Text] -> FZFResolver
fuzzySelectFromList argDescription options =
(FZFResolver {argDescription, getOptions = \_codebase _projCtx _branch -> pure options})
fuzzySelectFromList :: [Text] -> FZFResolver
fuzzySelectFromList options =
(FZFResolver {getOptions = \_codebase _projCtx _branch -> pure options})
-- | Combine multiple option fetchers into one resolver.
multiResolver :: Text -> [OptionFetcher] -> FZFResolver
multiResolver argDescription resolvers =
multiResolver :: [OptionFetcher] -> FZFResolver
multiResolver resolvers =
let getOptions :: Codebase IO Symbol Ann -> ProjectContext -> Branch0 IO -> IO [Text]
getOptions codebase projCtx searchBranch0 = do
List.nubOrd <$> foldMapM (\f -> f codebase projCtx searchBranch0) resolvers
in (FZFResolver {argDescription, getOptions})
in (FZFResolver {getOptions})
definitionResolver :: FZFResolver
definitionResolver = FZFResolver {getOptions = definitionOptions}
typeDefinitionResolver :: FZFResolver
typeDefinitionResolver = FZFResolver {getOptions = typeDefinitionOptions}
termDefinitionResolver :: FZFResolver
termDefinitionResolver = FZFResolver {getOptions = termDefinitionOptions}
namespaceResolver :: FZFResolver
namespaceResolver = FZFResolver {getOptions = namespaceOptions}
namespaceOrDefinitionResolver :: FZFResolver
namespaceOrDefinitionResolver = multiResolver [definitionOptions, namespaceOptions]
-- | A project name, branch name, or both.
projectAndOrBranchArg :: FZFResolver
projectAndOrBranchArg = multiResolver [projectBranchOptions, projectNameOptions]
projectOrBranchResolver :: FZFResolver
projectOrBranchResolver = multiResolver [projectBranchOptions, namespaceOptions]
projectBranchResolver :: FZFResolver
projectBranchResolver = FZFResolver {getOptions = projectBranchOptions}
projectNameResolver :: FZFResolver
projectNameResolver = FZFResolver {getOptions = projectNameOptions}
-- | All possible local project names
-- E.g. '@unison/base'
@ -123,3 +158,20 @@ projectBranchOptionsWithinCurrentProject codebase projCtx _searchBranch0 = do
ProjectBranchPath currentProjectId _projectBranchId _path -> do
Codebase.runTransaction codebase (Q.loadAllProjectBranchesBeginningWith currentProjectId Nothing)
<&> fmap (into @Text . snd)
-- | Exported from here just so the debug command and actual implementation can use the same
-- messaging.
--
-- >>> fuzzySelectHeader "definition to view"
-- "Select a definition to view:"
--
-- >>> fuzzySelectHeader "alias name"
-- "Select an alias name:"
fuzzySelectHeader :: Text -> Text
fuzzySelectHeader argDesc = "Select " <> aOrAn argDesc <> " " <> argDesc <> ":"
where
aOrAn :: Text -> Text
aOrAn txt =
Text.uncons txt & \case
Just (c, _) | c `elem` ("aeiou" :: [Char]) -> "an"
_ -> "a"

View File

@ -1,148 +0,0 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ViewPatterns #-}
-- | Provides Globbing for selecting types, terms and namespaces using wildcards.
module Unison.CommandLine.Globbing
( expandGlobs,
containsGlob,
TargetType (..),
)
where
import Control.Lens as Lens hiding (noneOf)
import Data.Either qualified as Either
import Data.Set qualified as Set
import Data.Text qualified as Text
import Unison.Codebase.Branch (Branch0)
import Unison.Codebase.Branch qualified as Branch
import Unison.Codebase.Path qualified as Path
import Unison.NameSegment (NameSegment (NameSegment))
import Unison.NameSegment qualified as NameSegment
import Unison.Prelude
import Unison.Util.Monoid qualified as Monoid
import Unison.Util.Relation qualified as Relation
import Unison.Util.Star3 qualified as Star3
-- | Possible targets which a glob may select.
data TargetType
= Type
| Term
| Namespace
deriving (Eq, Ord, Show)
-- | Glob paths are always relative to some branch.
type GlobPath = [Either NameSegment GlobArg]
-- | Represents a name segment containing a glob pattern
-- e.g. start?end -> GlobArg "start" "end"
data GlobArg = GlobArg
{ namespacePrefix :: Text,
namespaceSuffix :: Text
}
deriving (Show)
-- | Constructs a namespace "matcher" from a 'GlobArg'
globPredicate :: Either NameSegment GlobArg -> (NameSegment -> Bool)
globPredicate globArg (NameSegment.toText -> ns') =
case globArg of
Left (NameSegment.toText -> ns) -> ns == ns'
Right (GlobArg prefix suffix) -> prefix `Text.isPrefixOf` ns' && suffix `Text.isSuffixOf` ns'
-- | Expands a glob into a list of paths which lead to valid targets.
expandGlobToPaths :: Set TargetType -> GlobPath -> Branch0 m -> [Path.Relative]
expandGlobToPaths targets globPath branch =
(Path.Relative . Path.fromList) <$> expandGlobToNameSegments targets branch globPath
-- | Helper for 'expandGlobToPaths'
expandGlobToNameSegments :: forall m. Set TargetType -> Branch0 m -> GlobPath -> [[NameSegment]]
expandGlobToNameSegments targets branch globPath =
case globPath of
-- The glob path was empty; it yields no matches.
[] -> []
-- If we're at the end of the path, add any targets which match.
[segment] ->
Monoid.whenM (Set.member Term targets) matchingTerms
<> Monoid.whenM (Set.member Type targets) matchingTypes
<> Monoid.whenM (Set.member Namespace targets) matchingNamespaces
where
predicate :: NameSegment -> Bool
predicate = globPredicate segment
matchingNamespaces, matchingTerms, matchingTypes :: [[NameSegment]]
matchingNamespaces = branch ^.. matchingChildBranches predicate . asIndex . to (pure @[])
matchingTerms = matchingNamesInStar predicate (Branch._terms branch)
matchingTypes = matchingNamesInStar predicate (Branch._types branch)
matchingNamesInStar :: (NameSegment -> Bool) -> Branch.Star a NameSegment -> [[NameSegment]]
matchingNamesInStar predicate star =
star
& Star3.d1
& Relation.ran
& Set.toList
& filter predicate
& fmap (pure @[]) -- Embed each name segment into a path.
-- If we have multiple remaining segments, descend into any children matching the current
-- segment, then keep matching on the remainder of the path.
(segment : rest) -> recursiveMatches
where
nextBranches :: [(NameSegment, (Branch0 m))]
nextBranches = branch ^@.. matchingChildBranches (globPredicate segment)
recursiveMatches :: [[NameSegment]]
recursiveMatches =
foldMap (\(ns, b) -> (ns :) <$> expandGlobToNameSegments targets b rest) nextBranches
-- | Find all child branches whose name matches a predicate.
matchingChildBranches :: (NameSegment -> Bool) -> IndexedTraversal' NameSegment (Branch0 m) (Branch0 m)
matchingChildBranches keyPredicate = Branch.children0 . indices keyPredicate
-- | Expand a single glob pattern into all matching targets of the specified types.
expandGlobs ::
forall m.
Set TargetType ->
-- | Root branch
Branch0 m ->
-- | UCM's current path
Path.Absolute ->
-- | The glob string, e.g. .base.List.?.doc
String ->
-- | Nothing if arg was not a glob.
-- otherwise, fully expanded, absolute paths. E.g. [".base.List.map"]
Maybe [String]
expandGlobs targets rootBranch currentPath s = do
guard (not . null $ targets)
let (isAbsolute, globPath) = globbedPathParser (Text.pack s)
guard (any Either.isRight $ globPath)
let currentBranch :: Branch0 m
currentBranch
| isAbsolute = rootBranch
| otherwise = Branch.getAt0 (Path.unabsolute currentPath) rootBranch
let paths = expandGlobToPaths targets globPath currentBranch
let relocatedPaths
| isAbsolute = (Path.Absolute . Path.unrelative) <$> paths
| otherwise = Path.resolve currentPath <$> paths
pure (Path.convert <$> relocatedPaths)
containsGlob :: String -> Bool
containsGlob s =
let (_, globPath) = globbedPathParser (Text.pack s)
in any Either.isRight $ globPath
-- | Parses a single name segment into a GlobArg or a bare segment according to whether
-- there's a glob.
-- E.g.
-- "toList" -> Left (NameSegment "toList")
-- "to?" -> Left (GlobArg "to" "")
-- We unintuitively use '?' for glob patterns right now since they're not valid in names.
globbedPathParser :: Text -> (Bool, GlobPath)
globbedPathParser txt =
let (isAbsolute, segments) =
case Text.split (== '.') txt of
-- An initial '.' creates an empty split
("" : segments) -> (True, segments)
(segments) -> (False, segments)
in (isAbsolute, fmap globArgParser segments)
globArgParser :: Text -> Either NameSegment GlobArg
globArgParser txt =
case Text.split (== '?') txt of
[prefix, suffix] -> Right (GlobArg prefix suffix)
_ -> Left (NameSegment txt)

View File

@ -5,6 +5,7 @@
module Unison.CommandLine.InputPattern
( InputPattern (..),
ArgumentType (..),
ArgumentDescription,
argType,
FZFResolver (..),
IsOptional (..),
@ -18,6 +19,7 @@ module Unison.CommandLine.InputPattern
)
where
import Control.Lens
import Data.List.Extra qualified as List
import System.Console.Haskeline qualified as Line
import Unison.Auth.HTTPClient (AuthenticatedHttpClient)
@ -25,7 +27,6 @@ import Unison.Codebase (Codebase)
import Unison.Codebase.Editor.Input (Input (..))
import Unison.Codebase.Path as Path
import Unison.CommandLine.FZFResolvers (FZFResolver (..))
import Unison.CommandLine.Globbing qualified as Globbing
import Unison.Prelude
import Unison.Util.ColorText qualified as CT
import Unison.Util.Monoid (foldMapM)
@ -43,11 +44,16 @@ data IsOptional
data Visibility = Hidden | Visible
deriving (Show, Eq, Ord)
-- | Argument description
-- It should fit grammatically into sentences like "I was expecting an argument for the <argDesc>"
-- e.g. "namespace to merge", "definition to delete", "remote target to push to" etc.
type ArgumentDescription = Text
data InputPattern = InputPattern
{ patternName :: String,
aliases :: [String],
visibility :: Visibility, -- Allow hiding certain commands when debugging or work-in-progress
argTypes :: [(IsOptional, ArgumentType)],
args :: [(ArgumentDescription, IsOptional, ArgumentType)],
help :: P.Pretty CT.ColorText,
parse :: [String] -> Either (P.Pretty CT.ColorText) Input
}
@ -63,9 +69,6 @@ data ArgumentType = ArgumentType
AuthenticatedHttpClient ->
Path.Absolute -> -- Current path
m [Line.Completion],
-- | Select which targets glob patterns may expand into for this argument.
-- An empty set disables globbing.
globTargets :: Set Globbing.TargetType,
-- | If an argument is marked as required, but not provided, the fuzzy finder will be triggered if
-- available.
fzfResolver :: Maybe FZFResolver
@ -77,55 +80,64 @@ instance Show ArgumentType where
-- `argType` gets called when the user tries to autocomplete an `i`th argument (zero-indexed).
-- todo: would be nice if we could alert the user if they try to autocomplete
-- past the end. It would also be nice if
argType :: InputPattern -> Int -> Maybe ArgumentType
argType ip i = go (i, argTypes ip)
argInfo :: InputPattern -> Int -> Maybe (ArgumentDescription, ArgumentType)
argInfo InputPattern {args, patternName} i = go (i, args)
where
-- Strategy: all of these input patterns take some number of arguments.
-- If it takes no arguments, then don't autocomplete.
go :: (Int, [(Text, IsOptional, ArgumentType)]) -> Maybe (ArgumentDescription, ArgumentType)
go (_, []) = Nothing
-- If requesting the 0th of >=1 arguments, return it.
go (0, (_, t) : _) = Just t
go (0, (argName, _, t) : _) = Just (argName, t)
-- Vararg parameters should appear at the end of the arg list, and work for
-- any later argument number.
go (_, [(ZeroPlus, t)]) = Just t
go (_, [(OnePlus, t)]) = Just t
go (_, [(argName, ZeroPlus, t)]) = Just (argName, t)
go (_, [(argName, OnePlus, t)]) = Just (argName, t)
-- If requesting a later parameter, decrement and drop one.
go (n, (o, _) : argTypes)
go (n, (_argName, o, _) : argTypes)
| o == Optional || o == Required = go (n - 1, argTypes)
-- The argument list spec is invalid if something follows a vararg
go args =
error $
"Input pattern "
<> show (patternName ip)
<> show patternName
<> " has an invalid argument list: "
<> show args
-- `argType` gets called when the user tries to autocomplete an `i`th argument (zero-indexed).
-- todo: would be nice if we could alert the user if they try to autocomplete
-- past the end. It would also be nice if
argType :: InputPattern -> Int -> Maybe ArgumentType
argType ip i = snd <$> (argInfo ip i)
minArgs :: InputPattern -> Int
minArgs ip@(fmap fst . argTypes -> argTypes) = go argTypes
minArgs (InputPattern {args, patternName}) =
go (args ^.. folded . _2)
where
go [] = 0
go (Required : argTypes) = 1 + go argTypes
go [_] = 0
go _ =
error $
"Invalid argTypes for InputPattern ("
<> show (patternName ip)
"Invalid args for InputPattern ("
<> show patternName
<> "): "
<> show argTypes
<> show args
maxArgs :: InputPattern -> Maybe Int
maxArgs ip@(fmap fst . argTypes -> args) = go args
maxArgs (InputPattern {args, patternName}) = go argTypes
where
argTypes = args ^.. folded . _2
go [] = Just 0
go (Required : argTypes) = (1 +) <$> go argTypes
go [Optional] = Just 0
go [_] = Nothing
go _ =
error $
"Invalid argTypes for InputPattern ("
<> show (patternName ip)
"Invalid args for InputPattern ("
<> show patternName
<> "): "
<> show args
<> show argTypes
-- | Union suggestions from all possible completions
unionSuggestions ::

File diff suppressed because it is too large Load Diff

View File

@ -81,6 +81,7 @@ import Unison.Codebase.TermEdit qualified as TermEdit
import Unison.Codebase.Type (GitError (GitCodebaseError, GitProtocolError, GitSqliteCodebaseError))
import Unison.Codebase.TypeEdit qualified as TypeEdit
import Unison.CommandLine (bigproblem, note, tip)
import Unison.CommandLine.FZFResolvers qualified as FZFResolvers
import Unison.CommandLine.InputPattern (InputPattern)
import Unison.CommandLine.InputPatterns (makeExample')
import Unison.CommandLine.InputPatterns qualified as IP
@ -820,34 +821,6 @@ notifyUser dir = \case
<> " with the codebase, or the term was deleted just now "
<> " by someone else. Trying your command again might fix it."
]
MetadataMissingType ppe ref ->
pure . P.fatalCallout . P.lines $
[ P.wrap $
"The metadata value "
<> P.red (prettyTermName ppe ref)
<> "is missing a type signature in the codebase.",
"",
P.wrap $
"This might be due to pulling an incomplete"
<> "or invalid codebase, or because files inside the codebase"
<> "are being deleted external to UCM."
]
MetadataAmbiguous hq _ppe [] ->
pure
. P.warnCallout
. P.wrap
$ "I couldn't find any metadata matching "
<> P.syntaxToColor (prettyHashQualified hq)
MetadataAmbiguous _ ppe refs ->
pure . P.warnCallout . P.lines $
[ P.wrap $
"I'm not sure which metadata value you're referring to"
<> "since there are multiple matches:",
"",
P.indentN 2 $ P.spaced (P.blue . prettyTermName ppe <$> refs),
"",
tip "Try again and supply one of the above definitions explicitly."
]
EvaluationFailure err -> pure err
TypeTermMismatch typeName termName ->
pure $
@ -1026,8 +999,6 @@ notifyUser dir = \case
]
ListOfDefinitions fscope ppe detailed results ->
listOfDefinitions fscope ppe detailed results
ListOfLinks ppe results ->
listOfLinks ppe [(name, tm) | (name, _ref, tm) <- results]
ListNames global len types terms ->
if null types && null terms
then
@ -1455,19 +1426,6 @@ notifyUser dir = \case
(P.column2 . fmap format) ([(1 :: Integer) ..] `zip` (toList patches))
where
format (i, p) = (P.hiBlack . fromString $ show i <> ".", prettyName p)
ConfiguredMetadataParseError p md err ->
pure . P.fatalCallout . P.lines $
[ P.wrap $
"I couldn't understand the default metadata that's set for "
<> prettyPath' p
<> " in .unisonConfig.",
P.wrap $
"The value I found was"
<> (P.backticked . P.blue . P.string) md
<> "but I encountered the following error when trying to parse it:",
"",
err
]
NoConfiguredRemoteMapping pp p -> do
let (localPathExample, sharePathExample) =
if Path.isRoot p
@ -1697,7 +1655,6 @@ notifyUser dir = \case
pure (P.okCallout "No conflicts or edits in progress.")
HelpMessage pat -> pure $ IP.showPatternHelp pat
NoOp -> pure $ P.string "I didn't make any changes."
DefaultMetadataNotification -> pure $ P.wrap "I added some default metadata."
DumpBitBooster head map ->
let go output [] = output
go output (head : queue) = case Map.lookup head map of
@ -1848,7 +1805,7 @@ notifyUser dir = \case
DebugDisplayFuzzyOptions argDesc fuzzyOptions ->
pure $
P.lines
[P.string argDesc, P.indentN 2 $ P.bulleted (P.string <$> fuzzyOptions)]
[P.text (FZFResolvers.fuzzySelectHeader argDesc), P.indentN 2 $ P.bulleted (P.string <$> fuzzyOptions)]
DebugFuzzyOptionsNoResolver -> pure "No resolver found for fuzzy options in this slot."
ClearScreen -> do
ANSI.clearScreen
@ -2224,12 +2181,14 @@ notifyUser dir = \case
<> operationName
<> "again."
]
UpgradeFailure old new ->
UpgradeFailure path old new ->
pure . P.wrap $
"I couldn't automatically upgrade"
<> P.text (NameSegment.toText old)
<> "to"
<> P.group (P.text (NameSegment.toText new) <> ".")
<> "However, I've added the definitions that need attention to the top of"
<> P.group (prettyFilePath path <> ".")
UpgradeSuccess old new ->
pure . P.wrap $
"I upgraded"
@ -2898,33 +2857,6 @@ listOfDefinitions ::
listOfDefinitions fscope ppe detailed results =
pure $ listOfDefinitions' fscope ppe detailed results
listOfLinks ::
(Var v) => PPE.PrettyPrintEnv -> [(HQ.HashQualified Name, Maybe (Type v a))] -> IO Pretty
listOfLinks _ [] =
pure . P.callout "😶" . P.wrap $
"No results. Try using the "
<> IP.makeExample IP.link []
<> "command to add metadata to a definition."
listOfLinks ppe results =
pure $
P.lines
[ P.numberedColumn2
num
[ (P.syntaxToColor $ prettyHashQualified hq, ": " <> prettyType typ) | (hq, typ) <- results
],
"",
tip $
"Try using"
<> IP.makeExample IP.display ["1"]
<> "to display the first result or"
<> IP.makeExample IP.view ["1"]
<> "to view its source."
]
where
num i = P.hiBlack $ P.shown i <> "."
prettyType Nothing = "❓ (missing a type for this definition)"
prettyType (Just t) = TypePrinter.pretty ppe t
data ShowNumbers = ShowNumbers | HideNumbers
-- | `ppe` is just for rendering type signatures
@ -2974,7 +2906,6 @@ showDiffNamespace sn ppe oldPath newPath OBD.BranchDiffOutput {..} =
else pure mempty,
if (not . null) updatedTypes
|| (not . null) updatedTerms
|| propagatedUpdates > 0
|| (not . null) updatedPatches
then do
prettyUpdatedTypes :: [Pretty] <- traverse prettyUpdateType updatedTypes
@ -2985,16 +2916,6 @@ showDiffNamespace sn ppe oldPath newPath OBD.BranchDiffOutput {..} =
"\n\n"
[ P.bold "Updates:",
P.indentNonEmptyN 2 . P.sepNonEmpty "\n\n" $ prettyUpdatedTypes <> prettyUpdatedTerms,
if propagatedUpdates > 0
then
P.indentN 2 $
P.wrap
( P.hiBlack $
"There were "
<> P.shown propagatedUpdates
<> "auto-propagated updates."
)
else mempty,
P.indentNonEmptyN 2 . P.linesNonEmpty $ prettyUpdatedPatches
]
else pure mempty,
@ -3140,7 +3061,7 @@ showDiffNamespace sn ppe oldPath newPath OBD.BranchDiffOutput {..} =
-}
prettyUpdateType (OBD.UpdateTypeDisplay (Just olds) news) =
do
olds <- traverse (mdTypeLine oldPath) [OBD.TypeDisplay name r decl mempty | (name, r, decl) <- olds]
olds <- traverse (mdTypeLine oldPath) [OBD.TypeDisplay name r decl | (name, r, decl) <- olds]
news <- traverse (mdTypeLine newPath) news
let (oldnums, olddatas) = unzip olds
let (newnums, newdatas) = unzip news
@ -3150,47 +3071,46 @@ showDiffNamespace sn ppe oldPath newPath OBD.BranchDiffOutput {..} =
(P.boxLeft olddatas <> [downArrow] <> P.boxLeft newdatas)
{-
13. ability Yyz (+1 metadata)
14. ability copies.Yyz (+2 metadata)
13. ability Yyz
14. ability copies.Yyz
-}
prettyAddTypes :: forall a. [OBD.AddedTypeDisplay v a] -> Numbered Pretty
prettyAddTypes = fmap P.lines . traverse prettyGroup
where
prettyGroup :: OBD.AddedTypeDisplay v a -> Numbered Pretty
prettyGroup (hqmds, r, odecl) = do
pairs <- traverse (prettyLine r odecl) hqmds
prettyGroup (hqs, r, odecl) = do
pairs <- traverse (prettyLine r odecl) hqs
let (nums, decls) = unzip pairs
let boxLeft = case hqmds of _ : _ : _ -> P.boxLeft; _ -> id
let boxLeft = case hqs of
_ : _ : _ -> P.boxLeft
_ -> id
pure . P.column2 $ zip nums (boxLeft decls)
prettyLine :: Reference -> Maybe (DD.DeclOrBuiltin v a) -> (HQ'.HashQualified Name, [OBD.MetadataDisplay v a]) -> Numbered (Pretty, Pretty)
prettyLine r odecl (hq, mds) = do
prettyLine :: Reference -> Maybe (DD.DeclOrBuiltin v a) -> HQ'.HashQualified Name -> Numbered (Pretty, Pretty)
prettyLine r odecl hq = do
n <- numHQ' newPath hq (Referent.Ref r)
pure . (n,) $
prettyDecl hq odecl <> case length mds of
0 -> mempty
c -> " (+" <> P.shown c <> " metadata)"
pure . (n,) $ prettyDecl hq odecl
prettyAddTerms :: forall a. [OBD.AddedTermDisplay v a] -> Numbered Pretty
prettyAddTerms = fmap (P.column3 . mconcat) . traverse prettyGroup . reorderTerms
where
reorderTerms = sortOn (not . Referent.isConstructor . view _2)
prettyGroup :: OBD.AddedTermDisplay v a -> Numbered [(Pretty, Pretty, Pretty)]
prettyGroup (hqmds, r, otype) = do
pairs <- traverse (prettyLine r otype) hqmds
prettyGroup (hqs, r, otype) = do
pairs <- traverse (prettyLine r otype) hqs
let (nums, names, decls) = unzip3 pairs
boxLeft = case hqmds of _ : _ : _ -> P.boxLeft; _ -> id
boxLeft =
case hqs of
_ : _ : _ -> P.boxLeft
_ -> id
pure $ zip3 nums (boxLeft names) decls
prettyLine ::
Referent ->
Maybe (Type v a) ->
(HQ'.HashQualified Name, [OBD.MetadataDisplay v a]) ->
HQ'.HashQualified Name ->
Numbered (Pretty, Pretty, Pretty)
prettyLine r otype (hq, mds) = do
prettyLine r otype hq = do
n <- numHQ' newPath hq r
pure . (n,phq' hq,) $
": " <> prettyType otype <> case length mds of
0 -> mempty
c -> " (+" <> P.shown c <> " metadata)"
pure . (n,phq' hq,) $ ": " <> prettyType otype
prettySummarizePatch, prettyNamePatch :: Input.AbsBranchId -> OBD.PatchDisplay -> Numbered Pretty
-- 12. patch p (added 3 updates, deleted 1)
@ -3258,11 +3178,10 @@ showDiffNamespace sn ppe oldPath newPath OBD.BranchDiffOutput {..} =
downArrow = P.bold ""
mdTypeLine :: Input.AbsBranchId -> OBD.TypeDisplay v a -> Numbered (Pretty, Pretty)
mdTypeLine p (OBD.TypeDisplay hq r odecl mddiff) = do
mdTypeLine p (OBD.TypeDisplay hq r odecl) = do
n <- numHQ' p hq (Referent.Ref r)
fmap ((n,) . P.linesNonEmpty) . sequence $
[ pure $ prettyDecl hq odecl,
P.indentN leftNumsWidth <$> prettyMetadataDiff mddiff
[ pure $ prettyDecl hq odecl
]
-- + 2. MIT : License
@ -3272,12 +3191,11 @@ showDiffNamespace sn ppe oldPath newPath OBD.BranchDiffOutput {..} =
P.Width ->
OBD.TermDisplay v a ->
Numbered (Pretty, Pretty)
mdTermLine p namesWidth (OBD.TermDisplay hq r otype mddiff) = do
mdTermLine p namesWidth (OBD.TermDisplay hq r otype) = do
n <- numHQ' p hq r
fmap ((n,) . P.linesNonEmpty)
. sequence
$ [ pure $ P.rightPad namesWidth (phq' hq) <> " : " <> prettyType otype,
prettyMetadataDiff mddiff
$ [ pure $ P.rightPad namesWidth (phq' hq) <> " : " <> prettyType otype
]
prettyUpdateTerm :: OBD.UpdateTermDisplay v a -> Numbered Pretty
@ -3291,7 +3209,7 @@ showDiffNamespace sn ppe oldPath newPath OBD.BranchDiffOutput {..} =
olds <-
traverse
(mdTermLine oldPath namesWidth)
[OBD.TermDisplay name r typ mempty | (name, r, typ) <- olds]
[OBD.TermDisplay name r typ | (name, r, typ) <- olds]
news <- traverse (mdTermLine newPath namesWidth) news
let (oldnums, olddatas) = unzip olds
let (newnums, newdatas) = unzip news
@ -3305,16 +3223,6 @@ showDiffNamespace sn ppe oldPath newPath OBD.BranchDiffOutput {..} =
fmap (P.Width . HQ'.nameLength Name.toText . view #name) news
<> fmap (P.Width . HQ'.nameLength Name.toText . view _1) olds
prettyMetadataDiff :: OBD.MetadataDiff (OBD.MetadataDisplay v a) -> Numbered Pretty
prettyMetadataDiff OBD.MetadataDiff {..} =
P.column2M $
map (elem oldPath "- ") removedMetadata
<> map (elem newPath "+ ") addedMetadata
where
elem p x (hq, r, otype) = do
num <- numHQ p hq r
pure (x <> num <> " " <> phq hq, ": " <> prettyType otype)
prettyType :: Maybe (Type v a) -> Pretty
prettyType = maybe (P.red "type not found") (TypePrinter.pretty ppe)
prettyDecl hq =
@ -3322,17 +3230,12 @@ showDiffNamespace sn ppe oldPath newPath OBD.BranchDiffOutput {..} =
(P.red "type not found")
(P.syntaxToColor . DeclPrinter.prettyDeclOrBuiltinHeader (HQ'.toHQ hq))
phq' :: _ -> Pretty = P.syntaxToColor . prettyHashQualified'
phq :: _ -> Pretty = P.syntaxToColor . prettyHashQualified
-- DeclPrinter.prettyDeclHeader : HQ -> Either
numPatch :: Input.AbsBranchId -> Name -> Numbered Pretty
numPatch prefix name =
addNumberedArg' $ prefixBranchId prefix name
numHQ :: Input.AbsBranchId -> HQ.HashQualified Name -> Referent -> Numbered Pretty
numHQ prefix hq r =
addNumberedArg' . HQ.toStringWith (prefixBranchId prefix) . HQ.requalify hq $ r
numHQ' :: Input.AbsBranchId -> HQ'.HashQualified Name -> Referent -> Numbered Pretty
numHQ' prefix hq r =
addNumberedArg' . HQ'.toStringWith (prefixBranchId prefix) . HQ'.requalify hq $ r

View File

@ -193,57 +193,6 @@ test =
```
|]
),
pushPullTest
"metadataForTerm"
fmt
( \repo ->
[i|
```unison:hide
doc = "y is the number 3"
y = 3
```
```ucm
.> debug.file
.> add
.> link doc y
.> links y
.> history
.> push.create git(${repo})
```
|]
)
( \repo ->
[i|
```ucm
.> pull git(${repo})
.> links y
```
|]
),
pushPullTest
"metadataForType"
fmt
( \repo ->
[i|
```unison:hide
doc = "Nat means natural number"
```
```ucm
.> add
.> alias.type ##Nat Nat
.> link doc Nat
.> push.create git(${repo})
```
|]
)
( \repo ->
[i|
```ucm
.> pull git(${repo})
.> links Nat
```
|]
),
pushPullTest
"subNamespace"
fmt

View File

@ -54,7 +54,6 @@ library
Unison.Codebase.Editor.HandleInput.DeleteProject
Unison.Codebase.Editor.HandleInput.FindAndReplace
Unison.Codebase.Editor.HandleInput.Load
Unison.Codebase.Editor.HandleInput.MetadataUtils
Unison.Codebase.Editor.HandleInput.MoveAll
Unison.Codebase.Editor.HandleInput.MoveBranch
Unison.Codebase.Editor.HandleInput.MoveTerm
@ -96,7 +95,6 @@ library
Unison.CommandLine.DisplayValues
Unison.CommandLine.FuzzySelect
Unison.CommandLine.FZFResolvers
Unison.CommandLine.Globbing
Unison.CommandLine.InputPattern
Unison.CommandLine.InputPatterns
Unison.CommandLine.Main

View File

@ -29,7 +29,7 @@ This transcript is intended to make visible accidental changes to the hashing al
bSplit : [(a, b)] -> a -> ([(a, b)], [(a, b)])
9. -- #1j3e8vsn97qrprjr69ls6llab601sdh577uuvtu8pafmngf59suakbjr7asheadidcj3red140fnmdagsv9ihhdar1mc05ig28jtfr0
unique type builtin.ANSI.Color
type builtin.ANSI.Color
10. -- #1j3e8vsn97qrprjr69ls6llab601sdh577uuvtu8pafmngf59suakbjr7asheadidcj3red140fnmdagsv9ihhdar1mc05ig28jtfr0#0
builtin.ANSI.Color.Black : Color
@ -89,7 +89,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.Any.unsafeExtract : Any -> a
29. -- #345f3nptqq1c1ped6gq8578kb2bhp1jejnqborsn6fq59rpe1rren3ogia9o9u8oc339vll953inma8pocc686ooknaitud8i5m27vg
unique type builtin.Author
type builtin.Author
30. -- #345f3nptqq1c1ped6gq8578kb2bhp1jejnqborsn6fq59rpe1rren3ogia9o9u8oc339vll953inma8pocc686ooknaitud8i5m27vg#0
builtin.Author.Author : GUID -> Text -> Author
@ -345,7 +345,7 @@ This transcript is intended to make visible accidental changes to the hashing al
->{Exception} Either [Link.Term] [Link.Term]
109. -- #ldqsht5qvddaabskcad3idka4nqkv6lfncrp0s0o4rqbbnk1qvq269bueu7qobhvaf7gpluqtpn9bgp9u69jsntv0u6o4qtbktnfrs0
unique type builtin.ConsoleText
type builtin.ConsoleText
110. -- #ldqsht5qvddaabskcad3idka4nqkv6lfncrp0s0o4rqbbnk1qvq269bueu7qobhvaf7gpluqtpn9bgp9u69jsntv0u6o4qtbktnfrs0#5
builtin.ConsoleText.Background : Color
@ -371,7 +371,7 @@ This transcript is intended to make visible accidental changes to the hashing al
-> ConsoleText
116. -- #pgornst1pqaea8qmf8ckbtvrm7f6hn49djhffgebajmo12faf4jku63ftc9fp0r4k58e0qcdi77g08f34b2ihvsu97s48du6mfn7vko
unique type builtin.CopyrightHolder
type builtin.CopyrightHolder
117. -- #pgornst1pqaea8qmf8ckbtvrm7f6hn49djhffgebajmo12faf4jku63ftc9fp0r4k58e0qcdi77g08f34b2ihvsu97s48du6mfn7vko#0
builtin.CopyrightHolder.CopyrightHolder : GUID
@ -464,7 +464,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.Debug.watch : Text -> a -> a
141. -- #p65rcethk26an850aaaceojremfu054hqllhoip1mt9s22584j9r62o08qo9t0pri7ssgu9m7f0rfp4nujhulgbmo41tkgl182quhd8
unique type builtin.Doc
type builtin.Doc
142. -- #baiqeiovdrs4ju0grn5q5akq64k4kuhgifqno52smkkttqg31jkgm3qa9o3ohe54fgpiigd1tj0an7rfveopfg622sjj9v9g44n27go
builtin.Doc.++ : Doc2 -> Doc2 -> Doc2
@ -488,7 +488,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.Doc.Source : Link -> Doc
149. -- #ej86si0ur1lsjade71dojr25phk9bbom9rdks6dltolos5tjivakujcriqe02npba53n9gd7tkh8bmv08ttjb9t35lq2ch5heshqcs0
unique type builtin.Doc2
type builtin.Doc2
150. -- #ej86si0ur1lsjade71dojr25phk9bbom9rdks6dltolos5tjivakujcriqe02npba53n9gd7tkh8bmv08ttjb9t35lq2ch5heshqcs0#27
builtin.Doc2.Anchor : Text -> Doc2 -> Doc2
@ -524,7 +524,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.Doc2.Folded : Boolean -> Doc2 -> Doc2 -> Doc2
161. -- #h3gajooii4tsdseghcbcsq4qq7c33mtb71u5npg35b06mgv7v654g0n55gpq212umfmq7nvi11o28m1v13r5fto5g8ium3ee4qk1i68
unique type builtin.Doc2.FrontMatter
type builtin.Doc2.FrontMatter
162. -- #h3gajooii4tsdseghcbcsq4qq7c33mtb71u5npg35b06mgv7v654g0n55gpq212umfmq7nvi11o28m1v13r5fto5g8ium3ee4qk1i68#0
builtin.Doc2.FrontMatter.FrontMatter : [(Text, Text)]
@ -546,7 +546,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.Doc2.Join : [Doc2] -> Doc2
167. -- #lpf7g5c2ct61mci2okedmug8o0i2j0rhpealc05r2musapmn15cina6dsqdvis234evvb2bo09l2p8v5qhh0me7gi1j37nqqp47qvto
unique type builtin.Doc2.LaTeXInline
type builtin.Doc2.LaTeXInline
168. -- #lpf7g5c2ct61mci2okedmug8o0i2j0rhpealc05r2musapmn15cina6dsqdvis234evvb2bo09l2p8v5qhh0me7gi1j37nqqp47qvto#0
builtin.Doc2.LaTeXInline.LaTeXInline : Text
@ -556,7 +556,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.Doc2.Linebreak : Doc2
170. -- #ut0tds116gr0soc9p6nroaalqlq423u1mao3p4jjultjmok3vbck69la7rs26duptji5v5hscijpek4hotu4krbfah8np3sntr87gb0
unique type builtin.Doc2.MediaSource
type builtin.Doc2.MediaSource
171. -- #ut0tds116gr0soc9p6nroaalqlq423u1mao3p4jjultjmok3vbck69la7rs26duptji5v5hscijpek4hotu4krbfah8np3sntr87gb0#0
builtin.Doc2.MediaSource.MediaSource : Text
@ -611,7 +611,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.Doc2.Special : SpecialForm -> Doc2
184. -- #e46kdnv67raqhc4m3jnitkh3o9seq3q5mtlqnvobjlqnnd2tk7nui54b6grui7eql62fne4fo3ndetmeb23oj5es85habha5f6saoi0
unique type builtin.Doc2.SpecialForm
type builtin.Doc2.SpecialForm
185. -- #e46kdnv67raqhc4m3jnitkh3o9seq3q5mtlqnvobjlqnnd2tk7nui54b6grui7eql62fne4fo3ndetmeb23oj5es85habha5f6saoi0#4
builtin.Doc2.SpecialForm.Embed : Any -> SpecialForm
@ -667,7 +667,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.Doc2.Style : Text -> Doc2 -> Doc2
198. -- #sv2cta4p4th10h7tpurvr0t6s3cbahlevvmpadk01v32e39kse8aicdvfsm2dbk6ltc68ht788jvkfhk6ol2mch7eubngtug019e8fg
unique type builtin.Doc2.Svg
type builtin.Doc2.Svg
199. -- #sv2cta4p4th10h7tpurvr0t6s3cbahlevvmpadk01v32e39kse8aicdvfsm2dbk6ltc68ht788jvkfhk6ol2mch7eubngtug019e8fg#0
builtin.Doc2.Svg.Svg : Text -> Svg
@ -676,7 +676,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.Doc2.Table : [[Doc2]] -> Doc2
201. -- #s0an21vospbdlsbddiskuvt3ngbf00n78sip2o1mnp4jgp16i7sursbm14bf8ap7osphqbis2lduep3i29b7diu8sf03f8tlqd7rgcg
unique type builtin.Doc2.Term
type builtin.Doc2.Term
202. -- #42hub6f3fn0p5fk8t5bb2njhbgg5dj75vtqijvins6h45pkorakbu3g8h312ghu98ee4h75tb61fti192ckpk9cpdle9hsr8pdthkjo
builtin.Doc2.term : '{g} a -> Doc2.Term
@ -691,7 +691,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.Doc2.UntitledSection : [Doc2] -> Doc2
206. -- #794fndq1941e2khqv5uh7fmk9es2g4fkp8pr48objgs6blc1pqsdt2ab4o79noril2l7s70iu2eimn1smpd8t40j4g18btian8a2pt0
unique type builtin.Doc2.Video
type builtin.Doc2.Video
207. -- #46er7fsgre91rer0mpk6vhaa2vie19i0piubvtnfmt3vq7odcjfr6tlf0mc57q4jnij9rkolpekjd6dpqdotn41guk9lp9qioa88m58
builtin.Doc2.Video.config : Video -> [(Text, Text)]
@ -870,7 +870,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.Float.truncate : Float -> Int
260. -- #hqectlr3gt02r6r984b3627eg5bq3d82lab5q18e3ql09u1ka8dblf5k50ae0q0d8gk87udqd7b6767q86gogdt8ghpdiq77gk6blr8
unique type builtin.GUID
type builtin.GUID
261. -- #hqectlr3gt02r6r984b3627eg5bq3d82lab5q18e3ql09u1ka8dblf5k50ae0q0d8gk87udqd7b6767q86gogdt8ghpdiq77gk6blr8#0
builtin.GUID.GUID : Bytes -> GUID
@ -1039,13 +1039,13 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.Int.xor : Int -> Int -> Int
308. -- #s6ijmhqkkaus51chjgahogc7sdrqj9t66i599le2k7ts6fkl216f997hbses3mqk6a21vaj3cm1mertbldn0g503jt522vfo4rfv720
unique type builtin.io2.ArithmeticFailure
type builtin.io2.ArithmeticFailure
309. -- #6dtvam7msqc64dimm8p0d8ehdf0330o4qbd2fdafb11jj1c2rg4ke3jdcmbgo6s4pf2jgm0vb76jeavv4ba6ht71t74p963a1miekag
unique type builtin.io2.ArrayFailure
type builtin.io2.ArrayFailure
310. -- #dc6n5ebu839ik3b6ohmnqm6p0cifn7o94em1g41mjp4ae0gmv3b4rupba499lbasfrp4bqce9u4hd6518unlbg8vk993c0q6rigos98
unique type builtin.io2.BufferMode
type builtin.io2.BufferMode
311. -- #dc6n5ebu839ik3b6ohmnqm6p0cifn7o94em1g41mjp4ae0gmv3b4rupba499lbasfrp4bqce9u4hd6518unlbg8vk993c0q6rigos98#2
builtin.io2.BufferMode.BlockBuffering : BufferMode
@ -1090,7 +1090,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin type builtin.io2.Clock.internals.TimeSpec
323. -- #r29dja8j9dmjjp45trccchaata8eo1h6d6haar1eai74pq1jt4m7u3ldhlq79f7phfo57eq4bau39vqotl2h63k7ff1m5sj5o9ajuf8
unique type builtin.io2.Failure
type builtin.io2.Failure
324. -- #r29dja8j9dmjjp45trccchaata8eo1h6d6haar1eai74pq1jt4m7u3ldhlq79f7phfo57eq4bau39vqotl2h63k7ff1m5sj5o9ajuf8#0
builtin.io2.Failure.Failure : Type
@ -1099,7 +1099,7 @@ This transcript is intended to make visible accidental changes to the hashing al
-> Failure
325. -- #jhnlob35huv3rr7jg6aa4gtd8okhprla7gvlq8io429qita8vj7k696n9jvp4b8ct9i2pc1jodb8ap2bipqtgp138epdgfcth7vqvt8
unique type builtin.io2.FileMode
type builtin.io2.FileMode
326. -- #jhnlob35huv3rr7jg6aa4gtd8okhprla7gvlq8io429qita8vj7k696n9jvp4b8ct9i2pc1jodb8ap2bipqtgp138epdgfcth7vqvt8#2
builtin.io2.FileMode.Append : FileMode
@ -1360,7 +1360,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.io2.IO.tryEval : '{IO} a ->{IO, Exception} a
391. -- #h4smnou0l3fg4dn92g2r88j0imfvufjerkgbuscvvmaprv12l22nk6sff3c12edlikb2vfg3vfdj4b23a09q4lvtk75ckbe4lsmtuc0
unique type builtin.io2.IOError
type builtin.io2.IOError
392. -- #h4smnou0l3fg4dn92g2r88j0imfvufjerkgbuscvvmaprv12l22nk6sff3c12edlikb2vfg3vfdj4b23a09q4lvtk75ckbe4lsmtuc0#0
builtin.io2.IOError.AlreadyExists : IOError
@ -1387,10 +1387,10 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.io2.IOError.UserError : IOError
400. -- #6ivk1e38hh0l9gcl8fn4mhf8bmak3qaji36vevg5e1n16ju5i4cl9u5gmqi7u16b907rd98gd60pouma892efbqt2ri58tmu99hp77g
unique type builtin.io2.IOFailure
type builtin.io2.IOFailure
401. -- #574pvphqahl981k517dtrqtq812m05h3hj6t2bt9sn3pknenfik1krscfdb6r66nf1sm7g3r1r56k0c6ob7vg4opfq4gihi8njbnhsg
unique type builtin.io2.MiscFailure
type builtin.io2.MiscFailure
402. -- ##MVar
builtin type builtin.io2.MVar
@ -1468,13 +1468,13 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.io2.Ref.Ticket.read : Ticket a -> a
423. -- #vph2eas3lf2gi259f3khlrspml3id2l8u0ru07kb5fd833h238jk4iauju0b6decth9i3nao5jkf5eej1e1kovgmu5tghhh8jq3i7p8
unique type builtin.io2.RuntimeFailure
type builtin.io2.RuntimeFailure
424. -- ##sandboxLinks
builtin.io2.sandboxLinks : Link.Term ->{IO} [Link.Term]
425. -- #1bca3hq98sfgr6a4onuon1tsda69cdjggq8pkmlsfola6492dbrih5up6dv18ptfbqeocm9q6parf64pj773p7p19qe76238o4trc40
unique type builtin.io2.SeekMode
type builtin.io2.SeekMode
426. -- #1bca3hq98sfgr6a4onuon1tsda69cdjggq8pkmlsfola6492dbrih5up6dv18ptfbqeocm9q6parf64pj773p7p19qe76238o4trc40#0
builtin.io2.SeekMode.AbsoluteSeek : SeekMode
@ -1489,7 +1489,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin type builtin.io2.Socket
430. -- #121tku5rfh21t247v1cakhd6ir44fakkqsm799rrfp5qcjdls4nvdu4r3nco80stdd86tdo2hhh0ulcpoaofnrnkjun04kqnfmjqio8
unique type builtin.io2.StdHandle
type builtin.io2.StdHandle
431. -- #121tku5rfh21t247v1cakhd6ir44fakkqsm799rrfp5qcjdls4nvdu4r3nco80stdd86tdo2hhh0ulcpoaofnrnkjun04kqnfmjqio8#2
builtin.io2.StdHandle.StdErr : StdHandle
@ -1510,13 +1510,13 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.io2.STM.retry : '{STM} a
437. -- #cggbdfff21ac5uedf4qvn4to83clinvhsovrila35u7f7e73g4l6hoj8pjmjnk713a8luhnn4bi1j9ai1nl0can1un66hvg230eog9g
unique type builtin.io2.STMFailure
type builtin.io2.STMFailure
438. -- ##ThreadId
builtin type builtin.io2.ThreadId
439. -- #ggh649864d9bfnk90n7kgtj7dflddc4kn8osu7u7mub8p7l8biid8dgtungj4u005h7karbgupfpum9jp94spks3ma1sgh39bhirv38
unique type builtin.io2.ThreadKilledFailure
type builtin.io2.ThreadKilledFailure
440. -- ##Tls
builtin type builtin.io2.Tls
@ -1620,7 +1620,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin type builtin.io2.Tls.Version
465. -- #r3gag1btclr8iclbdt68irgt8n1d1vf7agv5umke3dgdbl11acj6easav6gtihanrjnct18om07638rne9ej06u2bkv2v4l36knm2l0
unique type builtin.io2.TlsFailure
type builtin.io2.TlsFailure
466. -- ##TVar
builtin type builtin.io2.TVar
@ -1654,19 +1654,19 @@ This transcript is intended to make visible accidental changes to the hashing al
->{IO} Either [Link.Term] [Link.Term]
475. -- #c23jofurcegj93796o0karmkcm6baifupiuu1rtkniu74avn6a4r1n66ga5rml5di7easkgn4iak800u3tnb6kfisbrv6tcfgkb13a8
unique type builtin.IsPropagated
type builtin.IsPropagated
476. -- #c23jofurcegj93796o0karmkcm6baifupiuu1rtkniu74avn6a4r1n66ga5rml5di7easkgn4iak800u3tnb6kfisbrv6tcfgkb13a8#0
builtin.IsPropagated.IsPropagated : IsPropagated
477. -- #q6snodsh7i7u6k7gtqj73tt7nv6htjofs5f37vg2v3dsfk6hau71fs5mcv0hq3lqg111fsvoi92mngm08850aftfgh65uka9mhqvft0
unique type builtin.IsTest
type builtin.IsTest
478. -- #q6snodsh7i7u6k7gtqj73tt7nv6htjofs5f37vg2v3dsfk6hau71fs5mcv0hq3lqg111fsvoi92mngm08850aftfgh65uka9mhqvft0#0
builtin.IsTest.IsTest : IsTest
479. -- #68haromionghg6cvojngjrgc7t0ob658nkk8b20fpho6k6ltjtf6rfmr4ia1omige97hk34lu21qsj933vl1dkpbna7evbjfkh71r9g
unique type builtin.License
type builtin.License
480. -- #knhl4mlkqf0mt877flahlbas2ufb7bub8f11vi9ihh9uf7r6jqaglk7rm6912q1vml50866ddl0qfa4o6d7o0gomchaoae24m0u2nk8
builtin.License.copyrightHolders : License
@ -1715,13 +1715,13 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.License.years.set : [Year] -> License -> License
490. -- #uj652rrb45urfnojgt1ssqoji7iiibu27uhrc1sfl68lm54hbr7r1dpgppsv0pvf0oile2uk2h2gn1h4vgng30fga66idihhen14qc0
unique type builtin.LicenseType
type builtin.LicenseType
491. -- #uj652rrb45urfnojgt1ssqoji7iiibu27uhrc1sfl68lm54hbr7r1dpgppsv0pvf0oile2uk2h2gn1h4vgng30fga66idihhen14qc0#0
builtin.LicenseType.LicenseType : Doc -> LicenseType
492. -- #f4b37niu61dc517c32h3os36ig34fgnt7inaaoqdbecmscchthi14gdo0vj3eee1ru746ibvl9vnmm1pglrv3125qnhsbc0i1tqtic0
unique type builtin.Link
type builtin.Link
493. -- ##Link.Term
builtin type builtin.Link.Term
@ -2023,7 +2023,7 @@ This transcript is intended to make visible accidental changes to the hashing al
structural type builtin.Pretty txt
576. -- #fqfaur9v9v4fks5d0c74ouitpjp121c3fbu2l9t05km8otjcj43gk453vu668pg54rte6qmh4v3uao6vbfpntrtaq057jgni1jk8fj8
unique type builtin.Pretty.Annotated w txt
type builtin.Pretty.Annotated w txt
577. -- #fqfaur9v9v4fks5d0c74ouitpjp121c3fbu2l9t05km8otjcj43gk453vu668pg54rte6qmh4v3uao6vbfpntrtaq057jgni1jk8fj8#1
builtin.Pretty.Annotated.Append : w
@ -2134,7 +2134,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin type builtin.Request
603. -- #bga77hj5p43epjosu36iero5ulpm7hqrct1slj5ivdcajsr52ksjam8d5smq2965netv9t43o3g0amgva26qoatt4qth29khkuds2t0
unique type builtin.RewriteCase a b
type builtin.RewriteCase a b
604. -- #bga77hj5p43epjosu36iero5ulpm7hqrct1slj5ivdcajsr52ksjam8d5smq2965netv9t43o3g0amgva26qoatt4qth29khkuds2t0#0
builtin.RewriteCase.RewriteCase : a
@ -2142,13 +2142,13 @@ This transcript is intended to make visible accidental changes to the hashing al
-> RewriteCase a b
605. -- #qcot4bpj2skgnui8hoignn6fl2gnn2nfrur451ft2egd5n1ndu6ti4uu7r1mvtc8r4p7iielfijk2mb7md9tt2m2rdvaikah4oluf7o
unique type builtin.Rewrites a
type builtin.Rewrites a
606. -- #qcot4bpj2skgnui8hoignn6fl2gnn2nfrur451ft2egd5n1ndu6ti4uu7r1mvtc8r4p7iielfijk2mb7md9tt2m2rdvaikah4oluf7o#0
builtin.Rewrites.Rewrites : a -> Rewrites a
607. -- #nu6eab37fl81lb5hfcainu83hph0ksqjsjgjbqvc3t8o13djtt5511qfa6tuggc5c3re06c5p6eto5o2cqme0jdlo31nnd13npqigjo
unique type builtin.RewriteSignature a b
type builtin.RewriteSignature a b
608. -- #nu6eab37fl81lb5hfcainu83hph0ksqjsjgjbqvc3t8o13djtt5511qfa6tuggc5c3re06c5p6eto5o2cqme0jdlo31nnd13npqigjo#0
builtin.RewriteSignature.RewriteSignature : (a
@ -2157,7 +2157,7 @@ This transcript is intended to make visible accidental changes to the hashing al
-> RewriteSignature a b
609. -- #bvffhraos4oatd3qmedt676dqul9c1oj8r4cqns36lsrue84kl0ote15iqbbmgu8joek3gce1h2raqas5b9nnvs2d79l9mrpmmi2sf0
unique type builtin.RewriteTerm a b
type builtin.RewriteTerm a b
610. -- #bvffhraos4oatd3qmedt676dqul9c1oj8r4cqns36lsrue84kl0ote15iqbbmgu8joek3gce1h2raqas5b9nnvs2d79l9mrpmmi2sf0#0
builtin.RewriteTerm.RewriteTerm : a
@ -2327,7 +2327,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.syntax.docWord : Text -> Doc2
660. -- #aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0
unique type builtin.Test.Result
type builtin.Test.Result
661. -- #aql7qk3iud6vs4cvu43aimopoosgk0fnipibdkc3so13adencmibgfn0u5c01r0adei55nkl3ttsjhl8gbj7tr4gnpj63g64ftbq6s0#0
builtin.Test.Result.Fail : Text -> Result
@ -2511,7 +2511,7 @@ This transcript is intended to make visible accidental changes to the hashing al
builtin.Value.value : a -> Value
720. -- #dem6aglnj8cppfrnq9qipl7geo5pim3auo9cmv1rhh5la9edalj19sspbpm1pd4vh0plokdh6qfo48gs034dqlg0s7j9fhr9p9ndtpo
unique type builtin.Year
type builtin.Year
721. -- #dem6aglnj8cppfrnq9qipl7geo5pim3auo9cmv1rhh5la9edalj19sspbpm1pd4vh0plokdh6qfo48gs034dqlg0s7j9fhr9p9ndtpo#0
builtin.Year.Year : Nat -> Year

View File

@ -64,7 +64,7 @@ testABunchOfNats _ =
⍟ These new definitions are ok to `add`:
unique type EncDec
type EncDec
BE16 : EncDec
BE32 : EncDec
BE64 : EncDec
@ -81,7 +81,7 @@ testABunchOfNats _ =
⍟ I've added these definitions:
unique type EncDec
type EncDec
BE16 : EncDec
BE32 : EncDec
BE64 : EncDec

View File

@ -38,7 +38,7 @@ unique type time.DayOfWeek = Sun | Mon | Tue | Wed | Thu | Fri | Sat
⍟ These new definitions are ok to `add`:
unique type time.DayOfWeek
type time.DayOfWeek
ImportantConstant : Nat
ImportantConstant.doc : Doc2
d1 : Doc2
@ -63,14 +63,7 @@ You can preview what docs will look like when rendered to the console using the
The 7 days of the week, defined as:
unique type DayOfWeek
= Sun
| Mon
| Tue
| Wed
| Thu
| Fri
| Sat
type DayOfWeek = Sun | Mon | Tue | Wed | Thu | Fri | Sat
```
The `docs ImportantConstant` command will look for `ImportantConstant.doc` in the file or codebase. You can do this instead of explicitly linking docs to definitions.

View File

@ -2,12 +2,12 @@ This tests a case where a function was somehow discarding abilities.
```unison:error
ability Trivial where
structural ability Trivial where
trivial : ()
-- This handler SHOULD leave any additional effects alone and unhandled
handleTrivial : '{e, Trivial} a -> {e} a
handleTrivial action =
handleTrivial action =
h : Request {Trivial} a -> a
h = cases
{trivial -> resume} -> handle !resume with h
@ -15,8 +15,8 @@ handleTrivial action =
handle !action with h
testAction : '{Exception, IO, Trivial} ()
testAction _ =
printText "hi!"
testAction = do
printLine "hi!"
trivial
wat : ()

View File

@ -2,12 +2,12 @@ This tests a case where a function was somehow discarding abilities.
```unison
ability Trivial where
structural ability Trivial where
trivial : ()
-- This handler SHOULD leave any additional effects alone and unhandled
handleTrivial : '{e, Trivial} a -> {e} a
handleTrivial action =
handleTrivial action =
h : Request {Trivial} a -> a
h = cases
{trivial -> resume} -> handle !resume with h
@ -15,8 +15,8 @@ handleTrivial action =
handle !action with h
testAction : '{Exception, IO, Trivial} ()
testAction _ =
printText "hi!"
testAction = do
printLine "hi!"
trivial
wat : ()
@ -29,13 +29,9 @@ wat = handleTrivial testAction -- Somehow this completely forgets about Excepti
Loading changes detected in scratch.u.
I expected to see `structural` or `unique` at the start of
this line:
The expression in red needs the {Exception} ability, but this location does not have access to any abilities.
1 | ability Trivial where
19 | wat = handleTrivial testAction -- Somehow this completely forgets about Exception and IO
Learn more about when to use `structural` vs `unique` in the
Unison Docs:
https://www.unison-lang.org/learn/language-reference/unique-types/
```

View File

@ -22,6 +22,5 @@ hasMetadata = 3
```ucm
.dependencies> add
.dependencies> link .metadata.myMetadata hasMetadata
.dependencies> namespace.dependencies
```

View File

@ -23,13 +23,6 @@ hasMetadata = 3
dependsOnNat : Nat
hasMetadata : Nat
.dependencies> link .metadata.myMetadata hasMetadata
Updates:
1. dependencies.hasMetadata : Nat
+ 2. myMetadata : Text
.dependencies> namespace.dependencies
External dependency Dependents in .dependencies

View File

@ -1,18 +0,0 @@
When updating a term from a test to a non-test, we don't delete its metadata that indicates it's a test. This is a bug.
```unison
test> foo = []
```
```ucm
.> add
```
```unison
foo = 1
```
```ucm
.> update.old
.> links foo
```

View File

@ -1,66 +0,0 @@
When updating a term from a test to a non-test, we don't delete its metadata that indicates it's a test. This is a bug.
```unison
test> foo = []
```
```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 : [Result]
Now evaluating any watch expressions (lines starting with
`>`)... Ctrl+C cancels.
1 | test> foo = []
```
```ucm
.> add
⍟ I've added these definitions:
foo : [Result]
```
```unison
foo = 1
```
```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 names already exist. You can `update` them to your
new definition:
foo : Nat
```
```ucm
.> update.old
⍟ I've updated these names to your new definition:
foo : Nat
.> links foo
1. builtin.metadata.isTest : IsTest
Tip: Try using `display 1` to display the first result or
`view 1` to view its source.
```

View File

@ -27,7 +27,7 @@ ha = cases
⍟ These new definitions are ok to `add`:
unique ability A
ability A
ha : Request {A} r -> r
```
@ -36,7 +36,7 @@ ha = cases
⍟ I've added these definitions:
unique ability A
ability A
ha : Request {A} r -> r
```

View File

@ -24,8 +24,8 @@ term2 _ = ()
⍟ These new definitions are ok to `add`:
unique ability Bar
unique ability Foo
ability Bar
ability Foo
term1 : '{Bar, Foo} ()
term2 : '{Bar, Foo} ()
@ -35,8 +35,8 @@ term2 _ = ()
⍟ I've added these definitions:
unique ability Bar
unique ability Foo
ability Bar
ability Foo
term1 : '{Bar, Foo} ()
term2 : '{Bar, Foo} ()

View File

@ -20,7 +20,7 @@ unique ability Channels where
⍟ These new definitions are ok to `add`:
unique ability Channels
ability Channels
```
```ucm
@ -30,7 +30,7 @@ unique ability Channels where
⍟ I've added these definitions:
unique ability Channels
ability Channels
```
Now we update the ability, changing the name of the constructor, _but_, we simultaneously
@ -64,7 +64,7 @@ thing _ = send 1
⍟ These names already exist. You can `update` them to your
new definition:
unique ability Channels
ability Channels
```
These should fail with a term/ctor conflict since we exclude the ability from the update.
@ -88,7 +88,7 @@ These should fail with a term/ctor conflict since we exclude the ability from th
⍟ I've updated these names to your new definition:
unique ability Channels
ability Channels
```
If however, `Channels.send` and `thing` _depend_ on `Channels`, updating them should succeed since it pulls in the ability as a dependency.

View File

@ -114,7 +114,7 @@ Let's try it!
90. Debug.toText : a -> Optional (Either Text Text)
91. Debug.trace : Text -> a -> ()
92. Debug.watch : Text -> a -> a
93. unique type Doc
93. type Doc
94. Doc.Blob : Text -> Doc
95. Doc.Evaluate : Term -> Doc
96. Doc.Join : [Doc] -> Doc
@ -235,9 +235,9 @@ Let's try it!
187. Int.trailingZeros : Int -> Nat
188. Int.truncate0 : Int -> Nat
189. Int.xor : Int -> Int -> Int
190. unique type io2.ArithmeticFailure
191. unique type io2.ArrayFailure
192. unique type io2.BufferMode
190. type io2.ArithmeticFailure
191. type io2.ArrayFailure
192. type io2.BufferMode
193. io2.BufferMode.BlockBuffering : BufferMode
194. io2.BufferMode.LineBuffering : BufferMode
195. io2.BufferMode.NoBuffering : BufferMode
@ -257,9 +257,9 @@ Let's try it!
203. io2.Clock.internals.threadCPUTime : '{IO} Either
Failure TimeSpec
204. builtin type io2.Clock.internals.TimeSpec
205. unique type io2.Failure
205. type io2.Failure
206. io2.Failure.Failure : Type -> Text -> Any -> Failure
207. unique type io2.FileMode
207. type io2.FileMode
208. io2.FileMode.Append : FileMode
209. io2.FileMode.Read : FileMode
210. io2.FileMode.ReadWrite : FileMode
@ -380,7 +380,7 @@ Let's try it!
270. io2.IO.systemTime.impl : '{IO} Either Failure Nat
271. io2.IO.systemTimeMicroseconds : '{IO} Int
272. io2.IO.tryEval : '{IO} a ->{IO, Exception} a
273. unique type io2.IOError
273. type io2.IOError
274. io2.IOError.AlreadyExists : IOError
275. io2.IOError.EOF : IOError
276. io2.IOError.IllegalOperation : IOError
@ -389,8 +389,8 @@ Let's try it!
279. io2.IOError.ResourceBusy : IOError
280. io2.IOError.ResourceExhausted : IOError
281. io2.IOError.UserError : IOError
282. unique type io2.IOFailure
283. unique type io2.MiscFailure
282. type io2.IOFailure
283. type io2.MiscFailure
284. builtin type io2.MVar
285. io2.MVar.isEmpty : MVar a ->{IO} Boolean
286. io2.MVar.new : a ->{IO} MVar a
@ -416,23 +416,23 @@ Let's try it!
302. io2.Ref.readForCas : Ref {IO} a ->{IO} Ticket a
303. builtin type io2.Ref.Ticket
304. io2.Ref.Ticket.read : Ticket a -> a
305. unique type io2.RuntimeFailure
305. type io2.RuntimeFailure
306. io2.sandboxLinks : Term ->{IO} [Term]
307. unique type io2.SeekMode
307. type io2.SeekMode
308. io2.SeekMode.AbsoluteSeek : SeekMode
309. io2.SeekMode.RelativeSeek : SeekMode
310. io2.SeekMode.SeekFromEnd : SeekMode
311. builtin type io2.Socket
312. unique type io2.StdHandle
312. type io2.StdHandle
313. io2.StdHandle.StdErr : StdHandle
314. io2.StdHandle.StdIn : StdHandle
315. io2.StdHandle.StdOut : StdHandle
316. builtin type io2.STM
317. io2.STM.atomically : '{STM} a ->{IO} a
318. io2.STM.retry : '{STM} a
319. unique type io2.STMFailure
319. type io2.STMFailure
320. builtin type io2.ThreadId
321. unique type io2.ThreadKilledFailure
321. type io2.ThreadKilledFailure
322. builtin type io2.Tls
323. builtin type io2.Tls.Cipher
324. builtin type io2.Tls.ClientConfig
@ -479,7 +479,7 @@ Let's try it!
344. builtin type io2.Tls.SignedCert
345. io2.Tls.terminate.impl : Tls ->{IO} Either Failure ()
346. builtin type io2.Tls.Version
347. unique type io2.TlsFailure
347. type io2.TlsFailure
348. builtin type io2.TVar
349. io2.TVar.new : a ->{STM} TVar a
350. io2.TVar.newIO : a ->{IO} TVar a
@ -491,11 +491,11 @@ Let's try it!
356. io2.Value.validateSandboxed : [Term]
-> Value
->{IO} Either [Term] [Term]
357. unique type IsPropagated
357. type IsPropagated
358. IsPropagated.IsPropagated : IsPropagated
359. unique type IsTest
359. type IsTest
360. IsTest.IsTest : IsTest
361. unique type Link
361. type Link
362. builtin type Link.Term
363. Link.Term : Term -> Link
364. Link.Term.toText : Term -> Text
@ -628,15 +628,15 @@ Let's try it!
444. Ref.read : Ref g a ->{g} a
445. Ref.write : Ref g a -> a ->{g} ()
446. builtin type Request
447. unique type RewriteCase a b
447. type RewriteCase a b
448. RewriteCase.RewriteCase : a -> b -> RewriteCase a b
449. unique type Rewrites a
449. type Rewrites a
450. Rewrites.Rewrites : a -> Rewrites a
451. unique type RewriteSignature a b
451. type RewriteSignature a b
452. RewriteSignature.RewriteSignature : (a -> b -> ())
-> RewriteSignature
a b
453. unique type RewriteTerm a b
453. type RewriteTerm a b
454. RewriteTerm.RewriteTerm : a -> b -> RewriteTerm a b
455. builtin type Scope
456. Scope.array : Nat ->{Scope s} MutableArray (Scope s) a
@ -655,7 +655,7 @@ Let's try it!
463. SeqView.VElem : a -> b -> SeqView a b
464. SeqView.VEmpty : SeqView a b
465. Socket.toText : Socket -> Text
466. unique type Test.Result
466. type Test.Result
467. Test.Result.Fail : Text -> Result
468. Test.Result.Ok : Text -> Result
469. builtin type Text

View File

@ -1,17 +0,0 @@
## An example scenario that surfaces an 'ambiguous metadata' error.
```unison:hide
foo.doc = [: a :]
boo.doc = [: b :]
x = 1
```
```ucm:hide:all
.> add
```
```ucm:error
.> merge foo boo
.> link boo.doc x
```

View File

@ -1,44 +0,0 @@
## An example scenario that surfaces an 'ambiguous metadata' error.
```unison
foo.doc = [: a :]
boo.doc = [: b :]
x = 1
```
```ucm
.> merge foo boo
Here's what's changed in boo after the merge:
New name conflicts:
1. doc#7ivmrc4c8v : #p65rcethk2
2. ┌ doc#7ivmrc4c8v : #p65rcethk2
3. └ doc#9f3kmo37cv : #p65rcethk2
Tip: You can use `todo` to see if this generated any work to
do in this namespace and `test` to run the tests. Or you
can use `undo` or `reflog` to undo the results of this
merge.
Applying changes from patch...
.> link boo.doc x
⚠️
I'm not sure which metadata value you're referring to since
there are multiple matches:
doc#7ivmrc4c8v
foo.doc
Tip: Try again and supply one of the above definitions
explicitly.
I didn't make any changes.
```

View File

@ -13,5 +13,4 @@ def2 = 2
.foo> add
.foo> create.author alicecoder "Alice McGee"
.foo> view 2
.foo> link metadata.authors.alicecoder def1 def2
```

View File

@ -31,14 +31,4 @@ def2 = 2
metadata.copyrightHolders.alicecoder =
CopyrightHolder guid "Alice McGee"
.foo> link metadata.authors.alicecoder def1 def2
Updates:
1. foo.def1 : Nat
+ 2. authors.alicecoder : Author
3. foo.def2 : Nat
+ 4. authors.alicecoder : Author
```

View File

@ -161,12 +161,9 @@ structural type Foo = Foo
New name conflicts:
1. structural type Foo#089vmor9c5
2. ┌ structural type Foo#00nv2kob8f
3. └ structural type Foo#089vmor9c5
4. Foo.Foo#089vmor9c5#0 : 'Foo#089vmor9c5

View File

@ -83,7 +83,7 @@ unique[a] type Foo = Foo
⍟ These new definitions are ok to `add`:
unique type Foo
type Foo
```
```ucm
@ -91,7 +91,7 @@ unique[a] type Foo = Foo
⍟ I've added these definitions:
unique type Foo
type Foo
```
```unison
@ -109,7 +109,7 @@ unique[b] type Foo = Foo | Bar
⍟ These names already exist. You can `update` them to your
new definition:
unique type Foo
type Foo
```
```ucm
@ -117,7 +117,7 @@ unique[b] type Foo = Foo | Bar
⍟ I've updated these names to your new definition:
unique type Foo
type Foo
.> view.patch
@ -153,7 +153,7 @@ unique[aa] type bar = Foo
⍟ These new definitions are ok to `add`:
unique type bar
type bar
bar : ##Nat
```
@ -162,7 +162,7 @@ unique[aa] type bar = Foo
⍟ I've added these definitions:
unique type bar
type bar
bar : ##Nat
```
@ -181,7 +181,7 @@ unique[bb] type bar = Foo | Bar
⍟ These names already exist. You can `update` them to your
new definition:
unique type bar
type bar
```
```ucm
@ -189,7 +189,7 @@ unique[bb] type bar = Foo | Bar
⍟ I've updated these names to your new definition:
unique type bar
type bar
.> view.patch
@ -278,7 +278,7 @@ unique type qux = Qux
⍟ These new definitions are ok to `add`:
unique type qux
type qux
```
```ucm
@ -286,7 +286,7 @@ unique type qux = Qux
⍟ I've added these definitions:
unique type qux
type qux
.> delete.term-replacement qux

View File

@ -24,9 +24,8 @@ fslkdjflskdjflksjdf = 663
Things we want to test:
* Diffing identical namespaces
* Adds, removes, updates (with and without metadata updates)
* Adds, removes, updates
* Adds with multiple names
* Adds with multiple names and different metadata on each
* Moved and copied definitions
* Moves that have more that 1 initial or final name
* ... terms and types
@ -48,7 +47,6 @@ structural ability X a1 a2 where x : ()
.ns1> add
.ns1> alias.term fromJust fromJust'
.ns1> alias.term helloWorld helloWorld2
.ns1> link b fromJust
.ns1> fork .ns1 .ns2
.ns1> cd .
```
@ -83,17 +81,11 @@ unique type Y a b = Y a b
```ucm
.ns2> update.old
.ns2> links fromJust
.> diff.namespace ns1 ns2
.> alias.term ns2.d ns2.d'
.> alias.type ns2.A ns2.A'
.> alias.type ns2.X ns2.X'
.> diff.namespace ns1 ns2
.> link ns1.c ns2.f
.> link ns2.c ns2.c
.> diff.namespace ns1 ns2
.> unlink ns2.b ns2.fromJust
.> diff.namespace ns1 ns2
.> alias.type ns1.X ns1.X2
.> alias.type ns2.A' ns2.A''
.> view.patch ns2.patch
@ -198,17 +190,10 @@ Resolved name conflicts: -- updates where LHS had multiple hashes and RHS has on
- [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] check whether creating a name conflict + adding metadata puts the update
in both categories; if it does, then filter out metadataUpdates from the
other categories
- [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] When you delete a name with metadata, it also shows up in updates section
with the deleted metadata.
- [x] An add with new metadata is getting characterized as an update
- [x] can there be a metadata-only update where it's not a singleton old and new reference
- [x] 12.patch patch needs a space
- [x] This looks like garbage
- [x] Extra 2 blank lines at the end of the add section

View File

@ -91,9 +91,8 @@ fslkdjflskdjflksjdf = 663
Things we want to test:
* Diffing identical namespaces
* Adds, removes, updates (with and without metadata updates)
* Adds, removes, updates
* Adds with multiple names
* Adds with multiple names and different metadata on each
* Moved and copied definitions
* Moves that have more that 1 initial or final name
* ... terms and types
@ -134,16 +133,6 @@ structural ability X a1 a2 where x : ()
Done.
.ns1> link b fromJust
Updates:
1. ns1.fromJust : Nat
+ 2. b : Nat
3. ns1.fromJust' : Nat
+ 4. b : Nat
.ns1> fork .ns1 .ns2
Done.
@ -213,7 +202,7 @@ unique type Y a b = Y a b
⍟ I've added these definitions:
unique type Y a b
type Y a b
d : Nat
e : Nat
f : Nat
@ -224,13 +213,6 @@ unique type Y a b = Y a b
fromJust : Nat
(The old definition was also named fromJust'.)
.ns2> links fromJust
1. b : Text
Tip: Try using `display 1` to display the first result or
`view 1` to view its source.
.> diff.namespace ns1 ns2
Resolved name conflicts:
@ -239,30 +221,26 @@ unique type Y a b = Y a b
2. └ fromJust#rnbo52q2sh : Text
3. fromJust#6gn1k53ie0 : Nat
- 4. ns1.b : Nat
+ 5. ns2.b : Text
Updates:
6. b : Nat
4. b : Nat
7. b : Text
5. b : Text
8. fromJust' : Nat
6. fromJust' : Nat
9. fromJust' : Nat
- 10. ns1.b : Nat
+ 11. ns2.b : Text
7. fromJust' : Nat
Added definitions:
12. unique type Y a b
13. Y.Y : a -> b -> Y a b
14. d : Nat
15. e : Nat
16. f : Nat
8. type Y a b
9. Y.Y : a -> b -> Y a b
10. d : Nat
11. e : Nat
12. f : Nat
17. patch patch (added 2 updates)
13. patch patch (added 2 updates)
.> alias.term ns2.d ns2.d'
@ -284,144 +262,34 @@ unique type Y a b = Y a b
2. └ fromJust#rnbo52q2sh : Text
3. fromJust#6gn1k53ie0 : Nat
- 4. ns1.b : Nat
+ 5. ns2.b : Text
Updates:
6. b : Nat
4. b : Nat
7. b : Text
5. b : Text
8. fromJust' : Nat
6. fromJust' : Nat
9. fromJust' : Nat
- 10. ns1.b : Nat
+ 11. ns2.b : Text
7. fromJust' : Nat
Added definitions:
12. unique type Y a b
13. Y.Y : a -> b -> Y a b
14. ┌ d : Nat
15. └ d' : Nat
16. e : Nat
17. f : Nat
8. type Y a b
9. Y.Y : a -> b -> Y a b
10. ┌ d : Nat
11. └ d' : Nat
12. e : Nat
13. f : Nat
18. patch patch (added 2 updates)
14. patch patch (added 2 updates)
Name changes:
Original Changes
19. A 20. A' (added)
15. A 16. A' (added)
21. X 22. X' (added)
.> link ns1.c ns2.f
Updates:
1. ns2.f : Nat
+ 2. c : Nat
.> link ns2.c ns2.c
Updates:
1. ns2.c : Nat
+ 2. c : Nat
.> diff.namespace ns1 ns2
Resolved name conflicts:
1. ┌ fromJust#gjmq673r1v : Nat
2. └ fromJust#rnbo52q2sh : Text
3. fromJust#6gn1k53ie0 : Nat
- 4. ns1.b : Nat
+ 5. ns2.b : Text
Updates:
6. b : Nat
7. b : Text
8. c : Nat
+ 9. c : Nat
10. fromJust' : Nat
11. fromJust' : Nat
- 12. ns1.b : Nat
+ 13. ns2.b : Text
Added definitions:
14. unique type Y a b
15. Y.Y : a -> b -> Y a b
16. ┌ d : Nat
17. └ d' : Nat
18. e : Nat
19. f : Nat (+1 metadata)
20. patch patch (added 2 updates)
Name changes:
Original Changes
21. A 22. A' (added)
23. X 24. X' (added)
.> unlink ns2.b ns2.fromJust
I didn't make any changes.
.> diff.namespace ns1 ns2
Resolved name conflicts:
1. ┌ fromJust#gjmq673r1v : Nat
2. └ fromJust#rnbo52q2sh : Text
3. fromJust#6gn1k53ie0 : Nat
- 4. ns1.b : Nat
+ 5. ns2.b : Text
Updates:
6. b : Nat
7. b : Text
8. c : Nat
+ 9. c : Nat
10. fromJust' : Nat
11. fromJust' : Nat
- 12. ns1.b : Nat
+ 13. ns2.b : Text
Added definitions:
14. unique type Y a b
15. Y.Y : a -> b -> Y a b
16. ┌ d : Nat
17. └ d' : Nat
18. e : Nat
19. f : Nat (+1 metadata)
20. patch patch (added 2 updates)
Name changes:
Original Changes
21. A 22. A' (added)
23. X 24. X' (added)
17. X 18. X' (added)
.> alias.type ns1.X ns1.X2
@ -556,7 +424,7 @@ a = 555
Added definitions:
1. a : Nat
2. b : Nat (+1 metadata)
2. b : Nat
3. patch patch (added 1 updates)
@ -579,14 +447,15 @@ a = 555
2. ┌ a#mdl4vqtu00 : Nat
3. └ a#vrs8gtkl2t : Nat
4. b#unkqhuu66p : Nat
5. ┌ b#aapqletas7 : Nat
6. └ b#unkqhuu66p : Nat
Updates:
4. b#unkqhuu66p : Nat
There were 1 auto-propagated updates.
5. patch patch (added 1 updates)
7. patch patch (added 1 updates)
Tip: You can use `todo` to see if this generated any work to
do in this namespace and `test` to run the tests. Or you
@ -608,14 +477,15 @@ a = 555
2. ┌ a#mdl4vqtu00 : Nat
3. └ a#vrs8gtkl2t : Nat
Updates:
There were 2 auto-propagated updates.
4. b#lhigeb1let : Nat
5. ┌ b#aapqletas7 : Nat
6. └ b#unkqhuu66p : Nat
Added definitions:
4. patch patch (added 2 updates)
7. patch patch (added 2 updates)
.nsw> view a b
@ -743,17 +613,10 @@ Resolved name conflicts: -- updates where LHS had multiple hashes and RHS has on
- [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] check whether creating a name conflict + adding metadata puts the update
in both categories; if it does, then filter out metadataUpdates from the
other categories
- [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] When you delete a name with metadata, it also shows up in updates section
with the deleted metadata.
- [x] An add with new metadata is getting characterized as an update
- [x] can there be a metadata-only update where it's not a singleton old and new reference
- [x] 12.patch patch needs a space
- [x] This looks like garbage
- [x] Extra 2 blank lines at the end of the add section

View File

@ -7,14 +7,12 @@
Unison documentation is written in Unison. Documentation is a value of the following type:
```ucm
.> view builtin.Doc
.builtin> view 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
use .builtin
doc1 = [: This is some documentation.
It can span multiple lines.
@ -44,15 +42,13 @@ List.take.ex2 = take 2 [1,2,3,4,5]
```
```ucm
.> add
.builtin> add
```
And now let's write our docs and reference these examples:
```unison
use .builtin
docs.List.take = [:
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.)
## Examples:
@ -68,28 +64,20 @@ docs.List.take = [:
:]
```
Let's add it to the codebase, and link it to the definition:
Let's add it to the codebase.
```ucm
.> add
.> link docs.List.take builtin.List.take
.builtin> add
```
Now that documentation is linked to the definition. We can view it if we like:
We can view it with `docs`, which shows the `Doc` value that is associated with a definition.
```ucm
.> links builtin.List.take builtin.Doc
.> display 1
```
Or there's also a convenient function, `docs`, which shows the `Doc` values that are linked to a definition. It's implemented in terms of `links` and `display`:
```ucm
.> docs builtin.List.take
.builtin> docs List.take
```
Note that if we view the source of the documentation, the various references are *not* expanded.
```ucm
.> view docs.List.take
.builtin> view List.take
```

View File

@ -3,22 +3,20 @@
Unison documentation is written in Unison. Documentation is a value of the following type:
```ucm
.> view builtin.Doc
.builtin> view Doc
unique type builtin.Doc
type Doc
= Blob Text
| Link Link
| Source Link
| Signature Term
| Evaluate Term
| Join [builtin.Doc]
| Join [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
use .builtin
doc1 = [: This is some documentation.
It can span multiple lines.
@ -75,7 +73,7 @@ List.take.ex2 = take 2 [1,2,3,4,5]
```
```ucm
.> add
.builtin> add
⍟ I've added these definitions:
@ -86,9 +84,7 @@ List.take.ex2 = take 2 [1,2,3,4,5]
And now let's write our docs and reference these examples:
```unison
use .builtin
docs.List.take = [:
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.)
## Examples:
@ -114,78 +110,39 @@ docs.List.take = [:
⍟ These new definitions are ok to `add`:
docs.List.take : Doc
List.take.doc : Doc
```
Let's add it to the codebase, and link it to the definition:
Let's add it to the codebase.
```ucm
.> add
.builtin> add
⍟ I've added these definitions:
docs.List.take : Doc
.> link docs.List.take builtin.List.take
Updates:
1. builtin.List.take : Nat -> [a] -> [a]
+ 2. docs.List.take : Doc
List.take.doc : Doc
```
Now that documentation is linked to the definition. We can view it if we like:
We can view it with `docs`, which shows the `Doc` value that is associated with a definition.
```ucm
.> links builtin.List.take builtin.Doc
.builtin> docs List.take
1. docs.List.take : Doc
Tip: Try using `display 1` to display the first result or
`view 1` to view its source.
.> display 1
`builtin.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.)
`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.)
## Examples:
List.take.ex1 : [Nat]
List.take.ex1 = builtin.List.take 0 [1, 2, 3, 4, 5]
List.take.ex1 = List.take 0 [1, 2, 3, 4, 5]
🔽
ex1 = []
List.take.ex2 : [Nat]
List.take.ex2 = builtin.List.take 2 [1, 2, 3, 4, 5]
🔽
ex2 = [1, 2]
```
Or there's also a convenient function, `docs`, which shows the `Doc` values that are linked to a definition. It's implemented in terms of `links` and `display`:
```ucm
.> docs builtin.List.take
`builtin.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.)
## Examples:
List.take.ex1 : [Nat]
List.take.ex1 = builtin.List.take 0 [1, 2, 3, 4, 5]
🔽
ex1 = []
List.take.ex2 : [Nat]
List.take.ex2 = builtin.List.take 2 [1, 2, 3, 4, 5]
List.take.ex2 = List.take 2 [1, 2, 3, 4, 5]
🔽
ex2 = [1, 2]
@ -194,25 +151,8 @@ Or there's also a convenient function, `docs`, which shows the `Doc` values that
Note that if we view the source of the documentation, the various references are *not* expanded.
```ucm
.> view docs.List.take
.builtin> view List.take
docs.List.take : Doc
docs.List.take =
[: `@builtin.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.)
## Examples:
@[source] ex1
🔽
@ex1 = @[evaluate] ex1
@[source] ex2
🔽
@ex2 = @[evaluate] ex2
:]
builtin List.take : Nat -> [a] -> [a]
```

View File

@ -17,7 +17,7 @@ baz = cases
⍟ I've added these definitions:
unique type A
type A
bar : Text -> A
baz : A -> Text
foo : A

View File

@ -18,7 +18,7 @@ x = [(R,1005),(U,563),(R,417),(U,509),(L,237),(U,555),(R,397),(U,414),(L,490),(U
⍟ These new definitions are ok to `add`:
unique type Direction
type Direction
x : [(Direction, Nat)]
```

View File

@ -1,46 +0,0 @@
##### This transcript reproduces the failure to unlink documentation
```ucm:hide
.> builtins.merge
```
Step 1: code a term and documentation for it
```unison
x = 1
x.doc = [: I am the documentation for x:]
```
Step 2: add term and documentation, link, and check the documentation
```ucm
.trunk> add
.trunk> link x.doc x
.trunk> docs x
```
Step 2.5: We'll save this for later for some reason.
```ucm
.trunk> alias.term x.doc .backup.x.doc
```
Step 3: Oops I don't like the doc, so I will re-code it!
```unison
x.doc = [: I am the documentation for x, and I now look better:]
```
Step 4: I add it and expect to see it
```ucm
.trunk> update
.trunk> docs x
```
That works great. Let's relink the old doc too.
```ucm
.trunk> link .backup.x.doc x
```
Let's check that we see both docs:
```ucm
.trunk> docs x
```

View File

@ -1,101 +0,0 @@
##### This transcript reproduces the failure to unlink documentation
Step 1: code a term and documentation for it
```unison
x = 1
x.doc = [: I am the documentation for x:]
```
```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`:
x : Nat
x.doc : Doc
```
Step 2: add term and documentation, link, and check the documentation
```ucm
☝️ The namespace .trunk is empty.
.trunk> add
⍟ I've added these definitions:
x : Nat
x.doc : Doc
.trunk> link x.doc x
Updates:
1. trunk.x : Nat
+ 2. doc : Doc
.trunk> docs x
I am the documentation for x
```
Step 2.5: We'll save this for later for some reason.
```ucm
.trunk> alias.term x.doc .backup.x.doc
Done.
```
Step 3: Oops I don't like the doc, so I will re-code it!
```unison
x.doc = [: I am the documentation for x, and I now look better:]
```
```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 names already exist. You can `update` them to your
new definition:
x.doc : Doc
```
Step 4: I add it and expect to see it
```ucm
.trunk> update
Okay, I'm searching the branch for code that needs to be
updated...
Done.
.trunk> docs x
I am the documentation for x, and I now look better
```
That works great. Let's relink the old doc too.
```ucm
.trunk> link .backup.x.doc x
I didn't make any changes.
```
Let's check that we see both docs:
```ucm
.trunk> docs x
I am the documentation for x, and I now look better
```

View File

@ -4,9 +4,9 @@
```
```unison:error
ability Ask where ask : Nat
structural ability Ask where ask : Nat
unique ability Zoot where
ability Zoot where
zoot : Nat
Ask.provide : '{Zoot} Nat -> '{Ask} r -> r

View File

@ -1,8 +1,8 @@
```unison
ability Ask where ask : Nat
structural ability Ask where ask : Nat
unique ability Zoot where
ability Zoot where
zoot : Nat
Ask.provide : '{Zoot} Nat -> '{Ask} r -> r
@ -21,13 +21,9 @@ dialog = Ask.provide 'zoot '("Awesome number: " ++ Nat.toText Ask.ask ++ "!")
Loading changes detected in scratch.u.
I expected to see `structural` or `unique` at the start of
this line:
The expression in red needs the {Zoot} ability, but this location does not have access to any abilities.
1 | ability Ask where ask : Nat
13 | dialog = Ask.provide 'zoot '("Awesome number: " ++ Nat.toText Ask.ask ++ "!")
Learn more about when to use `structural` vs `unique` in the
Unison Docs:
https://www.unison-lang.org/learn/language-reference/unique-types/
```

View File

@ -21,8 +21,8 @@ snoc k aN = match k with
⍟ These new definitions are ok to `add`:
structural type One a
unique type Woot a b c
unique type Z
type Woot a b c
type Z
snoc : One a -> aN -> Woot (One a) (One aN) ##Nat
Now evaluating any watch expressions (lines starting with

View File

@ -58,8 +58,8 @@ Fold.Stream.fold =
⍟ These new definitions are ok to `add`:
unique type Fold g a b
unique type Fold' g a b x
type Fold g a b
type Fold' g a b x
structural ability Stream a
Fold.Stream.fold : Fold g a b
-> '{g, Stream a} r

View File

@ -40,7 +40,7 @@ We'll make our edits in a fork of the `a` namespace:
⍟ I've added these definitions:
unique type A a b c d
type A a b c d
structural type NeedsA a b
f : A Nat Nat Nat Nat -> Nat
f2 : A Nat Nat Nat Nat -> Nat
@ -70,11 +70,11 @@ Let's do the update now, and verify that the definitions all look good and there
⍟ I've updated these names to your new definition:
unique type A a b c d
type A a b c d
.a2> view A NeedsA f f2 f3 g
unique type A a b c d
type A a b c d
= B b
| D d
| E a d

View File

@ -25,8 +25,8 @@ test _ =
⍟ These new definitions are ok to `add`:
unique ability A
unique ability B
ability A
ability B
test : '{B} Nat
```

View File

@ -27,7 +27,7 @@ sneezy dee _ =
⍟ These new definitions are ok to `add`:
unique ability Nate
ability Nate
sneezy : (Nat ->{d} a) -> '{d, Nate} a
```

View File

@ -35,7 +35,7 @@ save a = !(save.impl a)
⍟ These new definitions are ok to `add`:
unique ability Storage d g
ability Storage d g
save : a ->{g, Storage d g} d a
```

View File

@ -21,8 +21,8 @@ pure.run a0 a =
⍟ These new definitions are ok to `add`:
unique ability Async t g
unique ability Exception
ability Async t g
ability Exception
pure.run : a -> (∀ t. '{Async t g} a) ->{g, Exception} a
```

View File

@ -49,9 +49,9 @@ x _ = Ex.catch '(C.pure.run '(A.pure.run ex))
⍟ These new definitions are ok to `add`:
unique ability A t g
unique ability C c
unique ability Ex
ability A t g
ability C c
ability Ex
A.pure.run : (∀ t. '{g, A t g} a) ->{g, Ex} a
C.pure.run : (∀ c. '{g, C c} r) ->{g, Ex} r
Ex.catch : '{g, Ex} a ->{g} Either () a

View File

@ -9,7 +9,7 @@ unique type foo.bar.baz.MyRecord = {
⍟ I've added these definitions:
unique type foo.bar.baz.MyRecord
type foo.bar.baz.MyRecord
foo.bar.baz.MyRecord.value : MyRecord -> Nat
foo.bar.baz.MyRecord.value.modify : (Nat ->{g} Nat)
-> MyRecord

View File

@ -15,7 +15,7 @@ mapWithKey f m = Tip
⍟ These new definitions are ok to `add`:
unique type Map k v
type Map k v
mapWithKey : (k ->{e} a ->{e} b) -> Map k a ->{e} Map k b
```
@ -24,7 +24,7 @@ mapWithKey f m = Tip
⍟ I've added these definitions:
unique type Map k v
type Map k v
mapWithKey : (k ->{e} a ->{e} b) -> Map k a ->{e} Map k b
```

View File

@ -7,9 +7,9 @@ First, a few \[hidden] definitions necessary for typechecking a simple Doc2.
⍟ I've added these definitions:
unique type Doc2
unique type Doc2.SpecialForm
unique type Doc2.Term
type Doc2
type Doc2.SpecialForm
type Doc2.Term
structural type Optional a
(also named builtin.Optional)
syntax.docParagraph : [Doc2] -> Doc2

View File

@ -38,7 +38,7 @@ w2 = cases W -> W
⍟ These new definitions are ok to `add`:
structural type W es
unique ability Zoot
ability Zoot
ex : '{Zoot} r
w1 : W {Zoot}
w2 : W {g} -> W {g}

View File

@ -58,9 +58,9 @@ blah.frobnicate = "Yay!"
⍟ These new definitions are ok to `add`:
unique ability Blah
unique type Oog.Foo
unique type Something
ability Blah
type Oog.Foo
type Something
Something.state : Something -> Text
Something.state.modify : (Text ->{g} Text)
-> Something

View File

@ -14,7 +14,7 @@ unique type sub.Foo =
⍟ These new definitions are ok to `add`:
unique type Foo
unique type sub.Foo
type Foo
type sub.Foo
```

View File

@ -13,8 +13,8 @@ countCat = cases
⍟ I've added these definitions:
unique type Cat.Dog
unique type Rat.Dog
type Cat.Dog
type Rat.Dog
countCat : Cat.Dog -> Rat.Dog
```

View File

@ -57,6 +57,8 @@ myproj/main> upgrade foo0 foo1
use lib.foo0.lib.bonk1 bar
##Nat.+ bar bar
I couldn't automatically upgrade foo0 to foo1.
I couldn't automatically upgrade foo0 to foo1. However, I've
added the definitions that need attention to the top of
scratch.u.
```

View File

@ -18,9 +18,9 @@ useBar = cases
⍟ These new definitions are ok to `add`:
unique type Bar
unique type Baz
unique type Foo
type Bar
type Baz
type Foo
useBar : Bar -> Nat
```
@ -29,9 +29,9 @@ myproject/main> add
⍟ I've added these definitions:
unique type Bar
unique type Baz
unique type Foo
type Bar
type Baz
type Foo
useBar : Bar -> Nat
```
@ -50,7 +50,7 @@ unique type Foo = Foo1 | Foo2
⍟ These names already exist. You can `update` them to your
new definition:
unique type Foo
type Foo
```
```ucm

View File

@ -1,7 +1,22 @@
# Test that the options selector for fuzzy finding is working as expected for different argument types.
If an argument is required but doesn't have a fuzzy resolver, the command should just print the help.
```unison
```ucm:error
-- The second argument of move.term is a 'new-name' and doesn't have a fuzzy resolver
.> 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:error
.empty> view
```
```unison:hide
optionOne = 1
nested.optionTwo = 2

View File

@ -1,29 +1,39 @@
# Test that the options selector for fuzzy finding is working as expected for different argument types.
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
.> move.term
`move.term foo bar` renames `foo` to `bar`.
```
If a fuzzy resolver doesn't have any options available it should print a message instead of
opening an empty fuzzy-select.
```ucm
☝️ The namespace .empty is empty.
.empty> view
⚠️
Sorry, I was expecting an argument for the definition to view, and I couldn't find any to suggest to you. 😅
```
```unison
optionOne = 1
nested.optionTwo = 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`:
nested.optionTwo : ##Nat
optionOne : ##Nat
```
Definition args
```ucm
☝️ The namespace . is empty.
.> add
⍟ I've added these definitions:
@ -33,7 +43,7 @@ Definition args
.> debug.fuzzy-options view _
Select a definition:
Select a definition to view:
* optionOne
* nested.optionTwo
@ -80,7 +90,7 @@ myproject/main> branch mybranch
.> debug.fuzzy-options switch _
Select a project or branch:
Select a project or branch to switch to:
* myproject/main
* myproject/mybranch
* myproject

View File

@ -1,67 +0,0 @@
# Globbing
## Overview
This allows quickly selecting terms, types, and namespaces for any "bulk" commands.
* Currently supports up to one wildcard PER SEGMENT; Each segment can have its own wildcard if you really want and it'll still be performant. E.g. `.base.?.to?`
* Can have a prefix, suffix or infix wildcard! E.g. `to?` or `?List` or `to?With!`
* I went with `?` instead of `*` for the wildcard symbol since `?` isn't currently a valid symbol name. This may cause some confusion since it differs from bash globbing though; so if anyone has thoughts/concerns about how to better handle this I'd love to hear them.
* Commands can select which targets they want globs to expand to; e.g. `cd` should only glob for namespace, `view` should only glob to terms & types.
## Demo
Add some definitions which we can match over:
```unison:hide
convertToThing = 1
convertFromThing = 2
otherTerm = 3
-- Nested definitions
nested.toList = 4
nested.toMap = 5
othernest.toList = 6
othernest.toMap = 7
```
```ucm:hide
.> add
```
Globbing as a prefix, infix, or suffix wildcard.
```ucm
.> view convert?
.> view convert?Thing
.> view ?Thing
```
Globbing can occur in any name segment.
```ucm
.> view ?.toList
.> view nested.to?
```
You may have up to one glob per name segment.
```ucm
.> view ?.to?
```
Globbing only expands to the appropriate argument type.
E.g. `view` should not see glob expansions for namespaces.
This should expand to only the otherTerm.
```ucm
.> view other?
```
Globbing should work from within a namespace with both absolute and relative patterns.
```ucm
.nested> view .othernest.to?
.nested> view to?
```

View File

@ -1,124 +0,0 @@
# Globbing
## Overview
This allows quickly selecting terms, types, and namespaces for any "bulk" commands.
* Currently supports up to one wildcard PER SEGMENT; Each segment can have its own wildcard if you really want and it'll still be performant. E.g. `.base.?.to?`
* Can have a prefix, suffix or infix wildcard! E.g. `to?` or `?List` or `to?With!`
* I went with `?` instead of `*` for the wildcard symbol since `?` isn't currently a valid symbol name. This may cause some confusion since it differs from bash globbing though; so if anyone has thoughts/concerns about how to better handle this I'd love to hear them.
* Commands can select which targets they want globs to expand to; e.g. `cd` should only glob for namespace, `view` should only glob to terms & types.
## Demo
Add some definitions which we can match over:
```unison
convertToThing = 1
convertFromThing = 2
otherTerm = 3
-- Nested definitions
nested.toList = 4
nested.toMap = 5
othernest.toList = 6
othernest.toMap = 7
```
Globbing as a prefix, infix, or suffix wildcard.
```ucm
.> view convert?
convertFromThing : ##Nat
convertFromThing = 2
convertToThing : ##Nat
convertToThing = 1
.> view convert?Thing
convertFromThing : ##Nat
convertFromThing = 2
convertToThing : ##Nat
convertToThing = 1
.> view ?Thing
convertFromThing : ##Nat
convertFromThing = 2
convertToThing : ##Nat
convertToThing = 1
```
Globbing can occur in any name segment.
```ucm
.> view ?.toList
nested.toList : ##Nat
nested.toList = 4
othernest.toList : ##Nat
othernest.toList = 6
.> view nested.to?
nested.toList : ##Nat
nested.toList = 4
nested.toMap : ##Nat
nested.toMap = 5
```
You may have up to one glob per name segment.
```ucm
.> view ?.to?
nested.toList : ##Nat
nested.toList = 4
nested.toMap : ##Nat
nested.toMap = 5
othernest.toList : ##Nat
othernest.toList = 6
othernest.toMap : ##Nat
othernest.toMap = 7
```
Globbing only expands to the appropriate argument type.
E.g. `view` should not see glob expansions for namespaces.
This should expand to only the otherTerm.
```ucm
.> view other?
otherTerm : ##Nat
otherTerm = 3
```
Globbing should work from within a namespace with both absolute and relative patterns.
```ucm
.nested> view .othernest.to?
.othernest.toList : ##Nat
.othernest.toList = 6
.othernest.toMap : ##Nat
.othernest.toMap = 7
.nested> view to?
toList : ##Nat
toList = 4
toMap : ##Nat
toMap = 5
```

View File

@ -77,7 +77,7 @@ Functor.blah = cases Functor f ->
⍟ These new definitions are ok to `add`:
unique type Functor f
type Functor f
Functor.blah : Functor f -> ()
Functor.map : Functor f
-> (∀ a b. (a -> b) -> f a -> f b)
@ -121,8 +121,8 @@ Loc.transform2 nt = cases Loc f ->
⍟ These new definitions are ok to `add`:
unique type Loc
unique ability Remote t
type Loc
ability Remote t
Loc.blah : Loc -> ()
Loc.transform : (∀ t a. '{Remote t} a -> '{Remote t} a)
-> Loc

View File

@ -1,39 +0,0 @@
This transcript tests that UCM can always access the definition of
`IsPropagated`/`isPropagated`, which is used internally.
```ucm:hide
.> alias.term ##Nat.+ +
.> alias.type ##Nat Nat
```
`y` depends on `x`,
```unison:hide
x = 3
y = x + 1
```
```ucm
.> add
```
so the `update` of `x` causes a propagated update of `y`, and UCM links the
`isPropagated` metadata to such resulting terms:
```unison:hide
x = 4
```
```ucm
.> update.old
.> links y
.> view 1
```
Well, it's hard to tell from those hashes, but those are right. We can confirm
by running `builtins.merge` to have UCM add names for them.
```ucm
.> builtins.merge
.> links y
.> view 1
```

View File

@ -1,66 +0,0 @@
This transcript tests that UCM can always access the definition of
`IsPropagated`/`isPropagated`, which is used internally.
`y` depends on `x`,
```unison
x = 3
y = x + 1
```
```ucm
.> add
⍟ I've added these definitions:
x : Nat
y : Nat
```
so the `update` of `x` causes a propagated update of `y`, and UCM links the
`isPropagated` metadata to such resulting terms:
```unison
x = 4
```
```ucm
.> update.old
⍟ I've updated these names to your new definition:
x : Nat
.> links y
1. #cb9e3iosob : #c23jofurce
Tip: Try using `display 1` to display the first result or
`view 1` to view its source.
.> view 1
#cb9e3iosob : #c23jofurce
#cb9e3iosob = #c23jofurce#0
```
Well, it's hard to tell from those hashes, but those are right. We can confirm
by running `builtins.merge` to have UCM add names for them.
```ucm
.> builtins.merge
Done.
.> links y
1. builtin.metadata.isPropagated : IsPropagated
Tip: Try using `display 1` to display the first result or
`view 1` to view its source.
.> view 1
builtin.metadata.isPropagated : IsPropagated
builtin.metadata.isPropagated = IsPropagated
```

View File

@ -1,18 +0,0 @@
This transcript tests that UCM can always access the definition of
`IsTest`/`isTest`, which is used internally.
```ucm
.> builtins.merge
```
```unison:hide
test> pass = [Ok "Passed"]
```
```ucm
.> add
.> links pass
.> display 1
```
The definition and type of `isTest` should exist.

View File

@ -1,33 +0,0 @@
This transcript tests that UCM can always access the definition of
`IsTest`/`isTest`, which is used internally.
```ucm
.> builtins.merge
Done.
```
```unison
test> pass = [Ok "Passed"]
```
```ucm
.> add
⍟ I've added these definitions:
pass : [Result]
.> links pass
1. builtin.metadata.isTest : IsTest
Tip: Try using `display 1` to display the first result or
`view 1` to view its source.
.> display 1
IsTest
```
The definition and type of `isTest should exist.

View File

@ -52,8 +52,8 @@ unique type Pong = Pong (Ping Optional)
⍟ These new definitions are ok to `add`:
unique type Ping a
unique type Pong
type Ping a
type Pong
```
Catch the conflict on the kind of `a` in `Ping a`. `Ping` restricts
@ -91,8 +91,8 @@ unique ability Pong a where
⍟ These new definitions are ok to `add`:
unique type Ping a
unique ability Pong a
type Ping a
ability Pong a
```
Catch conflict between mutually recursive type and ability
@ -130,8 +130,8 @@ unique type S = S (T Nat)
⍟ These new definitions are ok to `add`:
unique type S
unique type T a
type S
type T a
```
Delay kind defaulting until all components are processed. Here `S`
@ -153,8 +153,8 @@ unique type S = S (T Optional)
⍟ These new definitions are ok to `add`:
unique type S
unique type T a
type S
type T a
```
Catch invalid instantiation of `T`'s `a` parameter in `S`

View File

@ -1,73 +0,0 @@
# Linking definitions to metadata
```ucm:hide
.> builtins.mergeio
```
The `link` and `unlink` commands can be used to manage metadata linked to definitions. For example, you can link documentation to a definition:
```unison
use .builtin
coolFunction x = x * 2
coolFunction.doc = [: This is a cool function. :]
```
```ucm
.> add
.> link coolFunction.doc coolFunction
```
You can use arbitrary Unison values and link them as metadata to definitions:
```unison
toCopyrightHolder author = match author with
Author guid name -> CopyrightHolder guid name
alice = Author (GUID Bytes.empty) "Alice Coder"
coolFunction.license = License [toCopyrightHolder alice] [Year 2020] licenses.mit
licenses.mit = LicenseType [:
Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions:
The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software.
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
:]
```
```ucm
.> add
.> link coolFunction.license coolFunction
.> link alice coolFunction
```
We can look at the links we have:
```ucm
.> links coolFunction
.> links coolFunction License
```
We can link the same metadata simultaneously to multiple definitions:
```unison
myLibrary.f x = x + 1
myLibrary.g x = x + 2
myLibrary.h x = x + 3
```
```ucm
.> add
.> cd myLibrary
.myLibrary> find
.myLibrary> link .alice 1-3
.myLibrary> links f
.myLibrary> links g
.myLibrary> links h
.myLibrary> history
.> unlink coolFunction.doc coolFunction
```

View File

@ -1,216 +0,0 @@
# Linking definitions to metadata
The `link` and `unlink` commands can be used to manage metadata linked to definitions. For example, you can link documentation to a definition:
```unison
use .builtin
coolFunction x = x * 2
coolFunction.doc = [: This is a cool function. :]
```
```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`:
coolFunction : Nat -> Nat
coolFunction.doc : Doc
```
```ucm
.> add
⍟ I've added these definitions:
coolFunction : Nat -> Nat
coolFunction.doc : Doc
.> link coolFunction.doc coolFunction
Updates:
1. coolFunction : Nat -> Nat
+ 2. doc : Doc
```
You can use arbitrary Unison values and link them as metadata to definitions:
```unison
toCopyrightHolder author = match author with
Author guid name -> CopyrightHolder guid name
alice = Author (GUID Bytes.empty) "Alice Coder"
coolFunction.license = License [toCopyrightHolder alice] [Year 2020] licenses.mit
licenses.mit = LicenseType [:
Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions:
The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software.
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
:]
```
```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`:
alice : Author
coolFunction.license : License
licenses.mit : LicenseType
toCopyrightHolder : Author -> CopyrightHolder
```
```ucm
.> add
⍟ I've added these definitions:
alice : Author
coolFunction.license : License
licenses.mit : LicenseType
toCopyrightHolder : Author -> CopyrightHolder
.> link coolFunction.license coolFunction
Updates:
1. coolFunction : Nat -> Nat
+ 2. license : License
.> link alice coolFunction
Updates:
1. coolFunction : Nat -> Nat
+ 2. alice : Author
```
We can look at the links we have:
```ucm
.> links coolFunction
1. alice : Author
2. coolFunction.license : License
3. coolFunction.doc : Doc
Tip: Try using `display 1` to display the first result or
`view 1` to view its source.
.> links coolFunction License
1. coolFunction.license : License
Tip: Try using `display 1` to display the first result or
`view 1` to view its source.
```
We can link the same metadata simultaneously to multiple definitions:
```unison
myLibrary.f x = x + 1
myLibrary.g x = x + 2
myLibrary.h x = 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`:
myLibrary.f : Nat -> Nat
myLibrary.g : Nat -> Nat
myLibrary.h : Nat -> Nat
```
```ucm
.> add
⍟ I've added these definitions:
myLibrary.f : Nat -> Nat
myLibrary.g : Nat -> Nat
myLibrary.h : Nat -> Nat
.> cd myLibrary
.myLibrary> find
1. f : Nat -> Nat
2. g : Nat -> Nat
3. h : Nat -> Nat
.myLibrary> link .alice 1-3
Updates:
1. myLibrary.f : Nat -> Nat
+ 2. alice : Author
3. myLibrary.g : Nat -> Nat
+ 4. alice : Author
5. myLibrary.h : Nat -> Nat
+ 6. alice : Author
.myLibrary> links f
1. .alice : Author
Tip: Try using `display 1` to display the first result or
`view 1` to view its source.
.myLibrary> links g
1. .alice : Author
Tip: Try using `display 1` to display the first result or
`view 1` to view its source.
.myLibrary> links h
1. .alice : Author
Tip: Try using `display 1` to display the first result or
`view 1` to view its source.
.myLibrary> history
Note: The most recent namespace hash is immediately below this
message.
⊙ 1. #fa706ukb83
□ 2. #ikha0ltbmc (start of history)
.> unlink coolFunction.doc coolFunction
Updates:
1. coolFunction : Nat -> Nat
- 2. doc : Doc
```

View File

@ -12,7 +12,7 @@ unique type Foo = Foo
⍟ These new definitions are ok to `add`:
unique type Foo
type Foo
```
```ucm
@ -22,7 +22,7 @@ unique type Foo = Foo
⍟ I've added these definitions:
unique type Foo
type Foo
.> fork .a.b .c.d.f
@ -45,7 +45,7 @@ unique type Foo = Foo
⍟ These new definitions are ok to `add`:
unique type Foo
type Foo
```
```ucm
@ -53,7 +53,7 @@ unique type Foo = Foo
⍟ I've added these definitions:
unique type Foo
type Foo
```
```unison

View File

@ -294,12 +294,14 @@ Now merging `c1b` into `c1a` should result in the updated version of `a` and `f`
1. a : Nat
2. a : Text
There were 1 auto-propagated updates.
3. f : Text
4. f : Text
Added definitions:
3. patch patch (added 1 updates)
5. patch patch (added 1 updates)
Tip: You can use `todo` to see if this generated any work to
do in this namespace and `test` to run the tests. Or you

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