mirror of
https://github.com/github/semantic.git
synced 2024-12-25 07:55:12 +03:00
start defining some instances
This commit is contained in:
parent
24053a1477
commit
f7c27f8857
@ -1,6 +1,10 @@
|
||||
-- | Semantic functionality for Python programs.
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
{-# LANGUAGE StandaloneDeriving #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||
-- | Semantic functionality for Python programs.
|
||||
module Language.Python
|
||||
( Term(..)
|
||||
, TreeSitter.Python.tree_sitter_python
|
||||
@ -11,12 +15,16 @@ module Language.Python
|
||||
import Data.Foldable
|
||||
import Data.ScopeGraph (ToScopeGraph (..))
|
||||
import qualified Data.ScopeGraph as ScopeGraph
|
||||
import GHC.Generics
|
||||
import qualified Language.Python.Tags as PyTags
|
||||
import qualified Tags.Tagging.Precise as Tags
|
||||
import qualified TreeSitter.Python (tree_sitter_python)
|
||||
import qualified TreeSitter.Python.AST as Py
|
||||
import qualified TreeSitter.Unmarshal as TS
|
||||
|
||||
todo :: Show a => a -> b
|
||||
todo s = error ("TODO: " <> show s)
|
||||
|
||||
newtype Term a = Term { getTerm :: Py.Module a }
|
||||
|
||||
instance TS.Unmarshal Term where
|
||||
@ -30,3 +38,25 @@ instance ScopeGraph.ToScopeGraph Term where
|
||||
|
||||
instance ToScopeGraph Py.Module where
|
||||
scopeGraph Py.Module { Py.extraChildren = stmts } = fold <$> traverse scopeGraph stmts
|
||||
|
||||
instance (ToScopeGraph l, ToScopeGraph r) => ToScopeGraph (l :+: r) where
|
||||
scopeGraph (L1 l) = scopeGraph l
|
||||
scopeGraph (R1 r) = scopeGraph r
|
||||
|
||||
deriving instance ToScopeGraph Py.Expression
|
||||
|
||||
instance ToScopeGraph Py.ExpressionList where
|
||||
scopeGraph (Py.ExpressionList _ as) = fold <$> traverse scopeGraph as
|
||||
|
||||
deriving instance ToScopeGraph Py.CompoundStatement
|
||||
|
||||
instance ToScopeGraph Py.ReturnStatement where
|
||||
scopeGraph (Py.ReturnStatement _ mVal) = maybe (pure mempty) scopeGraph mVal
|
||||
|
||||
instance ToScopeGraph Py.NotOperator where
|
||||
scopeGraph (Py.NotOperator _ arg) = scopeGraph arg
|
||||
|
||||
deriving instance ToScopeGraph Py.SimpleStatement
|
||||
|
||||
instance ToScopeGraph Py.RaiseStatement where
|
||||
scopeGraph = todo
|
||||
|
Loading…
Reference in New Issue
Block a user