mirror of
https://github.com/github/semantic.git
synced 2025-01-02 04:10:29 +03:00
Merge branch 'master' into fire-old-import-rendering
This commit is contained in:
commit
417103ae50
@ -429,15 +429,17 @@ instance Evaluatable InstanceOf
|
||||
|
||||
|
||||
-- | ScopeResolution (e.g. import a.b in Python or a::b in C++)
|
||||
newtype ScopeResolution a = ScopeResolution { scopes :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
newtype ScopeResolution a = ScopeResolution { scopes :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
|
||||
instance Hashable1 ScopeResolution where liftHashWithSalt = foldl
|
||||
instance Eq1 ScopeResolution where liftEq = genericLiftEq
|
||||
instance Ord1 ScopeResolution where liftCompare = genericLiftCompare
|
||||
instance Show1 ScopeResolution where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for ScopeResolution
|
||||
instance Evaluatable ScopeResolution
|
||||
instance Evaluatable ScopeResolution where
|
||||
eval (ScopeResolution xs) = Rval <$> foldl1 f (fmap subtermAddress xs)
|
||||
where f ns = evaluateInScopedEnv (ns >>= deref)
|
||||
|
||||
|
||||
-- | A non-null expression such as Typescript or Swift's ! expression.
|
||||
|
@ -7,11 +7,14 @@ module Language.Ruby.Assignment
|
||||
, Term
|
||||
) where
|
||||
|
||||
import Assigning.Assignment hiding (Assignment, Error)
|
||||
import Data.Abstract.Name (name)
|
||||
import Data.List (elem)
|
||||
import Data.Record
|
||||
import Data.Syntax
|
||||
import Assigning.Assignment hiding (Assignment, Error)
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import Data.Abstract.Name (name)
|
||||
import Data.List (elem)
|
||||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
import Data.Record
|
||||
import Data.Sum
|
||||
import Data.Syntax
|
||||
( contextualize
|
||||
, emptyTerm
|
||||
, handleError
|
||||
@ -23,9 +26,6 @@ import Data.Syntax
|
||||
, parseError
|
||||
, postContextualize
|
||||
)
|
||||
import Language.Ruby.Grammar as Grammar
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import Data.Sum
|
||||
import qualified Data.Syntax as Syntax
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
@ -34,9 +34,10 @@ import qualified Data.Syntax.Expression as Expression
|
||||
import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Term as Term
|
||||
import Language.Ruby.Grammar as Grammar
|
||||
import qualified Language.Ruby.Syntax as Ruby.Syntax
|
||||
import Prologue hiding (for)
|
||||
import Proto3.Suite (Named1(..), Named(..))
|
||||
import Prologue hiding (for)
|
||||
import Proto3.Suite (Named (..), Named1 (..))
|
||||
|
||||
-- | The type of Ruby syntax.
|
||||
type Syntax = '[
|
||||
@ -275,7 +276,7 @@ module' :: Assignment Term
|
||||
module' = makeTerm <$> symbol Module <*> (withNewScope . children) (Ruby.Syntax.Module <$> expression <*> many expression)
|
||||
|
||||
scopeResolution :: Assignment Term
|
||||
scopeResolution = makeTerm <$> symbol ScopeResolution <*> children (Expression.ScopeResolution <$> many expression)
|
||||
scopeResolution = makeTerm <$> symbol ScopeResolution <*> children (Expression.ScopeResolution <$> NonEmpty.some1 expression)
|
||||
|
||||
parameter :: Assignment Term
|
||||
parameter = postContextualize comment (term uncontextualizedParameter)
|
||||
|
Loading…
Reference in New Issue
Block a user