diff --git a/parser-typechecker/src/Unison/Parser.hs b/parser-typechecker/src/Unison/Parser.hs index 6d876ce9c..732190965 100644 --- a/parser-typechecker/src/Unison/Parser.hs +++ b/parser-typechecker/src/Unison/Parser.hs @@ -263,6 +263,11 @@ matchToken x = P.satisfy ((==) x . L.payload) dot :: Var v => P v (L.Token L.Lexeme) dot = matchToken (L.SymbolyId ".") +dotId :: Var v => P v (L.Token String) +dotId = queryToken go where + go (L.SymbolyId ".") = Just "." + go _ = Nothing + -- Consume a virtual semicolon semi :: Var v => P v (L.Token ()) semi = fmap (const ()) <$> matchToken L.Semi diff --git a/parser-typechecker/src/Unison/TermParser.hs b/parser-typechecker/src/Unison/TermParser.hs index 74cec68c7..9e0d19724 100644 --- a/parser-typechecker/src/Unison/TermParser.hs +++ b/parser-typechecker/src/Unison/TermParser.hs @@ -334,24 +334,14 @@ block s = block' False s (openBlockWith s) closeBlock importp :: Var v => P v [(v, v)] importp = do - let name = Var.nameds . L.payload <$> (wordyId <|> symbolyId) - namesp = many name _ <- reserved "use" - e <- (Left <$> wordyId) <|> (Right <$> symbolyId) - case e of - Left w -> do - more <- (False <$ P.try (lookAhead semi)) <|> pure True - case more of - True -> do - i <- (Var.nameds . L.payload $ w) <$ optional dot - names <- namesp <|> (pure <$> name) - pure [ (n, Var.joinDot i n) | n <- names ] - False -> - let (_, n) = L.splitWordy (L.payload w) - in pure [ (Var.nameds n, Var.nameds $ L.payload w) ] - Right o -> - let (_, op) = L.splitSymboly (L.payload o) - in pure [ (Var.nameds op, Var.nameds $ L.payload o) ] + prefix <- wordyId <|> dotId + suffixes <- some (wordyId <|> symbolyId) P. "one or more identifiers" + pure $ do + let v = Var.nameds (L.payload prefix) + s <- suffixes + let suffix = Var.nameds . L.payload $ s + pure (suffix, Var.joinDot v suffix) --module Monoid where -- -- we replace all the binding names with Monoid.op, and diff --git a/parser-typechecker/src/Unison/Var.hs b/parser-typechecker/src/Unison/Var.hs index 2f578c6ed..6283ddb35 100644 --- a/parser-typechecker/src/Unison/Var.hs +++ b/parser-typechecker/src/Unison/Var.hs @@ -135,7 +135,9 @@ nameds :: Var v => String -> v nameds s = named (Text.pack s) joinDot :: Var v => v -> v -> v -joinDot v v2 = named (name v `mappend` "." `mappend` name v2) +joinDot prefix v2 = + if name prefix == "." then named (name prefix `mappend` name v2) + else named (name prefix `mappend` "." `mappend` name v2) freshes :: Var v => Set v -> [v] -> [v] freshes _ [] = [] diff --git a/parser-typechecker/tests/Unison/Test/TermPrinter.hs b/parser-typechecker/tests/Unison/Test/TermPrinter.hs index 4f72bdebb..7d6e46561 100755 --- a/parser-typechecker/tests/Unison/Test/TermPrinter.hs +++ b/parser-typechecker/tests/Unison/Test/TermPrinter.hs @@ -218,7 +218,6 @@ test = scope "termprinter" . tests $ \ else c" , tc_diff_rtt True "if foo\n\ \then\n\ - \ use bar\n\ \ and true true\n\ \ 12\n\ \else\n\ diff --git a/unison-src/tests/cce.u b/unison-src/tests/cce.u index 78c37af9c..1b53936e1 100644 --- a/unison-src/tests/cce.u +++ b/unison-src/tests/cce.u @@ -101,7 +101,7 @@ sort lte a = Node.increment : Node -> Node Node.increment n = - use Node.Node -- the constructor + use Node Node -- the constructor case n of Node n -> Node (n + 1) > Remote.runLocal '(dsort (<) [3,2,1,1,2,3,9182,1,2,34,1,23]) diff --git a/unison-src/tests/hang.u b/unison-src/tests/hang.u index 6819b9b5e..4343d0003 100644 --- a/unison-src/tests/hang.u +++ b/unison-src/tests/hang.u @@ -82,7 +82,7 @@ halve as = Node.increment : Node -> Node Node.increment n = - use Node.Node -- the constructor + use Node Node -- the constructor case n of Node n -> Node (n + 1) > Remote.runLocal '(dsort2 (<) [3,2,1,1,2,3,9182,1,2,34,1,23]) diff --git a/unison-src/tests/imports.u b/unison-src/tests/imports.u index 993dcd68b..d90cecf9b 100644 --- a/unison-src/tests/imports.u +++ b/unison-src/tests/imports.u @@ -1,5 +1,7 @@ +use . Int -- imports `.Int` from root path and gives it the local name `Int` + -- This brings `None` into scope unqualified -use Optional.None +use Optional None -- '.' is optional, this brings `None` and `Some` into -- scope unqualified @@ -7,12 +9,12 @@ use Optional None Some -- Can import operators this way also -- no need to put them in parens -use Nat.+ +use Nat + -- Later imports shadow earlier ones use Nat - * / -use Nat. drop * -use Nat . drop +use Nat drop * +use Nat drop -- use Int + -- this would cause type error below! > case Some (100 + 200 / 3 * 2) of diff --git a/unison-src/tests/soe.u b/unison-src/tests/soe.u index 3cee496b6..500ab6489 100644 --- a/unison-src/tests/soe.u +++ b/unison-src/tests/soe.u @@ -100,7 +100,7 @@ sort lte a = Node.increment : Node -> Node Node.increment n = - use Node.Node -- the constructor + use Node Node -- the constructor case n of Node n -> Node (n + 1) > Remote.runLocal '(dsort (<) [3,2,1,1,2,3,9182,1,2,34,1,23]) diff --git a/unison-src/tests/tictactoe0-array-oob1.u b/unison-src/tests/tictactoe0-array-oob1.u index f9947c690..4bbe0a810 100644 --- a/unison-src/tests/tictactoe0-array-oob1.u +++ b/unison-src/tests/tictactoe0-array-oob1.u @@ -2,7 +2,7 @@ type Board = Board Nat Nat Nat -use Board.Board +use Board Board -- uncommenting these gives errors from NPE to array index out of bounds -1, -2 -- x = 1 diff --git a/unison-src/tests/tictactoe0-npe.u b/unison-src/tests/tictactoe0-npe.u index a7b735d9e..7c78cb158 100644 --- a/unison-src/tests/tictactoe0-npe.u +++ b/unison-src/tests/tictactoe0-npe.u @@ -3,7 +3,7 @@ type P = X | O | E type Board = Board P P P P P P P P P -use Board.Board +use Board Board use P O X E whatevs a b c = a