mirror of
https://github.com/github/semantic.git
synced 2024-12-29 18:06:14 +03:00
Flesh out Calll expression
This commit is contained in:
parent
ff988e048c
commit
6664d6fb94
@ -5,6 +5,7 @@
|
|||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
{-# LANGUAGE KindSignatures #-}
|
{-# LANGUAGE KindSignatures #-}
|
||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
{-# LANGUAGE NamedFieldPuns #-}
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
{-# LANGUAGE PatternSynonyms #-}
|
||||||
@ -15,34 +16,29 @@
|
|||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||||
|
|
||||||
module Language.Python.ScopeGraph
|
module Language.Python.ScopeGraph
|
||||||
( scopeGraphModule
|
( scopeGraphModule
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import AST.Element
|
||||||
import Control.Algebra (Algebra (..), handleCoercible)
|
import Control.Algebra (Algebra (..), handleCoercible)
|
||||||
|
import Control.Effect.Fresh
|
||||||
import Control.Effect.Sketch
|
import Control.Effect.Sketch
|
||||||
import Data.Foldable
|
import Data.Foldable
|
||||||
import Data.Traversable
|
import qualified Data.Map.Strict as Map
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
import Data.Name
|
import qualified Data.Name as Name
|
||||||
import GHC.Generics
|
import qualified Data.ScopeGraph as ScopeGraph
|
||||||
|
import Data.Traversable
|
||||||
import GHC.Records
|
import GHC.Records
|
||||||
import GHC.TypeLits
|
import GHC.TypeLits
|
||||||
import Language.Python.Patterns
|
import Language.Python.Patterns
|
||||||
import ScopeGraph.Convert (Result (..), complete, todo)
|
import ScopeGraph.Convert (Result (..), complete, todo)
|
||||||
import Source.Loc
|
import Source.Loc
|
||||||
import qualified TreeSitter.Python.AST as Py
|
import qualified TreeSitter.Python.AST as Py
|
||||||
import qualified Data.Map.Strict as Map
|
|
||||||
import Control.Effect.Fresh
|
|
||||||
import Control.Effect.Reader
|
|
||||||
import Control.Effect.Sketch
|
|
||||||
import qualified Data.ScopeGraph as ScopeGraph
|
|
||||||
import qualified Data.Name as Name
|
|
||||||
import AST.Element
|
|
||||||
|
|
||||||
-- This orphan instance will perish once it lands in fused-effects.
|
-- This orphan instance will perish once it lands in fused-effects.
|
||||||
instance Algebra sig m => Algebra sig (Ap m) where
|
instance Algebra sig m => Algebra sig (Ap m) where
|
||||||
@ -119,7 +115,18 @@ instance ToScopeGraph Py.Block where scopeGraph = onChildren
|
|||||||
|
|
||||||
instance ToScopeGraph Py.BreakStatement where scopeGraph = mempty
|
instance ToScopeGraph Py.BreakStatement where scopeGraph = mempty
|
||||||
|
|
||||||
instance ToScopeGraph Py.Call where scopeGraph = todo
|
instance ToScopeGraph Py.Call where
|
||||||
|
scopeGraph Py.Call
|
||||||
|
{ function
|
||||||
|
, arguments = L1 Py.ArgumentList { extraChildren = args }
|
||||||
|
} = do
|
||||||
|
result <- scopeGraph function
|
||||||
|
let scopeGraphArg = \case
|
||||||
|
Prj expr -> scopeGraph (expr :: Py.Expression Loc)
|
||||||
|
_ -> undefined
|
||||||
|
args <- traverse scopeGraphArg args
|
||||||
|
pure (result <> mconcat args)
|
||||||
|
|
||||||
|
|
||||||
instance ToScopeGraph Py.ClassDefinition where scopeGraph = todo
|
instance ToScopeGraph Py.ClassDefinition where scopeGraph = todo
|
||||||
|
|
||||||
@ -182,7 +189,7 @@ instance ToScopeGraph Py.FunctionDefinition where
|
|||||||
withScope associatedScope $ do
|
withScope associatedScope $ do
|
||||||
let declProps = DeclProperties ScopeGraph.Parameter ScopeGraph.Default Nothing
|
let declProps = DeclProperties ScopeGraph.Parameter ScopeGraph.Default Nothing
|
||||||
let param (Py.Parameter (Prj (Py.Identifier _pann pname))) = Just (Name.name pname)
|
let param (Py.Parameter (Prj (Py.Identifier _pann pname))) = Just (Name.name pname)
|
||||||
param _ = Nothing
|
param _ = Nothing
|
||||||
let parameterMs = fmap param parameters
|
let parameterMs = fmap param parameters
|
||||||
if any isNothing parameterMs
|
if any isNothing parameterMs
|
||||||
then todo parameterMs
|
then todo parameterMs
|
||||||
|
Loading…
Reference in New Issue
Block a user