Switch to foo() with no space as preferred syntax instead of !foo

This commit is contained in:
Paul Chiusano 2024-06-20 16:52:57 -05:00
parent 25c4e6ebfc
commit d4a2ed9066
10 changed files with 37 additions and 13 deletions

View File

@ -38,6 +38,7 @@ import Unison.NameSegment qualified as NameSegment
import Unison.Names (Names)
import Unison.Names qualified as Names
import Unison.NamesWithHistory qualified as Names
import Unison.Parser.Ann qualified as Ann
import Unison.Parser.Ann (Ann)
import Unison.Pattern (Pattern)
import Unison.Pattern qualified as Pattern
@ -48,7 +49,7 @@ import Unison.Syntax.Lexer qualified as L
import Unison.Syntax.Name qualified as Name (toText, toVar, unsafeParseVar)
import Unison.Syntax.NameSegment qualified as NameSegment
import Unison.Syntax.Parser hiding (seq)
import Unison.Syntax.Parser qualified as Parser (seq, uniqueName)
import Unison.Syntax.Parser qualified as Parser (seq, uniqueName, seq')
import Unison.Syntax.TypeParser qualified as TypeParser
import Unison.Term (IsTop, Term)
import Unison.Term qualified as Term
@ -439,7 +440,8 @@ resolveHashQualified tok = do
termLeaf :: forall m v. (Monad m, Var v) => TermP v m
termLeaf =
asum
[ hashQualifiedPrefixTerm,
[ forceOrFnApplication,
hashQualifiedPrefixTerm,
text,
char,
number,
@ -991,6 +993,27 @@ bang = P.label "bang" do
e <- termLeaf
pure $ DD.forceTerm (ann start <> ann e) (ann start) e
forceOrFnApplication :: forall m v . (Monad m, Var v) => TermP v m
forceOrFnApplication = P.label "force" do
-- `foo sqrt(2.0)` parses as `foo (sqrt 2.0)`
-- `forkAt pool() blah` parses as `forkAt (pool ()) blah`
-- `foo max(x, y) z` parsed as `foo (max x y) z`
-- That is, parens immediately (no space) following a symbol is
-- treated as function application, but higher precedence than
-- the usual application syntax where args are separated by spaces
fn <- P.try do
r <- hashQualifiedPrefixTerm
P.lookAhead do
tok <- ann <$> openBlockWith "("
guard (L.column (Ann.start tok) == L.column (Ann.end (ann r)))
pure r
Parser.seq' "(" (done fn) term
where
done :: Term v Ann -> Ann -> [Term v Ann] -> Term v Ann
done fn a [] = DD.forceTerm a a fn
done fn _ [arg] = Term.apps' fn [arg]
done fn _ args = Term.apps' fn args
seqOp :: (Ord v) => P v m Pattern.SeqOp
seqOp =
Pattern.Snoc

View File

@ -490,7 +490,7 @@ pretty0
(App' x (Constructor' (ConstructorReference DD.UnitRef 0)), _) | isLeaf x -> do
px <- pretty0 (ac (if isBlock x then 0 else 9) Normal im doc) x
pure . paren (p >= 11 || isBlock x && p >= 3) $
fmt S.DelayForceChar (l "!") <> PP.indentNAfterNewline 1 px
px <> fmt S.DelayForceChar (l "()")
(Apps' f (unsnoc -> Just (args, lastArg)), _)
| isSoftHangable lastArg -> do
fun <- goNormal 9 f

View File

@ -67,11 +67,11 @@ ping _ = !pong + 3
ping : 'Nat
ping _ =
use Nat +
!pong + 3
pong() + 3
pong : 'Nat
pong _ =
use Nat +
!ping + 2
ping() + 2
```

View File

@ -70,6 +70,6 @@ ping _ = 3
pong : 'Nat
pong _ =
use Nat +
!ping + 2
ping() + 2
```

View File

@ -65,6 +65,6 @@ ping = 3
pong : 'Nat
pong _ =
use Nat +
!#4t465jk908.1 + 2
#4t465jk908.1() + 2
```

View File

@ -74,16 +74,16 @@ clang _ = !pong + 3
clang : 'Nat
clang _ =
use Nat +
!pong + 3
pong() + 3
ping : 'Nat
ping _ =
use Nat +
!clang + 1
clang() + 1
pong : 'Nat
pong _ =
use Nat +
!ping + 2
ping() + 2
```

View File

@ -65,7 +65,7 @@ inner.ping _ = !pong + 3
inner.ping : 'Nat
inner.ping _ =
use Nat +
!pong + 1
pong() + 1
```
The bug here is that `inner.ping` still refers to `pong` by name. But if we properly identified the nameless (in the

View File

@ -486,6 +486,6 @@ pong _ = 4 Nat.+ !ping
pong : 'Nat
pong _ =
use Nat +
4 + !#l9uq1dpl5v.1
4 + #l9uq1dpl5v.1()
```

View File

@ -142,7 +142,7 @@ provide a action =
h = cases
{ ask -> resume } -> handle resume a with h
{ r } -> r
handle !action with h
handle action() with h
Optional.doc = {{ A Doc before a type }}
structural type Optional a = More Text | Some | Other a | None Nat

View File

@ -39,6 +39,7 @@ module Unison.Syntax.Parser
run,
semi,
Unison.Syntax.Parser.seq,
Unison.Syntax.Parser.seq',
sepBy,
sepBy1,
string,