1
1
mirror of https://github.com/github/semantic.git synced 2025-01-07 07:58:12 +03:00

Make sure chained assignments don't lose their location info.

This commit is contained in:
Patrick Thomson 2019-09-27 18:11:36 -04:00
parent 794265d3a9
commit a51151afb5

View File

@ -18,15 +18,13 @@ import Data.Bifunctor
import Data.Coerce import Data.Coerce
import Data.Core as Core import Data.Core as Core
import Data.Foldable import Data.Foldable
import Data.List (mapAccumL, mapAccumR) import Data.Loc (Loc)
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.Loc import qualified Data.Loc
import Data.Name as Name import Data.Name as Name
import Data.Stack (Stack) import Data.Stack (Stack)
import qualified Data.Stack as Stack import qualified Data.Stack as Stack
import Data.String (IsString) import Data.String (IsString)
import Data.Text (Text) import Data.Text (Text)
import Debug.Trace (traceShowId, traceShowM)
import GHC.Generics import GHC.Generics
import GHC.Records import GHC.Records
import qualified TreeSitter.Python.AST as Py import qualified TreeSitter.Python.AST as Py
@ -101,17 +99,18 @@ compile :: ( Compile py
=> py -> m (t Name) => py -> m (t Name)
compile t = compileCC t (pure none) compile t = compileCC t (pure none)
locFromTSSpan :: SourcePath -> TreeSitter.Span -> Loc
locFromTSSpan fp (TreeSitter.Span (TreeSitter.Pos a b) (TreeSitter.Pos c d))
= Data.Loc.Loc (rawPath fp) (Data.Loc.Span (Data.Loc.Pos a b) (Data.Loc.Pos c d))
locate :: ( HasField "ann" syntax Span locate :: ( HasField "ann" syntax Span
, CoreSyntax syn t , CoreSyntax syn t
, Member (Reader SourcePath) sig , Member (Reader SourcePath) sig
, Carrier sig m , Carrier sig m
) => syntax -> t a -> m (t a) ) => syntax -> t a -> m (t a)
locate syn item = do locate syn item = do
fp <- asks @SourcePath rawPath fp <- ask @SourcePath
let locFromTSSpan (TreeSitter.Span (TreeSitter.Pos a b) (TreeSitter.Pos c d)) pure (Core.annAt (locFromTSSpan fp (getField @"ann" syn)) item)
= Data.Loc.Loc fp (Data.Loc.Span (Data.Loc.Pos a b) (Data.Loc.Pos c d))
pure (Core.annAt (locFromTSSpan (getField @"ann" syn)) item)
defaultCompile :: (MonadFail m, Show py) => py -> m (t Name) defaultCompile :: (MonadFail m, Show py) => py -> m (t Name)
defaultCompile t = fail $ "compilation unimplemented for " <> show t defaultCompile t = fail $ "compilation unimplemented for " <> show t
@ -145,14 +144,21 @@ instance Compile (Py.Attribute Span)
type RHS a = Either (Py.Assignment a) (Either (Py.AugmentedAssignment a) (Desugared a)) type RHS a = Either (Py.Assignment a) (Either (Py.AugmentedAssignment a) (Desugared a))
type Desugared a = Either (Py.ExpressionList a) (Py.Yield a) type Desugared a = Either (Py.ExpressionList a) (Py.Yield a)
-- We have to pair locations and names, and tuple syntax is harder to
-- read in this case than a happy little constructor.
data Located a = Located Loc a
-- Desugaring an RHS involves walking as deeply as possible into an -- Desugaring an RHS involves walking as deeply as possible into an
-- assignment, storing the names we encounter as we go and eventually -- assignment, storing the names we encounter as we go and eventually
-- returning a terminal expression. -- returning a terminal expression. We have to keep track of which
desugar :: (Show a, Member (Reader SourcePath) sig, Carrier sig m, MonadFail m) desugar :: (Member (Reader SourcePath) sig, Carrier sig m, MonadFail m)
=> RHS a -> m ([Name], Desugared a) => RHS Span
-> m ([Located Name], Desugared Span)
desugar = \case desugar = \case
Left it@Py.Assignment { left = OneExpression name, right = Just rhs} -> Left Py.Assignment { left = OneExpression name, right = Just rhs, ann} -> do
let located = name in fmap (first (located:)) (desugar rhs) loc <- locFromTSSpan <$> ask <*> pure ann
let cons = (Located loc name :)
fmap (first cons) (desugar rhs)
Right (Right any) -> pure ([], any) Right (Right any) -> pure ([], any)
other -> fail ("desugar: couldn't desugar RHS " <> show other) other -> fail ("desugar: couldn't desugar RHS " <> show other)
@ -165,20 +171,23 @@ desugar = \case
-- exercise to the reader. -- exercise to the reader.
collapseDesugared :: (CoreSyntax syn t, Member (Reader Bindings) sig, Carrier sig m) collapseDesugared :: (CoreSyntax syn t, Member (Reader Bindings) sig, Carrier sig m)
=> (t Name -> m (t Name)) -- A meta-continuation: it takes a name and returns a continuation => (t Name -> m (t Name)) -- A meta-continuation: it takes a name and returns a continuation
-> Name -- The current LHS to which to assign -> Located Name -- The current LHS to which to assign
-> t Name -- The current RHS to which to assign, yielded from an outer continuation -> t Name -- The current RHS to which to assign, yielded from an outer continuation
-> m (t Name) -- The properly-sequenced resolut -> m (t Name) -- The properly-sequenced resolut
collapseDesugared cont n rem = collapseDesugared cont (Located loc n) rem =
let assigning = fmap ((Name.named' n :<- rem) >>>=) let assigning = fmap (Core.annAt loc) . fmap ((Name.named' n :<- rem) >>>=)
in assigning (local (def n) (cont (pure n))) -- gotta call local here to record this assignment in assigning (local (def n) (cont (pure n))) -- gotta call local here to record this assignment
instance Compile (Py.Assignment Span) where instance Compile (Py.Assignment Span) where
compileCC it@Py.Assignment compileCC it@Py.Assignment
{ Py.left = OneExpression name { left = OneExpression name
, Py.right = Just rhs , right = Just rhs
, ann
} cc = do } cc = do
p <- ask @SourcePath
(names, val) <- desugar rhs (names, val) <- desugar rhs
compile val >>= foldl' collapseDesugared (const cc) (name:names) >>= locate it let allNames = Located (locFromTSSpan p ann) name : names
compile val >>= foldl' collapseDesugared (const cc) allNames >>= locate it
compileCC other _ = fail ("Unhandled assignment case: " <> show other) compileCC other _ = fail ("Unhandled assignment case: " <> show other)