Merge branch 'trunk' of github.com:unisonweb/unison into topic/codebaseserver-openapi

This commit is contained in:
runarorama 2020-11-10 12:44:03 -05:00
commit cba4cf36de
20 changed files with 318 additions and 52 deletions

View File

@ -89,19 +89,31 @@ resolveNames typeLookupf preexistingNames uf = do
possibleDeps = [ (Name.toText name, Var.name v, r) |
(name, r) <- Rel.toList (Names.terms0 preexistingNames),
v <- Set.toList (Term.freeVars tm),
Name.unqualified name == Name.unqualified (Name.fromVar v) ]
name `Name.endsWithSegments` Name.fromVar v ]
possibleRefs = Referent.toReference . view _3 <$> possibleDeps
tl <- lift . lift . fmap (UF.declsToTypeLookup uf <>)
$ typeLookupf (deps <> Set.fromList possibleRefs)
-- For populating the TDNR environment, we pick definitions
-- from the namespace and from the local file whose full name
-- has a suffix that equals one of the free variables in the file.
-- Example, the namespace has [foo.bar.baz, qux.quaffle] and
-- the file has definitons [utils.zonk, utils.blah] and
-- the file has free variables [bar.baz, zonk].
--
-- In this case, [foo.bar.baz, utils.zonk] are used to create
-- the TDNR environment.
let fqnsByShortName = List.multimap $
-- external TDNR possibilities
[ (shortname, nr) |
(name, shortname, r) <- possibleDeps,
typ <- toList $ TL.typeOfReferent tl r,
let nr = Typechecker.NamedReference name typ (Right r) ] <>
[ (shortname, nr) |
-- local file TDNR possibilities
[ (Var.name v, nr) |
(name, r) <- Rel.toList (Names.terms0 $ UF.toNames uf),
v <- Set.toList (Term.freeVars tm),
name `Name.endsWithSegments` Name.fromVar v,
typ <- toList $ TL.typeOfReferent tl r,
let shortname = Name.toText $ Name.unqualified name,
let nr = Typechecker.NamedReference (Name.toText name) typ (Right r) ]
pure (tm, fqnsByShortName, tl)

View File

@ -166,9 +166,9 @@ unique[b28d929d0a73d2c18eac86341a3bb9399f8550c11b5f35eabb2751e6803ccc20] type
d1 Doc.++ d2 =
use Doc
match (d1,d2) with
(Join ds, Join ds2) -> Join (ds Sequence.++ ds2)
(Join ds, _) -> Join (ds `Sequence.snoc` d2)
(_, Join ds) -> Join (d1 `Sequence.cons` ds)
(Join ds, Join ds2) -> Join (ds List.++ ds2)
(Join ds, _) -> Join (ds `List.snoc` d2)
(_, Join ds) -> Join (d1 `List.cons` ds)
_ -> Join [d1,d2]
unique[q1905679b27a97a4098bc965574da880c1074183a2c55ff1d481619c7fb8a1e1] type

View File

@ -135,16 +135,16 @@ match = do
-- Returns the arity of the pattern and the `MatchCase`. Examples:
--
-- (a, b) -> a - b -- arity 1
-- foo (hd +: tl) -> foo tl -- arity 2
-- foo, hd +: tl -> foo tl -- arity 2
--
-- Cases with arity greater than 1 are desugared to matching on tuples,
-- so the following are parsed the same:
--
-- 42 x -> ...
-- 42, x -> ...
-- (42, x) -> ...
matchCase :: Var v => P v (Int, Term.MatchCase Ann (Term v Ann))
matchCase = do
pats <- some parsePattern
pats <- sepBy1 (reserved ",") parsePattern
let boundVars' = [ v | (_,vs) <- pats, (_ann,v) <- vs ]
pat = case fst <$> pats of
[p] -> p

View File

@ -481,9 +481,9 @@ printCase env im doc ms = PP.lines $ map each gridArrowsAligned where
where
lhs = (case pats of
[pat] -> PP.group (fst (prettyPattern env (ac 0 Block im doc) (-1) vs pat))
pats -> PP.group . PP.spaced . (`evalState` vs) . for pats $ \pat -> do
pats -> PP.group . PP.sep ("," <> PP.softbreak) . (`evalState` vs) . for pats $ \pat -> do
vs <- State.get
let (p, rem) = prettyPattern env (ac 0 Block im doc) 10 vs pat
let (p, rem) = prettyPattern env (ac 0 Block im doc) (-1) vs pat
State.put rem
pure p)
<> printGuard guard
@ -1135,8 +1135,8 @@ pattern LamsNamedMatch' vs branches <- (unLamsMatch' -> Just (vs, branches))
-- (x, y) -> y ++ x
--
-- this function will return Just ([x], [ "a" "b" -> "abba", x y -> y ++ x])
-- and it would be rendered as `x -> cases "a" "b" -> "abba"
-- x y -> y ++ x
-- and it would be rendered as `x -> cases "a", "b" -> "abba"
-- x, y -> y ++ x
--
-- This function returns `Nothing` in cases where the term it is given isn't
-- a lambda, or when the lambda isn't in the correct form for lambda cases.

View File

@ -33,6 +33,7 @@ import Unison.Var (Var)
import qualified Unison.Var as Var
import qualified Unison.Typechecker.TypeLookup as TL
import Unison.Util.List ( uniqueBy )
import qualified Unison.Name as Name
type Name = Text
@ -62,7 +63,13 @@ data NamedReference v loc =
data Env v loc = Env
{ _ambientAbilities :: [Type v loc]
, _typeLookup :: TL.TypeLookup v loc
, _unqualifiedTerms :: Map Name [NamedReference v loc]
-- TDNR environment - maps short names like `+` to fully-qualified
-- lists of named references whose full name matches the short name
-- Example: `+` maps to [Nat.+, Float.+, Int.+]
--
-- This mapping is populated before typechecking with as few entries
-- as are needed to help resolve variables needing TDNR in the file.
, _termsByShortname :: Map Name [NamedReference v loc]
}
makeLenses ''Env
@ -232,8 +239,9 @@ typeDirectedNameResolution oldNotes oldType env = do
addTypedComponent :: Context.InfoNote v loc -> State (Env v loc) ()
addTypedComponent (Context.TopLevelComponent vtts)
= for_ vtts $ \(v, typ, _) ->
unqualifiedTerms %= Map.insertWith (<>)
(Var.unqualifiedName v)
for_ (Name.suffixes . Name.unsafeFromText . Var.name $ Var.reset v) $ \suffix ->
termsByShortname %=
Map.insertWith (<>) (Name.toText suffix)
[NamedReference (Var.name v) typ (Left v)]
addTypedComponent _ = pure ()
@ -276,7 +284,7 @@ typeDirectedNameResolution oldNotes oldType env = do
. join
. maybeToList
. Map.lookup (Text.pack n)
$ view unqualifiedTerms env
$ view termsByShortname env
resolveNote _ n = btw n >> pure Nothing
dedupe :: [Context.Suggestion v loc] -> [Context.Suggestion v loc]
dedupe = uniqueBy Context.suggestionReplacement

View File

@ -52,19 +52,19 @@ main = 'let
expected = ${expectedText}
-- Write to myFile
h1 = builtins.io.openFile (FilePath fp) Write
h1 = io.openFile (FilePath fp) Write
putText h1 expected
builtins.io.closeFile h1
io.closeFile h1
-- Read from myFile
h2 = builtins.io.openFile (FilePath fp) Read
h2 = builtin.io.openFile (FilePath fp) Read
myC = getText h2
builtins.io.closeFile h2
io.closeFile h2
-- Write what we read from myFile to resultFile
h3 = builtins.io.openFile (FilePath res) Write
h3 = io.openFile (FilePath res) Write
putText h3 myC
builtins.io.closeFile h3
builtin.io.closeFile h3
```
```ucm

View File

@ -164,14 +164,14 @@ test = scope "termprinter" $ tests
\ !f 1"
, tc "let\n\
\ f = cases\n\
\ 0 x -> 0\n\
\ x 0 -> x\n\
\ 0, x -> 0\n\
\ x, 0 -> x\n\
\ f y"
, tc "let\n\
\ interleave = cases\n\
\ [] x -> x\n\
\ x [] -> y\n\
\ (h +: t) (h2 +: t2) -> [h, h2] ++ interleave t t2\n\
\ [], x -> x\n\
\ x, [] -> y\n\
\ h +: t, h2 +: t2 -> [h, h2] ++ interleave t t2\n\
\ f y"
, pending $ tc "match x with Pair t 0 -> foo t" -- TODO hitting UnknownDataConstructor when parsing pattern
, pending $ tc "match x with Pair t 0 | pred t -> foo t" -- ditto

View File

@ -6,6 +6,7 @@
module Unison.Name
( Name(Name)
, endsWithSegments
, fromString
, isPrefixOf
, joinDot
@ -89,6 +90,14 @@ toString = Text.unpack . toText
isPrefixOf :: Name -> Name -> Bool
a `isPrefixOf` b = toText a `Text.isPrefixOf` toText b
-- foo.bar.baz `endsWithSegments` bar.baz == True
-- foo.bar.baz `endsWithSegments` baz == True
-- foo.bar.baz `endsWithSegments` az == False (not a full segment)
-- foo.bar.baz `endsWithSegments` zonk == False (doesn't match any segment)
-- foo.bar.baz `endsWithSegments` foo == False (matches a segment, but not at the end)
endsWithSegments :: Name -> Name -> Bool
endsWithSegments n ending = any (== ending) (suffixes n)
-- stripTextPrefix a.b. a.b.c = Just c
-- stripTextPrefix a.b a.b.c = Just .c; you probably don't want to do this
-- stripTextPrefix x.y. a.b.c = Nothing

View File

@ -1,5 +1,5 @@
foo a b =
if a Text.== "" then
if a `Text.eq` "" then
match Text.size b with
1 -> false
_ -> true

View File

@ -11,7 +11,7 @@ main = '(tell get)
replicate : Nat -> '{e} () -> {e} ()
replicate n x =
if n Nat.== 0 then () else
if n `Nat.eq` 0 then () else
!x
replicate (n `drop` 1) x

View File

@ -1,4 +1,4 @@
use Nat drop >=
use Nat drop
use Optional None Some
search : (Nat -> Int) -> Nat -> Nat -> Optional Nat

View File

@ -1,5 +1,5 @@
use Nat drop >=
use Nat drop
use Optional None Some
search : (Nat -> Int) -> Nat -> Nat -> Optional Nat

View File

@ -7,4 +7,4 @@ unfold s f =
Some (hd, s) -> go s (acc `List.snoc` hd)
go s []
> unfold 0 (n -> if n Nat.< 5 then Some (n, n + 1) else None)
> unfold 0 (n -> if n < 5 then Some (n, n + 1) else None)

View File

@ -1 +1 @@
> .builtin.Nat.toFloat 4
> Nat.toFloat 4

View File

@ -30,7 +30,7 @@ from n = unfold n (n -> Some (n, n + 1))
take n s =
step n = cases
{Emit.emit a -> k} ->
if n Nat.== 0 then ()
if n == 0 then ()
else
Emit.emit a
handle k () with step (n `drop` 1)

View File

@ -6,17 +6,17 @@
foo : Int
foo = +1
-- no imports needed here, even though FQNs are builtin.Optional.{None,Some}
-- no imports needed here, even though FQNs are Optional.{None,Some}
ex1 = cases
None -> 0
Some a -> a + 1
-- you can still use the
-- you can still use the FQN
ex2 = cases
Optional.None -> 99
Optional.Some _ -> 0
ex3 = builtin.Optional.None
ex3 = List.at 0 [ 1, 2, 3, 4 ]
-- TDNR would have handled this one before, but TDNR can't do
-- type resolution or pattern resolution

View File

@ -0,0 +1,57 @@
```ucm:hide
.> builtins.merge
```
Add `List.zonk` to the codebase:
```unison
List.zonk : [a] -> [a]
List.zonk xs = xs
Text.zonk : Text -> Text
Text.zonk txt = txt ++ "!! "
```
```ucm:hide
.> add
```
Now, typecheck a file with a reference to `Blah.zonk` (which doesn't exist in the codebase). This should fail:
```unison:error
-- should not typecheck as there's no `Blah.zonk` in the codebase
> Blah.zonk [1,2,3]
```
Here's another example, just checking that TDNR works for definitions in the same file:
```unison
foo.bar.baz = 42
qux.baz = "hello"
ex = baz ++ ", world!"
> ex
```
Here's another example, checking that TDNR works when multiple codebase definitions have matching names:
```unison
ex = zonk "hi"
> ex
```
Last example, showing that TDNR works when there are multiple matching names in both the file and the codebase:
```unison
woot.zonk = "woot"
woot2.zonk = 9384
ex = zonk "hi" -- should resolve to Text.zonk, from the codebase
++ zonk -- should resolve to the local `woot.zonk` from this file
> ex
```

View File

@ -0,0 +1,130 @@
Add `List.zonk` to the codebase:
```unison
List.zonk : [a] -> [a]
List.zonk xs = xs
Text.zonk : Text -> Text
Text.zonk txt = txt ++ "!! "
```
```ucm
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`:
List.zonk : [a] -> [a]
Text.zonk : Text -> Text
```
Now, typecheck a file with a reference to `Blah.zonk` (which doesn't exist in the codebase). This should fail:
```unison
-- should not typecheck as there's no `Blah.zonk` in the codebase
> Blah.zonk [1,2,3]
```
```ucm
I'm not sure what Blah.zonk means at line 2, columns 3-12
2 | > Blah.zonk [1,2,3]
Whatever it is, it has a type that conforms to [builtin.Nat] -> o.
```
Here's another example, just checking that TDNR works for definitions in the same file:
```unison
foo.bar.baz = 42
qux.baz = "hello"
ex = baz ++ ", world!"
> ex
```
```ucm
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`:
ex : Text
foo.bar.baz : Nat
qux.baz : Text
Now evaluating any watch expressions (lines starting with
`>`)... Ctrl+C cancels.
7 | > ex
"hello, world!"
```
Here's another example, checking that TDNR works when multiple codebase definitions have matching names:
```unison
ex = zonk "hi"
> ex
```
```ucm
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`:
ex : Text
Now evaluating any watch expressions (lines starting with
`>`)... Ctrl+C cancels.
3 | > ex
"hi!! "
```
Last example, showing that TDNR works when there are multiple matching names in both the file and the codebase:
```unison
woot.zonk = "woot"
woot2.zonk = 9384
ex = zonk "hi" -- should resolve to Text.zonk, from the codebase
++ zonk -- should resolve to the local `woot.zonk` from this file
> ex
```
```ucm
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`:
ex : Text
woot.zonk : Text
woot2.zonk : Nat
Now evaluating any watch expressions (lines starting with
`>`)... Ctrl+C cancels.
7 | > ex
"hi!! woot"
```

View File

@ -34,7 +34,7 @@ it shows the definition using `cases` syntax opportunistically, even though the
## Multi-argument cases
Functions that take multiple arguments and immediately match on a tuple of arguments can also be rewritten to use `cases`:
Functions that take multiple arguments and immediately match on a tuple of arguments can also be rewritten to use `cases`. Here's a version using regular `match` syntax on a tuple:
```unison:hide
merge : [a] -> [a] -> [a]
@ -50,14 +50,14 @@ merge xs ys = match (xs, ys) with
.> add
```
Here's a version using `cases`:
And here's a version using `cases`. The patterns are separated by commas:
```unison
merge2 : [a] -> [a] -> [a]
merge2 = cases
[] ys -> ys
xs [] -> xs
(h +: t) (h2 +: t2) ->
[], ys -> ys
xs, [] -> xs
h +: t, h2 +: t2 ->
if h <= h2 then h +: merge2 t (h2 +: t2)
else h2 +: merge2 (h +: t) t2
```
@ -69,3 +69,16 @@ Notice that Unison detects this as an alias of `merge`, and if we view `merge`
```
it again shows the definition using the multi-argument `cases` syntax opportunistically, even though the code was originally written without that syntax.
Here's another example:
```unison
type B = T | F
blah = cases
T, x -> "hi"
x, F -> "bye"
> blah T F
> blah F F
```

View File

@ -54,7 +54,7 @@ it shows the definition using `cases` syntax opportunistically, even though the
## Multi-argument cases
Functions that take multiple arguments and immediately match on a tuple of arguments can also be rewritten to use `cases`:
Functions that take multiple arguments and immediately match on a tuple of arguments can also be rewritten to use `cases`. Here's a version using regular `match` syntax on a tuple:
```unison
merge : [a] -> [a] -> [a]
@ -74,14 +74,14 @@ merge xs ys = match (xs, ys) with
merge : [a] ->{g} [a] ->{g} [a]
```
Here's a version using `cases`:
And here's a version using `cases`. The patterns are separated by commas:
```unison
merge2 : [a] -> [a] -> [a]
merge2 = cases
[] ys -> ys
xs [] -> xs
(h +: t) (h2 +: t2) ->
[], ys -> ys
xs, [] -> xs
h +: t, h2 +: t2 ->
if h <= h2 then h +: merge2 t (h2 +: t2)
else h2 +: merge2 (h +: t) t2
```
@ -105,11 +105,48 @@ Notice that Unison detects this as an alias of `merge`, and if we view `merge`
merge : [a] -> [a] -> [a]
merge = cases
[] ys -> ys
xs [] -> xs
(h +: t) (h2 +: t2) ->
[], ys -> ys
xs, [] -> xs
h +: t, h2 +: t2 ->
if h <= h2 then h +: merge t (h2 +: t2)
else h2 +: merge (h +: t) t2
```
it again shows the definition using the multi-argument `cases syntax opportunistically, even though the code was originally written without that syntax.
it again shows the definition using the multi-argument `cases` syntax opportunistically, even though the code was originally written without that syntax.
Here's another example:
```unison
type B = T | F
blah = cases
T, x -> "hi"
x, F -> "bye"
> blah T F
> blah F F
```
```ucm
I found and typechecked these definitions in scratch.u. If you
do an `add` or `update`, here's how your codebase would
change:
⍟ These new definitions are ok to `add`:
type B
blah : B -> B -> Text
Now evaluating any watch expressions (lines starting with
`>`)... Ctrl+C cancels.
7 | > blah T F
"hi"
8 | > blah F F
"bye"
```