mirror of
https://github.com/github/semantic.git
synced 2024-11-24 08:54:07 +03:00
Merge remote-tracking branch 'origin/master' into servant-experiment
This commit is contained in:
commit
f14412fe8f
@ -59,6 +59,8 @@ library
|
||||
, Data.Abstract.Declarations
|
||||
, Data.Abstract.Evaluatable
|
||||
, Data.Abstract.FreeVariables
|
||||
, Data.Abstract.AccessControls.Class
|
||||
, Data.Abstract.AccessControls.Instances
|
||||
, Data.Abstract.Heap
|
||||
, Data.Abstract.Live
|
||||
, Data.Abstract.Module
|
||||
|
@ -86,8 +86,8 @@ graphingTerms recur term@(Term (In a syntax)) = do
|
||||
Just (v@Method{}, name) -> recurWithContext v name
|
||||
Just (v@Variable{..}, name) -> do
|
||||
variableDefinition v
|
||||
addr <- lookupDeclaration (Declaration name)
|
||||
defined <- gets (Map.lookup addr)
|
||||
slot <- lookupSlot (Declaration name)
|
||||
defined <- gets (Map.lookup slot)
|
||||
maybe (pure ()) (appendGraph . connect (vertex v) . vertex) defined
|
||||
recur term
|
||||
_ -> recur term
|
||||
@ -97,7 +97,7 @@ graphingTerms recur term@(Term (In a syntax)) = do
|
||||
moduleInclusion v
|
||||
local (const v) $ do
|
||||
valRef <- recur term
|
||||
slot <- lookupDeclaration (Declaration name)
|
||||
slot <- lookupSlot (Declaration name)
|
||||
modify (Map.insert slot v)
|
||||
pure valRef
|
||||
|
||||
|
@ -100,7 +100,7 @@ instance CustomHasDeclaration whole Declaration.Function where
|
||||
|
||||
-- | Produce a 'MethodDeclaration' for 'Declaration.Method' nodes. If the method’s receiver is non-empty (defined as having a non-empty 'Range'), the 'declarationIdentifier' will be formatted as 'receiver.method_name'; otherwise it will be simply 'method_name'.
|
||||
instance CustomHasDeclaration whole Declaration.Method where
|
||||
customToDeclaration blob@Blob{..} ann decl@(Declaration.Method _ (Term (In receiverAnn receiverF), _) (Term (In identifierAnn _), _) _ _)
|
||||
customToDeclaration blob@Blob{..} ann decl@(Declaration.Method _ (Term (In receiverAnn receiverF), _) (Term (In identifierAnn _), _) _ _ _)
|
||||
-- Methods without a receiver
|
||||
| isEmpty receiverAnn = Just $ MethodDeclaration (getSource blobSource identifierAnn) methodSource (locationSpan ann) blobLanguage Nothing
|
||||
-- Methods with a receiver type and an identifier (e.g. (a *Type) in Go).
|
||||
|
@ -12,13 +12,14 @@ module Control.Abstract.Heap
|
||||
, alloc
|
||||
, dealloc
|
||||
, maybeLookupDeclaration
|
||||
, lookupDeclaration
|
||||
, lookupSlot
|
||||
, lookupDeclarationFrame
|
||||
, deref
|
||||
, assign
|
||||
, newFrame
|
||||
, CurrentFrame(..)
|
||||
, currentFrame
|
||||
, lookupFrame
|
||||
, withScopeAndFrame
|
||||
, withLexicalScopeAndFrame
|
||||
, withChildFrame
|
||||
@ -175,12 +176,13 @@ define :: ( HasCallStack
|
||||
)
|
||||
=> Declaration
|
||||
-> Relation
|
||||
-> AccessControl
|
||||
-> Evaluator term address value m value
|
||||
-> Evaluator term address value m ()
|
||||
define declaration rel def = withCurrentCallStack callStack $ do
|
||||
define declaration rel accessControl def = withCurrentCallStack callStack $ do
|
||||
-- TODO: This span is still wrong.
|
||||
declare declaration rel emptySpan Nothing
|
||||
slot <- lookupDeclaration declaration
|
||||
declare declaration rel accessControl emptySpan Nothing
|
||||
slot <- lookupSlot declaration
|
||||
value <- def
|
||||
assign slot value
|
||||
|
||||
@ -217,7 +219,11 @@ deref :: ( Member (Deref value) sig
|
||||
)
|
||||
=> Slot address
|
||||
-> Evaluator term address value m value
|
||||
deref slot@Slot{..} = gets (Heap.getSlot slot) >>= maybeM (throwAddressError (UnallocatedSlot slot)) >>= send . flip DerefCell ret >>= maybeM (throwAddressError $ UninitializedSlot slot)
|
||||
deref slot@Slot{..} = do
|
||||
maybeSlotValue <- gets (Heap.getSlotValue slot)
|
||||
slotValue <- maybeM (throwAddressError (UnallocatedSlot slot)) maybeSlotValue
|
||||
eff <- send $ DerefCell slotValue ret
|
||||
maybeM (throwAddressError $ UninitializedSlot slot) eff
|
||||
|
||||
putSlotDeclarationScope :: ( Member (State (Heap address address value)) sig
|
||||
, Member (State (ScopeGraph address)) sig
|
||||
@ -255,7 +261,7 @@ maybeLookupDeclaration decl = do
|
||||
pure (Just (Slot frameAddress (Heap.pathPosition path)))
|
||||
Nothing -> pure Nothing
|
||||
|
||||
lookupDeclaration :: ( Carrier sig m
|
||||
lookupSlot :: ( Carrier sig m
|
||||
, Member (Reader (CurrentFrame address)) sig
|
||||
, Member (Reader (CurrentScope address)) sig
|
||||
, Member (Reader ModuleInfo) sig
|
||||
@ -268,7 +274,7 @@ lookupDeclaration :: ( Carrier sig m
|
||||
)
|
||||
=> Declaration
|
||||
-> Evaluator term address value m (Slot address)
|
||||
lookupDeclaration decl = do
|
||||
lookupSlot decl = do
|
||||
path <- lookupScopePath decl
|
||||
frameAddress <- lookupFrameAddress path
|
||||
pure (Slot frameAddress (Heap.pathPosition path))
|
||||
@ -290,6 +296,19 @@ lookupDeclarationFrame decl = do
|
||||
path <- lookupScopePath decl
|
||||
lookupFrameAddress path
|
||||
|
||||
lookupFrame :: ( Member (State (Heap address address value)) sig
|
||||
, Member (Reader ModuleInfo) sig
|
||||
, Member (Reader Span) sig
|
||||
, Member (Resumable (BaseError (HeapError address))) sig
|
||||
, Ord address
|
||||
, Carrier sig m
|
||||
)
|
||||
=> address
|
||||
-> Evaluator term address value m (Heap.Frame address address value)
|
||||
lookupFrame address = do
|
||||
heap <- getHeap
|
||||
maybeM (throwHeapError (LookupFrameError address)) (Heap.frameLookup address heap)
|
||||
|
||||
-- | Follow a path through the heap and return the frame address associated with the declaration.
|
||||
lookupFrameAddress :: ( Member (State (Heap address address value)) sig
|
||||
, Member (Reader (CurrentFrame address)) sig
|
||||
@ -356,7 +375,7 @@ assign :: ( Member (Deref value) sig
|
||||
-> Evaluator term address value m ()
|
||||
assign addr value = do
|
||||
heap <- getHeap
|
||||
cell <- send (AssignCell value (fromMaybe lowerBound (Heap.getSlot addr heap)) ret)
|
||||
cell <- send (AssignCell value (fromMaybe lowerBound (Heap.getSlotValue addr heap)) ret)
|
||||
putHeap (Heap.setSlot addr cell heap)
|
||||
|
||||
dealloc :: ( Carrier sig m
|
||||
|
@ -34,20 +34,21 @@ defineBuiltIn :: ( HasCallStack
|
||||
)
|
||||
=> Declaration
|
||||
-> Relation
|
||||
-> AccessControl
|
||||
-> BuiltIn
|
||||
-> Evaluator term address value m ()
|
||||
defineBuiltIn declaration rel value = withCurrentCallStack callStack $ do
|
||||
defineBuiltIn declaration rel accessControl value = withCurrentCallStack callStack $ do
|
||||
currentScope' <- currentScope
|
||||
let lexicalEdges = Map.singleton Lexical [ currentScope' ]
|
||||
associatedScope <- newScope lexicalEdges
|
||||
-- TODO: This span is still wrong.
|
||||
declare declaration rel emptySpan (Just associatedScope)
|
||||
declare declaration rel accessControl emptySpan (Just associatedScope)
|
||||
|
||||
param <- gensym
|
||||
withScope associatedScope $ do
|
||||
declare (Declaration param) rel emptySpan Nothing
|
||||
declare (Declaration param) rel accessControl emptySpan Nothing
|
||||
|
||||
slot <- lookupDeclaration declaration
|
||||
slot <- lookupSlot declaration
|
||||
value <- builtIn associatedScope value
|
||||
assign slot value
|
||||
|
||||
@ -71,7 +72,7 @@ defineClass :: ( Carrier sig m
|
||||
-> [Declaration]
|
||||
-> Evaluator term address value m a
|
||||
-> Evaluator term address value m ()
|
||||
defineClass declaration superclasses body = void . define declaration Default $ do
|
||||
defineClass declaration superclasses body = void . define declaration Default Public $ do
|
||||
currentScope' <- currentScope
|
||||
|
||||
superScopes <- for superclasses associatedScope
|
||||
@ -106,7 +107,7 @@ defineNamespace :: ( AbstractValue term address value m
|
||||
=> Declaration
|
||||
-> Evaluator term address value m a
|
||||
-> Evaluator term address value m ()
|
||||
defineNamespace declaration@Declaration{..} body = void . define declaration Default $ do
|
||||
defineNamespace declaration@Declaration{..} body = void . define declaration Default Public $ do
|
||||
withChildFrame declaration $ \frame -> do
|
||||
_ <- body
|
||||
namespace unDeclaration frame
|
||||
|
@ -50,7 +50,7 @@ instance ( Carrier sig m
|
||||
put (FindPackages as)
|
||||
else if Just (name "setup") == name' then do
|
||||
packageState <- get
|
||||
if packageState == Unknown then do
|
||||
if packageState == Control.Abstract.PythonPackage.Unknown then do
|
||||
as <- maybe (pure mempty) (fmap (fmap stripQuotes) . asStrings) (Map.lookup (name "packages") bindings)
|
||||
put (Packages as)
|
||||
else
|
||||
|
@ -13,13 +13,16 @@ module Control.Abstract.ScopeGraph
|
||||
, EdgeLabel(..)
|
||||
, CurrentScope(..)
|
||||
, Info(..)
|
||||
, AccessControl(..)
|
||||
, currentScope
|
||||
, insertExportEdge
|
||||
, insertImportEdge
|
||||
, insertLexicalEdge
|
||||
, withScope
|
||||
, associatedScope
|
||||
, relationsOfScope
|
||||
, declarationByName
|
||||
, declarationsByAccessControl
|
||||
, declarationsByRelation
|
||||
, putDeclarationScope
|
||||
, putDeclarationSpan
|
||||
, insertImportReference
|
||||
@ -44,13 +47,17 @@ import Control.Effect.Carrier
|
||||
import Data.Abstract.BaseError
|
||||
import Data.Abstract.Module
|
||||
import Data.Abstract.Name hiding (name)
|
||||
import Data.Abstract.ScopeGraph (Declaration(..), EdgeLabel, Reference, Relation(..), Scope (..), ScopeGraph, Slot(..), Info(..))
|
||||
import Data.Abstract.ScopeGraph (Declaration(..), EdgeLabel, Reference, Relation(..), Scope (..), ScopeGraph, Slot(..), Info(..), AccessControl(..))
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
import Data.Span
|
||||
import Prelude hiding (lookup)
|
||||
import Prologue
|
||||
|
||||
lookup :: (Ord address, Member (State (ScopeGraph address)) sig, Carrier sig m) => Reference -> Evaluator term address value m (Maybe address)
|
||||
lookup :: ( Ord address
|
||||
, Member (State (ScopeGraph address)) sig
|
||||
, Carrier sig m)
|
||||
=> Reference
|
||||
-> Evaluator term address value m (Maybe address)
|
||||
lookup ref = ScopeGraph.scopeOfRef ref <$> get
|
||||
|
||||
declare :: ( Carrier sig m
|
||||
@ -60,23 +67,38 @@ declare :: ( Carrier sig m
|
||||
)
|
||||
=> Declaration
|
||||
-> Relation
|
||||
-> AccessControl
|
||||
-> Span
|
||||
-> Maybe address
|
||||
-> Evaluator term address value m ()
|
||||
declare decl rel span scope = do
|
||||
declare decl rel accessControl span scope = do
|
||||
currentAddress <- currentScope
|
||||
modify (fst . ScopeGraph.declare decl rel span scope currentAddress)
|
||||
modify (fst . ScopeGraph.declare decl rel accessControl span scope currentAddress)
|
||||
|
||||
putDeclarationScope :: (Ord address, Member (Reader (CurrentScope address)) sig, Member (State (ScopeGraph address)) sig, Carrier sig m) => Declaration -> address -> Evaluator term address value m ()
|
||||
putDeclarationScope :: ( Ord address
|
||||
, Member (Reader (CurrentScope address)) sig
|
||||
, Member (State (ScopeGraph address)) sig
|
||||
, Carrier sig m
|
||||
)
|
||||
=> Declaration
|
||||
-> address
|
||||
-> Evaluator term address value m ()
|
||||
putDeclarationScope decl assocScope = do
|
||||
currentAddress <- currentScope
|
||||
modify (ScopeGraph.insertDeclarationScope decl assocScope currentAddress)
|
||||
|
||||
putDeclarationSpan :: forall address sig m term value. (Ord address, Member (State (ScopeGraph address)) sig, Carrier sig m) => Declaration -> Span -> Evaluator term address value m ()
|
||||
putDeclarationSpan :: forall address sig m term value .
|
||||
( Ord address
|
||||
, Member (State (ScopeGraph address)) sig
|
||||
, Carrier sig m
|
||||
)
|
||||
=> Declaration
|
||||
-> Span
|
||||
-> Evaluator term address value m ()
|
||||
putDeclarationSpan decl = modify @(ScopeGraph address) . ScopeGraph.insertDeclarationSpan decl
|
||||
|
||||
reference :: forall address sig m term value
|
||||
. ( Ord address
|
||||
reference :: forall address sig m term value .
|
||||
( Ord address
|
||||
, Member (State (ScopeGraph address)) sig
|
||||
, Member (Reader (CurrentScope address)) sig
|
||||
, Carrier sig m
|
||||
@ -151,15 +173,37 @@ lookupScope :: ( Member (Resumable (BaseError (ScopeError address))) sig
|
||||
-> Evaluator term address value m (Scope address)
|
||||
lookupScope address = maybeM (throwScopeError LookupScopeError) . ScopeGraph.lookupScope address =<< get
|
||||
|
||||
relationsOfScope :: ( Member (State (ScopeGraph address)) sig
|
||||
declarationsByRelation :: ( Member (State (ScopeGraph address)) sig
|
||||
, Carrier sig m
|
||||
, Ord address
|
||||
)
|
||||
=> address
|
||||
-> Relation
|
||||
-> Evaluator term address value m [ Info address ]
|
||||
relationsOfScope scope relation =
|
||||
ScopeGraph.relationsOfScope scope relation <$> get
|
||||
declarationsByRelation scope relation = ScopeGraph.declarationsByRelation scope relation <$> get
|
||||
|
||||
declarationByName :: ( Member (Resumable (BaseError (ScopeError address))) sig
|
||||
, Member (Reader ModuleInfo) sig
|
||||
, Member (Reader Span) sig
|
||||
, Member (State (ScopeGraph address)) sig
|
||||
, Carrier sig m
|
||||
, Ord address
|
||||
)
|
||||
=> address
|
||||
-> Declaration
|
||||
-> Evaluator term address value m (Info address)
|
||||
declarationByName scope name = do
|
||||
scopeGraph <- get
|
||||
maybeM (throwScopeError $ DeclarationByNameError name) (ScopeGraph.declarationByName scope name scopeGraph)
|
||||
|
||||
declarationsByAccessControl :: ( Member (State (ScopeGraph address)) sig
|
||||
, Carrier sig m
|
||||
, Ord address
|
||||
)
|
||||
=> address
|
||||
-> AccessControl
|
||||
-> Evaluator term address value m [ Info address ]
|
||||
declarationsByAccessControl scopeAddress accessControl = ScopeGraph.declarationsByAccessControl scopeAddress accessControl <$> get
|
||||
|
||||
insertImportReference :: ( Member (Resumable (BaseError (ScopeError address))) sig
|
||||
, Member (Reader ModuleInfo) sig
|
||||
@ -189,8 +233,7 @@ insertScope :: ( Member (State (ScopeGraph address)) sig
|
||||
-> Evaluator term address value m ()
|
||||
insertScope scopeAddress scope = modify (ScopeGraph.insertScope scopeAddress scope)
|
||||
|
||||
maybeLookupScopePath ::
|
||||
( Member (State (ScopeGraph address)) sig
|
||||
maybeLookupScopePath :: ( Member (State (ScopeGraph address)) sig
|
||||
, Member (Reader (CurrentScope address)) sig
|
||||
, Carrier sig m
|
||||
, Ord address
|
||||
@ -223,7 +266,9 @@ lookupDeclarationScope :: ( Member (Resumable (BaseError (ScopeError address)))
|
||||
, Member (Reader (CurrentScope address)) sig
|
||||
, Carrier sig m
|
||||
, Ord address
|
||||
) => Declaration -> Evaluator term address value m address
|
||||
)
|
||||
=> Declaration
|
||||
-> Evaluator term address value m address
|
||||
lookupDeclarationScope decl = do
|
||||
path <- lookupScopePath decl
|
||||
currentScope' <- currentScope
|
||||
@ -255,6 +300,7 @@ data ScopeError address return where
|
||||
ImportReferenceError :: ScopeError address (Scope address)
|
||||
LookupPathError :: Declaration -> ScopeError address (ScopeGraph.Path address)
|
||||
LookupDeclarationScopeError :: Declaration -> ScopeError address address
|
||||
DeclarationByNameError :: Declaration -> ScopeError address (Info address)
|
||||
CurrentScopeError :: ScopeError address address
|
||||
|
||||
deriving instance Eq (ScopeError address return)
|
||||
@ -271,6 +317,7 @@ instance Eq1 (ScopeError address) where
|
||||
|
||||
instance NFData1 (ScopeError address) where
|
||||
liftRnf _ x = case x of
|
||||
DeclarationByNameError n -> rnf n
|
||||
ScopeError d s -> rnf d `seq` rnf s
|
||||
LookupScopeError -> ()
|
||||
ImportReferenceError -> ()
|
||||
|
26
src/Data/Abstract/AccessControls/Class.hs
Normal file
26
src/Data/Abstract/AccessControls/Class.hs
Normal file
@ -0,0 +1,26 @@
|
||||
module Data.Abstract.AccessControls.Class
|
||||
( AccessControls (..)
|
||||
, AccessControls1 (..)
|
||||
) where
|
||||
|
||||
import Data.Abstract.ScopeGraph (AccessControl(..))
|
||||
|
||||
{-|
|
||||
The 'AccessControls' typeclass provides a mapping between a syntax and its associated 'AccessControl' type (i.e. public, protected, or private).
|
||||
|
||||
Because not every syntax relates to the idea of access control, the 'termToAccessControl' method defaults to returning a 'Nothing' as the default for all syntax.
|
||||
|
||||
Specialized instances should be defined per syntax when considering its 'AccessControl' is necessary for its evaluation.
|
||||
-}
|
||||
class AccessControls syntax where
|
||||
termToAccessControl :: syntax -> Maybe AccessControl
|
||||
termToAccessControl = const Nothing
|
||||
|
||||
{-|
|
||||
The 'AccessControls1' typeclass allows lifting of a function mapping a syntax to its 'AccessControl' type for rank 1 types.
|
||||
|
||||
As described in the notes for the 'AccessControls' typeclass, the default for the 'liftTermToAccessControl' method is 'Nothing' for syntax terms whose evaluation does not require consideration of access control.
|
||||
-}
|
||||
class AccessControls1 syntax where
|
||||
liftTermToAccessControl :: (a -> Maybe AccessControl) -> syntax a -> Maybe AccessControl
|
||||
liftTermToAccessControl _ _ = Nothing
|
526
src/Data/Abstract/AccessControls/Instances.hs
Normal file
526
src/Data/Abstract/AccessControls/Instances.hs
Normal file
@ -0,0 +1,526 @@
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, UndecidableInstances #-}
|
||||
{-# OPTIONS_GHC -Wno-orphans -Wno-missing-export-lists #-}
|
||||
module Data.Abstract.AccessControls.Instances where
|
||||
|
||||
import Data.Sum
|
||||
import Data.Term
|
||||
import Data.Abstract.AccessControls.Class
|
||||
|
||||
import qualified Data.Syntax as Syntax
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
import qualified Data.Syntax.Directive as Directive
|
||||
import qualified Data.Syntax.Expression as Expression
|
||||
import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Syntax.Type as Type
|
||||
import qualified Language.Go.Syntax as Go
|
||||
import qualified Language.Go.Type as Go
|
||||
import qualified Language.Haskell.Syntax as Haskell
|
||||
import qualified Language.Java.Syntax as Java
|
||||
import qualified Language.Markdown.Syntax as Markdown
|
||||
import qualified Language.PHP.Syntax as PHP
|
||||
import qualified Language.Python.Syntax as Python
|
||||
import qualified Language.Ruby.Syntax as Ruby
|
||||
import qualified Language.TypeScript.Syntax as TypeScript
|
||||
|
||||
deriving instance AccessControls1 syntax => AccessControls (Term syntax ann)
|
||||
|
||||
instance (AccessControls recur, AccessControls1 syntax) => AccessControls (TermF syntax ann recur) where
|
||||
termToAccessControl = liftTermToAccessControl termToAccessControl . termFOut
|
||||
|
||||
instance Apply AccessControls1 fs => AccessControls1 (Sum fs) where
|
||||
liftTermToAccessControl f = apply @AccessControls1 (liftTermToAccessControl f)
|
||||
|
||||
instance AccessControls1 []
|
||||
instance AccessControls1 Comment.Comment
|
||||
instance AccessControls1 Comment.HashBang
|
||||
|
||||
instance AccessControls1 Expression.And
|
||||
instance AccessControls1 Expression.Await
|
||||
instance AccessControls1 Expression.BAnd
|
||||
instance AccessControls1 Expression.BOr
|
||||
instance AccessControls1 Expression.BXOr
|
||||
instance AccessControls1 Expression.Call
|
||||
instance AccessControls1 Expression.Cast
|
||||
instance AccessControls1 Expression.Comparison
|
||||
instance AccessControls1 Expression.Complement
|
||||
instance AccessControls1 Expression.Delete
|
||||
instance AccessControls1 Expression.DividedBy
|
||||
instance AccessControls1 Expression.Enumeration
|
||||
instance AccessControls1 Expression.Equal
|
||||
instance AccessControls1 Expression.FloorDivision
|
||||
instance AccessControls1 Expression.GreaterThan
|
||||
instance AccessControls1 Expression.GreaterThanEqual
|
||||
instance AccessControls1 Expression.InstanceOf
|
||||
instance AccessControls1 Expression.LessThan
|
||||
instance AccessControls1 Expression.LessThanEqual
|
||||
instance AccessControls1 Expression.LShift
|
||||
instance AccessControls1 Expression.Matches
|
||||
instance AccessControls1 Expression.Member
|
||||
instance AccessControls1 Expression.MemberAccess
|
||||
instance AccessControls1 Expression.Minus
|
||||
instance AccessControls1 Expression.Modulo
|
||||
instance AccessControls1 Expression.Negate
|
||||
instance AccessControls1 Expression.New
|
||||
instance AccessControls1 Expression.NonNullExpression
|
||||
instance AccessControls1 Expression.Not
|
||||
instance AccessControls1 Expression.NotMatches
|
||||
instance AccessControls1 Expression.Or
|
||||
instance AccessControls1 Expression.Plus
|
||||
instance AccessControls1 Expression.Power
|
||||
instance AccessControls1 Expression.RShift
|
||||
instance AccessControls1 Expression.ScopeResolution
|
||||
instance AccessControls1 Expression.SequenceExpression
|
||||
instance AccessControls1 Expression.StrictEqual
|
||||
instance AccessControls1 Expression.Subscript
|
||||
instance AccessControls1 Expression.Super
|
||||
instance AccessControls1 Expression.Times
|
||||
instance AccessControls1 Expression.Typeof
|
||||
instance AccessControls1 Expression.UnsignedRShift
|
||||
instance AccessControls1 Expression.Void
|
||||
instance AccessControls1 Expression.XOr
|
||||
|
||||
instance AccessControls1 Literal.Boolean
|
||||
instance AccessControls1 Literal.Integer
|
||||
instance AccessControls1 Literal.Float
|
||||
instance AccessControls1 Literal.Rational
|
||||
instance AccessControls1 Literal.Complex
|
||||
instance AccessControls1 Literal.String
|
||||
instance AccessControls1 Literal.Character
|
||||
instance AccessControls1 Literal.InterpolationElement
|
||||
instance AccessControls1 Literal.TextElement
|
||||
instance AccessControls1 Literal.EscapeSequence
|
||||
instance AccessControls1 Literal.Symbol
|
||||
instance AccessControls1 Literal.SymbolElement
|
||||
instance AccessControls1 Literal.Regex
|
||||
instance AccessControls1 Literal.Array
|
||||
instance AccessControls1 Literal.Hash
|
||||
instance AccessControls1 Literal.Tuple
|
||||
instance AccessControls1 Literal.Set
|
||||
instance AccessControls1 Literal.Pointer
|
||||
instance AccessControls1 Literal.Reference
|
||||
instance AccessControls1 Literal.Null
|
||||
instance AccessControls1 Literal.KeyValue
|
||||
|
||||
instance AccessControls1 Statement.Assignment
|
||||
instance AccessControls1 Statement.Break
|
||||
instance AccessControls1 Statement.Catch
|
||||
instance AccessControls1 Statement.Continue
|
||||
instance AccessControls1 Statement.DoWhile
|
||||
instance AccessControls1 Statement.Else
|
||||
instance AccessControls1 Statement.Finally
|
||||
instance AccessControls1 Statement.For
|
||||
instance AccessControls1 Statement.ForEach
|
||||
instance AccessControls1 Statement.Goto
|
||||
instance AccessControls1 Statement.If
|
||||
instance AccessControls1 Statement.Let
|
||||
instance AccessControls1 Statement.Match
|
||||
instance AccessControls1 Statement.NoOp
|
||||
instance AccessControls1 Statement.Pattern
|
||||
instance AccessControls1 Statement.PostDecrement
|
||||
instance AccessControls1 Statement.PostIncrement
|
||||
instance AccessControls1 Statement.PreDecrement
|
||||
instance AccessControls1 Statement.PreIncrement
|
||||
instance AccessControls1 Statement.Retry
|
||||
instance AccessControls1 Statement.Return
|
||||
instance AccessControls1 Statement.ScopeEntry
|
||||
instance AccessControls1 Statement.ScopeExit
|
||||
instance AccessControls1 Statement.StatementBlock
|
||||
instance AccessControls1 Statement.Statements
|
||||
instance AccessControls1 Statement.Throw
|
||||
instance AccessControls1 Statement.Try
|
||||
instance AccessControls1 Statement.While
|
||||
instance AccessControls1 Statement.Yield
|
||||
|
||||
instance AccessControls1 Syntax.Context
|
||||
instance AccessControls1 Syntax.Empty
|
||||
instance AccessControls1 Syntax.Error
|
||||
instance AccessControls1 Syntax.Identifier
|
||||
instance AccessControls1 Syntax.AccessibilityModifier
|
||||
|
||||
instance AccessControls1 Type.Annotation
|
||||
instance AccessControls1 Type.Array
|
||||
instance AccessControls1 Type.Bool
|
||||
instance AccessControls1 Type.Double
|
||||
instance AccessControls1 Type.Float
|
||||
instance AccessControls1 Type.Function
|
||||
instance AccessControls1 Type.Int
|
||||
instance AccessControls1 Type.Interface
|
||||
instance AccessControls1 Type.Map
|
||||
instance AccessControls1 Type.Parenthesized
|
||||
instance AccessControls1 Type.Pointer
|
||||
instance AccessControls1 Type.Product
|
||||
instance AccessControls1 Type.Readonly
|
||||
instance AccessControls1 Type.Slice
|
||||
instance AccessControls1 Type.TypeParameters
|
||||
instance AccessControls1 Type.Void
|
||||
|
||||
instance AccessControls1 Declaration.Class
|
||||
instance AccessControls1 Declaration.Comprehension
|
||||
instance AccessControls1 Declaration.Constructor
|
||||
instance AccessControls1 Declaration.Datatype
|
||||
instance AccessControls1 Declaration.Decorator
|
||||
instance AccessControls1 Declaration.Function
|
||||
instance AccessControls1 Declaration.InterfaceDeclaration
|
||||
instance AccessControls1 Declaration.Method
|
||||
instance AccessControls1 Declaration.MethodSignature
|
||||
instance AccessControls1 Declaration.OptionalParameter
|
||||
instance AccessControls1 Declaration.PublicFieldDefinition
|
||||
instance AccessControls1 Declaration.RequiredParameter
|
||||
instance AccessControls1 Declaration.Type
|
||||
instance AccessControls1 Declaration.TypeAlias
|
||||
instance AccessControls1 Declaration.Variable
|
||||
instance AccessControls1 Declaration.VariableDeclaration
|
||||
|
||||
instance AccessControls1 Directive.File
|
||||
instance AccessControls1 Directive.Line
|
||||
|
||||
instance AccessControls1 Haskell.UnitConstructor
|
||||
instance AccessControls1 Haskell.ListConstructor
|
||||
instance AccessControls1 Haskell.FunctionConstructor
|
||||
instance AccessControls1 Haskell.RecordDataConstructor
|
||||
instance AccessControls1 Haskell.AllConstructors
|
||||
instance AccessControls1 Haskell.GADTConstructor
|
||||
instance AccessControls1 Haskell.LabeledConstruction
|
||||
instance AccessControls1 Haskell.InfixDataConstructor
|
||||
instance AccessControls1 Haskell.TupleConstructor
|
||||
instance AccessControls1 Haskell.TypeConstructorExport
|
||||
instance AccessControls1 Haskell.KindParenthesizedConstructor
|
||||
instance AccessControls1 Haskell.ConstructorSymbol
|
||||
instance AccessControls1 Haskell.Module
|
||||
instance AccessControls1 Haskell.Field
|
||||
instance AccessControls1 Haskell.GADT
|
||||
instance AccessControls1 Haskell.InfixOperatorPattern
|
||||
instance AccessControls1 Haskell.NewType
|
||||
instance AccessControls1 Haskell.ImportDeclaration
|
||||
instance AccessControls1 Haskell.QualifiedImportDeclaration
|
||||
instance AccessControls1 Haskell.ImportAlias
|
||||
instance AccessControls1 Haskell.App
|
||||
instance AccessControls1 Haskell.InfixOperatorApp
|
||||
instance AccessControls1 Haskell.ListComprehension
|
||||
instance AccessControls1 Haskell.Generator
|
||||
instance AccessControls1 Haskell.ArithmeticSequence
|
||||
instance AccessControls1 Haskell.RightOperatorSection
|
||||
instance AccessControls1 Haskell.LeftOperatorSection
|
||||
instance AccessControls1 Haskell.BindPattern
|
||||
instance AccessControls1 Haskell.Lambda
|
||||
instance AccessControls1 Haskell.FixityAlt
|
||||
instance AccessControls1 Haskell.RecordWildCards
|
||||
instance AccessControls1 Haskell.Wildcard
|
||||
instance AccessControls1 Haskell.Let
|
||||
instance AccessControls1 Haskell.FieldBind
|
||||
instance AccessControls1 Haskell.Pragma
|
||||
instance AccessControls1 Haskell.Deriving
|
||||
instance AccessControls1 Haskell.ContextAlt
|
||||
instance AccessControls1 Haskell.Class
|
||||
instance AccessControls1 Haskell.Export
|
||||
instance AccessControls1 Haskell.ModuleExport
|
||||
instance AccessControls1 Haskell.QuotedName
|
||||
instance AccessControls1 Haskell.ScopedTypeVariables
|
||||
instance AccessControls1 Haskell.DefaultDeclaration
|
||||
instance AccessControls1 Haskell.VariableOperator
|
||||
instance AccessControls1 Haskell.ConstructorOperator
|
||||
instance AccessControls1 Haskell.TypeOperator
|
||||
instance AccessControls1 Haskell.PromotedTypeOperator
|
||||
instance AccessControls1 Haskell.VariableSymbol
|
||||
instance AccessControls1 Haskell.Import
|
||||
instance AccessControls1 Haskell.HiddenImport
|
||||
instance AccessControls1 Haskell.TypeApp
|
||||
instance AccessControls1 Haskell.TupleExpression
|
||||
instance AccessControls1 Haskell.TuplePattern
|
||||
instance AccessControls1 Haskell.ConstructorPattern
|
||||
instance AccessControls1 Haskell.Do
|
||||
instance AccessControls1 Haskell.PrefixNegation
|
||||
instance AccessControls1 Haskell.CPPDirective
|
||||
instance AccessControls1 Haskell.NamedFieldPun
|
||||
instance AccessControls1 Haskell.NegativeLiteral
|
||||
instance AccessControls1 Haskell.LambdaCase
|
||||
instance AccessControls1 Haskell.LabeledUpdate
|
||||
instance AccessControls1 Haskell.QualifiedTypeClassIdentifier
|
||||
instance AccessControls1 Haskell.QualifiedTypeConstructorIdentifier
|
||||
instance AccessControls1 Haskell.QualifiedConstructorIdentifier
|
||||
instance AccessControls1 Haskell.QualifiedInfixVariableIdentifier
|
||||
instance AccessControls1 Haskell.QualifiedModuleIdentifier
|
||||
instance AccessControls1 Haskell.QualifiedVariableIdentifier
|
||||
instance AccessControls1 Haskell.TypeVariableIdentifier
|
||||
instance AccessControls1 Haskell.TypeConstructorIdentifier
|
||||
instance AccessControls1 Haskell.ModuleIdentifier
|
||||
instance AccessControls1 Haskell.ConstructorIdentifier
|
||||
instance AccessControls1 Haskell.ImplicitParameterIdentifier
|
||||
instance AccessControls1 Haskell.InfixConstructorIdentifier
|
||||
instance AccessControls1 Haskell.InfixVariableIdentifier
|
||||
instance AccessControls1 Haskell.TypeClassIdentifier
|
||||
instance AccessControls1 Haskell.VariableIdentifier
|
||||
instance AccessControls1 Haskell.PrimitiveConstructorIdentifier
|
||||
instance AccessControls1 Haskell.PrimitiveVariableIdentifier
|
||||
instance AccessControls1 Haskell.AsPattern
|
||||
instance AccessControls1 Haskell.FieldPattern
|
||||
instance AccessControls1 Haskell.ViewPattern
|
||||
instance AccessControls1 Haskell.PatternGuard
|
||||
instance AccessControls1 Haskell.StrictPattern
|
||||
instance AccessControls1 Haskell.ListPattern
|
||||
instance AccessControls1 Haskell.TypePattern
|
||||
instance AccessControls1 Haskell.IrrefutablePattern
|
||||
instance AccessControls1 Haskell.CaseGuardPattern
|
||||
instance AccessControls1 Haskell.FunctionGuardPattern
|
||||
instance AccessControls1 Haskell.LabeledPattern
|
||||
instance AccessControls1 Haskell.Guard
|
||||
instance AccessControls1 Haskell.QuasiQuotation
|
||||
instance AccessControls1 Haskell.QuasiQuotationPattern
|
||||
instance AccessControls1 Haskell.QuasiQuotationType
|
||||
instance AccessControls1 Haskell.QuasiQuotationDeclaration
|
||||
instance AccessControls1 Haskell.QuasiQuotationExpression
|
||||
instance AccessControls1 Haskell.QuasiQuotationExpressionBody
|
||||
instance AccessControls1 Haskell.QuasiQuotationQuoter
|
||||
instance AccessControls1 Haskell.Splice
|
||||
instance AccessControls1 Haskell.StrictType
|
||||
instance AccessControls1 Haskell.Type
|
||||
instance AccessControls1 Haskell.TypeSynonym
|
||||
instance AccessControls1 Haskell.AnnotatedTypeVariable
|
||||
instance AccessControls1 Haskell.StandaloneDerivingInstance
|
||||
instance AccessControls1 Haskell.FunctionType
|
||||
instance AccessControls1 Haskell.TypeSignature
|
||||
instance AccessControls1 Haskell.ExpressionTypeSignature
|
||||
instance AccessControls1 Haskell.KindFunctionType
|
||||
instance AccessControls1 Haskell.Star
|
||||
instance AccessControls1 Haskell.EqualityConstraint
|
||||
instance AccessControls1 Haskell.TypeInstance
|
||||
instance AccessControls1 Haskell.TypeClassInstance
|
||||
instance AccessControls1 Haskell.TypeClass
|
||||
instance AccessControls1 Haskell.DefaultSignature
|
||||
instance AccessControls1 Haskell.TypeFamily
|
||||
instance AccessControls1 Haskell.StrictTypeVariable
|
||||
instance AccessControls1 Haskell.KindSignature
|
||||
instance AccessControls1 Haskell.Kind
|
||||
instance AccessControls1 Haskell.KindListType
|
||||
instance AccessControls1 Haskell.Instance
|
||||
instance AccessControls1 Haskell.KindTupleType
|
||||
instance AccessControls1 Haskell.FunctionalDependency
|
||||
|
||||
|
||||
instance AccessControls1 Java.Import
|
||||
instance AccessControls1 Java.Package
|
||||
instance AccessControls1 Java.CatchType
|
||||
instance AccessControls1 Java.SpreadParameter
|
||||
instance AccessControls1 Java.StaticInitializer
|
||||
instance AccessControls1 Java.LambdaBody
|
||||
instance AccessControls1 Java.ClassBody
|
||||
instance AccessControls1 Java.ClassLiteral
|
||||
instance AccessControls1 Java.DefaultValue
|
||||
instance AccessControls1 Java.Module
|
||||
instance AccessControls1 Java.EnumDeclaration
|
||||
instance AccessControls1 Java.Variable
|
||||
instance AccessControls1 Java.Synchronized
|
||||
instance AccessControls1 Java.New
|
||||
instance AccessControls1 Java.Asterisk
|
||||
instance AccessControls1 Java.Constructor
|
||||
instance AccessControls1 Java.TypeParameter
|
||||
instance AccessControls1 Java.Annotation
|
||||
instance AccessControls1 Java.AnnotationField
|
||||
instance AccessControls1 Java.GenericType
|
||||
instance AccessControls1 Java.AnnotatedType
|
||||
instance AccessControls1 Java.TypeWithModifiers
|
||||
instance AccessControls1 Java.Wildcard
|
||||
instance AccessControls1 Java.WildcardBounds
|
||||
instance AccessControls1 Java.MethodReference
|
||||
instance AccessControls1 Java.NewKeyword
|
||||
instance AccessControls1 Java.Lambda
|
||||
instance AccessControls1 Java.ArrayCreationExpression
|
||||
instance AccessControls1 Java.DimsExpr
|
||||
instance AccessControls1 Java.TryWithResources
|
||||
instance AccessControls1 Java.AssertStatement
|
||||
instance AccessControls1 Java.AnnotationTypeElement
|
||||
|
||||
instance AccessControls1 Python.Ellipsis
|
||||
instance AccessControls1 Python.FutureImport
|
||||
instance AccessControls1 Python.Import
|
||||
instance AccessControls1 Python.QualifiedAliasedImport
|
||||
instance AccessControls1 Python.QualifiedImport
|
||||
instance AccessControls1 Python.Redirect
|
||||
|
||||
instance AccessControls1 Go.BidirectionalChannel
|
||||
instance AccessControls1 Go.ReceiveChannel
|
||||
instance AccessControls1 Go.SendChannel
|
||||
instance AccessControls1 Go.Import
|
||||
instance AccessControls1 Go.QualifiedImport
|
||||
instance AccessControls1 Go.SideEffectImport
|
||||
instance AccessControls1 Go.Composite
|
||||
instance AccessControls1 Go.Label
|
||||
instance AccessControls1 Go.Send
|
||||
instance AccessControls1 Go.Slice
|
||||
instance AccessControls1 Go.TypeSwitch
|
||||
instance AccessControls1 Go.Receive
|
||||
instance AccessControls1 Go.Field
|
||||
instance AccessControls1 Go.Package
|
||||
instance AccessControls1 Go.TypeAssertion
|
||||
instance AccessControls1 Go.TypeConversion
|
||||
instance AccessControls1 Go.Variadic
|
||||
instance AccessControls1 Go.DefaultPattern
|
||||
instance AccessControls1 Go.Defer
|
||||
instance AccessControls1 Go.Go
|
||||
instance AccessControls1 Go.Rune
|
||||
instance AccessControls1 Go.Select
|
||||
instance AccessControls1 Go.TypeSwitchGuard
|
||||
instance AccessControls1 Go.ReceiveOperator
|
||||
|
||||
instance AccessControls1 Markdown.Document
|
||||
instance AccessControls1 Markdown.Paragraph
|
||||
instance AccessControls1 Markdown.UnorderedList
|
||||
instance AccessControls1 Markdown.OrderedList
|
||||
instance AccessControls1 Markdown.BlockQuote
|
||||
instance AccessControls1 Markdown.HTMLBlock
|
||||
instance AccessControls1 Markdown.Table
|
||||
instance AccessControls1 Markdown.TableRow
|
||||
instance AccessControls1 Markdown.TableCell
|
||||
instance AccessControls1 Markdown.Strong
|
||||
instance AccessControls1 Markdown.Emphasis
|
||||
instance AccessControls1 Markdown.Text
|
||||
instance AccessControls1 Markdown.Strikethrough
|
||||
instance AccessControls1 Markdown.Heading
|
||||
instance AccessControls1 Markdown.ThematicBreak
|
||||
instance AccessControls1 Markdown.Link
|
||||
instance AccessControls1 Markdown.Image
|
||||
instance AccessControls1 Markdown.Code
|
||||
instance AccessControls1 Markdown.LineBreak
|
||||
|
||||
instance AccessControls1 PHP.Text
|
||||
instance AccessControls1 PHP.VariableName
|
||||
instance AccessControls1 PHP.Require
|
||||
instance AccessControls1 PHP.RequireOnce
|
||||
instance AccessControls1 PHP.Include
|
||||
instance AccessControls1 PHP.IncludeOnce
|
||||
instance AccessControls1 PHP.ArrayElement
|
||||
instance AccessControls1 PHP.GlobalDeclaration
|
||||
instance AccessControls1 PHP.SimpleVariable
|
||||
instance AccessControls1 PHP.CastType
|
||||
instance AccessControls1 PHP.ErrorControl
|
||||
instance AccessControls1 PHP.Clone
|
||||
instance AccessControls1 PHP.ShellCommand
|
||||
instance AccessControls1 PHP.Update
|
||||
instance AccessControls1 PHP.NewVariable
|
||||
instance AccessControls1 PHP.RelativeScope
|
||||
instance AccessControls1 PHP.NamespaceName
|
||||
instance AccessControls1 PHP.ConstDeclaration
|
||||
instance AccessControls1 PHP.ClassInterfaceClause
|
||||
instance AccessControls1 PHP.ClassBaseClause
|
||||
instance AccessControls1 PHP.UseClause
|
||||
instance AccessControls1 PHP.ReturnType
|
||||
instance AccessControls1 PHP.TypeDeclaration
|
||||
instance AccessControls1 PHP.BaseTypeDeclaration
|
||||
instance AccessControls1 PHP.ScalarType
|
||||
instance AccessControls1 PHP.EmptyIntrinsic
|
||||
instance AccessControls1 PHP.ExitIntrinsic
|
||||
instance AccessControls1 PHP.IssetIntrinsic
|
||||
instance AccessControls1 PHP.EvalIntrinsic
|
||||
instance AccessControls1 PHP.PrintIntrinsic
|
||||
instance AccessControls1 PHP.NamespaceAliasingClause
|
||||
instance AccessControls1 PHP.NamespaceUseDeclaration
|
||||
instance AccessControls1 PHP.NamespaceUseClause
|
||||
instance AccessControls1 PHP.NamespaceUseGroupClause
|
||||
instance AccessControls1 PHP.TraitUseSpecification
|
||||
instance AccessControls1 PHP.Static
|
||||
instance AccessControls1 PHP.ClassModifier
|
||||
instance AccessControls1 PHP.InterfaceBaseClause
|
||||
instance AccessControls1 PHP.Echo
|
||||
instance AccessControls1 PHP.Unset
|
||||
instance AccessControls1 PHP.DeclareDirective
|
||||
instance AccessControls1 PHP.LabeledStatement
|
||||
instance AccessControls1 PHP.QualifiedName
|
||||
instance AccessControls1 PHP.ClassConstDeclaration
|
||||
instance AccessControls1 PHP.Namespace
|
||||
instance AccessControls1 PHP.TraitDeclaration
|
||||
instance AccessControls1 PHP.AliasAs
|
||||
instance AccessControls1 PHP.InsteadOf
|
||||
instance AccessControls1 PHP.TraitUseClause
|
||||
instance AccessControls1 PHP.DestructorDeclaration
|
||||
instance AccessControls1 PHP.ConstructorDeclaration
|
||||
instance AccessControls1 PHP.PropertyDeclaration
|
||||
instance AccessControls1 PHP.PropertyModifier
|
||||
instance AccessControls1 PHP.InterfaceDeclaration
|
||||
instance AccessControls1 PHP.Declare
|
||||
|
||||
instance AccessControls1 Ruby.Assignment
|
||||
instance AccessControls1 Ruby.Class
|
||||
instance AccessControls1 Ruby.Send
|
||||
instance AccessControls1 Ruby.Require
|
||||
instance AccessControls1 Ruby.Load
|
||||
instance AccessControls1 Ruby.LowPrecedenceAnd
|
||||
instance AccessControls1 Ruby.LowPrecedenceOr
|
||||
instance AccessControls1 Ruby.Module
|
||||
instance AccessControls1 Ruby.ZSuper
|
||||
|
||||
instance AccessControls1 TypeScript.JavaScriptRequire
|
||||
instance AccessControls1 TypeScript.Debugger
|
||||
instance AccessControls1 TypeScript.Super
|
||||
instance AccessControls1 TypeScript.Undefined
|
||||
instance AccessControls1 TypeScript.With
|
||||
instance AccessControls1 TypeScript.JsxElement
|
||||
instance AccessControls1 TypeScript.JsxOpeningElement
|
||||
instance AccessControls1 TypeScript.JsxSelfClosingElement
|
||||
instance AccessControls1 TypeScript.JsxAttribute
|
||||
instance AccessControls1 TypeScript.OptionalParameter
|
||||
instance AccessControls1 TypeScript.RequiredParameter
|
||||
instance AccessControls1 TypeScript.RestParameter
|
||||
instance AccessControls1 TypeScript.JsxNamespaceName
|
||||
instance AccessControls1 TypeScript.JsxText
|
||||
instance AccessControls1 TypeScript.JsxExpression
|
||||
instance AccessControls1 TypeScript.JsxClosingElement
|
||||
instance AccessControls1 TypeScript.ImplementsClause
|
||||
instance AccessControls1 TypeScript.JsxFragment
|
||||
instance AccessControls1 TypeScript.Import
|
||||
instance AccessControls1 TypeScript.QualifiedAliasedImport
|
||||
instance AccessControls1 TypeScript.QualifiedExportFrom
|
||||
instance AccessControls1 TypeScript.LookupType
|
||||
instance AccessControls1 TypeScript.Union
|
||||
instance AccessControls1 TypeScript.Intersection
|
||||
instance AccessControls1 TypeScript.FunctionType
|
||||
instance AccessControls1 TypeScript.AmbientFunction
|
||||
instance AccessControls1 TypeScript.ImportRequireClause
|
||||
instance AccessControls1 TypeScript.Constructor
|
||||
instance AccessControls1 TypeScript.TypeParameter
|
||||
instance AccessControls1 TypeScript.TypeAssertion
|
||||
instance AccessControls1 TypeScript.NestedIdentifier
|
||||
instance AccessControls1 TypeScript.NestedTypeIdentifier
|
||||
instance AccessControls1 TypeScript.GenericType
|
||||
instance AccessControls1 TypeScript.TypePredicate
|
||||
instance AccessControls1 TypeScript.EnumDeclaration
|
||||
instance AccessControls1 TypeScript.PropertySignature
|
||||
instance AccessControls1 TypeScript.CallSignature
|
||||
instance AccessControls1 TypeScript.ConstructSignature
|
||||
instance AccessControls1 TypeScript.IndexSignature
|
||||
instance AccessControls1 TypeScript.AbstractMethodSignature
|
||||
instance AccessControls1 TypeScript.ForOf
|
||||
instance AccessControls1 TypeScript.LabeledStatement
|
||||
instance AccessControls1 TypeScript.InternalModule
|
||||
instance AccessControls1 TypeScript.ImportAlias
|
||||
instance AccessControls1 TypeScript.ClassHeritage
|
||||
instance AccessControls1 TypeScript.AbstractClass
|
||||
instance AccessControls1 TypeScript.SideEffectImport
|
||||
instance AccessControls1 TypeScript.QualifiedExport
|
||||
instance AccessControls1 TypeScript.DefaultExport
|
||||
instance AccessControls1 TypeScript.ShorthandPropertyIdentifier
|
||||
instance AccessControls1 TypeScript.ImportClause
|
||||
instance AccessControls1 TypeScript.Tuple
|
||||
instance AccessControls1 TypeScript.Annotation
|
||||
instance AccessControls1 TypeScript.Decorator
|
||||
instance AccessControls1 TypeScript.ComputedPropertyName
|
||||
instance AccessControls1 TypeScript.Constraint
|
||||
instance AccessControls1 TypeScript.DefaultType
|
||||
instance AccessControls1 TypeScript.ParenthesizedType
|
||||
instance AccessControls1 TypeScript.PredefinedType
|
||||
instance AccessControls1 TypeScript.TypeIdentifier
|
||||
instance AccessControls1 TypeScript.ObjectType
|
||||
instance AccessControls1 TypeScript.AmbientDeclaration
|
||||
instance AccessControls1 TypeScript.ExtendsClause
|
||||
instance AccessControls1 TypeScript.ArrayType
|
||||
instance AccessControls1 TypeScript.FlowMaybeType
|
||||
instance AccessControls1 TypeScript.TypeQuery
|
||||
instance AccessControls1 TypeScript.IndexTypeQuery
|
||||
instance AccessControls1 TypeScript.TypeArguments
|
||||
instance AccessControls1 TypeScript.ThisType
|
||||
instance AccessControls1 TypeScript.ExistentialType
|
||||
instance AccessControls1 TypeScript.LiteralType
|
||||
instance AccessControls1 TypeScript.Update
|
||||
instance AccessControls1 TypeScript.MetaProperty
|
||||
instance AccessControls1 TypeScript.Module
|
@ -29,6 +29,7 @@ import Data.Abstract.FreeVariables as X
|
||||
import Data.Abstract.Module
|
||||
import Data.Abstract.Name as X
|
||||
import Data.Abstract.ScopeGraph (Relation(..))
|
||||
import Data.Abstract.AccessControls.Class as X
|
||||
import Data.Language
|
||||
import Data.Scientific (Scientific)
|
||||
import Data.Semigroup.App
|
||||
@ -44,6 +45,7 @@ class (Show1 constr, Foldable constr) => Evaluatable constr where
|
||||
, Carrier sig m
|
||||
, Declarations term
|
||||
, FreeVariables term
|
||||
, AccessControls term
|
||||
, Member (Allocator address) sig
|
||||
, Member (Bitwise value) sig
|
||||
, Member (Boolean value) sig
|
||||
@ -148,26 +150,26 @@ instance HasPrelude 'PHP
|
||||
|
||||
instance HasPrelude 'Python where
|
||||
definePrelude _ =
|
||||
defineBuiltIn (Declaration $ X.name "print") Default Print
|
||||
defineBuiltIn (Declaration $ X.name "print") Default Public Print
|
||||
|
||||
instance HasPrelude 'Ruby where
|
||||
definePrelude _ = do
|
||||
defineSelf
|
||||
|
||||
defineBuiltIn (Declaration $ X.name "puts") Default Print
|
||||
defineBuiltIn (Declaration $ X.name "puts") Default Public Print
|
||||
|
||||
defineClass (Declaration (X.name "Object")) [] $ do
|
||||
defineBuiltIn (Declaration $ X.name "inspect") Default Show
|
||||
defineBuiltIn (Declaration $ X.name "inspect") Default Public Show
|
||||
|
||||
instance HasPrelude 'TypeScript where
|
||||
definePrelude _ = do
|
||||
defineSelf
|
||||
defineNamespace (Declaration (X.name "console")) $ defineBuiltIn (Declaration $ X.name "log") Default Print
|
||||
defineNamespace (Declaration (X.name "console")) $ defineBuiltIn (Declaration $ X.name "log") Default Public Print
|
||||
|
||||
instance HasPrelude 'JavaScript where
|
||||
definePrelude _ = do
|
||||
defineSelf
|
||||
defineNamespace (Declaration (X.name "console")) $ defineBuiltIn (Declaration $ X.name "log") Default Print
|
||||
defineNamespace (Declaration (X.name "console")) $ defineBuiltIn (Declaration $ X.name "log") Default Public Print
|
||||
|
||||
defineSelf :: ( Carrier sig m
|
||||
, Member (State (ScopeGraph address)) sig
|
||||
@ -185,8 +187,8 @@ defineSelf :: ( Carrier sig m
|
||||
=> Evaluator term address value m ()
|
||||
defineSelf = do
|
||||
let self = Declaration X.__self
|
||||
declare self Default emptySpan Nothing
|
||||
slot <- lookupDeclaration self
|
||||
declare self Default Public emptySpan Nothing
|
||||
slot <- lookupSlot self
|
||||
assign slot =<< object =<< currentFrame
|
||||
|
||||
|
||||
@ -194,6 +196,7 @@ defineSelf = do
|
||||
|
||||
-- | The type of error thrown when failing to evaluate a term.
|
||||
data EvalError term address value return where
|
||||
AccessControlError :: (Name, AccessControl) -> (Name, AccessControl) -> value -> EvalError term address value value
|
||||
ConstructorError :: Name -> EvalError term address value address
|
||||
DefaultExportError :: EvalError term address value ()
|
||||
DerefError :: value -> EvalError term address value value
|
||||
@ -220,6 +223,7 @@ deriving instance (Show term, Show value) => Show (EvalError term address value
|
||||
|
||||
instance (NFData term, NFData value) => NFData1 (EvalError term address value) where
|
||||
liftRnf _ x = case x of
|
||||
AccessControlError requester requested v -> rnf requester `seq` rnf requested `seq` rnf v
|
||||
ConstructorError n -> rnf n
|
||||
DefaultExportError -> ()
|
||||
DerefError v -> rnf v
|
||||
@ -235,14 +239,15 @@ instance (NFData term, NFData value, NFData return) => NFData (EvalError term ad
|
||||
rnf = liftRnf rnf
|
||||
|
||||
instance (Eq term, Eq value) => Eq1 (EvalError term address value) where
|
||||
liftEq _ (AccessControlError a b c) (AccessControlError a' b' c') = a == a' && b == b' && c == c'
|
||||
liftEq _ (DerefError v) (DerefError v2) = v == v2
|
||||
liftEq _ DefaultExportError DefaultExportError = True
|
||||
liftEq _ (ExportError a b) (ExportError c d) = (a == c) && (b == d)
|
||||
liftEq _ (ExportError a b) (ExportError c d) = a == c && b == d
|
||||
liftEq _ (FloatFormatError a) (FloatFormatError b) = a == b
|
||||
liftEq _ (IntegerFormatError a) (IntegerFormatError b) = a == b
|
||||
liftEq _ (NoNameError t1) (NoNameError t2) = t1 == t2
|
||||
liftEq _ (RationalFormatError a) (RationalFormatError b) = a == b
|
||||
liftEq _ (ReferenceError v n) (ReferenceError v2 n2) = (v == v2) && (n == n2)
|
||||
liftEq _ (ReferenceError v n) (ReferenceError v2 n2) = v == v2 && n == n2
|
||||
liftEq _ _ _ = False
|
||||
|
||||
instance (Show term, Show value) => Show1 (EvalError term address value) where
|
||||
|
@ -6,7 +6,7 @@ module Data.Abstract.Heap
|
||||
, scopeLookup
|
||||
, frameSlots
|
||||
, frameLinks
|
||||
, getSlot
|
||||
, getSlotValue
|
||||
, setSlot
|
||||
, deleteSlot
|
||||
, initFrame
|
||||
@ -77,8 +77,8 @@ frameSlots address = fmap slots . frameLookup address
|
||||
frameLinks :: Ord address => address -> Heap scope address value -> Maybe (Map EdgeLabel (Map scope address))
|
||||
frameLinks address = fmap links . frameLookup address
|
||||
|
||||
getSlot :: Ord address => Slot address -> Heap address address value -> Maybe (Set value)
|
||||
getSlot Slot{..} = (IntMap.lookup (unPosition position) =<<) . frameSlots frameAddress
|
||||
getSlotValue :: Ord address => Slot address -> Heap address address value -> Maybe (Set value)
|
||||
getSlotValue Slot{..} = (IntMap.lookup (unPosition position) =<<) . frameSlots frameAddress
|
||||
|
||||
setSlot :: Ord address => Slot address -> Set value -> Heap scope address value -> Heap scope address value
|
||||
setSlot Slot{..} value h@(Heap heap) = case frameLookup frameAddress h of
|
||||
@ -92,7 +92,12 @@ deleteSlot Slot{..} h@(Heap heap) = case frameLookup frameAddress h of
|
||||
Heap (Map.insert frameAddress (frame { slots = IntMap.delete (unPosition position) slotMap }) heap)
|
||||
Nothing -> h
|
||||
|
||||
lookupDeclaration :: Ord address => Declaration -> (address, address) -> ScopeGraph address -> Heap address address value -> Maybe (Slot address)
|
||||
lookupDeclaration :: Ord address
|
||||
=> Declaration
|
||||
-> (address, address)
|
||||
-> ScopeGraph address
|
||||
-> Heap address address value
|
||||
-> Maybe (Slot address)
|
||||
lookupDeclaration Declaration{..} (currentScope, currentFrame) scopeGraph heap = do
|
||||
path <- lookupScopePath unDeclaration currentScope scopeGraph
|
||||
frameAddress <- lookupFrameAddress path currentFrame heap
|
||||
|
@ -3,7 +3,9 @@ module Data.Abstract.ScopeGraph
|
||||
( Slot(..)
|
||||
, Info(..)
|
||||
, associatedScope
|
||||
, relationsOfScope
|
||||
, declarationByName
|
||||
, declarationsByAccessControl
|
||||
, declarationsByRelation
|
||||
, Declaration(..) -- TODO don't export these constructors
|
||||
, declare
|
||||
, EdgeLabel(..)
|
||||
@ -29,31 +31,80 @@ module Data.Abstract.ScopeGraph
|
||||
, pathDeclarationScope
|
||||
, putDeclarationScopeAtPosition
|
||||
, declarationNames
|
||||
, AccessControl(..)
|
||||
) where
|
||||
|
||||
import Control.Abstract.Hole
|
||||
import Data.Abstract.Name
|
||||
import Data.Aeson
|
||||
import Data.JSON.Fields (ToJSONFields(..))
|
||||
import qualified Data.Map.Strict as Map
|
||||
import qualified Data.Sequence as Seq
|
||||
import qualified Data.Set as Set
|
||||
import Data.Span
|
||||
import Prelude hiding (lookup)
|
||||
import Prologue
|
||||
import qualified Proto3.Suite as Proto
|
||||
import qualified Proto3.Wire.Encode as Encode
|
||||
import qualified Proto3.Wire.Decode as Decode
|
||||
|
||||
-- A slot is a location in the heap where a value is stored.
|
||||
data Slot address = Slot { frameAddress :: address, position :: Position }
|
||||
deriving (Eq, Show, Ord, Generic, NFData)
|
||||
|
||||
data Relation = Default | Instance
|
||||
deriving (Eq, Show, Ord, Generic, NFData)
|
||||
data AccessControl = Public
|
||||
| Protected
|
||||
| Private
|
||||
deriving (Bounded, Enum, Eq, Proto.Finite, Generic, Hashable, ToJSON, Proto.MessageField, Proto.Named, NFData, Show)
|
||||
|
||||
instance Proto.Primitive AccessControl where
|
||||
encodePrimitive = Encode.enum
|
||||
decodePrimitive = fromRight Proto.def <$> Decode.enum
|
||||
primType _ = Proto.Named (Proto.Single (Proto.nameOf (Proxy @AccessControl)))
|
||||
|
||||
instance Proto.HasDefault AccessControl where
|
||||
def = Public
|
||||
|
||||
instance ToJSONFields AccessControl where
|
||||
toJSONFields accessControl = ["accessControl" .= accessControl]
|
||||
|
||||
-- | The Ord AccessControl instance represents an order specification of AccessControls.
|
||||
-- AccessControls that are less than or equal to another AccessControl implies access.
|
||||
-- It is helpful to consider `Public <= Private` as saying "Can a Public syntax term access a Private syntax term?"
|
||||
-- In this way, Public AccessControl is the top of the order specification, and Private AccessControl is the bottom.
|
||||
instance Ord AccessControl where
|
||||
-- | Private AccessControl represents the least overlap or accessibility with other AccessControls.
|
||||
-- When asking if the AccessControl "on the left" is less than the AccessControl "on the right", Private AccessControl on the left always implies access to the thing on the right.
|
||||
(<=) Private _ = True
|
||||
(<=) _ Private = False
|
||||
|
||||
-- | Protected AccessControl is inbetween Private and Public in the order specification.
|
||||
-- Protected AccessControl "on the left" has access to Protected or Public AccessControls "on the right".
|
||||
(<=) Protected Public = True
|
||||
(<=) Protected Protected = True
|
||||
|
||||
-- | Public AccessControl "on the left" has access only to Public AccessControl "on the right".
|
||||
-- In all other cases, Public AccessControl "on the left" implies no access.
|
||||
(<=) Public Public = True
|
||||
(<=) Public _ = False
|
||||
|
||||
|
||||
data Relation = Default | Instance deriving (Eq, Show, Ord, Generic, NFData)
|
||||
|
||||
instance Lower Relation where
|
||||
lowerBound = Default
|
||||
|
||||
data Info scopeAddress = Info
|
||||
{ infoDeclaration :: Declaration
|
||||
, infoRelation :: Relation
|
||||
, infoAccessControl :: AccessControl
|
||||
, infoSpan :: Span
|
||||
, infoAssociatedScope :: Maybe scopeAddress
|
||||
} deriving (Eq, Show, Ord, Generic, NFData)
|
||||
|
||||
instance Lower (Info scopeAddress) where
|
||||
lowerBound = Info lowerBound lowerBound Public lowerBound Nothing
|
||||
|
||||
-- Offsets and frame addresses in the heap should be addresses?
|
||||
data Scope address = Scope
|
||||
{ edges :: Map EdgeLabel [address]
|
||||
@ -70,6 +121,9 @@ instance AbstractHole (Scope scopeAddress) where
|
||||
instance AbstractHole address => AbstractHole (Slot address) where
|
||||
hole = Slot hole (Position 0)
|
||||
|
||||
instance AbstractHole (Info address) where
|
||||
hole = lowerBound
|
||||
|
||||
newtype Position = Position { unPosition :: Int }
|
||||
deriving (Eq, Show, Ord, Generic, NFData)
|
||||
|
||||
@ -121,26 +175,44 @@ ddataOfScope scope = fmap declarations . Map.lookup scope . unScopeGraph
|
||||
linksOfScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Map EdgeLabel [scope])
|
||||
linksOfScope scope = fmap edges . Map.lookup scope . unScopeGraph
|
||||
|
||||
relationsOfScope :: Ord scope => scope -> Relation -> ScopeGraph scope -> [ Info scope ]
|
||||
relationsOfScope scope relation g = fromMaybe mempty $ do
|
||||
declarationsByAccessControl :: Ord scope => scope -> AccessControl -> ScopeGraph scope -> [ Info scope ]
|
||||
declarationsByAccessControl scope accessControl g = fromMaybe mempty $ do
|
||||
dataSeq <- ddataOfScope scope g
|
||||
pure . toList $ Seq.filter (\Info{..} -> accessControl <= infoAccessControl) dataSeq
|
||||
|
||||
declarationsByRelation :: Ord scope => scope -> Relation -> ScopeGraph scope -> [ Info scope ]
|
||||
declarationsByRelation scope relation g = fromMaybe mempty $ do
|
||||
dataSeq <- ddataOfScope scope g
|
||||
pure . toList $ Seq.filter (\Info{..} -> infoRelation == relation) dataSeq
|
||||
|
||||
declarationByName :: Ord scope => scope -> Declaration -> ScopeGraph scope -> Maybe (Info scope)
|
||||
declarationByName scope name g = do
|
||||
dataSeq <- ddataOfScope scope g
|
||||
find (\Info{..} -> infoDeclaration == name) dataSeq
|
||||
|
||||
-- Lookup a scope in the scope graph.
|
||||
lookupScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Scope scope)
|
||||
lookupScope scope = Map.lookup scope . unScopeGraph
|
||||
|
||||
-- Declare a declaration with a span and an associated scope in the scope graph.
|
||||
-- TODO: Return the whole value in Maybe or Either.
|
||||
declare :: Ord scope => Declaration -> Relation -> Span -> Maybe scope -> scope -> ScopeGraph scope -> (ScopeGraph scope, Maybe Position)
|
||||
declare decl rel declSpan assocScope currentScope g = fromMaybe (g, Nothing) $ do
|
||||
declare :: Ord scope
|
||||
=> Declaration
|
||||
-> Relation
|
||||
-> AccessControl
|
||||
-> Span
|
||||
-> Maybe scope
|
||||
-> scope
|
||||
-> ScopeGraph scope
|
||||
-> (ScopeGraph scope, Maybe Position)
|
||||
declare decl rel accessControl declSpan assocScope currentScope g = fromMaybe (g, Nothing) $ do
|
||||
scope <- lookupScope currentScope g
|
||||
|
||||
dataSeq <- ddataOfScope currentScope g
|
||||
case Seq.findIndexR (\Info{..} -> decl == infoDeclaration && declSpan == infoSpan && rel == infoRelation) dataSeq of
|
||||
Just index -> pure (g, Just (Position index))
|
||||
Nothing -> do
|
||||
let newScope = scope { declarations = declarations scope Seq.|> Info decl rel declSpan assocScope }
|
||||
let newScope = scope { declarations = declarations scope Seq.|> Info decl rel accessControl declSpan assocScope }
|
||||
pure (insertScope currentScope newScope g, Just (Position (length (declarations newScope))))
|
||||
|
||||
-- | Add a reference to a declaration in the scope graph.
|
||||
@ -271,9 +343,15 @@ associatedScope Declaration{..} g@(ScopeGraph graph) = go (Map.keys graph)
|
||||
newtype Reference = Reference { unReference :: Name }
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
|
||||
instance Lower Reference where
|
||||
lowerBound = Reference $ name ""
|
||||
|
||||
newtype Declaration = Declaration { unDeclaration :: Name }
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
|
||||
instance Lower Declaration where
|
||||
lowerBound = Declaration $ name ""
|
||||
|
||||
-- | The type of edge from a scope to its parent scopes.
|
||||
-- Either a lexical edge or an import edge in the case of non-lexical edges.
|
||||
data EdgeLabel = Lexical | Import | Export | Superclass
|
||||
|
@ -48,8 +48,8 @@ instance ( Member (Allocator address) sig
|
||||
frame <- newFrame scope frameLinks
|
||||
res <- withScopeAndFrame frame $ do
|
||||
for_ params $ \param -> do
|
||||
address <- lookupDeclaration (Declaration param)
|
||||
assign address Abstract
|
||||
slot <- lookupSlot (Declaration param)
|
||||
assign slot Abstract
|
||||
catchReturn (runFunction (Evaluator . eval) (Evaluator (eval body)))
|
||||
Evaluator $ runFunctionC (k res) eval
|
||||
BuiltIn _ _ k -> runFunctionC (k Abstract) eval
|
||||
|
@ -113,8 +113,8 @@ instance ( FreeVariables term
|
||||
maybe (pure ()) (`assign` object) maybeSlot
|
||||
Nothing -> pure ()
|
||||
for_ (zip names params) $ \(name, param) -> do
|
||||
addr <- lookupDeclaration (Declaration name)
|
||||
assign addr param
|
||||
slot <- lookupSlot (Declaration name)
|
||||
assign slot param
|
||||
catchReturn (runFunction (Evaluator . eval) (Evaluator (eval body)))
|
||||
_ -> throwValueError (CallError op)
|
||||
Evaluator $ runFunctionC (k boxed) eval) op)
|
||||
|
@ -267,8 +267,8 @@ instance ( Member (Allocator address) sig
|
||||
res <- withScopeAndFrame frame $ do
|
||||
tvars <- foldr (\ param rest -> do
|
||||
tvar <- Var <$> fresh
|
||||
address <- lookupDeclaration (Declaration param)
|
||||
assign address tvar
|
||||
slot <- lookupSlot (Declaration param)
|
||||
assign slot tvar
|
||||
(tvar :) <$> rest) (pure []) params
|
||||
-- TODO: We may still want to represent this as a closure and not a function type
|
||||
(zeroOrMoreProduct tvars :->) <$> catchReturn (runFunction (Evaluator . eval) (Evaluator (eval body)))
|
||||
|
@ -7,13 +7,15 @@ module Data.Quieterm
|
||||
import Control.DeepSeq
|
||||
import Data.Abstract.Declarations (Declarations)
|
||||
import Data.Abstract.FreeVariables (FreeVariables)
|
||||
import Data.Abstract.AccessControls.Class
|
||||
import Data.Abstract.AccessControls.Instances ()
|
||||
import Data.Functor.Classes
|
||||
import Data.Functor.Foldable
|
||||
import Data.Term
|
||||
import Text.Show (showListWith)
|
||||
|
||||
newtype Quieterm syntax ann = Quieterm { unQuieterm :: TermF syntax ann (Quieterm syntax ann) }
|
||||
deriving (Declarations, FreeVariables)
|
||||
deriving (Declarations, FreeVariables, AccessControls)
|
||||
|
||||
type instance Base (Quieterm syntax ann) = TermF syntax ann
|
||||
instance Functor syntax => Recursive (Quieterm syntax ann) where project = unQuieterm
|
||||
|
@ -26,7 +26,7 @@ import qualified Proto3.Suite.DotProto as Proto
|
||||
import qualified Proto3.Wire.Encode as Encode
|
||||
import qualified Proto3.Wire.Decode as Decode
|
||||
import Control.Abstract.ScopeGraph (reference, Reference(..), Declaration(..))
|
||||
import Control.Abstract.Heap (deref, lookupDeclaration)
|
||||
import Control.Abstract.Heap (deref, lookupSlot)
|
||||
|
||||
-- Combinators
|
||||
|
||||
@ -167,7 +167,7 @@ instance Evaluatable Identifier where
|
||||
|
||||
ref _ _ (Identifier name) = do
|
||||
reference (Reference name) (Declaration name)
|
||||
lookupDeclaration (Declaration name)
|
||||
lookupSlot (Declaration name)
|
||||
|
||||
|
||||
instance Tokenize Identifier where
|
||||
|
@ -8,7 +8,8 @@ import Proto3.Suite.Class
|
||||
import qualified Data.Map.Strict as Map
|
||||
import qualified Data.Set as Set
|
||||
|
||||
import Control.Abstract hiding (Function)
|
||||
import Control.Abstract hiding (Function, AccessControl(..))
|
||||
import Data.Abstract.ScopeGraph as ScopeGraph (AccessControl(..))
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Name (__self)
|
||||
import Data.JSON.Fields
|
||||
@ -31,17 +32,18 @@ instance Evaluatable Function where
|
||||
eval _ _ Function{..} = do
|
||||
name <- maybeM (throwNoNameError functionName) (declaredName functionName)
|
||||
span <- ask @Span
|
||||
associatedScope <- declareFunction name span
|
||||
associatedScope <- declareFunction name Default ScopeGraph.Public span
|
||||
|
||||
params <- withScope associatedScope . for functionParameters $ \paramNode -> do
|
||||
param <- maybeM (throwNoNameError paramNode) (declaredName paramNode)
|
||||
param <$ declare (Declaration param) Default span Nothing
|
||||
param <$ declare (Declaration param) Default ScopeGraph.Public span Nothing
|
||||
|
||||
addr <- lookupDeclaration (Declaration name)
|
||||
addr <- lookupSlot (Declaration name)
|
||||
v <- function name params functionBody associatedScope
|
||||
v <$ assign addr v
|
||||
|
||||
declareFunction :: ( Carrier sig m
|
||||
declareFunction ::
|
||||
( Carrier sig m
|
||||
, Member (State (ScopeGraph address)) sig
|
||||
, Member (Allocator address) sig
|
||||
, Member (Reader (CurrentScope address)) sig
|
||||
@ -49,13 +51,15 @@ declareFunction :: ( Carrier sig m
|
||||
, Ord address
|
||||
)
|
||||
=> Name
|
||||
-> Relation
|
||||
-> AccessControl
|
||||
-> Span
|
||||
-> Evaluator term address value m address
|
||||
declareFunction name span = do
|
||||
declareFunction name relation accessControl span = do
|
||||
currentScope' <- currentScope
|
||||
let lexicalEdges = Map.singleton Lexical [ currentScope' ]
|
||||
associatedScope <- newScope lexicalEdges
|
||||
declare (Declaration name) Default span (Just associatedScope)
|
||||
declare (Declaration name) relation accessControl span (Just associatedScope)
|
||||
pure associatedScope
|
||||
|
||||
instance Tokenize Function where
|
||||
@ -70,8 +74,14 @@ instance Declarations1 Function where
|
||||
instance FreeVariables1 Function where
|
||||
liftFreeVariables freeVariables f@Function{..} = foldMap freeVariables f `Set.difference` foldMap freeVariables functionParameters
|
||||
|
||||
|
||||
data Method a = Method { methodContext :: ![a], methodReceiver :: !a, methodName :: !a, methodParameters :: ![a], methodBody :: !a }
|
||||
data Method a = Method
|
||||
{ methodContext :: [a]
|
||||
, methodReceiver :: a
|
||||
, methodName :: a
|
||||
, methodParameters :: [a]
|
||||
, methodBody :: a
|
||||
, methodAccessControl :: AccessControl
|
||||
}
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Method
|
||||
|
||||
@ -84,16 +94,15 @@ instance Evaluatable Method where
|
||||
eval _ _ Method{..} = do
|
||||
name <- maybeM (throwNoNameError methodName) (declaredName methodName)
|
||||
span <- ask @Span
|
||||
associatedScope <- declareFunction name span
|
||||
associatedScope <- declareFunction name Default methodAccessControl span
|
||||
|
||||
params <- withScope associatedScope $ do
|
||||
-- TODO: Should we give `self` a special Relation?
|
||||
declare (Declaration __self) Default emptySpan Nothing
|
||||
declare (Declaration __self) Default ScopeGraph.Public emptySpan Nothing
|
||||
for methodParameters $ \paramNode -> do
|
||||
param <- maybeM (throwNoNameError paramNode) (declaredName paramNode)
|
||||
param <$ declare (Declaration param) Default span Nothing
|
||||
param <$ declare (Declaration param) Default ScopeGraph.Public span Nothing
|
||||
|
||||
addr <- lookupDeclaration (Declaration name)
|
||||
addr <- lookupSlot (Declaration name)
|
||||
v <- function name params methodBody associatedScope
|
||||
v <$ assign addr v
|
||||
|
||||
@ -111,7 +120,12 @@ instance FreeVariables1 Method where
|
||||
|
||||
|
||||
-- | A method signature in TypeScript or a method spec in Go.
|
||||
data MethodSignature a = MethodSignature { methodSignatureContext :: ![a], methodSignatureName :: !a, methodSignatureParameters :: ![a] }
|
||||
data MethodSignature a = MethodSignature
|
||||
{ methodSignatureContext :: [a]
|
||||
, methodSignatureName :: a
|
||||
, methodSignatureParameters :: [a]
|
||||
, methodSignatureAccessControl :: AccessControl
|
||||
}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically MethodSignature
|
||||
|
||||
@ -147,7 +161,7 @@ instance Evaluatable VariableDeclaration where
|
||||
eval eval _ (VariableDeclaration decs) = do
|
||||
for_ decs $ \declaration -> do
|
||||
name <- maybeM (throwNoNameError declaration) (declaredName declaration)
|
||||
declare (Declaration name) Default emptySpan Nothing
|
||||
declare (Declaration name) Default ScopeGraph.Public emptySpan Nothing
|
||||
(span, _) <- do
|
||||
ref <- eval declaration
|
||||
subtermSpan <- get @Span
|
||||
@ -176,7 +190,12 @@ instance Declarations a => Declarations (InterfaceDeclaration a) where
|
||||
|
||||
|
||||
-- | A public field definition such as a field definition in a JavaScript class.
|
||||
data PublicFieldDefinition a = PublicFieldDefinition { publicFieldContext :: ![a], publicFieldPropertyName :: !a, publicFieldValue :: !a }
|
||||
data PublicFieldDefinition a = PublicFieldDefinition
|
||||
{ publicFieldContext :: [a]
|
||||
, publicFieldPropertyName :: a
|
||||
, publicFieldValue :: a
|
||||
, publicFieldAccessControl :: AccessControl
|
||||
}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PublicFieldDefinition
|
||||
|
||||
@ -186,8 +205,8 @@ instance Evaluatable PublicFieldDefinition where
|
||||
span <- ask @Span
|
||||
propertyName <- maybeM (throwNoNameError publicFieldPropertyName) (declaredName publicFieldPropertyName)
|
||||
|
||||
declare (Declaration propertyName) Instance span Nothing
|
||||
slot <- lookupDeclaration (Declaration propertyName)
|
||||
declare (Declaration propertyName) Instance publicFieldAccessControl span Nothing
|
||||
slot <- lookupSlot (Declaration propertyName)
|
||||
value <- eval publicFieldValue
|
||||
assign slot value
|
||||
unit
|
||||
@ -218,7 +237,7 @@ instance Evaluatable Class where
|
||||
superScopes <- for classSuperclasses $ \superclass -> do
|
||||
name <- maybeM (throwNoNameError superclass) (declaredName superclass)
|
||||
scope <- associatedScope (Declaration name)
|
||||
slot <- lookupDeclaration (Declaration name)
|
||||
slot <- lookupSlot (Declaration name)
|
||||
superclassFrame <- scopedEnvironment =<< deref slot
|
||||
pure $ case (scope, superclassFrame) of
|
||||
(Just scope, Just frame) -> Just (scope, frame)
|
||||
@ -228,12 +247,12 @@ instance Evaluatable Class where
|
||||
current = (Lexical, ) <$> pure (pure currentScope')
|
||||
edges = Map.fromList (superclassEdges <> current)
|
||||
classScope <- newScope edges
|
||||
declare (Declaration name) Default span (Just classScope)
|
||||
declare (Declaration name) Default ScopeGraph.Public span (Just classScope)
|
||||
|
||||
let frameEdges = Map.singleton Superclass (Map.fromList (catMaybes superScopes))
|
||||
classFrame <- newFrame classScope frameEdges
|
||||
|
||||
classSlot <- lookupDeclaration (Declaration name)
|
||||
classSlot <- lookupSlot (Declaration name)
|
||||
assign classSlot =<< klass (Declaration name) classFrame
|
||||
|
||||
withScopeAndFrame classFrame $ do
|
||||
@ -304,10 +323,10 @@ instance Evaluatable TypeAlias where
|
||||
span <- ask @Span
|
||||
assocScope <- associatedScope (Declaration kindName)
|
||||
-- TODO: Should we consider a special Relation for `TypeAlias`?
|
||||
declare (Declaration name) Default span assocScope
|
||||
declare (Declaration name) Default ScopeGraph.Public span assocScope
|
||||
|
||||
slot <- lookupDeclaration (Declaration name)
|
||||
kindSlot <- lookupDeclaration (Declaration kindName)
|
||||
slot <- lookupSlot (Declaration name)
|
||||
kindSlot <- lookupSlot (Declaration kindName)
|
||||
assign slot =<< deref kindSlot
|
||||
|
||||
unit
|
||||
|
@ -413,15 +413,30 @@ instance Evaluatable MemberAccess where
|
||||
eval eval _ MemberAccess{..} = do
|
||||
lhsValue <- eval lhs
|
||||
lhsFrame <- Abstract.scopedEnvironment lhsValue
|
||||
slot <- case lhsFrame of
|
||||
|
||||
rhsSlot <- case lhsFrame of
|
||||
Just lhsFrame ->
|
||||
withScopeAndFrame lhsFrame $ do
|
||||
reference (Reference rhs) (Declaration rhs)
|
||||
lookupDeclaration (Declaration rhs)
|
||||
lookupSlot (Declaration rhs)
|
||||
-- Throw a ReferenceError since we're attempting to reference a name within a value that is not an Object.
|
||||
Nothing -> throwEvalError (ReferenceError lhsValue rhs)
|
||||
value <- deref slot
|
||||
bindThis lhsValue value
|
||||
|
||||
rhsValue <- deref rhsSlot
|
||||
rhsScope <- scopeLookup (frameAddress rhsSlot)
|
||||
|
||||
let lhsAccessControl = fromMaybe Public (termToAccessControl lhs)
|
||||
infos <- declarationsByAccessControl rhsScope lhsAccessControl
|
||||
|
||||
rhsValue' <- case find (\Info{..} -> Declaration rhs == infoDeclaration) infos of
|
||||
Just _ -> pure rhsValue
|
||||
Nothing -> do
|
||||
let lhsName = fromMaybe (name "") (declaredName lhs)
|
||||
info <- declarationByName rhsScope (Declaration rhs)
|
||||
throwEvalError $ AccessControlError (lhsName, lhsAccessControl) (rhs, infoAccessControl info) rhsValue
|
||||
|
||||
bindThis lhsValue rhsValue'
|
||||
|
||||
|
||||
ref eval _ MemberAccess{..} = do
|
||||
lhsValue <- eval lhs
|
||||
@ -430,7 +445,7 @@ instance Evaluatable MemberAccess where
|
||||
Just lhsFrame ->
|
||||
withScopeAndFrame lhsFrame $ do
|
||||
reference (Reference rhs) (Declaration rhs)
|
||||
lookupDeclaration (Declaration rhs)
|
||||
lookupSlot (Declaration rhs)
|
||||
-- Throw a ReferenceError since we're attempting to reference a name within a value that is not an Object.
|
||||
Nothing -> throwEvalError (ReferenceError lhsValue rhs)
|
||||
|
||||
@ -516,20 +531,20 @@ instance Evaluatable Await where
|
||||
eval eval _ (Await a) = eval a
|
||||
|
||||
-- | An object constructor call in Javascript, Java, etc.
|
||||
data New a = New { subject :: a , typeParameters :: a, arguments :: [a] }
|
||||
data New a = New { newSubject :: a , newTypeParameters :: a, newArguments :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically New
|
||||
|
||||
instance Declarations1 New where
|
||||
liftDeclaredName declaredName New{..} = declaredName subject
|
||||
liftDeclaredName declaredName New{..} = declaredName newSubject
|
||||
|
||||
-- TODO: Implement Eval instance for New
|
||||
instance Evaluatable New where
|
||||
eval eval _ New{..} = do
|
||||
name <- maybeM (throwNoNameError subject) (declaredName subject)
|
||||
name <- maybeM (throwNoNameError newSubject) (declaredName newSubject)
|
||||
assocScope <- maybeM (throwEvalError $ ConstructorError name) =<< associatedScope (Declaration name)
|
||||
objectScope <- newScope (Map.singleton Superclass [ assocScope ])
|
||||
slot <- lookupDeclaration (Declaration name)
|
||||
slot <- lookupSlot (Declaration name)
|
||||
classVal <- deref slot
|
||||
classFrame <- maybeM (throwEvalError $ ScopedEnvError classVal) =<< scopedEnvironment classVal
|
||||
|
||||
@ -537,17 +552,17 @@ instance Evaluatable New where
|
||||
objectVal <- object objectFrame
|
||||
|
||||
classScope <- scopeLookup classFrame
|
||||
instanceMembers <- relationsOfScope classScope Instance
|
||||
instanceMembers <- declarationsByRelation classScope Instance
|
||||
|
||||
void . withScopeAndFrame objectFrame $ do
|
||||
for_ instanceMembers $ \Info{..} -> do
|
||||
declare infoDeclaration Default infoSpan infoAssociatedScope
|
||||
declare infoDeclaration Default infoAccessControl infoSpan infoAssociatedScope
|
||||
|
||||
-- TODO: This is a typescript specific name and we should allow languages to customize it.
|
||||
let constructorName = Name.name "constructor"
|
||||
reference (Reference constructorName) (Declaration constructorName)
|
||||
constructor <- deref =<< lookupDeclaration (Declaration constructorName)
|
||||
args <- traverse eval arguments
|
||||
constructor <- deref =<< lookupSlot (Declaration constructorName)
|
||||
args <- traverse eval newArguments
|
||||
boundConstructor <- bindThis objectVal constructor
|
||||
call boundConstructor args
|
||||
|
||||
@ -579,4 +594,7 @@ instance Tokenize This where
|
||||
instance Evaluatable This where
|
||||
eval _ _ This = do
|
||||
reference (Reference __self) (Declaration __self)
|
||||
deref =<< lookupDeclaration (Declaration __self)
|
||||
deref =<< lookupSlot (Declaration __self)
|
||||
|
||||
instance AccessControls1 This where
|
||||
liftTermToAccessControl _ _ = Just Private
|
||||
|
@ -128,9 +128,9 @@ instance Evaluatable Let where
|
||||
assocScope <- associatedScope (Declaration valueName)
|
||||
|
||||
_ <- withLexicalScopeAndFrame $ do
|
||||
declare (Declaration name) Default letSpan assocScope
|
||||
declare (Declaration name) Default Public letSpan assocScope
|
||||
letVal <- eval letValue
|
||||
slot <- lookupDeclaration (Declaration name)
|
||||
slot <- lookupSlot (Declaration name)
|
||||
assign slot letVal
|
||||
eval letBody
|
||||
unit
|
||||
|
@ -11,6 +11,7 @@ import Prologue
|
||||
|
||||
import Assigning.Assignment hiding (Assignment, Error)
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph (AccessControl(..))
|
||||
import Data.Abstract.Name (Name, name)
|
||||
import Data.Syntax
|
||||
(contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError)
|
||||
@ -129,6 +130,8 @@ type Syntax =
|
||||
, []
|
||||
, Literal.String
|
||||
, Literal.EscapeSequence
|
||||
, Literal.Null
|
||||
, Literal.Boolean
|
||||
]
|
||||
|
||||
type Term = Term.Term (Sum Syntax) Location
|
||||
@ -153,6 +156,7 @@ expressionChoices :: [Assignment Term]
|
||||
expressionChoices =
|
||||
[ argumentList
|
||||
, assignment'
|
||||
, boolean
|
||||
, binaryExpression
|
||||
, block
|
||||
, breakStatement
|
||||
@ -196,6 +200,7 @@ expressionChoices =
|
||||
, methodDeclaration
|
||||
, methodSpec
|
||||
, methodSpecList
|
||||
, nil
|
||||
, packageClause
|
||||
, packageIdentifier
|
||||
, parameterDeclaration
|
||||
@ -269,9 +274,6 @@ floatLiteral = makeTerm <$> symbol FloatLiteral <*> (Literal.Float <$> source)
|
||||
identifier :: Assignment Term
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier' <|> symbol Identifier'') <*> (Syntax.Identifier . name <$> source)
|
||||
|
||||
identifier' :: Assignment Name
|
||||
identifier' = (symbol Identifier <|> symbol Identifier' <|> symbol Identifier'') *> (name <$> source)
|
||||
|
||||
imaginaryLiteral :: Assignment Term
|
||||
imaginaryLiteral = makeTerm <$> symbol ImaginaryLiteral <*> (Literal.Complex <$> source)
|
||||
|
||||
@ -306,6 +308,13 @@ typeIdentifier = makeTerm <$> symbol TypeIdentifier <*> (Syntax.Identifier . nam
|
||||
typeIdentifier' :: Assignment Name
|
||||
typeIdentifier' = symbol TypeIdentifier *> (name <$> source)
|
||||
|
||||
nil :: Assignment Term
|
||||
nil = makeTerm <$> symbol Nil <*> (Literal.Null <$ source)
|
||||
|
||||
boolean :: Assignment Term
|
||||
boolean = makeTerm <$> token Grammar.True <*> pure Literal.true
|
||||
<|> makeTerm <$> token Grammar.False <*> pure Literal.false
|
||||
|
||||
|
||||
-- Primitive Types
|
||||
|
||||
@ -348,7 +357,7 @@ pointerType :: Assignment Term
|
||||
pointerType = makeTerm <$> symbol PointerType <*> children (Type.Pointer <$> expression)
|
||||
|
||||
qualifiedType :: Assignment Term
|
||||
qualifiedType = makeTerm <$> symbol QualifiedType <*> children (Expression.MemberAccess <$> expression <*> (identifier' <|> typeIdentifier'))
|
||||
qualifiedType = makeTerm <$> symbol QualifiedType <*> children (Expression.MemberAccess <$> expression <*> typeIdentifier')
|
||||
|
||||
sliceType :: Assignment Term
|
||||
sliceType = makeTerm <$> symbol SliceType <*> children (Type.Slice <$> expression)
|
||||
@ -458,20 +467,23 @@ indexExpression :: Assignment Term
|
||||
indexExpression = makeTerm <$> symbol IndexExpression <*> children (Expression.Subscript <$> expression <*> manyTerm expression)
|
||||
|
||||
methodDeclaration :: Assignment Term
|
||||
methodDeclaration = makeTerm <$> symbol MethodDeclaration <*> children (mkTypedMethodDeclaration <$> receiver <*> term fieldIdentifier <*> params <*> returnParameters <*> (term block <|> emptyTerm))
|
||||
methodDeclaration = makeTerm <$> symbol MethodDeclaration <*> children (mkTypedMethodDeclaration <$> receiver <*> pure publicAccessControl <*> term fieldIdentifier <*> params <*> returnParameters <*> (term block <|> emptyTerm))
|
||||
where
|
||||
params = symbol ParameterList *> children (manyTerm expression)
|
||||
receiver = symbol ParameterList *> children expressions
|
||||
mkTypedMethodDeclaration receiver' name' parameters' type'' body' = Declaration.Method type'' receiver' name' parameters' body'
|
||||
mkTypedMethodDeclaration receiver' accessControl name' parameters' type'' body' = Declaration.Method type'' receiver' name' parameters' body' accessControl
|
||||
returnParameters = (symbol ParameterList *> children (manyTerm expression))
|
||||
<|> pure <$> expression
|
||||
<|> pure []
|
||||
|
||||
methodSpec :: Assignment Term
|
||||
methodSpec = makeTerm <$> symbol MethodSpec <*> children (mkMethodSpec <$> expression <*> params <*> (expression <|> emptyTerm))
|
||||
methodSpec = makeTerm <$> symbol MethodSpec <*> children (mkMethodSpec publicAccessControl <$> expression <*> params <*> (expression <|> emptyTerm))
|
||||
where
|
||||
params = symbol ParameterList *> children (manyTerm expression)
|
||||
mkMethodSpec name' params optionalTypeLiteral = Declaration.MethodSignature [optionalTypeLiteral] name' params
|
||||
mkMethodSpec accessControl name' params optionalTypeLiteral = Declaration.MethodSignature [optionalTypeLiteral] name' params accessControl
|
||||
|
||||
publicAccessControl :: ScopeGraph.AccessControl
|
||||
publicAccessControl = ScopeGraph.Public
|
||||
|
||||
methodSpecList :: Assignment Term
|
||||
methodSpecList = symbol MethodSpecList *> children expressions
|
||||
@ -489,7 +501,7 @@ parenthesizedExpression :: Assignment Term
|
||||
parenthesizedExpression = symbol ParenthesizedExpression *> children expressions
|
||||
|
||||
selectorExpression :: Assignment Term
|
||||
selectorExpression = makeWithContext <$> symbol SelectorExpression <*> children ((,,) <$> expression <*> optional comment <*> (identifier' <|> fieldIdentifier'))
|
||||
selectorExpression = makeWithContext <$> symbol SelectorExpression <*> children ((,,) <$> expression <*> optional comment <*> fieldIdentifier')
|
||||
where makeWithContext loc (lhs, comment, rhs) = maybe (makeTerm loc (Expression.MemberAccess lhs rhs)) (\c -> makeTerm loc (Syntax.Context (c :| []) (makeTerm loc (Expression.MemberAccess lhs rhs)))) comment
|
||||
|
||||
sliceExpression :: Assignment Term
|
||||
|
@ -31,7 +31,7 @@ resolveGoImport :: ( Member (Modules address value) sig
|
||||
)
|
||||
=> ImportPath
|
||||
-> Evaluator term address value m [ModulePath]
|
||||
resolveGoImport (ImportPath path Unknown) = throwResolutionError $ GoImportError path
|
||||
resolveGoImport (ImportPath path Data.ImportPath.Unknown) = throwResolutionError $ GoImportError path
|
||||
resolveGoImport (ImportPath path Relative) = do
|
||||
ModuleInfo{..} <- currentModule
|
||||
paths <- listModulesInDir (joinPaths (takeDirectory modulePath) path)
|
||||
@ -79,8 +79,8 @@ instance Evaluatable QualifiedImport where
|
||||
alias <- maybeM (throwNoNameError aliasTerm) (declaredName aliasTerm)
|
||||
span <- ask @Span
|
||||
scopeAddress <- newScope mempty
|
||||
declare (Declaration alias) Default span (Just scopeAddress)
|
||||
aliasSlot <- lookupDeclaration (Declaration alias)
|
||||
declare (Declaration alias) Default Public span (Just scopeAddress)
|
||||
aliasSlot <- lookupSlot (Declaration alias)
|
||||
|
||||
withScope scopeAddress $ do
|
||||
let
|
||||
|
@ -13,6 +13,7 @@ import Prologue hiding (for, try, This, catches, finally)
|
||||
import Assigning.Assignment hiding (Assignment, Error, try)
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import Data.Abstract.Name
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph (AccessControl(..))
|
||||
import Data.Functor (($>))
|
||||
import Data.List.NonEmpty (some1)
|
||||
import Data.Syntax
|
||||
@ -334,12 +335,13 @@ fieldDeclaration :: Assignment Term
|
||||
fieldDeclaration = makeTerm <$> symbol FieldDeclaration <*> children ((,) <$> manyTerm modifier <*> type' <**> variableDeclaratorList)
|
||||
|
||||
method :: Assignment Term
|
||||
method = makeTerm <$> symbol MethodDeclaration <*> children (makeMethod <$> many modifier <*> emptyTerm <*> methodHeader <*> methodBody)
|
||||
method = makeTerm <$> symbol MethodDeclaration <*> children (makeMethod <$> many modifier <*> emptyTerm <*> pure accessibility <*> methodHeader <*> methodBody)
|
||||
where
|
||||
methodBody = symbol MethodBody *> children (term expression <|> emptyTerm)
|
||||
methodDeclarator = symbol MethodDeclarator *> children ( (,) <$> identifier <*> formalParameters)
|
||||
accessibility = ScopeGraph.Public
|
||||
methodHeader = symbol MethodHeader *> children ((,,,,) <$> (typeParameters <|> pure []) <*> manyTerm annotation <*> type' <*> methodDeclarator <*> (throws <|> pure []))
|
||||
makeMethod modifiers receiver (typeParams, annotations, returnType, (name, params), throws) = Declaration.Method (returnType : modifiers <> typeParams <> annotations <> throws) receiver name params
|
||||
makeMethod modifiers receiver accessibility (typeParams, annotations, returnType, (name, params), throws) methodBody = Declaration.Method (returnType : modifiers <> typeParams <> annotations <> throws) receiver name params methodBody accessibility
|
||||
|
||||
generic :: Assignment Term
|
||||
generic = makeTerm <$> symbol Grammar.GenericType <*> children(Java.Syntax.GenericType <$> term type' <*> manyTerm type')
|
||||
|
@ -11,6 +11,7 @@ module Language.MiniRuby.Assignment
|
||||
import Assigning.Assignment hiding (Assignment, Error)
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import Data.Abstract.Name (name)
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph (AccessControl(..))
|
||||
import Data.List (elem)
|
||||
import Data.Sum
|
||||
import Data.Syntax
|
||||
@ -103,9 +104,10 @@ identifier =
|
||||
else pure $ makeTerm loc (Ruby.Syntax.Send Nothing (Just identTerm) [] Nothing)
|
||||
|
||||
method :: Assignment Term
|
||||
method = makeTerm <$> symbol Method <*> (withNewScope . children) (Declaration.Method [] <$> emptyTerm <*> methodSelector <*> params <*> expressions')
|
||||
method = makeTerm <$> symbol Method <*> (withNewScope . children) (Declaration.Method [] <$> emptyTerm <*> methodSelector <*> params <*> expressions' <*> pure accessibility)
|
||||
where params = symbol MethodParameters *> children (many parameter) <|> pure []
|
||||
expressions' = makeTerm <$> location <*> many expression
|
||||
accessibility = ScopeGraph.Public
|
||||
|
||||
methodSelector :: Assignment Term
|
||||
methodSelector = makeTerm <$> symbols <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
@ -12,6 +12,7 @@ import Prologue
|
||||
import Assigning.Assignment hiding (Assignment, Error)
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import qualified Data.Abstract.Name as Name
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph (AccessControl(..))
|
||||
import qualified Data.Diff as Diff
|
||||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
import Data.Syntax
|
||||
@ -159,7 +160,8 @@ type Syntax = '[
|
||||
, Syntax.UseClause
|
||||
, Syntax.VariableName
|
||||
, Type.Annotation
|
||||
, [] ]
|
||||
, []
|
||||
]
|
||||
|
||||
type Term = Term.Term (Sum Syntax) Location
|
||||
type Assignment = Assignment.Assignment [] Grammar
|
||||
@ -443,12 +445,17 @@ classMemberDeclaration = choice [
|
||||
traitUseClause
|
||||
]
|
||||
|
||||
publicAccessControl :: ScopeGraph.AccessControl
|
||||
publicAccessControl = ScopeGraph.Public
|
||||
|
||||
-- TODO: Update to check for AccessControl.
|
||||
methodDeclaration :: Assignment Term
|
||||
methodDeclaration = (makeTerm <$> symbol MethodDeclaration <*> children (makeMethod1 <$> manyTerm methodModifier <*> emptyTerm <*> functionDefinitionParts)) <|> makeTerm <$> symbol MethodDeclaration <*> children (makeMethod2 <$> someTerm methodModifier <*> emptyTerm <*> term name <*> parameters <*> term (returnType <|> emptyTerm) <*> emptyTerm)
|
||||
methodDeclaration = (makeTerm <$> symbol MethodDeclaration <*> children (makeMethod1 publicAccessControl <$> manyTerm methodModifier <*> emptyTerm <*> functionDefinitionParts))
|
||||
<|> makeTerm <$> symbol MethodDeclaration <*> children (makeMethod2 publicAccessControl <$> someTerm methodModifier <*> emptyTerm <*> term name <*> parameters <*> term (returnType <|> emptyTerm) <*> emptyTerm)
|
||||
where
|
||||
functionDefinitionParts = symbol FunctionDefinition *> children ((,,,) <$> term name <*> parameters <*> term (returnType <|> emptyTerm) <*> (term compoundStatement <|> emptyTerm))
|
||||
makeMethod1 modifiers receiver (name, params, returnType, compoundStatement) = Declaration.Method (modifiers <> [returnType]) receiver name params compoundStatement
|
||||
makeMethod2 modifiers receiver name params returnType compoundStatement = Declaration.Method (modifiers <> [returnType]) receiver name params compoundStatement
|
||||
makeMethod1 accessControl modifiers receiver (name, params, returnType, compoundStatement) = Declaration.Method (modifiers <> [returnType]) receiver name params compoundStatement accessControl
|
||||
makeMethod2 accessControl modifiers receiver name params returnType compoundStatement = Declaration.Method (modifiers <> [returnType]) receiver name params compoundStatement accessControl
|
||||
|
||||
classBaseClause :: Assignment Term
|
||||
classBaseClause = makeTerm <$> symbol ClassBaseClause <*> children (Syntax.ClassBaseClause <$> term qualifiedName)
|
||||
@ -457,10 +464,11 @@ classInterfaceClause :: Assignment Term
|
||||
classInterfaceClause = makeTerm <$> symbol ClassInterfaceClause <*> children (Syntax.ClassInterfaceClause <$> someTerm qualifiedName)
|
||||
|
||||
classConstDeclaration :: Assignment Term
|
||||
classConstDeclaration = makeTerm <$> symbol ClassConstDeclaration <*> children (Syntax.ClassConstDeclaration <$> (term visibilityModifier <|> emptyTerm) <*> manyTerm constElement)
|
||||
classConstDeclaration = makeTerm <$> symbol ClassConstDeclaration <*> children (Syntax.ClassConstDeclaration <$> (term accessControlModifier <|> emptyTerm) <*> manyTerm constElement)
|
||||
|
||||
visibilityModifier :: Assignment Term
|
||||
visibilityModifier = makeTerm <$> symbol VisibilityModifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
-- TODO: Update to ScopeGraph.AccessControl
|
||||
accessControlModifier :: Assignment Term
|
||||
accessControlModifier = makeTerm <$> symbol VisibilityModifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
|
||||
constElement :: Assignment Term
|
||||
constElement = makeTerm <$> symbol ConstElement <*> children (Statement.Assignment [] <$> term name <*> term expression)
|
||||
@ -672,7 +680,7 @@ propertyDeclaration :: Assignment Term
|
||||
propertyDeclaration = makeTerm <$> symbol PropertyDeclaration <*> children (Syntax.PropertyDeclaration <$> term propertyModifier <*> someTerm propertyElement)
|
||||
|
||||
propertyModifier :: Assignment Term
|
||||
propertyModifier = (makeTerm <$> symbol PropertyModifier <*> children (Syntax.PropertyModifier <$> (term visibilityModifier <|> emptyTerm) <*> (term staticModifier <|> emptyTerm))) <|> term (makeTerm <$> symbol PropertyModifier <*> (Syntax.Identifier . Name.name <$> source))
|
||||
propertyModifier = (makeTerm <$> symbol PropertyModifier <*> children (Syntax.PropertyModifier <$> (term accessControlModifier <|> emptyTerm) <*> (term staticModifier <|> emptyTerm))) <|> term (makeTerm <$> symbol PropertyModifier <*> (Syntax.Identifier . Name.name <$> source))
|
||||
|
||||
propertyElement :: Assignment Term
|
||||
propertyElement = makeTerm <$> symbol PropertyElement <*> children (Statement.Assignment [] <$> term variableName <*> term propertyInitializer) <|> (symbol PropertyElement *> children (term variableName))
|
||||
@ -686,7 +694,7 @@ destructorDeclaration = makeTerm <$> symbol DestructorDeclaration <*> children (
|
||||
|
||||
methodModifier :: Assignment Term
|
||||
methodModifier = choice [
|
||||
visibilityModifier,
|
||||
accessControlModifier,
|
||||
classModifier,
|
||||
staticModifier
|
||||
]
|
||||
@ -710,7 +718,7 @@ traitSelectInsteadOfClause :: Assignment Term
|
||||
traitSelectInsteadOfClause = makeTerm <$> symbol TraitSelectInsteadOfClause <*> children (Syntax.InsteadOf <$> term (classConstantAccessExpression <|> name) <*> term name)
|
||||
|
||||
traitAliasAsClause :: Assignment Term
|
||||
traitAliasAsClause = makeTerm <$> symbol TraitAliasAsClause <*> children (Syntax.AliasAs <$> term (classConstantAccessExpression <|> name) <*> (term visibilityModifier <|> emptyTerm) <*> (term name <|> emptyTerm))
|
||||
traitAliasAsClause = makeTerm <$> symbol TraitAliasAsClause <*> children (Syntax.AliasAs <$> term (classConstantAccessExpression <|> name) <*> (term accessControlModifier <|> emptyTerm) <*> (term name <|> emptyTerm))
|
||||
|
||||
namespaceDefinition :: Assignment Term
|
||||
namespaceDefinition = makeTerm <$> symbol NamespaceDefinition <*> children (Syntax.Namespace <$> (toList <$> namespaceName' <|> pure []) <*> (term compoundStatement <|> emptyTerm))
|
||||
|
@ -185,8 +185,8 @@ instance Evaluatable QualifiedName where
|
||||
frameAddress <- newFrame childScope (Map.singleton Lexical (Map.singleton currentScopeAddress currentFrameAddress))
|
||||
withScopeAndFrame frameAddress $ do
|
||||
reference (Reference propName) (Declaration propName)
|
||||
address <- lookupDeclaration (Declaration propName)
|
||||
deref address
|
||||
slot <- lookupSlot (Declaration propName)
|
||||
deref slot
|
||||
Nothing ->
|
||||
-- TODO: Throw an ReferenceError because we can't find the associated child scope for `obj`.
|
||||
unit
|
||||
|
@ -142,9 +142,9 @@ instance Evaluatable Import where
|
||||
aliasFrame <- newFrame importScope (Map.singleton ScopeGraph.Import scopeMap)
|
||||
|
||||
-- Add declaration of the alias name to the current scope (within our current module).
|
||||
declare (Declaration aliasName) Default span (Just importScope)
|
||||
declare (Declaration aliasName) Default Public span (Just importScope)
|
||||
-- Retrieve the frame slot for the new declaration.
|
||||
aliasSlot <- lookupDeclaration (Declaration aliasName)
|
||||
aliasSlot <- lookupSlot (Declaration aliasName)
|
||||
assign aliasSlot =<< object aliasFrame
|
||||
|
||||
unit
|
||||
@ -210,8 +210,8 @@ instance Evaluatable QualifiedImport where
|
||||
go ((name, modulePath) : namesAndPaths) = do
|
||||
span <- ask @Span
|
||||
scopeAddress <- newScope mempty
|
||||
declare (Declaration name) Default span (Just scopeAddress)
|
||||
aliasSlot <- lookupDeclaration (Declaration name)
|
||||
declare (Declaration name) Default Public span (Just scopeAddress)
|
||||
aliasSlot <- lookupSlot (Declaration name)
|
||||
-- a.b.c
|
||||
withScope scopeAddress $
|
||||
mkScopeMap modulePath (\scopeMap -> do
|
||||
@ -243,10 +243,10 @@ instance Evaluatable QualifiedAliasedImport where
|
||||
span <- ask @Span
|
||||
scopeAddress <- newScope mempty
|
||||
alias <- maybeM (throwNoNameError aliasTerm) (declaredName aliasTerm)
|
||||
declare (Declaration alias) Default span (Just scopeAddress)
|
||||
declare (Declaration alias) Default Public span (Just scopeAddress)
|
||||
objFrame <- newFrame scopeAddress mempty
|
||||
val <- object objFrame
|
||||
aliasSlot <- lookupDeclaration (Declaration alias)
|
||||
aliasSlot <- lookupSlot (Declaration alias)
|
||||
assign aliasSlot val
|
||||
|
||||
withScopeAndFrame objFrame .
|
||||
|
@ -12,6 +12,7 @@ import Prologue hiding (for, unless)
|
||||
import Assigning.Assignment hiding (Assignment, Error)
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import Data.Abstract.Name (name)
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph (AccessControl(..))
|
||||
import Data.List (elem)
|
||||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
import Data.Syntax
|
||||
@ -331,13 +332,16 @@ parameter = postContextualize comment (term uncontextualizedParameter)
|
||||
keywordParameter = symbol KeywordParameter *> children (lhsIdent <* optional expression)
|
||||
optionalParameter = symbol OptionalParameter *> children (lhsIdent <* expression)
|
||||
|
||||
publicAccessControl :: ScopeGraph.AccessControl
|
||||
publicAccessControl = ScopeGraph.Public
|
||||
|
||||
method :: Assignment Term
|
||||
method = makeTerm <$> symbol Method <*> (withNewScope . children) (Declaration.Method [] <$> emptyTerm <*> methodSelector <*> params <*> expressions')
|
||||
method = makeTerm <$> symbol Method <*> (withNewScope . children) (Declaration.Method [] <$> emptyTerm <*> methodSelector <*> params <*> expressions' <*> pure publicAccessControl)
|
||||
where params = symbol MethodParameters *> children (many parameter) <|> pure []
|
||||
expressions' = makeTerm <$> location <*> many expression
|
||||
|
||||
singletonMethod :: Assignment Term
|
||||
singletonMethod = makeTerm <$> symbol SingletonMethod <*> (withNewScope . children) (Declaration.Method [] <$> expression <*> methodSelector <*> params <*> expressions)
|
||||
singletonMethod = makeTerm <$> symbol SingletonMethod <*> (withNewScope . children) (Declaration.Method [] <$> expression <*> methodSelector <*> params <*> expressions <*> pure publicAccessControl)
|
||||
where params = symbol MethodParameters *> children (many parameter) <|> pure []
|
||||
|
||||
lambda :: Assignment Term
|
||||
|
@ -73,13 +73,13 @@ instance Evaluatable Send where
|
||||
Nothing ->
|
||||
pure (Name.name "call")
|
||||
|
||||
let self = deref =<< lookupDeclaration (Declaration __self)
|
||||
let self = deref =<< lookupSlot (Declaration __self)
|
||||
lhsValue <- maybe self eval sendReceiver
|
||||
lhsFrame <- Abstract.scopedEnvironment lhsValue
|
||||
|
||||
let callFunction = do
|
||||
reference (Reference sel) (Declaration sel)
|
||||
func <- deref =<< lookupDeclaration (Declaration sel)
|
||||
func <- deref =<< lookupSlot (Declaration sel)
|
||||
args <- traverse eval sendArgs
|
||||
boundFunc <- bindThis lhsValue func
|
||||
call boundFunc args -- TODO pass through sendBlock
|
||||
@ -200,7 +200,7 @@ instance Evaluatable Class where
|
||||
superScopes <- for classSuperclasses $ \superclass -> do
|
||||
name <- maybeM (throwNoNameError superclass) (declaredName superclass)
|
||||
scope <- associatedScope (Declaration name)
|
||||
slot <- lookupDeclaration (Declaration name)
|
||||
slot <- lookupSlot (Declaration name)
|
||||
superclassFrame <- scopedEnvironment =<< deref slot
|
||||
pure $ case (scope, superclassFrame) of
|
||||
(Just scope, Just frame) -> Just (scope, frame)
|
||||
@ -210,7 +210,7 @@ instance Evaluatable Class where
|
||||
current = (Lexical, ) <$> pure (pure currentScope')
|
||||
edges = Map.fromList (superclassEdges <> current)
|
||||
classScope <- newScope edges
|
||||
declare (Declaration name) Default span (Just classScope)
|
||||
declare (Declaration name) Default Public span (Just classScope)
|
||||
|
||||
let frameEdges = Map.singleton Superclass (Map.fromList (catMaybes superScopes))
|
||||
childFrame <- newFrame classScope frameEdges
|
||||
@ -218,7 +218,7 @@ instance Evaluatable Class where
|
||||
withScopeAndFrame childFrame $ do
|
||||
void $ eval classBody
|
||||
|
||||
classSlot <- lookupDeclaration (Declaration name)
|
||||
classSlot <- lookupSlot (Declaration name)
|
||||
assign classSlot =<< klass (Declaration name) childFrame
|
||||
|
||||
unit
|
||||
@ -260,7 +260,7 @@ instance Evaluatable Module where
|
||||
Nothing -> do
|
||||
let edges = Map.singleton Lexical [ currentScope' ]
|
||||
classScope <- newScope edges
|
||||
declare (Declaration name) Default span (Just classScope)
|
||||
declare (Declaration name) Default Public span (Just classScope)
|
||||
|
||||
currentFrame' <- currentFrame
|
||||
let frameEdges = Map.singleton Lexical (Map.singleton currentScope' currentFrame')
|
||||
@ -268,7 +268,7 @@ instance Evaluatable Module where
|
||||
|
||||
withScopeAndFrame childFrame (void moduleBody)
|
||||
|
||||
moduleSlot <- lookupDeclaration (Declaration name)
|
||||
moduleSlot <- lookupSlot (Declaration name)
|
||||
assign moduleSlot =<< klass (Declaration name) childFrame
|
||||
|
||||
unit
|
||||
@ -326,7 +326,7 @@ instance Evaluatable Assignment where
|
||||
lhsName <- maybeM (throwNoNameError assignmentTarget) (declaredName assignmentTarget)
|
||||
maybeSlot <- maybeLookupDeclaration (Declaration lhsName)
|
||||
assignmentSpan <- ask @Span
|
||||
maybe (declare (Declaration lhsName) Default assignmentSpan Nothing) (const (pure ())) maybeSlot
|
||||
maybe (declare (Declaration lhsName) Default Public assignmentSpan Nothing) (const (pure ())) maybeSlot
|
||||
|
||||
lhs <- ref assignmentTarget
|
||||
rhs <- eval assignmentValue
|
||||
|
@ -9,6 +9,7 @@ module Language.TypeScript.Assignment
|
||||
|
||||
import Assigning.Assignment hiding (Assignment, Error)
|
||||
import Data.Abstract.Name (Name, name)
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph (AccessControl(..))
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import Data.Sum
|
||||
import Data.Syntax
|
||||
@ -362,8 +363,8 @@ abstractClass :: Assignment Term
|
||||
abstractClass = makeTerm <$> symbol Grammar.AbstractClass <*> children (TypeScript.Syntax.AbstractClass <$> term typeIdentifier <*> (term typeParameters <|> emptyTerm) <*> (classHeritage' <|> pure []) <*> classBodyStatements)
|
||||
|
||||
abstractMethodSignature :: Assignment Term
|
||||
abstractMethodSignature = makeSignature <$> symbol Grammar.AbstractMethodSignature <*> children ((,,) <$> (term accessibilityModifier' <|> emptyTerm) <*> term propertyName <*> callSignatureParts)
|
||||
where makeSignature loc (modifier, propertyName, (typeParams, params, annotation)) = makeTerm loc (TypeScript.Syntax.AbstractMethodSignature [modifier, typeParams, annotation] propertyName params)
|
||||
abstractMethodSignature = makeSignature <$> symbol Grammar.AbstractMethodSignature <*> children ((,,) <$> accessibilityModifier' <*> term propertyName <*> callSignatureParts)
|
||||
where makeSignature loc (modifier, propertyName, (typeParams, params, annotation)) = makeTerm loc (TypeScript.Syntax.AbstractMethodSignature [typeParams, annotation] propertyName params modifier)
|
||||
|
||||
classHeritage' :: Assignment [Term]
|
||||
classHeritage' = symbol Grammar.ClassHeritage *> children ((mappend `on` toList) <$> optional (term extendsClause) <*> optional (term implementsClause'))
|
||||
@ -480,8 +481,13 @@ parameter = requiredParameter
|
||||
<|> restParameter
|
||||
<|> optionalParameter
|
||||
|
||||
accessibilityModifier' :: Assignment Term
|
||||
accessibilityModifier' = makeTerm <$> symbol AccessibilityModifier <*> children (Syntax.Identifier . name <$> source)
|
||||
accessibilityModifier' :: Assignment ScopeGraph.AccessControl
|
||||
accessibilityModifier' = (symbol AccessibilityModifier >> children (public <|> protected <|> private)) <|> default'
|
||||
where public = symbol AnonPublic >> pure ScopeGraph.Public
|
||||
protected = symbol AnonProtected >> pure ScopeGraph.Protected
|
||||
private = symbol AnonPrivate >> pure ScopeGraph.Private
|
||||
default' = pure ScopeGraph.Public
|
||||
|
||||
|
||||
destructuringPattern :: Assignment Term
|
||||
destructuringPattern = object <|> array
|
||||
@ -495,9 +501,9 @@ readonly' = makeTerm <$> symbol Readonly <*> (Type.Readonly <$ rawSource)
|
||||
methodDefinition :: Assignment Term
|
||||
methodDefinition = makeMethod <$>
|
||||
symbol MethodDefinition
|
||||
<*> children ((,,,,,) <$> (term accessibilityModifier' <|> emptyTerm) <*> (term readonly' <|> emptyTerm) <*> emptyTerm <*> term propertyName <*> callSignatureParts <*> term statementBlock)
|
||||
<*> children ((,,,,,) <$> accessibilityModifier' <*> (term readonly' <|> emptyTerm) <*> emptyTerm <*> term propertyName <*> callSignatureParts <*> term statementBlock)
|
||||
where
|
||||
makeMethod loc (modifier, readonly, receiver, propertyName', (typeParameters', params, ty'), statements) = makeTerm loc (Declaration.Method [modifier, readonly, typeParameters', ty'] receiver propertyName' params statements)
|
||||
makeMethod loc (modifier, readonly, receiver, propertyName', (typeParameters', params, ty'), statements) = makeTerm loc (Declaration.Method [readonly, typeParameters', ty'] receiver propertyName' params statements modifier)
|
||||
|
||||
callSignatureParts :: Assignment (Term, [Term], Term)
|
||||
callSignatureParts = contextualize' <$> Assignment.manyThrough comment (postContextualize' <$> callSignature' <*> many comment)
|
||||
@ -520,8 +526,8 @@ indexSignature :: Assignment Term
|
||||
indexSignature = makeTerm <$> symbol Grammar.IndexSignature <*> children (TypeScript.Syntax.IndexSignature <$> term identifier <*> predefinedTy <*> term typeAnnotation')
|
||||
|
||||
methodSignature :: Assignment Term
|
||||
methodSignature = makeMethodSignature <$> symbol Grammar.MethodSignature <*> children ((,,,) <$> (term accessibilityModifier' <|> emptyTerm) <*> (term readonly' <|> emptyTerm) <*> term propertyName <*> callSignatureParts)
|
||||
where makeMethodSignature loc (modifier, readonly, propertyName, (typeParams, params, annotation)) = makeTerm loc (Declaration.MethodSignature [modifier, readonly, typeParams, annotation] propertyName params)
|
||||
methodSignature = makeMethodSignature <$> symbol Grammar.MethodSignature <*> children ((,,,) <$> accessibilityModifier' <*> (term readonly' <|> emptyTerm) <*> term propertyName <*> callSignatureParts)
|
||||
where makeMethodSignature loc (accessControl, readonly, propertyName, (typeParams, params, annotation)) = makeTerm loc (Declaration.MethodSignature [readonly, typeParams, annotation] propertyName params accessControl)
|
||||
|
||||
formalParameters :: Assignment [Term]
|
||||
formalParameters = symbol FormalParameters *> children (contextualize' <$> Assignment.manyThrough comment (postContextualize' <$> (concat <$> many ((\as b -> as <> [b]) <$> manyTerm decorator <*> term parameter)) <*> many comment))
|
||||
@ -665,8 +671,8 @@ classBodyStatements = makeTerm'' <$> symbol ClassBody <*> children (contextualiz
|
||||
Nothing -> formalParams
|
||||
|
||||
publicFieldDefinition :: Assignment Term
|
||||
publicFieldDefinition = makeField <$> symbol Grammar.PublicFieldDefinition <*> children ((,,,,) <$> (term accessibilityModifier' <|> emptyTerm) <*> (term readonly' <|> emptyTerm) <*> term propertyName <*> (term typeAnnotation' <|> emptyTerm) <*> (term expression <|> emptyTerm))
|
||||
where makeField loc (modifier, readonly, propertyName, annotation, expression) = makeTerm loc (Declaration.PublicFieldDefinition [modifier, readonly, annotation] propertyName expression)
|
||||
publicFieldDefinition = makeField <$> symbol Grammar.PublicFieldDefinition <*> children ((,,,,) <$> accessibilityModifier' <*> (term readonly' <|> emptyTerm) <*> term propertyName <*> (term typeAnnotation' <|> emptyTerm) <*> (term expression <|> emptyTerm))
|
||||
where makeField loc (accessControl, readonly, propertyName, annotation, expression) = makeTerm loc (Declaration.PublicFieldDefinition [readonly, annotation] propertyName expression accessControl)
|
||||
|
||||
|
||||
statement :: Assignment Term
|
||||
@ -821,8 +827,8 @@ exportStatement = makeTerm <$> symbol Grammar.ExportStatement <*> children (flip
|
||||
fromClause = symbol Grammar.String *> (TypeScript.Resolution.importPath <$> source)
|
||||
|
||||
propertySignature :: Assignment Term
|
||||
propertySignature = makePropertySignature <$> symbol Grammar.PropertySignature <*> children ((,,,) <$> (term accessibilityModifier' <|> emptyTerm) <*> (term readonly' <|> emptyTerm) <*> term propertyName <*> (term typeAnnotation' <|> emptyTerm))
|
||||
where makePropertySignature loc (modifier, readonly, propertyName, annotation) = makeTerm loc (TypeScript.Syntax.PropertySignature [modifier, readonly, annotation] propertyName)
|
||||
propertySignature = makePropertySignature <$> symbol Grammar.PropertySignature <*> children ((,,,) <$> accessibilityModifier' <*> (term readonly' <|> emptyTerm) <*> term propertyName <*> (term typeAnnotation' <|> emptyTerm))
|
||||
where makePropertySignature loc (modifier, readonly, propertyName, annotation) = makeTerm loc (TypeScript.Syntax.PropertySignature [readonly, annotation] propertyName modifier)
|
||||
|
||||
propertyName :: Assignment Term
|
||||
propertyName = (makeTerm <$> symbol PropertyIdentifier <*> (Syntax.Identifier . name <$> source)) <|> term string <|> term number <|> term computedPropertyName
|
||||
@ -840,21 +846,21 @@ requiredParameter :: Assignment Term
|
||||
requiredParameter = makeRequiredParameter
|
||||
<$> symbol Grammar.RequiredParameter
|
||||
<*> children ( (,,,,)
|
||||
<$> (term accessibilityModifier' <|> emptyTerm)
|
||||
<$> accessibilityModifier'
|
||||
<*> (term readonly' <|> emptyTerm)
|
||||
<*> term (identifier <|> destructuringPattern <|> this)
|
||||
<*> (term typeAnnotation' <|> emptyTerm)
|
||||
<*> (term expression <|> emptyTerm))
|
||||
where
|
||||
makeRequiredParameter loc (modifier, readonly, identifier, annotation, initializer) = makeTerm loc (TypeScript.Syntax.RequiredParameter [modifier, readonly, annotation] identifier initializer)
|
||||
makeRequiredParameter loc (modifier, readonly, identifier, annotation, initializer) = makeTerm loc (TypeScript.Syntax.RequiredParameter [readonly, annotation] identifier initializer modifier)
|
||||
|
||||
restParameter :: Assignment Term
|
||||
restParameter = makeRestParameter <$> symbol Grammar.RestParameter <*> children ((,) <$> term identifier <*> (term typeAnnotation' <|> emptyTerm))
|
||||
where makeRestParameter loc (identifier, annotation) = makeTerm loc (TypeScript.Syntax.RestParameter [annotation] identifier)
|
||||
|
||||
optionalParameter :: Assignment Term
|
||||
optionalParameter = makeOptionalParam <$> symbol Grammar.OptionalParameter <*> children ((,,,,) <$> (term accessibilityModifier' <|> emptyTerm) <*> (term readonly' <|> emptyTerm) <*> (term identifier <|> destructuringPattern) <*> (term typeAnnotation' <|> emptyTerm) <*> (term expression <|> emptyTerm))
|
||||
where makeOptionalParam loc (modifier, readonly, subject, annotation, initializer) = makeTerm loc (TypeScript.Syntax.OptionalParameter [modifier, readonly, annotation] (makeTerm loc (Statement.Assignment [] subject initializer)))
|
||||
optionalParameter = makeOptionalParam <$> symbol Grammar.OptionalParameter <*> children ((,,,,) <$> accessibilityModifier' <*> (term readonly' <|> emptyTerm) <*> (term identifier <|> destructuringPattern) <*> (term typeAnnotation' <|> emptyTerm) <*> (term expression <|> emptyTerm))
|
||||
where makeOptionalParam loc (modifier, readonly, subject, annotation, initializer) = makeTerm loc (TypeScript.Syntax.OptionalParameter [readonly, annotation] (makeTerm loc (Statement.Assignment [] subject initializer)) modifier)
|
||||
|
||||
internalModule :: Assignment Term
|
||||
internalModule = makeTerm <$> symbol Grammar.InternalModule <*> children (TypeScript.Syntax.InternalModule <$> term (string <|> identifier <|> nestedIdentifier) <*> statements)
|
||||
|
@ -59,8 +59,8 @@ instance Evaluatable QualifiedAliasedImport where
|
||||
aliasFrame <- newFrame importScope (Map.singleton ScopeGraph.Import scopeMap)
|
||||
|
||||
alias <- maybeM (throwNoNameError aliasTerm) (declaredName aliasTerm)
|
||||
declare (Declaration alias) Default span (Just importScope)
|
||||
aliasSlot <- lookupDeclaration (Declaration alias)
|
||||
declare (Declaration alias) Default Public span (Just importScope)
|
||||
aliasSlot <- lookupSlot (Declaration alias)
|
||||
assign aliasSlot =<< object aliasFrame
|
||||
|
||||
unit
|
||||
@ -136,8 +136,8 @@ instance Evaluatable DefaultExport where
|
||||
withScopeAndFrame exportFrame $ do
|
||||
valueRef <- eval term
|
||||
let declaration = Declaration $ Name.name "__default"
|
||||
declare declaration Default exportSpan Nothing
|
||||
defaultSlot <- lookupDeclaration declaration
|
||||
declare declaration Default Public exportSpan Nothing
|
||||
defaultSlot <- lookupSlot declaration
|
||||
assign defaultSlot valueRef
|
||||
|
||||
insertExportEdge exportScope
|
||||
|
@ -8,6 +8,7 @@ import qualified Data.Text as T
|
||||
import Proto3.Suite
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.ScopeGraph (AccessControl(..))
|
||||
import Data.JSON.Fields
|
||||
import Diffing.Algorithm
|
||||
import qualified Data.Map.Strict as Map
|
||||
@ -61,13 +62,13 @@ newtype ImplementsClause a = ImplementsClause { implementsClauseTypes :: [a] }
|
||||
|
||||
instance Evaluatable ImplementsClause
|
||||
|
||||
data OptionalParameter a = OptionalParameter { optionalParameterContext :: ![a], optionalParameterSubject :: !a }
|
||||
data OptionalParameter a = OptionalParameter { optionalParameterContext :: ![a], optionalParameterSubject :: !a, optionalParameterAccessControl :: AccessControl }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically OptionalParameter
|
||||
|
||||
instance Evaluatable OptionalParameter
|
||||
|
||||
data RequiredParameter a = RequiredParameter { requiredParameterContext :: [a], requiredParameterSubject :: a, requiredParameterValue :: a }
|
||||
data RequiredParameter a = RequiredParameter { requiredParameterContext :: [a], requiredParameterSubject :: a, requiredParameterValue :: a, requiredParameterAccessControl :: AccessControl }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically RequiredParameter
|
||||
|
||||
@ -78,7 +79,7 @@ instance Evaluatable RequiredParameter where
|
||||
eval eval ref RequiredParameter{..} = do
|
||||
name <- maybeM (throwNoNameError requiredParameterSubject) (declaredName requiredParameterSubject)
|
||||
span <- ask @Span
|
||||
declare (Declaration name) Default span Nothing
|
||||
declare (Declaration name) Default Public span Nothing
|
||||
|
||||
lhs <- ref requiredParameterSubject
|
||||
rhs <- eval requiredParameterValue
|
||||
|
@ -28,10 +28,10 @@ instance Evaluatable JavaScriptRequire where
|
||||
Just alias -> do
|
||||
span <- ask @Span
|
||||
importScope <- newScope (Map.singleton ScopeGraph.Import [ moduleScope ])
|
||||
declare (Declaration alias) Default span (Just importScope)
|
||||
declare (Declaration alias) Default Public span (Just importScope)
|
||||
let scopeMap = Map.singleton moduleScope moduleFrame
|
||||
aliasFrame <- newFrame importScope (Map.singleton ScopeGraph.Import scopeMap)
|
||||
aliasSlot <- lookupDeclaration (Declaration alias)
|
||||
aliasSlot <- lookupSlot (Declaration alias)
|
||||
assign aliasSlot =<< object aliasFrame
|
||||
Nothing -> do
|
||||
insertImportEdge moduleScope
|
||||
|
@ -9,6 +9,7 @@ import Proto3.Suite
|
||||
|
||||
import Control.Abstract hiding (Import)
|
||||
import Data.Abstract.Evaluatable as Evaluatable
|
||||
import Data.Abstract.ScopeGraph (AccessControl(..))
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Data.Semigroup.App
|
||||
@ -115,7 +116,7 @@ instance Evaluatable ExtendsClause where
|
||||
traverse_ eval extendsClauses
|
||||
unit
|
||||
|
||||
data PropertySignature a = PropertySignature { modifiers :: ![a], propertySignaturePropertyName :: !a }
|
||||
data PropertySignature a = PropertySignature { modifiers :: [a], propertySignaturePropertyName :: a, propertySignatureAccessControl :: AccessControl }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PropertySignature
|
||||
|
||||
@ -140,7 +141,7 @@ data IndexSignature a = IndexSignature { subject :: a, subjectType :: a, typeAnn
|
||||
|
||||
instance Evaluatable IndexSignature
|
||||
|
||||
data AbstractMethodSignature a = AbstractMethodSignature { abstractMethodSignatureContext :: ![a], abstractMethodSignatureName :: !a, abstractMethodSignatureParameters :: ![a] }
|
||||
data AbstractMethodSignature a = AbstractMethodSignature { abstractMethodSignatureContext :: ![a], abstractMethodSignatureName :: a, abstractMethodSignatureParameters :: [a], abstractMethodAccessControl :: AccessControl }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically AbstractMethodSignature
|
||||
|
||||
@ -212,7 +213,7 @@ declareModule eval identifier statements = do
|
||||
Nothing -> do
|
||||
let edges = Map.singleton Lexical [ currentScope' ]
|
||||
childScope <- newScope edges
|
||||
declare (Declaration name) Default span (Just childScope)
|
||||
declare (Declaration name) Default Public span (Just childScope)
|
||||
|
||||
currentFrame' <- currentFrame
|
||||
let frameEdges = Map.singleton Lexical (Map.singleton currentScope' currentFrame')
|
||||
@ -220,7 +221,7 @@ declareModule eval identifier statements = do
|
||||
|
||||
withScopeAndFrame childFrame (void moduleBody)
|
||||
|
||||
moduleSlot <- lookupDeclaration (Declaration name)
|
||||
moduleSlot <- lookupSlot (Declaration name)
|
||||
assign moduleSlot =<< namespace name childFrame
|
||||
|
||||
unit
|
||||
@ -264,7 +265,7 @@ instance Evaluatable AbstractClass where
|
||||
superScopes <- for classHeritage $ \superclass -> do
|
||||
name <- maybeM (throwNoNameError superclass) (declaredName superclass)
|
||||
scope <- associatedScope (Declaration name)
|
||||
slot <- lookupDeclaration (Declaration name)
|
||||
slot <- lookupSlot (Declaration name)
|
||||
superclassFrame <- scopedEnvironment =<< deref slot
|
||||
pure $ case (scope, superclassFrame) of
|
||||
(Just scope, Just frame) -> Just (scope, frame)
|
||||
@ -274,7 +275,7 @@ instance Evaluatable AbstractClass where
|
||||
current = (Lexical, ) <$> pure (pure currentScope')
|
||||
edges = Map.fromList (superclassEdges <> current)
|
||||
classScope <- newScope edges
|
||||
declare (Declaration name) Default span (Just classScope)
|
||||
declare (Declaration name) Default Public span (Just classScope)
|
||||
|
||||
let frameEdges = Map.singleton Superclass (Map.fromList (catMaybes superScopes))
|
||||
childFrame <- newFrame classScope frameEdges
|
||||
@ -282,7 +283,7 @@ instance Evaluatable AbstractClass where
|
||||
withScopeAndFrame childFrame $ do
|
||||
void $ eval classBody
|
||||
|
||||
classSlot <- lookupDeclaration (Declaration name)
|
||||
classSlot <- lookupSlot (Declaration name)
|
||||
assign classSlot =<< klass (Declaration name) childFrame
|
||||
|
||||
unit
|
||||
|
@ -11,6 +11,7 @@ module Parsing.Parser
|
||||
, ApplyAll'
|
||||
-- À la carte parsers
|
||||
, goParser
|
||||
, goASTParser
|
||||
, javaParser
|
||||
, javaASTParser
|
||||
, jsonParser
|
||||
@ -125,6 +126,9 @@ type family ApplyAll (typeclasses :: [(* -> *) -> Constraint]) (syntax :: * -> *
|
||||
goParser :: Parser Go.Term
|
||||
goParser = AssignmentParser (ASTParser tree_sitter_go) Go.assignment
|
||||
|
||||
goASTParser :: Parser (AST [] Go.Grammar)
|
||||
goASTParser = ASTParser tree_sitter_go
|
||||
|
||||
rubyParser :: Parser Ruby.Term
|
||||
rubyParser = AssignmentParser (ASTParser tree_sitter_ruby) Ruby.assignment
|
||||
|
||||
|
@ -160,6 +160,7 @@ evalTerm :: ( Carrier sig m
|
||||
, Declarations term
|
||||
, Evaluatable (Base term)
|
||||
, FreeVariables term
|
||||
, AccessControls term
|
||||
, AbstractValue term address value m
|
||||
, Member (Allocator address) sig
|
||||
, Member (Bitwise value) sig
|
||||
|
@ -46,6 +46,7 @@ import Data.Abstract.Value.Abstract as Abstract
|
||||
import Data.Abstract.Value.Concrete as Concrete
|
||||
(Value, ValueError (..), runValueErrorWith)
|
||||
import Data.Abstract.Value.Type as Type
|
||||
import Data.Abstract.AccessControls.Instances ()
|
||||
import Data.Blob
|
||||
import Data.File
|
||||
import Data.Graph
|
||||
@ -67,7 +68,7 @@ import Text.Show.Pretty (ppShow)
|
||||
|
||||
data GraphType = ImportGraph | CallGraph
|
||||
|
||||
type AnalysisClasses = '[ Declarations1, Eq1, Evaluatable, FreeVariables1, Foldable, Functor, Ord1, Show1 ]
|
||||
type AnalysisClasses = '[ Declarations1, Eq1, Evaluatable, FreeVariables1, AccessControls1, Foldable, Functor, Ord1, Show1 ]
|
||||
|
||||
runGraph :: ( Member Distribute sig
|
||||
, Member (Error SomeException) sig
|
||||
@ -95,6 +96,7 @@ runGraph CallGraph includePackages project
|
||||
|
||||
runCallGraph :: ( VertexDeclarationWithStrategy (VertexDeclarationStrategy syntax) syntax syntax
|
||||
, Declarations1 syntax
|
||||
, AccessControls1 syntax
|
||||
, Ord1 syntax
|
||||
, Functor syntax
|
||||
, Evaluatable syntax
|
||||
@ -145,6 +147,7 @@ runModuleTable = raiseHandler $ runReader lowerBound
|
||||
runImportGraphToModuleInfos :: ( Declarations term
|
||||
, Evaluatable (Base term)
|
||||
, FreeVariables term
|
||||
, AccessControls term
|
||||
, HasPrelude lang
|
||||
, Member Trace sig
|
||||
, Recursive term
|
||||
@ -161,6 +164,7 @@ runImportGraphToModuleInfos lang (package :: Package term) = runImportGraph lang
|
||||
runImportGraphToModules :: ( Declarations term
|
||||
, Evaluatable (Base term)
|
||||
, FreeVariables term
|
||||
, AccessControls term
|
||||
, HasPrelude lang
|
||||
, Member Trace sig
|
||||
, Recursive term
|
||||
@ -177,6 +181,7 @@ runImportGraphToModules lang (package :: Package term) = runImportGraph lang pac
|
||||
runImportGraph :: ( Declarations term
|
||||
, Evaluatable (Base term)
|
||||
, FreeVariables term
|
||||
, AccessControls term
|
||||
, HasPrelude lang
|
||||
, Member Trace sig
|
||||
, Recursive term
|
||||
@ -245,6 +250,7 @@ parsePythonPackage :: forall syntax sig m term.
|
||||
( Declarations1 syntax
|
||||
, Evaluatable syntax
|
||||
, FreeVariables1 syntax
|
||||
, AccessControls1 syntax
|
||||
, Functor syntax
|
||||
, term ~ Term syntax Location
|
||||
, Member (Error SomeException) sig
|
||||
@ -366,6 +372,7 @@ resumingEvalError :: ( Carrier sig m
|
||||
m)) a
|
||||
-> Evaluator term address value m a
|
||||
resumingEvalError = runEvalErrorWith (\ baseError -> traceError "EvalError" baseError *> case baseErrorException baseError of
|
||||
AccessControlError{} -> pure hole
|
||||
ConstructorError{} -> pure hole
|
||||
DefaultExportError{} -> pure ()
|
||||
DerefError{} -> pure hole
|
||||
@ -444,6 +451,7 @@ resumingScopeError :: ( Carrier sig m
|
||||
, AbstractHole (Slot address)
|
||||
, AbstractHole (Scope address)
|
||||
, AbstractHole (Path address)
|
||||
, AbstractHole (Info address)
|
||||
, AbstractHole address
|
||||
)
|
||||
=> Evaluator term address value (ResumableWithC (BaseError (ScopeError address)) (Eff m)) a
|
||||
@ -454,7 +462,8 @@ resumingScopeError = runScopeErrorWith (\ baseError -> traceError "ScopeError" b
|
||||
LookupScopeError -> pure hole
|
||||
LookupPathError _ -> pure hole
|
||||
CurrentScopeError -> pure hole
|
||||
LookupDeclarationScopeError _ -> pure hole)
|
||||
LookupDeclarationScopeError _ -> pure hole
|
||||
DeclarationByNameError _ -> pure hole)
|
||||
|
||||
resumingTypeError :: ( Carrier sig m
|
||||
, Member NonDet sig
|
||||
|
@ -3,7 +3,7 @@
|
||||
Taggable allows projecting syntax terms to a list of named symbols. In order to
|
||||
identify a new syntax as Taggable, you need to:
|
||||
|
||||
1. Give that syntax a non-derived Taggable instance and implement as least the
|
||||
1. Give that syntax a non-derived Taggable instance and implement at least the
|
||||
'symbolName' method.
|
||||
|
||||
2. Make sure that 'symbolsToSummarize' in Tagging.hs includes the string
|
||||
@ -169,12 +169,12 @@ instance Taggable Declaration.Function where
|
||||
symbolName = declaredName . Declaration.functionName
|
||||
|
||||
instance Taggable Declaration.Method where
|
||||
docsLiteral Python (Declaration.Method _ _ _ _ (Term (In _ bodyF)))
|
||||
docsLiteral Python (Declaration.Method _ _ _ _ (Term (In _ bodyF)) _)
|
||||
| (Term (In exprAnn exprF):_) <- toList bodyF
|
||||
, isTextElement exprF = Just (locationByteRange exprAnn)
|
||||
| otherwise = Nothing
|
||||
docsLiteral _ _ = Nothing
|
||||
snippet ann (Declaration.Method _ _ _ _ (Term (In body _))) = Just $ subtractLocation ann body
|
||||
snippet ann (Declaration.Method _ _ _ _ (Term (In body _)) _) = Just $ subtractLocation ann body
|
||||
symbolName = declaredName . Declaration.methodName
|
||||
|
||||
instance Taggable Declaration.Class where
|
||||
|
@ -1,6 +1,8 @@
|
||||
module Analysis.TypeScript.Spec (spec) where
|
||||
|
||||
import Control.Abstract.ScopeGraph
|
||||
import Data.Syntax.Statement (StatementBlock(..))
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph (AccessControl(..))
|
||||
import Control.Abstract.ScopeGraph hiding (AccessControl(..))
|
||||
import Control.Abstract.Value as Value hiding (String, Unit)
|
||||
import Control.Arrow ((&&&))
|
||||
import Data.Abstract.Evaluatable
|
||||
@ -14,6 +16,7 @@ import Data.Abstract.Value.Concrete as Concrete
|
||||
import qualified Data.Language as Language
|
||||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
import Data.Location
|
||||
import qualified Data.Map.Internal as Map
|
||||
import Data.Quieterm
|
||||
import Data.Scientific (scientific)
|
||||
import Data.Sum
|
||||
@ -163,8 +166,25 @@ spec config = parallel $ do
|
||||
Right (Just (Module _ (_, value))) -> value `shouldBe` (Concrete.Float (Number.Decimal 9.0))
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "member access of private field definition throws AccessControlError" $ do
|
||||
(_, (_, res)) <- evaluate ["access_control/adder.ts", "access_control/private_field_definition.ts"]
|
||||
let expected = Left (SomeError (inject @TypeScriptEvalError (BaseError (ModuleInfo "private_field_definition.ts") (Span (Pos 4 1) (Pos 4 6)) (AccessControlError ("foo", ScopeGraph.Public) ("y", ScopeGraph.Private) (Concrete.Float (Decimal 2.0))))))
|
||||
res `shouldBe` expected
|
||||
|
||||
it "member access of private static field definition throws AccessControlError" $ do
|
||||
(_, (_, res)) <- evaluate ["access_control/adder.ts", "access_control/private_static_field_definition.ts"]
|
||||
let expected = Left (SomeError (inject @TypeScriptEvalError (BaseError (ModuleInfo "private_static_field_definition.ts") (Span (Pos 3 1) (Pos 3 8)) (AccessControlError ("Adder", ScopeGraph.Public) ("z", ScopeGraph.Private) Unit))))
|
||||
res `shouldBe` expected
|
||||
|
||||
it "member access of private methods throws AccessControlError" $ do
|
||||
(_, (_, res)) <- evaluate ["access_control/adder.ts", "access_control/private_method.ts"]
|
||||
let expected = Left (SomeError (inject @TypeScriptEvalError (BaseError (ModuleInfo "private_method.ts") (Span (Pos 4 1) (Pos 4 16)) (AccessControlError ("foo", ScopeGraph.Public) ("private_add", ScopeGraph.Private) (Closure (PackageInfo "access_control" mempty) (ModuleInfo "adder.ts") (Just "private_add") Nothing [] (Right (Quieterm (In (Location (Range 146 148) (Span (Pos 7 27) (Pos 7 29))) (inject (StatementBlock []))))) (Precise 20) (Precise 18))))))
|
||||
res `shouldBe` expected
|
||||
|
||||
where
|
||||
fixtures = "test/fixtures/typescript/analysis/"
|
||||
evaluate = evalTypeScriptProject . map (fixtures <>)
|
||||
evalTypeScriptProject = testEvaluating <=< (evaluateProject' config (Proxy :: Proxy 'Language.TypeScript) typescriptParser)
|
||||
|
||||
type TypeScriptTerm = Quieterm (Sum TypeScript.Syntax) Location
|
||||
type TypeScriptEvalError = BaseError (EvalError TypeScriptTerm Precise (Concrete.Value TypeScriptTerm Precise))
|
||||
|
@ -35,11 +35,11 @@ spec = parallel $ do
|
||||
let lexicalEdges = Map.singleton Lexical [ currentScope' ]
|
||||
x = SpecHelpers.name "x"
|
||||
associatedScope <- newScope lexicalEdges
|
||||
declare (ScopeGraph.Declaration "identity") Default emptySpan (Just associatedScope)
|
||||
declare (ScopeGraph.Declaration "identity") Default Public emptySpan (Just associatedScope)
|
||||
withScope associatedScope $ do
|
||||
declare (Declaration x) Default emptySpan Nothing
|
||||
declare (Declaration x) Default Public emptySpan Nothing
|
||||
identity <- function "identity" [ x ]
|
||||
(SpecEff (Heap.lookupDeclaration (ScopeGraph.Declaration (SpecHelpers.name "x")) >>= deref)) associatedScope
|
||||
(SpecEff (Heap.lookupSlot (ScopeGraph.Declaration (SpecHelpers.name "x")) >>= deref)) associatedScope
|
||||
val <- integer 123
|
||||
call identity [val]
|
||||
expected `shouldBe` Right (Value.Integer (Number.Integer 123))
|
||||
|
@ -21,6 +21,7 @@ import Analysis.CyclomaticComplexity
|
||||
import Analysis.TOCSummary
|
||||
import Control.Monad.Free as Free
|
||||
import Control.Monad.Trans.Free as FreeF
|
||||
import Data.Abstract.ScopeGraph (AccessControl(..))
|
||||
import Data.Bifunctor.Join
|
||||
import Data.ByteString (ByteString)
|
||||
import Data.Char (chr)
|
||||
@ -116,6 +117,13 @@ liftCons5 :: [Tier a] -> [Tier b] -> [Tier c] -> [Tier d] -> [Tier e] -> (a -> b
|
||||
liftCons5 tiers1 tiers2 tiers3 tiers4 tiers5 f = mapT (uncurry5 f) (tiers1 >< tiers2 >< tiers3 >< tiers4 >< tiers5) `addWeight` 1
|
||||
where uncurry5 f (a, (b, (c, (d, e)))) = f a b c d e
|
||||
|
||||
-- | Lifts a senary constructor to a list of tiers, given lists of tiers for its arguments.
|
||||
--
|
||||
-- Commonly used in the definition of 'Listable1' and 'Listable2' instances.
|
||||
liftCons6 :: [Tier a] -> [Tier b] -> [Tier c] -> [Tier d] -> [Tier e] -> [Tier f] -> (a -> b -> c -> d -> e -> f -> g) -> [Tier g]
|
||||
liftCons6 tiers1 tiers2 tiers3 tiers4 tiers5 tiers6 f = mapT (uncurry6 f) (tiers1 >< tiers2 >< tiers3 >< tiers4 >< tiers5 >< tiers6) `addWeight` 1
|
||||
where uncurry6 g (a, (b, (c, (d, (e, f))))) = g a b c d e f
|
||||
|
||||
-- | Convenient wrapper for 'Listable1' type constructors and 'Listable' types, where a 'Listable' instance would necessarily be orphaned.
|
||||
newtype ListableF f a = ListableF { unListableF :: f a }
|
||||
deriving Show
|
||||
@ -199,6 +207,9 @@ instance (Listable1 syntax) => Listable3 (DiffF syntax) where
|
||||
instance (Listable1 syntax, Listable ann1, Listable ann2, Listable recur) => Listable (DiffF syntax ann1 ann2 recur) where
|
||||
tiers = tiers3
|
||||
|
||||
instance Listable AccessControl where
|
||||
tiers = cons0 Public \/ cons0 Protected \/ cons0 Private
|
||||
|
||||
instance Listable1 f => Listable2 (Diff f) where
|
||||
liftTiers2 annTiers1 annTiers2 = go where go = liftCons1 (liftTiers3 annTiers1 annTiers2 go) Diff
|
||||
|
||||
@ -230,7 +241,7 @@ instance Listable1 Declaration.Function where
|
||||
liftTiers tiers = liftCons4 (liftTiers tiers) tiers (liftTiers tiers) tiers Declaration.Function
|
||||
|
||||
instance Listable1 Declaration.Method where
|
||||
liftTiers tiers = liftCons5 (liftTiers tiers) tiers tiers (liftTiers tiers) tiers Declaration.Method
|
||||
liftTiers tiers' = liftCons6 (liftTiers tiers') tiers' tiers' (liftTiers tiers') tiers' tiers Declaration.Method
|
||||
|
||||
instance Listable1 Statement.If where
|
||||
liftTiers tiers = liftCons3 tiers tiers tiers Statement.If
|
||||
|
@ -1,9 +1,7 @@
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
module Main (main) where
|
||||
|
||||
import Control.Exception (displayException)
|
||||
import Control.Monad
|
||||
import Control.Monad.IO.Class
|
||||
import Control.Effect
|
||||
import qualified Data.ByteString as B
|
||||
import Data.ByteString.Builder
|
||||
@ -17,9 +15,10 @@ import Data.Quieterm
|
||||
import Data.Typeable (cast)
|
||||
import Data.Void
|
||||
import Parsing.Parser
|
||||
import Rendering.Renderer
|
||||
import Semantic.Config (Config (..), Options (..), defaultOptions)
|
||||
import qualified Semantic.IO as IO
|
||||
import Semantic.API (parseTermBuilder, TermOutputFormat(..))
|
||||
import Semantic.Parse
|
||||
import Semantic.Task
|
||||
import Semantic.Task.Files
|
||||
import Semantic.Util (TaskConfig (..))
|
||||
@ -86,8 +85,7 @@ languages =
|
||||
, le "typescript" ".ts" "examples" (Just "script/known_failures.txt")
|
||||
, le "typescript" ".js" "examples" Nothing -- parse JavaScript with TypeScript parser.
|
||||
|
||||
-- TODO: Investigate Go assignment errors
|
||||
-- , le "go" ".go" "examples" (Just "script/known-failures.txt")
|
||||
, le "go" ".go" "examples" (Just "script/known-failures.txt")
|
||||
|
||||
-- TODO: Java assignment errors need to be investigated
|
||||
-- , le "java" ".java" "examples/guava" (Just "script/known_failures_guava.txt")
|
||||
@ -102,8 +100,8 @@ languages =
|
||||
-- , ("php", ".php") -- TODO: No parse-examples in tree-sitter yet
|
||||
]
|
||||
|
||||
parseFilePath :: (Member (Error SomeException) sig, Member Distribute sig, Member Task sig, Member Files sig, Carrier sig m, MonadIO m) => FilePath -> m Bool
|
||||
parseFilePath path = readBlob (file path) >>= parseTermBuilder @[] TermShow . pure >>= const (pure True)
|
||||
parseFilePath :: (Member (Error SomeException) sig, Member Task sig, Member Files sig, Carrier sig m, Monad m) => FilePath -> m Bool
|
||||
parseFilePath path = readBlob (file path) >>= runParse' >>= const (pure True)
|
||||
|
||||
languagesDir :: FilePath
|
||||
languagesDir = "vendor/haskell-tree-sitter/languages"
|
||||
|
@ -93,9 +93,9 @@ spec = parallel $ do
|
||||
prop "roundtrips" $
|
||||
\sp -> shouldRoundtrip1 @Statement.Statements @(Term (Sum Syntax) ()) (unListableF sp)
|
||||
|
||||
describe "methods" $
|
||||
prop "roundtrips" $
|
||||
\sp -> shouldRoundtrip1 @Declaration.Method @(Term (Sum Syntax) ()) (unListableF sp)
|
||||
-- describe "methods" $
|
||||
-- prop "roundtrips" $
|
||||
-- \sp -> shouldRoundtrip1 @Declaration.Method @(Term (Sum Syntax) ()) (unListableF sp)
|
||||
|
||||
describe "blobs" $ do
|
||||
it "should roundtrip given a Message instance" $ do
|
||||
|
@ -186,7 +186,7 @@ lookupDeclaration :: Name -> (Precise, Precise) -> Heap Precise Precise (Value t
|
||||
lookupDeclaration name (currentScope, currentFrame) heap scopeGraph = do
|
||||
path <- ScopeGraph.lookupScopePath name currentScope scopeGraph
|
||||
frameAddress <- Heap.lookupFrameAddress path currentFrame heap
|
||||
toList <$> Heap.getSlot (Slot frameAddress (Heap.pathPosition path)) heap
|
||||
toList <$> Heap.getSlotValue (Slot frameAddress (Heap.pathPosition path)) heap
|
||||
|
||||
newtype Verbatim = Verbatim ByteString
|
||||
deriving (Eq)
|
||||
|
1
test/fixtures/cli/diff-tree.json
vendored
1
test/fixtures/cli/diff-tree.json
vendored
@ -6,6 +6,7 @@
|
||||
"statements": [{
|
||||
"merge": {
|
||||
"term": "Method",
|
||||
"methodAccessControl":"Public",
|
||||
"methodBody": {
|
||||
"merge": {
|
||||
"children": [{
|
||||
|
@ -4,19 +4,16 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
|
@ -4,19 +4,16 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -9,7 +9,6 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -9,7 +9,6 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -7,7 +7,6 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -7,7 +7,6 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -7,10 +7,8 @@
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
@ -23,10 +21,8 @@
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
@ -39,10 +35,8 @@
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
@ -51,7 +45,6 @@
|
||||
{+(Return
|
||||
{+(Identifier)+})+})+})+}
|
||||
{-(PublicFieldDefinition
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
@ -61,10 +54,8 @@
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
@ -77,10 +68,8 @@
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
@ -93,10 +82,8 @@
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
|
@ -3,7 +3,6 @@
|
||||
(TypeIdentifier)
|
||||
(Statements
|
||||
{+(PublicFieldDefinition
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
@ -13,11 +12,9 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
@ -30,11 +27,9 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
@ -47,11 +42,9 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -3,7 +3,6 @@
|
||||
(TypeIdentifier)
|
||||
(Statements
|
||||
(PublicFieldDefinition
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
@ -13,10 +12,8 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
@ -29,10 +26,8 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
@ -45,10 +40,8 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -7,10 +7,8 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
@ -23,10 +21,8 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
@ -39,10 +35,8 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -9,19 +9,16 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
|
@ -9,19 +9,16 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
|
@ -8,13 +8,11 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -8,13 +8,11 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -5,13 +5,11 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -5,13 +5,11 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -5,13 +5,11 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
|
@ -5,13 +5,11 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
@ -21,13 +19,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
@ -21,13 +19,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
@ -21,13 +19,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -4,13 +4,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
@ -21,13 +19,11 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -5,17 +5,14 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -5,17 +5,14 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -5,16 +5,13 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -5,16 +5,13 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
13
test/fixtures/typescript/analysis/access_control/adder.ts
vendored
Normal file
13
test/fixtures/typescript/analysis/access_control/adder.ts
vendored
Normal file
@ -0,0 +1,13 @@
|
||||
class Adder {
|
||||
public x: number;
|
||||
private y: number;
|
||||
public static w: number;
|
||||
private static z: number;
|
||||
|
||||
private private_add() {}
|
||||
|
||||
constructor(x, y) {
|
||||
this.x = x;
|
||||
this.y = y;
|
||||
}
|
||||
}
|
4
test/fixtures/typescript/analysis/access_control/private_field_definition.ts
vendored
Normal file
4
test/fixtures/typescript/analysis/access_control/private_field_definition.ts
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
import { Adder } from "./adder"
|
||||
|
||||
var foo = new Adder(1, 2)
|
||||
foo.y;
|
4
test/fixtures/typescript/analysis/access_control/private_method.ts
vendored
Normal file
4
test/fixtures/typescript/analysis/access_control/private_method.ts
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
import { Adder } from "./adder"
|
||||
|
||||
var foo = new Adder(1, 2)
|
||||
foo.private_add()
|
3
test/fixtures/typescript/analysis/access_control/private_static_field_definition.ts
vendored
Normal file
3
test/fixtures/typescript/analysis/access_control/private_static_field_definition.ts
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
import { Adder } from "./adder"
|
||||
|
||||
Adder.z
|
@ -7,7 +7,6 @@
|
||||
{ (TypeIdentifier)
|
||||
->(TypeIdentifier) }
|
||||
{ (PublicFieldDefinition
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Annotation
|
||||
{-(TypeIdentifier)-})-}
|
||||
@ -32,7 +31,6 @@
|
||||
{-(PredefinedType)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Annotation
|
||||
{-(PredefinedType)-})-}
|
||||
@ -47,7 +45,6 @@
|
||||
{-(PredefinedType)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Annotation
|
||||
{-(PredefinedType)-})-}
|
||||
@ -64,7 +61,6 @@
|
||||
{-(TypeIdentifier)-}
|
||||
{-(ObjectType
|
||||
{-(PropertySignature
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Annotation
|
||||
{-(PredefinedType)-})-}
|
||||
@ -74,19 +70,16 @@
|
||||
{-(TypeIdentifier)-}
|
||||
{-(ObjectType
|
||||
{-(PropertySignature
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Annotation
|
||||
{-(PredefinedType)-})-}
|
||||
{-(Identifier)-})-}
|
||||
{-(PropertySignature
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Annotation
|
||||
{-(PredefinedType)-})-}
|
||||
{-(Identifier)-})-}
|
||||
{-(PropertySignature
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Annotation
|
||||
{-(PredefinedType)-})-}
|
||||
@ -99,24 +92,20 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(PublicFieldDefinition
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(MethodSignature
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
|
@ -3,7 +3,6 @@
|
||||
{+(Class
|
||||
{+(TypeIdentifier)+}
|
||||
{+(PublicFieldDefinition
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Annotation
|
||||
{+(TypeIdentifier)+})+}
|
||||
@ -23,7 +22,6 @@
|
||||
{+(PredefinedType)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Annotation
|
||||
{+(PredefinedType)+})+}
|
||||
@ -38,7 +36,6 @@
|
||||
{+(PredefinedType)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Annotation
|
||||
{+(PredefinedType)+})+}
|
||||
@ -55,7 +52,6 @@
|
||||
{+(TypeIdentifier)+}
|
||||
{+(ObjectType
|
||||
{+(PropertySignature
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Annotation
|
||||
{+(PredefinedType)+})+}
|
||||
@ -65,19 +61,16 @@
|
||||
{+(TypeIdentifier)+}
|
||||
{+(ObjectType
|
||||
{+(PropertySignature
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Annotation
|
||||
{+(PredefinedType)+})+}
|
||||
{+(Identifier)+})+}
|
||||
{+(PropertySignature
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Annotation
|
||||
{+(PredefinedType)+})+}
|
||||
{+(Identifier)+})+}
|
||||
{+(PropertySignature
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Annotation
|
||||
{+(PredefinedType)+})+}
|
||||
@ -102,24 +95,20 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(PublicFieldDefinition
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(MethodSignature
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
|
@ -3,7 +3,6 @@
|
||||
(Class
|
||||
(TypeIdentifier)
|
||||
(PublicFieldDefinition
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(TypeIdentifier))
|
||||
@ -23,7 +22,6 @@
|
||||
(PredefinedType))
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
@ -38,7 +36,6 @@
|
||||
(PredefinedType))
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
@ -55,7 +52,6 @@
|
||||
(TypeIdentifier)
|
||||
(ObjectType
|
||||
(PropertySignature
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
@ -65,19 +61,16 @@
|
||||
(TypeIdentifier)
|
||||
(ObjectType
|
||||
(PropertySignature
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier))
|
||||
(PropertySignature
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier))
|
||||
(PropertySignature
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
@ -90,24 +83,20 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(PublicFieldDefinition
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(MethodSignature
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
|
@ -19,24 +19,20 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(PublicFieldDefinition
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(MethodSignature
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
|
@ -8,14 +8,12 @@
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Annotation
|
||||
{+(PredefinedType)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Annotation
|
||||
{+(PredefinedType)+})+}
|
||||
|
@ -5,14 +5,12 @@
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Annotation
|
||||
{-(PredefinedType)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Annotation
|
||||
{-(PredefinedType)-})-}
|
||||
|
@ -5,14 +5,12 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
|
@ -4,19 +4,16 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
{-(RequiredParameter
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
(RequiredParameter
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
{+(RequiredParameter
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
|
Some files were not shown because too many files have changed in this diff Show More
Loading…
Reference in New Issue
Block a user