mirror of
https://github.com/github/semantic.git
synced 2024-11-28 10:15:55 +03:00
Merge remote-tracking branch 'origin/environment-scoping' into typescript-exports
This commit is contained in:
commit
60721252cf
@ -15,9 +15,9 @@ library
|
||||
hs-source-dirs: src
|
||||
exposed-modules:
|
||||
-- Analyses & term annotations
|
||||
-- Analysis.Abstract.Caching
|
||||
Analysis.Abstract.Caching
|
||||
-- , Analysis.Abstract.Collecting
|
||||
Analysis.Abstract.Dead
|
||||
, Analysis.Abstract.Dead
|
||||
, Analysis.Abstract.Evaluating
|
||||
-- , Analysis.Abstract.Tracing
|
||||
, Analysis.ConstructorName
|
||||
@ -37,10 +37,10 @@ library
|
||||
-- Control flow
|
||||
, Control.Effect
|
||||
-- Effects used for program analysis
|
||||
-- , Control.Monad.Effect.Cache
|
||||
, Control.Monad.Effect.Cache
|
||||
, Control.Monad.Effect.Fresh
|
||||
-- , Control.Monad.Effect.GC
|
||||
-- , Control.Monad.Effect.NonDet
|
||||
, Control.Monad.Effect.NonDet
|
||||
-- , Control.Monad.Effect.Trace
|
||||
-- Datatypes for abstract interpretation
|
||||
, Data.Abstract.Address
|
||||
@ -48,9 +48,9 @@ library
|
||||
, Data.Abstract.Configuration
|
||||
, Data.Abstract.Environment
|
||||
, Data.Abstract.Evaluatable
|
||||
, Data.Abstract.Linker
|
||||
, Data.Abstract.FreeVariables
|
||||
, Data.Abstract.Live
|
||||
, Data.Abstract.ModuleTable
|
||||
, Data.Abstract.Store
|
||||
, Data.Abstract.Type
|
||||
, Data.Abstract.Value
|
||||
@ -163,6 +163,7 @@ library
|
||||
, pointed
|
||||
, recursion-schemes
|
||||
, semigroups
|
||||
, scientific
|
||||
, split
|
||||
, stm-chans
|
||||
, template-haskell
|
||||
|
@ -1,16 +1,14 @@
|
||||
{-# LANGUAGE ConstraintKinds, DataKinds, ScopedTypeVariables, TypeApplications #-}
|
||||
module Analysis.Abstract.Caching where
|
||||
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, MultiParamTypeClasses, ScopedTypeVariables, StandaloneDeriving, TypeApplications, UndecidableInstances #-}
|
||||
module Analysis.Abstract.Caching
|
||||
( evaluateCache )
|
||||
where
|
||||
|
||||
import Prologue
|
||||
import Data.Monoid (Alt(..))
|
||||
import Analysis.Abstract.Collecting
|
||||
import Control.Abstract.Evaluator
|
||||
import Control.Effect
|
||||
import Control.Monad.Effect.Addressable
|
||||
import Control.Monad.Effect.Cache
|
||||
import Control.Monad.Effect.Env
|
||||
import Control.Monad.Effect.Fail
|
||||
import Control.Monad.Effect.Fresh
|
||||
import Control.Monad.Effect.Internal hiding (run)
|
||||
import Control.Monad.Effect.NonDet
|
||||
import Control.Monad.Effect.Reader
|
||||
import Control.Monad.Effect.State
|
||||
@ -18,108 +16,107 @@ import Data.Abstract.Address
|
||||
import Data.Abstract.Cache
|
||||
import Data.Abstract.Configuration
|
||||
import Data.Abstract.Environment
|
||||
import Data.Abstract.Eval
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.ModuleTable
|
||||
import Data.Abstract.Live
|
||||
import Data.Abstract.Store
|
||||
import Data.Abstract.Value
|
||||
import qualified Data.Set as Set
|
||||
|
||||
-- | The effects necessary for caching analyses.
|
||||
type Caching t v
|
||||
type CachingEffects t v
|
||||
= '[ Fresh -- For 'MonadFresh'.
|
||||
, Reader (Live (LocationFor v) v) -- For 'MonadGC'.
|
||||
, Reader (Environment (LocationFor v) v) -- For 'MonadEnv'.
|
||||
, State (Environment (LocationFor v) v) -- For 'MonadEvaluator'.
|
||||
, Fail -- For 'MonadFail'.
|
||||
, NonDetEff -- For 'Alternative' & 'MonadNonDet'.
|
||||
, State (Store (LocationFor v) v) -- For 'MonadStore'.
|
||||
, Reader (Cache (LocationFor v) t v) -- For 'MonadCacheIn'.
|
||||
, State (Cache (LocationFor v) t v) -- For 'MonadCacheOut'.
|
||||
, Reader (ModuleTable t) -- Cache of unevaluated modules
|
||||
, State (ModuleTable (EnvironmentFor v)) -- Cache of evaluated modules
|
||||
]
|
||||
|
||||
-- | A constraint synonym for the interfaces necessary for caching analyses.
|
||||
type MonadCaching t v m
|
||||
= ( MonadEnv v m
|
||||
, MonadStore v m
|
||||
, MonadCacheIn t v m
|
||||
, MonadCacheOut t v m
|
||||
, MonadGC v m
|
||||
, Alternative m
|
||||
)
|
||||
newtype CachingAnalysis term value a = CachingAnalysis { runCachingAnalysis :: Evaluator (CachingEffects term value) term value a }
|
||||
deriving (Alternative, Applicative, Functor, Monad, MonadFail, MonadFresh, MonadNonDet)
|
||||
|
||||
deriving instance MonadEvaluator term value (CachingAnalysis term value)
|
||||
|
||||
-- TODO: reabstract these later on
|
||||
|
||||
askCache :: CachingAnalysis t v (Cache (LocationFor v) t v)
|
||||
askCache = CachingAnalysis (Evaluator ask)
|
||||
|
||||
localCache :: (Cache (LocationFor v) t v -> Cache (LocationFor v) t v) -> CachingAnalysis t v a -> CachingAnalysis t v a
|
||||
localCache f (CachingAnalysis (Evaluator a)) = CachingAnalysis (Evaluator (local f a))
|
||||
|
||||
asksCache :: (Cache (LocationFor v) t v -> a) -> CachingAnalysis t v a
|
||||
asksCache f = f <$> askCache
|
||||
|
||||
getsCache :: (Cache (LocationFor v) t v -> a) -> CachingAnalysis t v a
|
||||
getsCache f = f <$> getCache
|
||||
|
||||
getCache :: CachingAnalysis t v (Cache (LocationFor v) t v)
|
||||
getCache = CachingAnalysis (Evaluator get)
|
||||
|
||||
putCache :: Cache (LocationFor v) t v -> CachingAnalysis t v ()
|
||||
putCache v = CachingAnalysis (Evaluator (put v))
|
||||
|
||||
modifyCache :: (Cache (LocationFor v) t v -> Cache (LocationFor v) t v) -> CachingAnalysis t v ()
|
||||
modifyCache f = fmap f getCache >>= putCache
|
||||
|
||||
-- | This instance coinductively iterates the analysis of a term until the results converge.
|
||||
instance ( Corecursive t
|
||||
, Ord t
|
||||
, Ord v
|
||||
, Ord (Cell (LocationFor v) v)
|
||||
, Evaluatable (Base t)
|
||||
, Foldable (Cell (LocationFor v))
|
||||
, FreeVariables t
|
||||
, MonadAddressable (LocationFor v) v (CachingAnalysis t v)
|
||||
, MonadValue t v (CachingAnalysis t v)
|
||||
, Recursive t
|
||||
, Semigroup (Cell (LocationFor v) v)
|
||||
)
|
||||
=> MonadAnalysis t v (CachingAnalysis t v) where
|
||||
analyzeTerm e = do
|
||||
c <- getConfiguration (embedSubterm e)
|
||||
-- Convergence here is predicated upon an Eq instance, not α-equivalence
|
||||
cache <- converge (\ prevCache -> do
|
||||
putCache (mempty :: Cache (LocationFor v) t v)
|
||||
putStore (configurationStore c)
|
||||
-- We need to reset fresh generation so that this invocation converges.
|
||||
reset 0
|
||||
-- This is subtle: though the calling context supports nondeterminism, we want
|
||||
-- to corral all the nondeterminism that happens in this @eval@ invocation, so
|
||||
-- that it doesn't "leak" to the calling context and diverge
|
||||
-- (otherwise this would never complete).
|
||||
_ <- localCache (const prevCache) (gather Set.singleton (memoizeEval e))
|
||||
getCache) mempty
|
||||
maybe empty scatter (cacheLookup c cache)
|
||||
|
||||
|
||||
-- | Coinductively-cached evaluation.
|
||||
evalCache :: forall v term
|
||||
. ( Ord v
|
||||
, Ord term
|
||||
, Ord (LocationFor v)
|
||||
, Ord (Cell (LocationFor v) v)
|
||||
, Foldable (Cell (LocationFor v))
|
||||
, Functor (Base term)
|
||||
, Recursive term
|
||||
, Addressable (LocationFor v) (Eff (Caching term v))
|
||||
, Semigroup (Cell (LocationFor v) v)
|
||||
, ValueRoots (LocationFor v) v
|
||||
, Eval term v (Eff (Caching term v)) (Base term)
|
||||
)
|
||||
=> term
|
||||
-> Final (Caching term v) v
|
||||
evalCache e = run @(Caching term v) (fixCache (fix (evCache (evCollect (\ recur yield -> eval recur yield . project)))) pure e)
|
||||
|
||||
|
||||
-- | Evaluation of a single iteration of an analysis, given a 'MonadCacheIn' instance as an oracle for results and a 'MonadCacheOut' instance to record computed results in.
|
||||
evCache :: forall t v m
|
||||
. ( Ord (LocationFor v)
|
||||
, Ord t
|
||||
, Ord v
|
||||
, Ord (Cell (LocationFor v) v)
|
||||
, MonadCaching t v m
|
||||
)
|
||||
=> (((v -> m v) -> t -> m v) -> (v -> m v) -> t -> m v)
|
||||
-> ((v -> m v) -> t -> m v)
|
||||
-> (v -> m v) -> t -> m v
|
||||
evCache ev0 ev' yield e = do
|
||||
c <- getConfiguration e
|
||||
cached <- getsCache (cacheLookup c)
|
||||
case cached of
|
||||
Just pairs -> scatter pairs
|
||||
Nothing -> do
|
||||
pairs <- asksCache (fromMaybe mempty . cacheLookup c)
|
||||
modifyCache (cacheSet c pairs)
|
||||
v <- ev0 ev' yield e
|
||||
store' <- getStore
|
||||
modifyCache (cacheInsert c (v, store'))
|
||||
pure v
|
||||
|
||||
-- | Coinductively iterate the analysis of a term until the results converge.
|
||||
fixCache :: forall t v m
|
||||
. ( Ord (LocationFor v)
|
||||
, Ord t
|
||||
, Ord v
|
||||
, Ord (Cell (LocationFor v) v)
|
||||
, MonadCaching t v m
|
||||
, MonadNonDet m
|
||||
, MonadFresh m
|
||||
)
|
||||
=> ((v -> m v) -> t -> m v)
|
||||
-> (v -> m v) -> t -> m v
|
||||
fixCache ev' yield e = do
|
||||
c <- getConfiguration e
|
||||
cache <- converge (\ prevCache -> do
|
||||
putCache (mempty :: Cache (LocationFor v) t v)
|
||||
putStore (configurationStore c)
|
||||
reset 0
|
||||
_ <- localCache (const prevCache) (gather Set.singleton (ev' yield e))
|
||||
getCache) mempty
|
||||
maybe empty scatter (cacheLookup c cache)
|
||||
|
||||
-- | Get the current 'Configuration' with a passed-in term.
|
||||
getConfiguration :: (MonadEnv v m, MonadGC v m, MonadStore v m) => t -> m (Configuration (LocationFor v) t v)
|
||||
getConfiguration term = Configuration term <$> askRoots <*> askEnv <*> getStore
|
||||
|
||||
|
||||
-- | Nondeterministically write each of a collection of stores & return their associated results.
|
||||
scatter :: (Alternative m, Foldable t, MonadStore a m) => t (a, Store (LocationFor a) a) -> m a
|
||||
scatter = getAlt . foldMap (\ (value, store') -> Alt (putStore store' *> pure value))
|
||||
evaluateCache :: forall v term
|
||||
. ( Ord v
|
||||
, Ord term
|
||||
, Ord (LocationFor v)
|
||||
, Ord (Cell (LocationFor v) v)
|
||||
, Corecursive term
|
||||
, Evaluatable (Base term)
|
||||
, FreeVariables term
|
||||
, Foldable (Cell (LocationFor v))
|
||||
, Functor (Base term)
|
||||
, Recursive term
|
||||
, MonadAddressable (LocationFor v) v (CachingAnalysis term v)
|
||||
, MonadValue term v (CachingAnalysis term v)
|
||||
, Semigroup (Cell (LocationFor v) v)
|
||||
, ValueRoots (LocationFor v) v
|
||||
)
|
||||
=> term
|
||||
-> Final (CachingEffects term v) v
|
||||
evaluateCache = run @(CachingEffects term v) . runEvaluator . runCachingAnalysis . evaluateTerm
|
||||
|
||||
-- | Iterate a monadic action starting from some initial seed until the results converge.
|
||||
--
|
||||
@ -135,3 +132,41 @@ converge f = loop
|
||||
pure x
|
||||
else
|
||||
loop x'
|
||||
|
||||
-- | Get the current 'Configuration' with a passed-in term.
|
||||
getConfiguration :: Ord (LocationFor v) => t -> CachingAnalysis t v (Configuration (LocationFor v) t v)
|
||||
getConfiguration term = Configuration term mempty <$> askLocalEnv <*> getStore
|
||||
|
||||
-- | Nondeterministically write each of a collection of stores & return their associated results.
|
||||
scatter :: (Alternative m, Foldable t, MonadEvaluator term v m) => t (a, Store (LocationFor v) v) -> m a
|
||||
scatter = getAlt . foldMap (\ (value, store') -> Alt (putStore store' *> pure value))
|
||||
|
||||
-- | Evaluation of a single iteration of an analysis, given a 'MonadCacheIn' instance as an oracle for results and a 'MonadCacheOut' instance to record computed results in.
|
||||
memoizeEval :: forall v term
|
||||
. ( Ord v
|
||||
, Ord term
|
||||
, Ord (LocationFor v)
|
||||
, Ord (Cell (LocationFor v) v)
|
||||
, Corecursive term
|
||||
, Evaluatable (Base term)
|
||||
, FreeVariables term
|
||||
, Foldable (Cell (LocationFor v))
|
||||
, Functor (Base term)
|
||||
, Recursive term
|
||||
, MonadAddressable (LocationFor v) v (CachingAnalysis term v)
|
||||
, MonadValue term v (CachingAnalysis term v)
|
||||
, Semigroup (Cell (LocationFor v) v)
|
||||
)
|
||||
=> SubtermAlgebra (Base term) term (CachingAnalysis term v v)
|
||||
memoizeEval e = do
|
||||
c <- getConfiguration (embedSubterm e)
|
||||
cached <- getsCache (cacheLookup c)
|
||||
case cached of
|
||||
Just pairs -> scatter pairs
|
||||
Nothing -> do
|
||||
pairs <- asksCache (fromMaybe mempty . cacheLookup c)
|
||||
modifyCache (cacheSet c pairs)
|
||||
v <- eval e
|
||||
store' <- getStore
|
||||
modifyCache (cacheInsert c (v, store'))
|
||||
pure v
|
||||
|
@ -2,6 +2,7 @@
|
||||
module Analysis.Abstract.Collecting where
|
||||
|
||||
import Prologue
|
||||
import Control.Abstract.Evaluator
|
||||
import Control.Monad.Effect.GC
|
||||
import Data.Abstract.Address
|
||||
import Data.Abstract.Live
|
||||
@ -12,7 +13,7 @@ import Data.Abstract.Value
|
||||
evCollect :: forall t v m
|
||||
. ( Ord (LocationFor v)
|
||||
, Foldable (Cell (LocationFor v))
|
||||
, MonadStore v m
|
||||
, MonadEvaluator t v m
|
||||
, MonadGC v m
|
||||
, ValueRoots (LocationFor v) v
|
||||
)
|
||||
|
@ -9,7 +9,7 @@ import Control.Monad.Effect.Reader
|
||||
import Control.Monad.Effect.State
|
||||
import Data.Abstract.Address
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Linker
|
||||
import Data.Abstract.ModuleTable
|
||||
import Data.Abstract.Store
|
||||
import Data.Abstract.Value
|
||||
import Data.Set (delete)
|
||||
@ -17,14 +17,14 @@ import Prologue
|
||||
|
||||
-- | The effects necessary for dead code analysis.
|
||||
type DeadCodeEffects t v
|
||||
= '[ State (Dead t) -- The set of dead terms
|
||||
, Fail -- Failure with an error message
|
||||
, State (Store (LocationFor v) v) -- The heap
|
||||
, State (Map Name (Name, Maybe (Address (LocationFor v) v))) -- Set of exports
|
||||
, State (EnvironmentFor v) -- Global (imperative) environment
|
||||
, Reader (EnvironmentFor v) -- Local environment (e.g. binding over a closure)
|
||||
, Reader (Linker t) -- Cache of unevaluated modules
|
||||
, State (Linker (EnvironmentFor v)) -- Cache of evaluated modules
|
||||
= '[ State (Dead t) -- The set of dead terms
|
||||
, Fail -- Failure with an error message
|
||||
, State (Store (LocationFor v) v) -- The heap
|
||||
, State (Map Name (Name, Maybe (Address (LocationFor v) v))) -- Set of exports
|
||||
, State (EnvironmentFor v) -- Global (imperative) environment
|
||||
, Reader (EnvironmentFor v) -- Local environment (e.g. binding over a closure)
|
||||
, Reader (ModuleTable t) -- Cache of unevaluated modules
|
||||
, State (ModuleTable (EnvironmentFor v)) -- Cache of evaluated modules
|
||||
]
|
||||
|
||||
|
||||
@ -80,6 +80,6 @@ instance ( Corecursive t
|
||||
, Semigroup (Cell (LocationFor v) v)
|
||||
)
|
||||
=> MonadAnalysis t v (DeadCodeAnalysis t v) where
|
||||
evaluateTerm = foldSubterms (\ term -> do
|
||||
revive (embed (subterm <$> term))
|
||||
eval term)
|
||||
analyzeTerm term = do
|
||||
revive (embedSubterm term)
|
||||
eval term
|
||||
|
@ -8,11 +8,10 @@ import Control.Monad.Effect.Reader
|
||||
import Control.Monad.Effect.State
|
||||
import Data.Abstract.Address
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Linker
|
||||
import Data.Abstract.ModuleTable
|
||||
import Data.Abstract.Store
|
||||
import Data.Abstract.Value
|
||||
import Data.Blob
|
||||
import Data.List (intercalate)
|
||||
import Data.List.Split (splitWhen)
|
||||
import Prologue
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
@ -22,13 +21,13 @@ import System.FilePath.Posix
|
||||
|
||||
-- | The effects necessary for concrete interpretation.
|
||||
type EvaluationEffects t v
|
||||
= '[ Fail -- Failure with an error message
|
||||
, State (Store (LocationFor v) v) -- The heap
|
||||
, State (EnvironmentFor v) -- Global (imperative) environment
|
||||
, State (Map Name (Name, Maybe (Address (LocationFor v) v))) -- Set of exports
|
||||
, Reader (EnvironmentFor v) -- Local environment (e.g. binding over a closure)
|
||||
, Reader (Linker t) -- Cache of unevaluated modules
|
||||
, State (Linker (EnvironmentFor v)) -- Cache of evaluated modules
|
||||
= '[ Fail -- Failure with an error message
|
||||
, State (Store (LocationFor v) v) -- The heap
|
||||
, State (Map Name (Name, Maybe (Address (LocationFor v) v))) -- Set of exports
|
||||
, State (EnvironmentFor v) -- Global (imperative) environment
|
||||
, Reader (EnvironmentFor v) -- Local environment (e.g. binding over a closure)
|
||||
, Reader (ModuleTable t) -- Cache of unevaluated modules
|
||||
, State (ModuleTable (EnvironmentFor v)) -- Cache of evaluated modules
|
||||
]
|
||||
|
||||
-- | Evaluate a term to a value.
|
||||
@ -64,10 +63,10 @@ evaluates pairs (b, t) = run @(EvaluationEffects term v) (runEvaluator (runEvalu
|
||||
withModules :: (MonadAnalysis term value m, MonadEvaluator term value m) => Blob -> [(Blob, term)] -> m a -> m a
|
||||
withModules Blob{..} pairs = localModuleTable (const moduleTable)
|
||||
where
|
||||
moduleTable = Linker (Map.fromList (map (first moduleName) pairs))
|
||||
moduleTable = ModuleTable (Map.fromList (map (first moduleName) pairs))
|
||||
rootDir = dropFileName blobPath
|
||||
replacePathSeps str = intercalate "." (splitWhen (== pathSeparator) str)
|
||||
moduleName Blob{..} = BC.pack $ replacePathSeps (dropExtensions (makeRelative rootDir blobPath))
|
||||
moduleName Blob{..} = toName (dropExtensions (makeRelative rootDir blobPath))
|
||||
toName str = qualifiedName (fmap BC.pack (splitWhen (== pathSeparator) str))
|
||||
|
||||
-- | An analysis performing concrete evaluation of @term@s to @value@s.
|
||||
newtype Evaluation term value a = Evaluation { runEvaluation :: Evaluator (EvaluationEffects term value) term value a }
|
||||
@ -83,4 +82,4 @@ instance ( Evaluatable (Base t)
|
||||
, Semigroup (Cell (LocationFor v) v)
|
||||
)
|
||||
=> MonadAnalysis t v (Evaluation t v) where
|
||||
evaluateTerm = foldSubterms eval
|
||||
analyzeTerm = eval
|
||||
|
@ -14,6 +14,7 @@ import Data.Record
|
||||
import Data.Source as Source
|
||||
import Data.Span
|
||||
import Data.Term
|
||||
import Data.Abstract.FreeVariables
|
||||
import qualified Data.Syntax as Syntax
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
import qualified Data.Syntax.Expression as Expression
|
||||
@ -131,7 +132,7 @@ instance CustomHasDeclaration (Union fs) Declaration.QualifiedImport where
|
||||
| otherwise = alias
|
||||
basename = last . T.splitOn "/"
|
||||
getSource = T.dropAround (`elem` ['"', '\'']) . toText . flip Source.slice blobSource . getField
|
||||
getSymbol (a, b) = (T.decodeUtf8 a, T.decodeUtf8 b)
|
||||
getSymbol = let f = (T.decodeUtf8 . friendlyName) in bimap f f
|
||||
|
||||
instance (Expression.MemberAccess :< fs) => CustomHasDeclaration (Union fs) Expression.Call where
|
||||
customToDeclaration Blob{..} _ (Expression.Call _ (Term (In fromAnn fromF), _) _ _)
|
||||
|
@ -5,16 +5,17 @@ module Analysis.IdentifierName
|
||||
, identifierLabel
|
||||
) where
|
||||
|
||||
import Prologue
|
||||
import Data.Abstract.FreeVariables
|
||||
import Data.Aeson
|
||||
import Data.JSON.Fields
|
||||
import Data.Term
|
||||
import Data.Text.Encoding (decodeUtf8)
|
||||
import Prologue
|
||||
import qualified Data.Syntax
|
||||
|
||||
-- | Compute a 'IdentifierLabel' label for a 'Term'.
|
||||
identifierLabel :: IdentifierName syntax => TermF syntax a b -> Maybe IdentifierLabel
|
||||
identifierLabel (In _ s) = IdentifierLabel <$> (identifierName s)
|
||||
identifierLabel (In _ s) = IdentifierLabel <$> identifierName s
|
||||
|
||||
newtype IdentifierLabel = IdentifierLabel ByteString
|
||||
deriving (Show)
|
||||
@ -39,7 +40,7 @@ instance Apply IdentifierName fs => CustomIdentifierName (Union fs) where
|
||||
customIdentifierName = apply (Proxy :: Proxy IdentifierName) identifierName
|
||||
|
||||
instance CustomIdentifierName Data.Syntax.Identifier where
|
||||
customIdentifierName (Data.Syntax.Identifier name) = Just name
|
||||
customIdentifierName (Data.Syntax.Identifier name) = Just (friendlyName name)
|
||||
|
||||
data Strategy = Default | Custom
|
||||
|
||||
|
@ -1,9 +1,18 @@
|
||||
{-# LANGUAGE FunctionalDependencies #-}
|
||||
{-# LANGUAGE DefaultSignatures, FunctionalDependencies #-}
|
||||
module Control.Abstract.Analysis where
|
||||
|
||||
import Prologue
|
||||
|
||||
-- | A 'Monad' in which one can evaluate some specific term type to some specific value type.
|
||||
--
|
||||
-- This typeclass is left intentionally unconstrained to avoid circular dependencies between it and other typeclasses.
|
||||
class Monad m => MonadAnalysis term value m | m -> term, m -> value where
|
||||
-- | Evaluate a term to a value using the semantics of the current analysis. This should always be used instead of explicitly folding 'eval' over subterms, except in 'MonadAnalysis' instances themselves.
|
||||
evaluateTerm :: term -> m value
|
||||
-- | Analyze a term using the semantics of the current analysis. This should generally only be called by definitions of 'evaluateTerm' and 'analyzeTerm' in this or other instances.
|
||||
analyzeTerm :: SubtermAlgebra (Base term) term (m value)
|
||||
|
||||
-- | Evaluate a term to a value using the semantics of the current analysis.
|
||||
--
|
||||
-- This should always be called instead of explicitly folding either 'eval' or 'analyzeTerm' over subterms, except in 'MonadAnalysis' instances themselves.
|
||||
evaluateTerm :: MonadAnalysis term value m => term -> m value
|
||||
default evaluateTerm :: (MonadAnalysis term value m, Recursive term) => term -> m value
|
||||
evaluateTerm = foldSubterms analyzeTerm
|
||||
|
@ -5,13 +5,13 @@ import Prologue
|
||||
import Control.Monad.Effect
|
||||
import Control.Monad.Effect.Fail
|
||||
import Control.Monad.Effect.Fresh
|
||||
import Control.Monad.Effect.NonDetEff
|
||||
import Control.Monad.Effect.NonDet
|
||||
import Control.Monad.Effect.Reader
|
||||
import Control.Monad.Effect.State
|
||||
import Data.Abstract.Address
|
||||
import Data.Abstract.Linker
|
||||
import Data.Abstract.FreeVariables (Name)
|
||||
import Data.Map as Map
|
||||
import Data.Abstract.ModuleTable
|
||||
import Data.Abstract.Value
|
||||
import Prelude hiding (fail)
|
||||
|
||||
@ -52,22 +52,22 @@ class MonadFail m => MonadEvaluator term value m | m -> term, m -> value where
|
||||
modifyStore :: (StoreFor value -> StoreFor value) -> m ()
|
||||
|
||||
-- | Retrieve the table of evaluated modules.
|
||||
getModuleTable :: m (Linker (EnvironmentFor value))
|
||||
getModuleTable :: m (ModuleTable (EnvironmentFor value))
|
||||
-- | Update the table of evaluated modules.
|
||||
modifyModuleTable :: (Linker (EnvironmentFor value) -> Linker (EnvironmentFor value)) -> m ()
|
||||
modifyModuleTable :: (ModuleTable (EnvironmentFor value) -> ModuleTable (EnvironmentFor value)) -> m ()
|
||||
|
||||
-- | Retrieve the table of unevaluated modules.
|
||||
askModuleTable :: m (Linker term)
|
||||
askModuleTable :: m (ModuleTable term)
|
||||
-- | Run an action with a locally-modified table of unevaluated modules.
|
||||
localModuleTable :: (Linker term -> Linker term) -> m a -> m a
|
||||
localModuleTable :: (ModuleTable term -> ModuleTable term) -> m a -> m a
|
||||
|
||||
instance Members '[ Fail
|
||||
, Reader (EnvironmentFor value)
|
||||
, State (Map Name (Name, Maybe (Address (LocationFor value) value)))
|
||||
, State (EnvironmentFor value)
|
||||
, State (StoreFor value)
|
||||
, Reader (Linker term)
|
||||
, State (Linker (EnvironmentFor value))
|
||||
, Reader (ModuleTable term)
|
||||
, State (ModuleTable (EnvironmentFor value))
|
||||
] effects
|
||||
=> MonadEvaluator term value (Evaluator effects term value) where
|
||||
getGlobalEnv = Evaluator get
|
||||
@ -91,10 +91,14 @@ instance Members '[ Fail
|
||||
askModuleTable = Evaluator ask
|
||||
localModuleTable f a = Evaluator (local f (runEvaluator a))
|
||||
|
||||
putStore :: MonadEvaluator t value m => StoreFor value -> m ()
|
||||
putStore = modifyStore . const
|
||||
|
||||
-- | An evaluator of @term@s to @value@s, producing incremental results of type @a@ using a list of @effects@.
|
||||
newtype Evaluator effects term value a = Evaluator { runEvaluator :: Eff effects a }
|
||||
deriving (Applicative, Functor, Monad)
|
||||
|
||||
deriving instance Member Fail effects => MonadFail (Evaluator effects term value)
|
||||
deriving instance Member NonDetEff effects => Alternative (Evaluator effects term value)
|
||||
deriving instance Member NonDetEff effects => MonadNonDet (Evaluator effects term value)
|
||||
deriving instance Member Fresh effects => MonadFresh (Evaluator effects term value)
|
||||
|
@ -10,6 +10,7 @@ import Data.Abstract.Environment
|
||||
import Data.Abstract.FreeVariables
|
||||
import Data.Abstract.Value as Value
|
||||
import Data.Abstract.Type as Type
|
||||
import Data.Scientific (Scientific)
|
||||
import Prologue
|
||||
import Prelude hiding (fail)
|
||||
|
||||
@ -29,6 +30,9 @@ class (MonadEvaluator t v m) => MonadValue t v m where
|
||||
-- | Construct an abstract string value.
|
||||
string :: ByteString -> m v
|
||||
|
||||
-- | Construct a floating-point value.
|
||||
float :: Scientific -> m v
|
||||
|
||||
-- | Construct an abstract interface value.
|
||||
interface :: v -> m v
|
||||
|
||||
@ -57,6 +61,7 @@ instance ( FreeVariables t
|
||||
integer = pure . inj . Integer
|
||||
boolean = pure . inj . Boolean
|
||||
string = pure . inj . Value.String
|
||||
float = pure . inj . Value.Float
|
||||
interface v = inj . Value.Interface v <$> prunedEnv
|
||||
where
|
||||
-- TODO: If the set of exports is empty because no exports have been defined,
|
||||
@ -99,6 +104,7 @@ instance (Alternative m, MonadEvaluator t Type m, MonadFresh m) => MonadValue t
|
||||
integer _ = pure Int
|
||||
boolean _ = pure Bool
|
||||
string _ = pure Type.String
|
||||
float _ = pure Type.Float
|
||||
-- TODO
|
||||
interface = undefined
|
||||
|
||||
|
@ -18,7 +18,7 @@ import Control.Monad.Effect.Fail
|
||||
import Data.Abstract.Address
|
||||
import Data.Abstract.Environment
|
||||
import Data.Abstract.FreeVariables as FreeVariables
|
||||
import Data.Abstract.Linker
|
||||
import Data.Abstract.ModuleTable
|
||||
import Data.Abstract.Value
|
||||
import Data.Algebra
|
||||
import Data.Functor.Classes
|
||||
@ -83,7 +83,7 @@ require :: ( MonadAnalysis term v m
|
||||
)
|
||||
=> ModuleName
|
||||
-> m (EnvironmentFor v)
|
||||
require name = getModuleTable >>= maybe (load name) pure . linkerLookup name
|
||||
require name = getModuleTable >>= maybe (load name) pure . moduleTableLookup name
|
||||
|
||||
-- | Load another term/file and return an Effect.
|
||||
--
|
||||
@ -94,10 +94,10 @@ load :: ( MonadAnalysis term v m
|
||||
)
|
||||
=> ModuleName
|
||||
-> m (EnvironmentFor v)
|
||||
load name = askModuleTable >>= maybe notFound evalAndCache . linkerLookup name
|
||||
where notFound = fail ("cannot find " <> show name)
|
||||
load name = askModuleTable >>= maybe notFound evalAndCache . moduleTableLookup name
|
||||
where notFound = fail ("cannot load module: " <> show name)
|
||||
evalAndCache e = do
|
||||
v <- evaluateTerm e
|
||||
env <- environment v
|
||||
modifyModuleTable (linkerInsert name env)
|
||||
modifyModuleTable (moduleTableInsert name env)
|
||||
pure env
|
||||
|
@ -3,10 +3,20 @@ module Data.Abstract.FreeVariables where
|
||||
|
||||
import Prologue
|
||||
import Data.Term
|
||||
import Data.ByteString as B
|
||||
import Data.ByteString (intercalate)
|
||||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
|
||||
-- | The type of variable names.
|
||||
type Name = ByteString
|
||||
type Name = NonEmpty ByteString
|
||||
|
||||
name :: ByteString -> Name
|
||||
name x = x :| []
|
||||
|
||||
qualifiedName :: [ByteString] -> Name
|
||||
qualifiedName = NonEmpty.fromList
|
||||
|
||||
friendlyName :: Name -> ByteString
|
||||
friendlyName xs = intercalate "." (NonEmpty.toList xs)
|
||||
|
||||
|
||||
-- | Types which can contain unbound variables.
|
||||
@ -31,8 +41,10 @@ freeVariables1 = liftFreeVariables freeVariables
|
||||
freeVariable :: FreeVariables term => term -> Name
|
||||
freeVariable term = let [n] = toList (freeVariables term) in n
|
||||
|
||||
qualifiedName :: FreeVariables term => term -> Name
|
||||
qualifiedName term = let names = toList (freeVariables term) in B.intercalate "." names
|
||||
-- TODO: Need a dedicated concept of qualified names outside of freevariables (a
|
||||
-- Set) b/c you can have something like `a.a.b.a`
|
||||
-- qualifiedName :: FreeVariables term => term -> Name
|
||||
-- qualifiedName term = let names = toList (freeVariables term) in B.intercalate "." names
|
||||
|
||||
instance (FreeVariables1 syntax, Functor syntax) => FreeVariables (Term syntax ann) where
|
||||
freeVariables = cata (liftFreeVariables id)
|
||||
|
@ -1,18 +0,0 @@
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
module Data.Abstract.Linker where
|
||||
|
||||
import Data.Semigroup
|
||||
import GHC.Generics
|
||||
import Data.ByteString
|
||||
import qualified Data.Map as Map
|
||||
|
||||
type ModuleName = ByteString
|
||||
|
||||
newtype Linker a = Linker { unLinker :: Map.Map ModuleName a }
|
||||
deriving (Eq, Foldable, Functor, Generic1, Monoid, Ord, Semigroup, Show, Traversable)
|
||||
|
||||
linkerLookup :: ModuleName -> Linker a -> Maybe a
|
||||
linkerLookup k = Map.lookup k . unLinker
|
||||
|
||||
linkerInsert :: ModuleName -> a -> Linker a -> Linker a
|
||||
linkerInsert k v Linker{..} = Linker (Map.insert k v unLinker)
|
24
src/Data/Abstract/ModuleTable.hs
Normal file
24
src/Data/Abstract/ModuleTable.hs
Normal file
@ -0,0 +1,24 @@
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
module Data.Abstract.ModuleTable
|
||||
( ModuleName
|
||||
, ModuleTable (..)
|
||||
, moduleTableLookup
|
||||
, moduleTableInsert
|
||||
) where
|
||||
|
||||
import Data.Abstract.FreeVariables
|
||||
import Data.Semigroup
|
||||
import GHC.Generics
|
||||
import qualified Data.Map as Map
|
||||
|
||||
|
||||
type ModuleName = Name
|
||||
|
||||
newtype ModuleTable a = ModuleTable { unModuleTable :: Map.Map ModuleName a }
|
||||
deriving (Eq, Foldable, Functor, Generic1, Monoid, Ord, Semigroup, Show, Traversable)
|
||||
|
||||
moduleTableLookup :: ModuleName -> ModuleTable a -> Maybe a
|
||||
moduleTableLookup k = Map.lookup k . unModuleTable
|
||||
|
||||
moduleTableInsert :: ModuleName -> a -> ModuleTable a -> ModuleTable a
|
||||
moduleTableInsert k v ModuleTable{..} = ModuleTable (Map.insert k v unModuleTable)
|
@ -13,6 +13,7 @@ data Type
|
||||
| Bool -- ^ Primitive boolean type.
|
||||
| String -- ^ Primitive string type.
|
||||
| Unit -- ^ The unit type.
|
||||
| Float -- ^ Floating-point type.
|
||||
| Type :-> Type -- ^ Binary function types.
|
||||
| Var TName -- ^ A type variable.
|
||||
| Product [Type] -- ^ N-ary products.
|
||||
|
@ -8,8 +8,9 @@ import Data.Abstract.FreeVariables
|
||||
import Data.Abstract.Live
|
||||
import qualified Data.Abstract.Type as Type
|
||||
import qualified Data.Set as Set
|
||||
import Data.Scientific (Scientific)
|
||||
import Prologue
|
||||
import Prelude hiding (Integer, String, fail)
|
||||
import Prelude hiding (Float, Integer, String, fail)
|
||||
import qualified Prelude
|
||||
|
||||
type ValueConstructors location
|
||||
@ -17,6 +18,7 @@ type ValueConstructors location
|
||||
, Interface location
|
||||
, Unit
|
||||
, Boolean
|
||||
, Float
|
||||
, Integer
|
||||
, String
|
||||
]
|
||||
@ -80,6 +82,14 @@ instance Eq1 String where liftEq = genericLiftEq
|
||||
instance Ord1 String where liftCompare = genericLiftCompare
|
||||
instance Show1 String where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | Float values.
|
||||
newtype Float term = Float Scientific
|
||||
deriving (Eq, Generic1, Ord, Show)
|
||||
|
||||
instance Eq1 Float where liftEq = genericLiftEq
|
||||
instance Ord1 Float where liftCompare = genericLiftCompare
|
||||
instance Show1 Float where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | The environment for an abstract value type.
|
||||
type EnvironmentFor v = Environment (LocationFor v) v
|
||||
|
||||
|
@ -6,6 +6,7 @@ module Data.Algebra
|
||||
, OpenRAlgebra
|
||||
, Subterm(..)
|
||||
, SubtermAlgebra
|
||||
, embedSubterm
|
||||
, foldSubterms
|
||||
, fToR
|
||||
, fToOpenR
|
||||
@ -13,7 +14,10 @@ module Data.Algebra
|
||||
, openFToOpenR
|
||||
) where
|
||||
|
||||
import Data.Functor.Foldable (Base, Recursive(project))
|
||||
import Data.Functor.Foldable ( Base
|
||||
, Corecursive(embed)
|
||||
, Recursive(project)
|
||||
)
|
||||
|
||||
-- | An F-algebra on some 'Recursive' type @t@.
|
||||
--
|
||||
@ -51,6 +55,9 @@ type SubtermAlgebra f t a = f (Subterm t a) -> a
|
||||
foldSubterms :: Recursive t => SubtermAlgebra (Base t) t a -> t -> a
|
||||
foldSubterms algebra = go where go = algebra . fmap (Subterm <*> go) . project
|
||||
|
||||
-- | Extract a term from said term's 'Base' functor populated with 'Subterm' fields.
|
||||
embedSubterm :: Corecursive t => Base t (Subterm t a) -> t
|
||||
embedSubterm e = embed (subterm <$> e)
|
||||
|
||||
-- | Promote an 'FAlgebra' into an 'RAlgebra' (by dropping the original parameter).
|
||||
fToR :: Functor (Base t) => FAlgebra (Base t) a -> RAlgebra (Base t) t a
|
||||
|
@ -22,7 +22,7 @@ import Data.Aeson
|
||||
import Data.Bifoldable
|
||||
import Data.Bifunctor
|
||||
import Data.Bitraversable
|
||||
import Data.Foldable (asum, toList)
|
||||
import Data.Foldable (asum)
|
||||
import Data.Functor.Classes
|
||||
import Data.Functor.Foldable hiding (fold)
|
||||
import Data.JSON.Fields
|
||||
@ -89,8 +89,8 @@ diffPatch diff = case unDiff diff of
|
||||
|
||||
diffPatches :: (Foldable syntax, Functor syntax) => Diff syntax ann1 ann2 -> [Patch (TermF syntax ann1 (Diff syntax ann1 ann2)) (TermF syntax ann2 (Diff syntax ann1 ann2))]
|
||||
diffPatches = para $ \ diff -> case diff of
|
||||
Patch patch -> bimap (fmap fst) (fmap fst) patch : bifoldMap (foldMap (toList . diffPatch . fst)) (foldMap (toList . diffPatch . fst)) patch
|
||||
Merge merge -> foldMap (toList . diffPatch . fst) merge
|
||||
Patch patch -> bimap (fmap fst) (fmap fst) patch : bifoldMap (foldMap snd) (foldMap snd) patch
|
||||
Merge merge -> foldMap snd merge
|
||||
|
||||
|
||||
-- | Recover the before state of a diff.
|
||||
|
@ -5,7 +5,6 @@ import Control.Monad.Fail
|
||||
import Data.Abstract.Environment
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.AST
|
||||
import Data.ByteString.Char8 (unpack)
|
||||
import Data.Range
|
||||
import Data.Record
|
||||
import Data.Span
|
||||
@ -100,7 +99,7 @@ infixContext context left right operators = uncurry (&) <$> postContextualizeThr
|
||||
-- Common
|
||||
|
||||
-- | An identifier of some other construct, whether a containing declaration (e.g. a class name) or a reference (e.g. a variable).
|
||||
newtype Identifier a = Identifier ByteString
|
||||
newtype Identifier a = Identifier Name
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Identifier where liftEq = genericLiftEq
|
||||
@ -110,24 +109,11 @@ instance Show1 Identifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Identifier where
|
||||
eval (Identifier name) = do
|
||||
env <- askLocalEnv
|
||||
maybe (fail ("free variable: " <> unpack name)) deref (envLookup name env)
|
||||
maybe (fail ("free variable: " <> show name)) deref (envLookup name env)
|
||||
|
||||
instance FreeVariables1 Identifier where
|
||||
liftFreeVariables _ (Identifier x) = point x
|
||||
|
||||
newtype QualifiedIdentifier a = QualifiedIdentifier a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||
|
||||
instance Eq1 QualifiedIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QualifiedIdentifier where
|
||||
eval (QualifiedIdentifier xs) = do
|
||||
env <- askLocalEnv
|
||||
let name = qualifiedName (subterm xs)
|
||||
maybe (fail ("free variable: " <> unpack name)) deref (envLookup name env)
|
||||
|
||||
|
||||
newtype Program a = Program [a]
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||
@ -145,7 +131,7 @@ instance Evaluatable Program where
|
||||
eval' (x:xs) = do
|
||||
_ <- subtermValue x
|
||||
env <- getGlobalEnv
|
||||
localEnv (const env) (eval' xs)
|
||||
localEnv (envUnion env) (eval' xs)
|
||||
|
||||
-- | An accessibility modifier, e.g. private, public, protected, etc.
|
||||
newtype AccessibilityModifier a = AccessibilityModifier ByteString
|
||||
|
@ -7,6 +7,7 @@ import Data.Abstract.Evaluatable
|
||||
import Diffing.Algorithm
|
||||
import qualified Data.Map as Map
|
||||
import Data.ByteString as B
|
||||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
|
||||
data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a }
|
||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||
@ -209,6 +210,7 @@ instance Show1 Comprehension where liftShowsPrec = genericLiftShowsPrec
|
||||
-- TODO: Implement Eval instance for Comprehension
|
||||
instance Evaluatable Comprehension
|
||||
|
||||
|
||||
-- | Qualified Import declarations (symbols are qualified in calling environment).
|
||||
data QualifiedImport a = QualifiedImport { qualifiedImportFrom :: !a, qualifiedImportAlias :: !a, qualifiedImportSymbols :: ![(Name, Name)]}
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||
@ -219,11 +221,11 @@ instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QualifiedImport where
|
||||
eval (QualifiedImport from alias xs) = do
|
||||
importedEnv <- withGlobalEnv mempty (require (qualifiedName (subterm from)))
|
||||
importedEnv <- withGlobalEnv mempty (require (freeVariable (subterm from)))
|
||||
modifyGlobalEnv (flip (Map.foldrWithKey copy) (unEnvironment importedEnv))
|
||||
unit
|
||||
where
|
||||
prefix = qualifiedName (subterm alias) <> "."
|
||||
prefix = freeVariable (subterm alias)
|
||||
symbols = Map.fromList xs
|
||||
copy = if Map.null symbols then qualifyInsert else directInsert
|
||||
qualifyInsert k v rest = envInsert (prefix <> k) v rest
|
||||
@ -240,8 +242,8 @@ instance Show1 QualifiedExport where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable QualifiedExport where
|
||||
eval (QualifiedExport from exportSymbols) = do
|
||||
-- If there's a from clause, require the module and export its symbols
|
||||
let moduleName = qualifiedName (subterm from)
|
||||
if not (B.null moduleName) then do
|
||||
let moduleName = freeVariable (subterm from)
|
||||
if not (B.null $ NonEmpty.head moduleName) then do
|
||||
importedEnv <- withGlobalEnv mempty (require moduleName)
|
||||
|
||||
-- Look up addresses in importedEnv and insert the aliases with addresses into the exports.
|
||||
@ -255,7 +257,8 @@ instance Evaluatable QualifiedExport where
|
||||
|
||||
unit
|
||||
|
||||
-- | Import declarations (symbols are added directly to calling environment).
|
||||
|
||||
-- | Import declarations (symbols are added directly to the calling env).
|
||||
--
|
||||
-- If symbols is empty, just import the module for its side effects.
|
||||
data Import a = Import { importFrom :: !a, importSymbols :: ![(Name, Name)] }
|
||||
@ -267,19 +270,17 @@ instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Import where
|
||||
eval (Import from xs) = do
|
||||
importedEnv <- withGlobalEnv mempty (require (qualifiedName (subterm from)))
|
||||
modifyGlobalEnv (flip (Map.foldrWithKey copy) (unEnvironment importedEnv))
|
||||
importedEnv <- withGlobalEnv mempty (require (freeVariable (subterm from)))
|
||||
modifyGlobalEnv (flip (Map.foldrWithKey directInsert) (unEnvironment importedEnv))
|
||||
unit
|
||||
where
|
||||
symbols = Map.fromList xs
|
||||
copy = if Map.null symbols then qualifyInsert else directInsert
|
||||
qualifyInsert k v rest = envInsert k v rest
|
||||
directInsert k v rest = maybe rest (\symAlias -> envInsert symAlias v rest) (Map.lookup k symbols)
|
||||
|
||||
-- | A wildcard import
|
||||
-- | A wildcard import (all symbols are added directly to the calling env)
|
||||
--
|
||||
-- Import a module updating the importing environments.
|
||||
data WildcardImport a = WildcardImport { wildcardImportFrom :: !a, wildcardImportSymbol :: !a }
|
||||
data WildcardImport a = WildcardImport { wildcardImportFrom :: !a, wildcardImportToken :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||
|
||||
instance Eq1 WildcardImport where liftEq = genericLiftEq
|
||||
@ -288,7 +289,7 @@ instance Show1 WildcardImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable WildcardImport where
|
||||
eval (WildcardImport from _) = do
|
||||
importedEnv <- withGlobalEnv mempty (require (qualifiedName (subterm from)))
|
||||
importedEnv <- withGlobalEnv mempty (require (freeVariable (subterm from)))
|
||||
modifyGlobalEnv (flip (Map.foldrWithKey envInsert) (unEnvironment importedEnv))
|
||||
unit
|
||||
|
||||
|
@ -1,10 +1,15 @@
|
||||
{-# LANGUAGE DataKinds, DeriveAnyClass, DeriveGeneric, MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE DataKinds, DeriveAnyClass, DeriveGeneric, MultiParamTypeClasses, TypeApplications #-}
|
||||
module Data.Syntax.Literal where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.ByteString.Char8 (readInteger)
|
||||
import Data.ByteString.Char8 (readInteger, unpack)
|
||||
import qualified Data.ByteString.Char8 as B
|
||||
import Data.Monoid (Endo (..), appEndo)
|
||||
import Data.Scientific (Scientific)
|
||||
import Diffing.Algorithm
|
||||
import Prelude hiding (Float, fail)
|
||||
import Prologue hiding (Set)
|
||||
import Text.Read (readMaybe)
|
||||
|
||||
-- Boolean
|
||||
|
||||
@ -45,16 +50,52 @@ instance Evaluatable Data.Syntax.Literal.Integer where
|
||||
-- TODO: Consider a Numeric datatype with FloatingPoint/Integral/etc constructors.
|
||||
|
||||
-- | A literal float of unspecified width.
|
||||
newtype Float a = Float { floatContent :: ByteString }
|
||||
newtype Float a = Float { floatContent :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Float where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Float where liftCompare = genericLiftCompare
|
||||
instance Show1 Data.Syntax.Literal.Float where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Float
|
||||
instance Evaluatable Data.Syntax.Literal.Float
|
||||
-- | Ensures that numbers of the form '.52' are parsed correctly. Most languages need this.
|
||||
padWithLeadingZero :: ByteString -> ByteString
|
||||
padWithLeadingZero b
|
||||
| fmap fst (B.uncons b) == Just '.' = B.cons '0' b
|
||||
| otherwise = b
|
||||
|
||||
-- | As @padWithLeadingZero@, but on the end. Not all languages need this.
|
||||
padWithTrailingZero :: ByteString -> ByteString
|
||||
padWithTrailingZero b
|
||||
| fmap snd (B.unsnoc b) == Just '.' = B.snoc b '0'
|
||||
| otherwise = b
|
||||
|
||||
-- | Removes underscores in numeric literals. Python 3 and Ruby support this, whereas Python 2, JS, and Go do not.
|
||||
removeUnderscores :: ByteString -> ByteString
|
||||
removeUnderscores = B.filter (/= '_')
|
||||
|
||||
-- | Strip suffixes from floating-point literals so as to handle Python's
|
||||
-- TODO: tree-sitter-python needs some love so that it parses j-suffixed floats as complexen
|
||||
dropAlphaSuffix :: ByteString -> ByteString
|
||||
dropAlphaSuffix = B.takeWhile (\x -> x `notElem` ("lLjJiI" :: [Char]))
|
||||
|
||||
-- | This is the shared function that munges a bytestring representation of a float
|
||||
-- so that it can be parsed to a @Scientific@ later. It takes as its arguments a list of functions, which
|
||||
-- will be some combination of the above 'ByteString -> ByteString' functions. This is meant
|
||||
-- to be called from an @Assignment@, hence the @MonadFail@ constraint. Caveat: the list is
|
||||
-- order-dependent; the rightmost function will be applied first.
|
||||
normalizeFloatString :: MonadFail m => [ByteString -> ByteString] -> ByteString -> m (Float a)
|
||||
normalizeFloatString preds val =
|
||||
let munger = appEndo (foldMap Endo preds)
|
||||
in case readMaybe @Scientific (unpack (munger val)) of
|
||||
Nothing -> fail ("Invalid floating-point value: " <> show val)
|
||||
Just _ -> pure (Float val)
|
||||
|
||||
instance Evaluatable Data.Syntax.Literal.Float where
|
||||
eval (Float s) = do
|
||||
sci <- case readMaybe (unpack s) of
|
||||
Just s -> pure s
|
||||
Nothing -> fail ("Bug: non-normalized float string: " <> show s)
|
||||
float sci
|
||||
|
||||
-- Rational literals e.g. `2/3r`
|
||||
newtype Rational a = Rational ByteString
|
||||
|
@ -6,11 +6,16 @@ module Language.Go.Assignment
|
||||
, Term
|
||||
) where
|
||||
|
||||
import Prologue
|
||||
import Assigning.Assignment hiding (Assignment, Error)
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import Data.Abstract.FreeVariables
|
||||
import Data.ByteString as B
|
||||
import Data.Record
|
||||
import Data.Syntax (contextualize, emptyTerm, parseError, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1)
|
||||
import Language.Go.Grammar as Grammar
|
||||
import Language.Go.Syntax as Go.Syntax
|
||||
import Language.Go.Type as Go.Type
|
||||
import Prologue
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import qualified Data.Syntax as Syntax
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
@ -19,15 +24,14 @@ import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Syntax.Type as Type
|
||||
import qualified Data.Term as Term
|
||||
import Language.Go.Grammar as Grammar
|
||||
import Language.Go.Syntax as Go.Syntax
|
||||
import Language.Go.Type as Go.Type
|
||||
|
||||
type Syntax =
|
||||
'[ Comment.Comment
|
||||
, Declaration.Constructor
|
||||
, Declaration.Function
|
||||
, Declaration.Import
|
||||
, Declaration.QualifiedImport
|
||||
, Declaration.WildcardImport
|
||||
, Declaration.Method
|
||||
, Declaration.MethodSignature
|
||||
, Declaration.Module
|
||||
@ -221,13 +225,13 @@ element :: Assignment
|
||||
element = symbol Element *> children expression
|
||||
|
||||
fieldIdentifier :: Assignment
|
||||
fieldIdentifier = makeTerm <$> symbol FieldIdentifier <*> (Syntax.Identifier <$> source)
|
||||
fieldIdentifier = makeTerm <$> symbol FieldIdentifier <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
floatLiteral :: Assignment
|
||||
floatLiteral = makeTerm <$> symbol FloatLiteral <*> (Literal.Float <$> source)
|
||||
floatLiteral = makeTerm <$> symbol FloatLiteral <*> (source >>= Literal.normalizeFloatString [Literal.padWithLeadingZero, Literal.dropAlphaSuffix])
|
||||
|
||||
identifier :: Assignment
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> source)
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
imaginaryLiteral :: Assignment
|
||||
imaginaryLiteral = makeTerm <$> symbol ImaginaryLiteral <*> (Literal.Complex <$> source)
|
||||
@ -242,7 +246,7 @@ literalValue :: Assignment
|
||||
literalValue = makeTerm <$> symbol LiteralValue <*> children (manyTerm expression)
|
||||
|
||||
packageIdentifier :: Assignment
|
||||
packageIdentifier = makeTerm <$> symbol PackageIdentifier <*> (Syntax.Identifier <$> source)
|
||||
packageIdentifier = makeTerm <$> symbol PackageIdentifier <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
parenthesizedType :: Assignment
|
||||
parenthesizedType = makeTerm <$> symbol Grammar.ParenthesizedType <*> children (Type.Parenthesized <$> expression)
|
||||
@ -254,7 +258,7 @@ runeLiteral :: Assignment
|
||||
runeLiteral = makeTerm <$> symbol Grammar.RuneLiteral <*> (Go.Syntax.Rune <$> source)
|
||||
|
||||
typeIdentifier :: Assignment
|
||||
typeIdentifier = makeTerm <$> symbol TypeIdentifier <*> (Syntax.Identifier <$> source)
|
||||
typeIdentifier = makeTerm <$> symbol TypeIdentifier <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
|
||||
-- Primitive Types
|
||||
@ -369,7 +373,7 @@ expressionSwitchStatement :: Assignment
|
||||
expressionSwitchStatement = makeTerm <$> symbol ExpressionSwitchStatement <*> children (Statement.Match <$> (makeTerm <$> location <*> manyTermsTill expression (void (symbol ExpressionCaseClause)) <|> emptyTerm) <*> expressions)
|
||||
|
||||
fallThroughStatement :: Assignment
|
||||
fallThroughStatement = makeTerm <$> symbol FallthroughStatement <*> (Statement.Pattern <$> (makeTerm <$> location <*> (Syntax.Identifier <$> source)) <*> emptyTerm)
|
||||
fallThroughStatement = makeTerm <$> symbol FallthroughStatement <*> (Statement.Pattern <$> (makeTerm <$> location <*> (Syntax.Identifier <$> (name <$> source))) <*> emptyTerm)
|
||||
|
||||
functionDeclaration :: Assignment
|
||||
functionDeclaration = makeTerm <$> (symbol FunctionDeclaration <|> symbol FuncLiteral) <*> children (mkFunctionDeclaration <$> (term identifier <|> emptyTerm) <*> manyTerm parameters <*> (term types <|> term identifier <|> term returnParameters <|> emptyTerm) <*> (term block <|> emptyTerm))
|
||||
@ -380,10 +384,27 @@ functionDeclaration = makeTerm <$> (symbol FunctionDeclaration <|> symbol FuncL
|
||||
importDeclaration :: Assignment
|
||||
importDeclaration = makeTerm'' <$> symbol ImportDeclaration <*> children (manyTerm (importSpec <|> importSpecList))
|
||||
where
|
||||
importSpec = makeTerm <$> symbol ImportSpec <*> children (namedImport <|> plainImport)
|
||||
namedImport = flip Declaration.QualifiedImport <$> expression <*> expression <*> pure []
|
||||
plainImport = Declaration.QualifiedImport <$> expression <*> emptyTerm <*> pure []
|
||||
importSpecList = makeTerm <$> symbol ImportSpecList <*> children (manyTerm (importSpec <|> comment))
|
||||
importSpec = makeTerm <$> symbol ImportSpec <*> children sideEffectImport
|
||||
<|> makeTerm <$> symbol ImportSpec <*> children dotImport
|
||||
<|> makeTerm <$> symbol ImportSpec <*> children namedImport
|
||||
<|> makeTerm <$> symbol ImportSpec <*> children plainImport
|
||||
|
||||
dotImport = symbol Dot *> source *> (Declaration.WildcardImport <$> expression <*> emptyTerm)
|
||||
sideEffectImport = symbol BlankIdentifier *> source *> (Declaration.Import <$> expression <*> pure [])
|
||||
namedImport = symbol PackageIdentifier >>= \loc -> do
|
||||
s <- source
|
||||
let alias = makeTerm loc (Syntax.Identifier (name s))
|
||||
Declaration.QualifiedImport <$> expression <*> pure alias <*> pure []
|
||||
plainImport = symbol InterpretedStringLiteral >>= \loc -> do
|
||||
s <- source
|
||||
let from = makeTerm loc (Literal.TextElement s)
|
||||
let alias = makeTerm loc (Syntax.Identifier (baseName s))
|
||||
Declaration.QualifiedImport <$> pure from <*> pure alias <*> pure []
|
||||
|
||||
baseName bs = name $ Prelude.last (B.split (toEnum (fromEnum '/')) (stripQuotes bs))
|
||||
stripQuotes = fromMaybe' (B.stripSuffix "\"") . fromMaybe' (B.stripPrefix "\"")
|
||||
fromMaybe' f x = fromMaybe x (f x)
|
||||
|
||||
indexExpression :: Assignment
|
||||
indexExpression = makeTerm <$> symbol IndexExpression <*> children (Expression.Subscript <$> expression <*> manyTerm expression)
|
||||
@ -547,7 +568,7 @@ keyedElement :: Assignment
|
||||
keyedElement = makeTerm <$> symbol KeyedElement <*> children (Literal.KeyValue <$> expression <*> expression)
|
||||
|
||||
labelName :: Assignment
|
||||
labelName = makeTerm <$> symbol LabelName <*> (Syntax.Identifier <$> source)
|
||||
labelName = makeTerm <$> symbol LabelName <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
labeledStatement :: Assignment
|
||||
labeledStatement = makeTerm <$> (symbol LabeledStatement <|> symbol LabeledStatement') <*> children (Go.Syntax.Label <$> expression <*> (expression <|> emptyTerm))
|
||||
|
@ -50,7 +50,7 @@ array :: Assignment
|
||||
array = makeTerm <$> symbol Array <*> children (Literal.Array <$> many jsonValue)
|
||||
|
||||
number :: Assignment
|
||||
number = makeTerm <$> symbol Number <*> (Literal.Float <$> source)
|
||||
number = makeTerm <$> symbol Number <*> (source >>= Literal.normalizeFloatString [Literal.padWithLeadingZero])
|
||||
|
||||
string :: Assignment
|
||||
string = makeTerm <$> symbol String <*> (Literal.TextElement <$> source)
|
||||
|
@ -6,21 +6,22 @@ module Language.PHP.Assignment
|
||||
, Term
|
||||
) where
|
||||
|
||||
import Prologue
|
||||
import Assigning.Assignment hiding (Assignment, Error)
|
||||
import Data.Record
|
||||
import qualified Data.Term as Term
|
||||
import Data.Syntax (emptyTerm, handleError, parseError, infixContext, makeTerm, makeTerm', makeTerm1, contextualize, postContextualize)
|
||||
import Language.PHP.Grammar as Grammar
|
||||
import Prologue
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import qualified Data.Abstract.FreeVariables as FV
|
||||
import qualified Data.Syntax as Syntax
|
||||
import qualified Language.PHP.Syntax as Syntax
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
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 Assigning.Assignment hiding (Assignment, Error)
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import Language.PHP.Grammar as Grammar
|
||||
import qualified Data.Term as Term
|
||||
import qualified Language.PHP.Syntax as Syntax
|
||||
|
||||
type Syntax = '[
|
||||
Comment.Comment
|
||||
@ -428,7 +429,7 @@ classConstDeclaration :: Assignment
|
||||
classConstDeclaration = makeTerm <$> symbol ClassConstDeclaration <*> children (Syntax.ClassConstDeclaration <$> (term visibilityModifier <|> emptyTerm) <*> manyTerm constElement)
|
||||
|
||||
visibilityModifier :: Assignment
|
||||
visibilityModifier = makeTerm <$> symbol VisibilityModifier <*> (Syntax.Identifier <$> source)
|
||||
visibilityModifier = makeTerm <$> symbol VisibilityModifier <*> (Syntax.Identifier <$> (FV.name <$> source))
|
||||
|
||||
constElement :: Assignment
|
||||
constElement = makeTerm <$> symbol ConstElement <*> children (Statement.Assignment [] <$> term name <*> term expression)
|
||||
@ -470,7 +471,7 @@ literal :: Assignment
|
||||
literal = integer <|> float <|> string
|
||||
|
||||
float :: Assignment
|
||||
float = makeTerm <$> symbol Float <*> (Literal.Float <$> source)
|
||||
float = makeTerm <$> symbol Float <*> (source >>= Literal.normalizeFloatString [Literal.padWithLeadingZero])
|
||||
|
||||
integer :: Assignment
|
||||
integer = makeTerm <$> symbol Integer <*> (Literal.Integer <$> source)
|
||||
@ -634,7 +635,7 @@ propertyDeclaration :: Assignment
|
||||
propertyDeclaration = makeTerm <$> symbol PropertyDeclaration <*> children (Syntax.PropertyDeclaration <$> term propertyModifier <*> someTerm propertyElement)
|
||||
|
||||
propertyModifier :: Assignment
|
||||
propertyModifier = (makeTerm <$> symbol PropertyModifier <*> children (Syntax.PropertyModifier <$> (term visibilityModifier <|> emptyTerm) <*> (term staticModifier <|> emptyTerm))) <|> term (makeTerm <$> symbol PropertyModifier <*> (Syntax.Identifier <$> source))
|
||||
propertyModifier = (makeTerm <$> symbol PropertyModifier <*> children (Syntax.PropertyModifier <$> (term visibilityModifier <|> emptyTerm) <*> (term staticModifier <|> emptyTerm))) <|> term (makeTerm <$> symbol PropertyModifier <*> (Syntax.Identifier <$> (FV.name <$> source)))
|
||||
|
||||
propertyElement :: Assignment
|
||||
propertyElement = makeTerm <$> symbol PropertyElement <*> children (Statement.Assignment [] <$> term variableName <*> term propertyInitializer) <|> (symbol PropertyElement *> children (term variableName))
|
||||
@ -695,7 +696,7 @@ namespaceAliasingClause = makeTerm <$> symbol NamespaceAliasingClause <*> childr
|
||||
|
||||
-- | TODO Do something better than Identifier
|
||||
namespaceFunctionOrConst :: Assignment
|
||||
namespaceFunctionOrConst = makeTerm <$> symbol NamespaceFunctionOrConst <*> (Syntax.Identifier <$> source)
|
||||
namespaceFunctionOrConst = makeTerm <$> symbol NamespaceFunctionOrConst <*> (Syntax.Identifier <$> (FV.name <$> source))
|
||||
|
||||
globalDeclaration :: Assignment
|
||||
globalDeclaration = makeTerm <$> symbol GlobalDeclaration <*> children (Syntax.GlobalDeclaration <$> manyTerm simpleVariable')
|
||||
@ -731,7 +732,7 @@ variableName :: Assignment
|
||||
variableName = makeTerm <$> symbol VariableName <*> children (Syntax.VariableName <$> term name)
|
||||
|
||||
name :: Assignment
|
||||
name = makeTerm <$> (symbol Name <|> symbol Name') <*> (Syntax.Identifier <$> source)
|
||||
name = makeTerm <$> (symbol Name <|> symbol Name') <*> (Syntax.Identifier <$> (FV.name <$> source))
|
||||
|
||||
functionStaticDeclaration :: Assignment
|
||||
functionStaticDeclaration = makeTerm <$> symbol FunctionStaticDeclaration <*> children (Declaration.VariableDeclaration <$> manyTerm staticVariableDeclaration)
|
||||
|
@ -7,10 +7,12 @@ module Language.Python.Assignment
|
||||
) where
|
||||
|
||||
import Assigning.Assignment hiding (Assignment, Error)
|
||||
import Data.Abstract.FreeVariables
|
||||
import Data.Functor (void)
|
||||
import Data.List.NonEmpty (some1)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.Record
|
||||
import Data.Semigroup
|
||||
import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize)
|
||||
import Data.Union
|
||||
import GHC.Stack
|
||||
@ -78,7 +80,6 @@ type Syntax =
|
||||
, Syntax.Empty
|
||||
, Syntax.Error
|
||||
, Syntax.Identifier
|
||||
, Syntax.QualifiedIdentifier
|
||||
, Syntax.Program
|
||||
, Type.Annotation
|
||||
, []
|
||||
@ -126,7 +127,6 @@ expressionChoices =
|
||||
, deleteStatement
|
||||
, dictionary
|
||||
, dictionarySplat
|
||||
, dottedName
|
||||
, ellipsis
|
||||
, exceptClause
|
||||
, execStatement
|
||||
@ -182,10 +182,10 @@ expressionList :: Assignment
|
||||
expressionList = makeTerm'' <$> symbol ExpressionList <*> children (someTerm expression)
|
||||
|
||||
listSplat :: Assignment
|
||||
listSplat = makeTerm <$> symbol ListSplat <*> (Syntax.Identifier <$> source)
|
||||
listSplat = makeTerm <$> symbol ListSplat <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
dictionarySplat :: Assignment
|
||||
dictionarySplat = makeTerm <$> symbol DictionarySplat <*> (Syntax.Identifier <$> source)
|
||||
dictionarySplat = makeTerm <$> symbol DictionarySplat <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
keywordArgument :: Assignment
|
||||
keywordArgument = makeTerm <$> symbol KeywordArgument <*> children (Statement.Assignment [] <$> term expression <*> term expression)
|
||||
@ -252,7 +252,7 @@ functionDefinition
|
||||
makeAsyncFunctionDeclaration loc (async', functionName', functionParameters, ty, functionBody) = makeTerm loc $ Type.Annotation (makeTerm loc $ Type.Annotation (makeTerm loc $ Declaration.Function [] functionName' functionParameters functionBody) (maybe (makeTerm loc Syntax.Empty) id ty)) async'
|
||||
|
||||
async' :: Assignment
|
||||
async' = makeTerm <$> symbol AnonAsync <*> (Syntax.Identifier <$> source)
|
||||
async' = makeTerm <$> symbol AnonAsync <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
classDefinition :: Assignment
|
||||
classDefinition = makeTerm <$> symbol ClassDefinition <*> children (Declaration.Class <$> pure [] <*> term expression <*> argumentList <*> expressions)
|
||||
@ -265,9 +265,6 @@ type' = symbol Type *> children (term expression)
|
||||
finallyClause :: Assignment
|
||||
finallyClause = makeTerm <$> symbol FinallyClause <*> children (Statement.Finally <$> expressions)
|
||||
|
||||
dottedName :: Assignment
|
||||
dottedName = makeTerm <$> symbol DottedName <*> children (Expression.ScopeResolution <$> manyTerm expression)
|
||||
|
||||
ellipsis :: Assignment
|
||||
ellipsis = makeTerm <$> token Grammar.Ellipsis <*> pure Python.Syntax.Ellipsis
|
||||
|
||||
@ -343,8 +340,17 @@ assignment' = makeTerm <$> symbol Assignment <*> children (Statement.Assignmen
|
||||
yield :: Assignment
|
||||
yield = makeTerm <$> symbol Yield <*> (Statement.Yield <$> children (term ( expression <|> emptyTerm )))
|
||||
|
||||
-- Identifiers and qualified identifiers (e.g. `a.b.c`) from things like DottedName and Attribute
|
||||
identifier :: Assignment
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> source)
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> (name <$> source))
|
||||
<|> makeQualifiedIdentifier <$> symbol Attribute <*> children (attribute <|> identifierPair)
|
||||
<|> makeQualifiedIdentifier <$> symbol DottedName <*> children (some identifier')
|
||||
<|> symbol DottedName *> children identifier
|
||||
where
|
||||
attribute = (\a b -> a <> [b]) <$> (symbol Attribute *> children (attribute <|> identifierPair)) <*> identifier'
|
||||
identifierPair = (\a b -> [a, b]) <$> identifier' <*> identifier'
|
||||
identifier' = (symbol Identifier <|> symbol Identifier') *> source
|
||||
makeQualifiedIdentifier loc xs = makeTerm loc (Syntax.Identifier (qualifiedName xs))
|
||||
|
||||
set :: Assignment
|
||||
set = makeTerm <$> symbol Set <*> children (Literal.Set <$> manyTerm expression)
|
||||
@ -365,7 +371,11 @@ concatenatedString :: Assignment
|
||||
concatenatedString = makeTerm <$> symbol ConcatenatedString <*> children (manyTerm string)
|
||||
|
||||
float :: Assignment
|
||||
float = makeTerm <$> symbol Float <*> (Literal.Float <$> source)
|
||||
float = makeTerm <$> symbol Float <*> (source >>= Literal.normalizeFloatString [ Literal.padWithLeadingZero
|
||||
, Literal.padWithTrailingZero
|
||||
, Literal.dropAlphaSuffix
|
||||
, Literal.removeUnderscores
|
||||
])
|
||||
|
||||
integer :: Assignment
|
||||
integer = makeTerm <$> symbol Integer <*> (Literal.Integer <$> source)
|
||||
@ -375,24 +385,27 @@ comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||
|
||||
import' :: Assignment
|
||||
import' = makeTerm'' <$> symbol ImportStatement <*> children (manyTerm (aliasedImport <|> plainImport))
|
||||
<|> makeTerm <$> symbol ImportFromStatement <*> children (Declaration.QualifiedImport <$> (dottedName <|> emptyTerm) <*> emptyTerm <*> some (aliasImportSymbol <|> importSymbol))
|
||||
<|> makeTerm <$> symbol ImportFromStatement <*> children (Declaration.WildcardImport <$> dottedName <*> wildcard)
|
||||
<|> makeTerm <$> symbol ImportFromStatement <*> children (Declaration.QualifiedImport <$> (identifier <|> emptyTerm) <*> emptyTerm <*> some (aliasImportSymbol <|> importSymbol))
|
||||
<|> makeTerm <$> symbol ImportFromStatement <*> children (Declaration.WildcardImport <$> identifier <*> wildcard)
|
||||
where
|
||||
rawIdentifier = (symbol Identifier <|> symbol Identifier' <|> symbol DottedName) *> source
|
||||
rawIdentifier = (name <$> identifier') <|> (qualifiedName <$> dottedName')
|
||||
dottedName' = symbol DottedName *> children (some identifier')
|
||||
identifier' = (symbol Identifier <|> symbol Identifier') *> source
|
||||
|
||||
makeNameAliasPair from (Just alias) = (from, alias)
|
||||
makeNameAliasPair from Nothing = (from, from)
|
||||
importSymbol = makeNameAliasPair <$> rawIdentifier <*> pure Nothing
|
||||
aliasImportSymbol = symbol AliasedImport *> children (makeNameAliasPair <$> rawIdentifier <*> (Just <$> rawIdentifier))
|
||||
|
||||
wildcard = makeTerm <$> symbol WildcardImport <*> (Syntax.Identifier <$> source)
|
||||
wildcard = makeTerm <$> symbol WildcardImport <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
aliasedImport = makeImport <$> symbol AliasedImport <*> children ((,) <$> expression <*> (Just <$> expression))
|
||||
plainImport = makeImport <$> symbol DottedName <*> children ((,) <$> expressions <*> pure Nothing)
|
||||
plainImport = makeImport <$> location <*> ((,) <$> identifier <*> pure Nothing)
|
||||
makeImport loc (from, Just alias) = makeTerm loc (Declaration.QualifiedImport from alias [])
|
||||
makeImport loc (from, Nothing) = makeTerm loc (Declaration.QualifiedImport from from [])
|
||||
|
||||
assertStatement :: Assignment
|
||||
assertStatement = makeTerm <$> symbol AssertStatement <*> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier <$> source)) <*> manyTerm expression <*> emptyTerm)
|
||||
assertStatement = makeTerm <$> symbol AssertStatement <*> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier <$> (name <$> source))) <*> manyTerm expression <*> emptyTerm)
|
||||
|
||||
printStatement :: Assignment
|
||||
printStatement = do
|
||||
@ -401,25 +414,25 @@ printStatement = do
|
||||
print <- term printKeyword
|
||||
term (redirectCallTerm location print <|> printCallTerm location print)
|
||||
where
|
||||
printKeyword = makeTerm <$> symbol AnonPrint <*> (Syntax.Identifier <$> source)
|
||||
printKeyword = makeTerm <$> symbol AnonPrint <*> (Syntax.Identifier <$> (name <$> source))
|
||||
redirectCallTerm location identifier = makeTerm location <$ symbol Chevron <*> (flip Python.Syntax.Redirect <$> children (term expression) <*> term (printCallTerm location identifier))
|
||||
printCallTerm location identifier = makeTerm location <$> (Expression.Call [] identifier <$> manyTerm expression <*> emptyTerm)
|
||||
|
||||
nonlocalStatement :: Assignment
|
||||
nonlocalStatement = makeTerm <$> symbol NonlocalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonNonlocal <*> (Syntax.Identifier <$> source)) <*> manyTerm expression <*> emptyTerm)
|
||||
nonlocalStatement = makeTerm <$> symbol NonlocalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonNonlocal <*> (Syntax.Identifier <$> (name <$> source))) <*> manyTerm expression <*> emptyTerm)
|
||||
|
||||
globalStatement :: Assignment
|
||||
globalStatement = makeTerm <$> symbol GlobalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonGlobal <*> (Syntax.Identifier <$> source)) <*> manyTerm expression <*> emptyTerm)
|
||||
globalStatement = makeTerm <$> symbol GlobalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonGlobal <*> (Syntax.Identifier <$> (name <$> source))) <*> manyTerm expression <*> emptyTerm)
|
||||
|
||||
await :: Assignment
|
||||
await = makeTerm <$> symbol Await <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier <$> source)) <*> manyTerm expression <*> emptyTerm)
|
||||
await = makeTerm <$> symbol Await <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier <$> (name <$> source))) <*> manyTerm expression <*> emptyTerm)
|
||||
|
||||
returnStatement :: Assignment
|
||||
returnStatement = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> term (expressionList <|> emptyTerm))
|
||||
|
||||
deleteStatement :: Assignment
|
||||
deleteStatement = makeTerm <$> symbol DeleteStatement <*> children (Expression.Call <$> pure [] <*> term deleteIdentifier <* symbol ExpressionList <*> children (manyTerm expression) <*> emptyTerm)
|
||||
where deleteIdentifier = makeTerm <$> symbol AnonDel <*> (Syntax.Identifier <$> source)
|
||||
where deleteIdentifier = makeTerm <$> symbol AnonDel <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
raiseStatement :: Assignment
|
||||
raiseStatement = makeTerm <$> symbol RaiseStatement <*> children (Statement.Throw <$> expressions)
|
||||
@ -430,7 +443,7 @@ ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> ter
|
||||
makeElif (loc, makeIf) rest = makeTerm loc (makeIf rest)
|
||||
|
||||
execStatement :: Assignment
|
||||
execStatement = makeTerm <$> symbol ExecStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> location <*> (Syntax.Identifier <$> source)) <*> manyTerm (string <|> expression) <*> emptyTerm)
|
||||
execStatement = makeTerm <$> symbol ExecStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> location <*> (Syntax.Identifier <$> (name <$> source))) <*> manyTerm (string <|> expression) <*> emptyTerm)
|
||||
|
||||
passStatement :: Assignment
|
||||
passStatement = makeTerm <$> symbol PassStatement <*> (Statement.NoOp <$> emptyTerm <* advance)
|
||||
@ -454,14 +467,7 @@ slice = makeTerm <$> symbol Slice <*> children
|
||||
<*> (term expression <|> emptyTerm))
|
||||
|
||||
call :: Assignment
|
||||
call = makeTerm <$> symbol Call <*> children (Expression.Call <$> pure [] <*> term qualifiedIdentifier <*> (symbol ArgumentList *> children (manyTerm expression) <|> someTerm comprehension) <*> emptyTerm)
|
||||
where
|
||||
qualifiedIdentifier = makeQualifiedIdentifier <$> symbol Attribute <*> children (some identifier)
|
||||
<|> plainIdentifier
|
||||
plainIdentifier = makeTerm <$> location <*> (Syntax.QualifiedIdentifier <$> identifier)
|
||||
makeQualifiedIdentifier loc [x] = makeTerm loc (Syntax.QualifiedIdentifier x)
|
||||
makeQualifiedIdentifier loc xs = makeTerm loc (Syntax.QualifiedIdentifier (makeTerm' loc (inj xs)))
|
||||
|
||||
call = makeTerm <$> symbol Call <*> children (Expression.Call <$> pure [] <*> term identifier <*> (symbol ArgumentList *> children (manyTerm expression) <|> someTerm comprehension) <*> emptyTerm)
|
||||
|
||||
boolean :: Assignment
|
||||
boolean = makeTerm <$> token Grammar.True <*> pure Literal.true
|
||||
|
@ -6,11 +6,13 @@ module Language.Ruby.Assignment
|
||||
, Term
|
||||
) where
|
||||
|
||||
import Prologue hiding (for)
|
||||
import Assigning.Assignment hiding (Assignment, Error)
|
||||
import Data.Record
|
||||
import Data.Abstract.FreeVariables
|
||||
import Data.List (elem)
|
||||
import Data.Record
|
||||
import Data.Syntax (contextualize, postContextualize, emptyTerm, parseError, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1)
|
||||
import Language.Ruby.Grammar as Grammar
|
||||
import Prologue hiding (for)
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import qualified Data.Syntax as Syntax
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
@ -19,7 +21,6 @@ import qualified Data.Syntax.Expression as Expression
|
||||
import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Term as Term
|
||||
import Language.Ruby.Grammar as Grammar
|
||||
|
||||
-- | The type of Ruby syntax.
|
||||
type Syntax = '[
|
||||
@ -156,7 +157,7 @@ identifier =
|
||||
<|> mk BlockArgument
|
||||
<|> mk ReservedIdentifier
|
||||
<|> mk Uninterpreted
|
||||
where mk s = makeTerm <$> symbol s <*> (Syntax.Identifier <$> source)
|
||||
where mk s = makeTerm <$> symbol s <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
-- TODO: Handle interpolation in all literals that support it (strings, regexes, symbols, subshells, etc).
|
||||
literal :: Assignment
|
||||
@ -165,7 +166,7 @@ literal =
|
||||
<|> makeTerm <$> token Grammar.False <*> pure Literal.false
|
||||
<|> makeTerm <$> token Grammar.Nil <*> pure Literal.Null
|
||||
<|> makeTerm <$> symbol Grammar.Integer <*> (Literal.Integer <$> source)
|
||||
<|> makeTerm <$> symbol Grammar.Float <*> (Literal.Float <$> source)
|
||||
<|> makeTerm <$> symbol Grammar.Float <*> (source >>= Literal.normalizeFloatString [Literal.padWithLeadingZero, Literal.removeUnderscores])
|
||||
<|> makeTerm <$> symbol Grammar.Rational <*> (Literal.Rational <$> source)
|
||||
<|> makeTerm <$> symbol Grammar.Complex <*> (Literal.Complex <$> source)
|
||||
-- TODO: Do we want to represent the difference between .. and ...
|
||||
@ -187,7 +188,7 @@ keyword =
|
||||
mk KeywordFILE
|
||||
<|> mk KeywordLINE
|
||||
<|> mk KeywordENCODING
|
||||
where mk s = makeTerm <$> symbol s <*> (Syntax.Identifier <$> source)
|
||||
where mk s = makeTerm <$> symbol s <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
beginBlock :: Assignment
|
||||
beginBlock = makeTerm <$> symbol BeginBlock <*> children (Statement.ScopeEntry <$> many expression)
|
||||
@ -217,7 +218,7 @@ parameter =
|
||||
<|> mk OptionalParameter
|
||||
<|> makeTerm <$> symbol DestructuredParameter <*> children (many parameter)
|
||||
<|> expression
|
||||
where mk s = makeTerm <$> symbol s <*> (Syntax.Identifier <$> source)
|
||||
where mk s = makeTerm <$> symbol s <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
method :: Assignment
|
||||
method = makeTerm <$> symbol Method <*> children (Declaration.Method <$> pure [] <*> emptyTerm <*> expression <*> params <*> expressions')
|
||||
@ -243,12 +244,12 @@ comment :: Assignment
|
||||
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||
|
||||
alias :: Assignment
|
||||
alias = makeTerm <$> symbol Alias <*> children (Expression.Call <$> pure [] <*> name <*> some expression <*> emptyTerm)
|
||||
where name = makeTerm <$> location <*> (Syntax.Identifier <$> source)
|
||||
alias = makeTerm <$> symbol Alias <*> children (Expression.Call <$> pure [] <*> name' <*> some expression <*> emptyTerm)
|
||||
where name' = makeTerm <$> location <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
undef :: Assignment
|
||||
undef = makeTerm <$> symbol Undef <*> children (Expression.Call <$> pure [] <*> name <*> some expression <*> emptyTerm)
|
||||
where name = makeTerm <$> location <*> (Syntax.Identifier <$> source)
|
||||
undef = makeTerm <$> symbol Undef <*> children (Expression.Call <$> pure [] <*> name' <*> some expression <*> emptyTerm)
|
||||
where name' = makeTerm <$> location <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
if' :: Assignment
|
||||
if' = ifElsif If
|
||||
@ -346,7 +347,7 @@ assignment' = makeTerm <$> symbol Assignment <*> children (Statement.As
|
||||
|
||||
lhs = makeTerm <$> symbol LeftAssignmentList <*> children (many expr) <|> expr
|
||||
rhs = makeTerm <$> symbol RightAssignmentList <*> children (many expr) <|> expr
|
||||
expr = makeTerm <$> symbol RestAssignment <*> (Syntax.Identifier <$> source)
|
||||
expr = makeTerm <$> symbol RestAssignment <*> (Syntax.Identifier <$> (name <$> source))
|
||||
<|> makeTerm <$> symbol DestructuredLeftAssignment <*> children (many expr)
|
||||
<|> expression
|
||||
|
||||
@ -355,7 +356,7 @@ unary = symbol Unary >>= \ location ->
|
||||
makeTerm location . Expression.Complement <$> children ( symbol AnonTilde *> expression )
|
||||
<|> makeTerm location . Expression.Not <$> children ( symbol AnonBang *> expression )
|
||||
<|> makeTerm location . Expression.Not <$> children ( symbol AnonNot *> expression )
|
||||
<|> makeTerm location <$> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonDefinedQuestion <*> (Syntax.Identifier <$> source)) <*> some expression <*> emptyTerm)
|
||||
<|> makeTerm location <$> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonDefinedQuestion <*> (Syntax.Identifier <$> (name <$> source))) <*> some expression <*> emptyTerm)
|
||||
<|> makeTerm location . Expression.Negate <$> children ( symbol AnonMinus' *> expression )
|
||||
<|> children ( symbol AnonPlus *> expression )
|
||||
|
||||
|
@ -6,11 +6,13 @@ module Language.TypeScript.Assignment
|
||||
, Term
|
||||
) where
|
||||
|
||||
import Prologue
|
||||
import Assigning.Assignment hiding (Assignment, Error)
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import Data.Abstract.FreeVariables
|
||||
import Data.Record
|
||||
import Data.Syntax (emptyTerm, handleError, parseError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, contextualize, postContextualize)
|
||||
import Language.TypeScript.Grammar as Grammar
|
||||
import Prologue
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import qualified Data.Syntax as Syntax
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
@ -18,11 +20,10 @@ import qualified Data.Syntax.Expression as Expression
|
||||
import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Syntax.Type as Type
|
||||
import Language.TypeScript.Grammar as Grammar
|
||||
import qualified Language.TypeScript.Syntax as TypeScript.Syntax
|
||||
import qualified Data.Term as Term
|
||||
import qualified Data.ByteString as B
|
||||
import Data.Char (ord)
|
||||
import qualified Language.TypeScript.Syntax as TypeScript.Syntax
|
||||
|
||||
-- | The type of TypeScript syntax.
|
||||
type Syntax = '[
|
||||
@ -326,7 +327,7 @@ importAlias' :: Assignment
|
||||
importAlias' = makeTerm <$> symbol Grammar.ImportAlias <*> children (TypeScript.Syntax.ImportAlias <$> term identifier <*> term (identifier <|> nestedIdentifier))
|
||||
|
||||
number :: Assignment
|
||||
number = makeTerm <$> symbol Grammar.Number <*> (Literal.Float <$> source)
|
||||
number = makeTerm <$> symbol Grammar.Number <*> (source >>= Literal.normalizeFloatString [Literal.padWithLeadingZero])
|
||||
|
||||
string :: Assignment
|
||||
string = makeTerm <$> symbol Grammar.String <*> (Literal.TextElement <$> source)
|
||||
@ -338,7 +339,7 @@ false :: Assignment
|
||||
false = makeTerm <$> symbol Grammar.False <*> (Literal.false <$ source)
|
||||
|
||||
identifier :: Assignment
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> source)
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
class' :: Assignment
|
||||
class' = makeClass <$> symbol Class <*> children ((,,,,) <$> manyTerm decorator <*> term identifier <*> (symbol TypeParameters *> children (manyTerm typeParameter') <|> pure []) <*> (classHeritage' <|> pure []) <*> classBodyStatements)
|
||||
@ -391,7 +392,7 @@ jsxAttribute = makeTerm <$> symbol Grammar.JsxAttribute <*> children (TypeScript
|
||||
where jsxAttributeValue = choice [ string, jsxExpression', jsxElement', jsxFragment ]
|
||||
|
||||
propertyIdentifier :: Assignment
|
||||
propertyIdentifier = makeTerm <$> symbol PropertyIdentifier <*> (Syntax.Identifier <$> source)
|
||||
propertyIdentifier = makeTerm <$> symbol PropertyIdentifier <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
sequenceExpression :: Assignment
|
||||
sequenceExpression = makeTerm <$> symbol Grammar.SequenceExpression <*> children (Expression.SequenceExpression <$> term expression <*> term expressions)
|
||||
@ -406,7 +407,7 @@ parameter =
|
||||
<|> optionalParameter
|
||||
|
||||
accessibilityModifier' :: Assignment
|
||||
accessibilityModifier' = makeTerm <$> symbol AccessibilityModifier <*> children (Syntax.Identifier <$> source)
|
||||
accessibilityModifier' = makeTerm <$> symbol AccessibilityModifier <*> children (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
destructuringPattern :: Assignment
|
||||
destructuringPattern = object <|> array
|
||||
@ -629,10 +630,10 @@ labeledStatement :: Assignment
|
||||
labeledStatement = makeTerm <$> symbol Grammar.LabeledStatement <*> children (TypeScript.Syntax.LabeledStatement <$> statementIdentifier <*> term statement)
|
||||
|
||||
statementIdentifier :: Assignment
|
||||
statementIdentifier = makeTerm <$> symbol StatementIdentifier <*> (Syntax.Identifier <$> source)
|
||||
statementIdentifier = makeTerm <$> symbol StatementIdentifier <*> (Syntax.Identifier <$> (name <$> source))
|
||||
|
||||
importStatement :: Assignment
|
||||
importStatement = makeImportTerm <$> symbol Grammar.ImportStatement <*> children ((,) <$> importClause <*> (makeTerm <$> symbol Grammar.String <*> (Syntax.Identifier . stripQuotes <$> source)))
|
||||
importStatement = makeImportTerm <$> symbol Grammar.ImportStatement <*> children ((,) <$> importClause <*> (makeTerm <$> symbol Grammar.String <*> (Syntax.Identifier . pure . stripQuotes <$> source)))
|
||||
<|> makeImport <$> symbol Grammar.ImportStatement <*> children requireImport
|
||||
<|> makeImport <$> symbol Grammar.ImportStatement <*> children bareRequireImport
|
||||
where
|
||||
@ -661,7 +662,7 @@ importStatement = makeImportTerm <$> symbol Grammar.ImportStatement <*> children
|
||||
namespaceImport = symbol Grammar.NamespaceImport *> children ((,,) <$> pure Prelude.True <*> (Just <$> (term identifier)) <*> pure []) -- import * as name from "./foo"
|
||||
importSymbol = symbol Grammar.ImportSpecifier *> children (makeNameAliasPair <$> rawIdentifier <*> (Just <$> rawIdentifier))
|
||||
<|> symbol Grammar.ImportSpecifier *> children (makeNameAliasPair <$> rawIdentifier <*> (pure Nothing))
|
||||
rawIdentifier = (symbol Identifier <|> symbol Identifier') *> source
|
||||
rawIdentifier = (symbol Identifier <|> symbol Identifier') *> (name <$> source)
|
||||
makeNameAliasPair from (Just alias) = (from, alias)
|
||||
makeNameAliasPair from Nothing = (from, from)
|
||||
|
||||
@ -719,20 +720,19 @@ exportStatement = makeTerm <$> symbol Grammar.ExportStatement <*> children (flip
|
||||
<|> symbol Grammar.ExportSpecifier *> children (makeNameAliasPair <$> rawIdentifier <*> (pure Nothing))
|
||||
makeNameAliasPair from (Just alias) = (from, alias)
|
||||
makeNameAliasPair from Nothing = (from, from)
|
||||
rawIdentifier :: Assignment.Assignment [] Grammar ByteString
|
||||
rawIdentifier = (symbol Identifier <|> symbol Identifier') *> source
|
||||
rawIdentifier = (symbol Identifier <|> symbol Identifier') *> (name <$> source)
|
||||
-- <|> (makeExport2 <$> manyTerm decorator <*> emptyTerm <*> (pure <$> term (fromClause <|> exportClause <|> declaration <|> expression <|> identifier <|> importAlias')))))
|
||||
-- makeExport2 decorators fromClause exportClause = Declaration.QualifiedExport fromClause exportClause
|
||||
|
||||
fromClause :: Assignment
|
||||
fromClause = makeTerm <$> symbol Grammar.String <*> (Syntax.Identifier . stripQuotes <$> source)
|
||||
fromClause = makeTerm <$> symbol Grammar.String <*> (Syntax.Identifier . name . stripQuotes <$> source)
|
||||
|
||||
propertySignature :: Assignment
|
||||
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)
|
||||
|
||||
propertyName :: Assignment
|
||||
propertyName = (makeTerm <$> symbol PropertyIdentifier <*> (Syntax.Identifier <$> source)) <|> term string <|> term number <|> term computedPropertyName
|
||||
propertyName = (makeTerm <$> symbol PropertyIdentifier <*> (Syntax.Identifier <$> (name <$> source))) <|> term string <|> term number <|> term computedPropertyName
|
||||
|
||||
computedPropertyName :: Assignment
|
||||
computedPropertyName = makeTerm <$> symbol Grammar.ComputedPropertyName <*> children (TypeScript.Syntax.ComputedPropertyName <$> term expression)
|
||||
|
@ -3,10 +3,12 @@
|
||||
module Semantic.Util where
|
||||
|
||||
import Prologue
|
||||
import Analysis.Abstract.Caching
|
||||
import Analysis.Abstract.Evaluating
|
||||
import Analysis.Declaration
|
||||
import Control.Monad.IO.Class
|
||||
import Data.Abstract.Address
|
||||
import Data.Abstract.Type
|
||||
import Data.Abstract.Value
|
||||
import Data.AST
|
||||
import Data.Blob
|
||||
@ -43,6 +45,9 @@ evaluateRubyFiles paths = do
|
||||
pure $ evaluates @RubyValue (zip bs ts) (b, t)
|
||||
|
||||
-- Python
|
||||
typecheckPythonFile path = evaluateCache @Type <$>
|
||||
(file path >>= runTask . parse pythonParser)
|
||||
|
||||
evaluatePythonFile path = evaluate @PythonValue <$>
|
||||
(file path >>= runTask . parse pythonParser)
|
||||
|
||||
|
@ -47,6 +47,7 @@ import qualified Data.Syntax as Syntax
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Abstract.FreeVariables as FV
|
||||
import Data.Term
|
||||
import Data.Text as T (Text, pack)
|
||||
import qualified Data.Text.Encoding as T
|
||||
@ -256,6 +257,8 @@ type ListableSyntax = Union
|
||||
, []
|
||||
]
|
||||
|
||||
instance Listable FV.Name where
|
||||
tiers = cons1 FV.name
|
||||
|
||||
instance Listable1 Gram where
|
||||
liftTiers tiers = liftCons2 (liftTiers (liftTiers tiers)) (liftTiers (liftTiers tiers)) Gram
|
||||
|
@ -1,6 +1,7 @@
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
module Diffing.Algorithm.RWS.Spec where
|
||||
|
||||
import Data.Abstract.FreeVariables
|
||||
import Analysis.Decorator
|
||||
import Data.Array.IArray
|
||||
import Data.Bifunctor
|
||||
@ -36,7 +37,7 @@ spec = parallel $ do
|
||||
(beforeTerm diff, afterTerm diff) `shouldBe` (Just (wrap (stripTerm <$> tas)), Just (wrap (stripTerm <$> tbs)))
|
||||
|
||||
it "produces unbiased insertions within branches" $
|
||||
let (a, b) = (decorate (termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier "a")) ])), decorate (termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier "b")) ]))) in
|
||||
let (a, b) = (decorate (termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier (name "a"))) ])), decorate (termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier (name "b"))) ]))) in
|
||||
fmap (bimap stripTerm stripTerm) (rws comparableTerms (equalTerms comparableTerms) [ b ] [ a, b ]) `shouldBe` fmap (bimap stripTerm stripTerm) [ That a, These b b ]
|
||||
|
||||
where decorate = defaultFeatureVectorDecorator constructorNameAndConstantFields
|
||||
|
@ -1,15 +1,16 @@
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
module Diffing.Interpreter.Spec where
|
||||
|
||||
import Data.Abstract.FreeVariables
|
||||
import Data.Diff
|
||||
import Data.Functor.Both
|
||||
import Data.Functor.Foldable hiding (Nil)
|
||||
import Data.Functor.Listable
|
||||
import Data.Record
|
||||
import qualified Data.Syntax as Syntax
|
||||
import Data.Term
|
||||
import Data.Union
|
||||
import Diffing.Interpreter
|
||||
import qualified Data.Syntax as Syntax
|
||||
import Test.Hspec (Spec, describe, it, parallel)
|
||||
import Test.Hspec.Expectations.Pretty
|
||||
import Test.Hspec.LeanCheck
|
||||
@ -18,8 +19,8 @@ spec :: Spec
|
||||
spec = parallel $ do
|
||||
describe "diffTerms" $ do
|
||||
it "returns a replacement when comparing two unicode equivalent terms" $
|
||||
let termA = termIn Nil (inj (Syntax.Identifier "t\776"))
|
||||
termB = termIn Nil (inj (Syntax.Identifier "\7831")) in
|
||||
let termA = termIn Nil (inj (Syntax.Identifier (name "t\776")))
|
||||
termB = termIn Nil (inj (Syntax.Identifier (name "\7831"))) in
|
||||
diffTerms termA termB `shouldBe` replacing termA (termB :: Term ListableSyntax (Record '[]))
|
||||
|
||||
prop "produces correct diffs" $
|
||||
@ -31,7 +32,7 @@ spec = parallel $ do
|
||||
length (diffPatches diff) `shouldBe` 0
|
||||
|
||||
it "produces unbiased insertions within branches" $
|
||||
let term s = termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier s)) ]) :: Term ListableSyntax (Record '[])
|
||||
let term s = termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier (name s))) ]) :: Term ListableSyntax (Record '[])
|
||||
wrap = termIn Nil . inj in
|
||||
diffTerms (wrap [ term "b" ]) (wrap [ term "a", term "b" ]) `shouldBe` merge (Nil, Nil) (inj [ inserting (term "a"), merging (term "b") ])
|
||||
|
||||
|
@ -14,7 +14,7 @@ import Rendering.TOC.Spec
|
||||
import Semantic
|
||||
import Semantic.Task
|
||||
import SpecHelpers
|
||||
import Test.Hspec (Spec, describe, it, parallel, pendingWith)
|
||||
import Test.Hspec (Spec, describe, it, xit, parallel, pendingWith)
|
||||
import Test.Hspec.Expectations.Pretty
|
||||
import Test.Hspec.LeanCheck
|
||||
import Test.LeanCheck
|
||||
@ -23,22 +23,22 @@ import Test.LeanCheck
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
describe "renderToImports" $ do
|
||||
it "works for Ruby" $ do
|
||||
xit "works for Ruby" $ do
|
||||
output <- parseToImports rubyParser "test/fixtures/ruby/import-graph/app.rb"
|
||||
expected <- readFileVerbatim "test/fixtures/ruby/import-graph/app.json"
|
||||
toVerbatimOutput output `shouldBe` expected
|
||||
|
||||
it "works for Python" $ do
|
||||
xit "works for Python" $ do
|
||||
output <- parseToImports pythonParser "test/fixtures/python/import-graph/main.py"
|
||||
expected <- readFileVerbatim "test/fixtures/python/import-graph/main.json"
|
||||
toVerbatimOutput output `shouldBe` expected
|
||||
|
||||
it "works for Go" $ do
|
||||
xit "works for Go" $ do
|
||||
output <- parseToImports goParser "test/fixtures/go/import-graph/main.go"
|
||||
expected <- readFileVerbatim "test/fixtures/go/import-graph/main.json"
|
||||
toVerbatimOutput output `shouldBe` expected
|
||||
|
||||
it "works for TypeScript" $ do
|
||||
xit "works for TypeScript" $ do
|
||||
output <- parseToImports typescriptParser "test/fixtures/typescript/import-graph/app.ts"
|
||||
expected <- readFileVerbatim "test/fixtures/typescript/import-graph/app.json"
|
||||
toVerbatimOutput output `shouldBe` expected
|
||||
|
@ -3,6 +3,7 @@ module Rendering.TOC.Spec where
|
||||
|
||||
import Analysis.Decorator (constructorNameAndConstantFields)
|
||||
import Analysis.Declaration
|
||||
import Data.Abstract.FreeVariables
|
||||
import Data.Aeson
|
||||
import Data.Bifunctor
|
||||
import Data.Blob
|
||||
@ -42,6 +43,7 @@ import Test.Hspec.Expectations.Pretty
|
||||
import Test.Hspec.LeanCheck
|
||||
import Test.LeanCheck
|
||||
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
describe "tableOfContentsBy" $ do
|
||||
@ -57,9 +59,11 @@ spec = parallel $ do
|
||||
patch (fmap Deleted) (fmap Inserted) (\ as bs -> Replaced (head bs) : fmap Deleted (tail as) <> fmap Inserted (tail bs)) (bimap (foldMap pure) (foldMap pure) (p :: Patch (Term ListableSyntax Int) (Term ListableSyntax Int)))
|
||||
|
||||
prop "produces changed entries for relevant nodes containing irrelevant patches" $
|
||||
\ diff -> let diff' = merge (0, 0) (inj [bimap (const 1) (const 1) (diff :: Diff ListableSyntax Int Int)]) in
|
||||
tableOfContentsBy (\ (n `In` _) -> if n == (0 :: Int) then Just n else Nothing) diff' `shouldBe`
|
||||
replicate (length (diffPatches diff')) (Changed 0)
|
||||
\ diff -> do
|
||||
let diff' = merge (True, True) (inj [bimap (const False) (const False) (diff :: Diff ListableSyntax Bool Bool)])
|
||||
let toc = tableOfContentsBy (\ (n `In` _) -> if n then Just n else Nothing) diff'
|
||||
toc `shouldBe` if null (diffPatches diff') then []
|
||||
else [Changed True]
|
||||
|
||||
describe "diffTOC" $ do
|
||||
it "blank if there are no methods" $
|
||||
@ -188,14 +192,14 @@ programWithChange :: Term' -> Diff'
|
||||
programWithChange body = merge (programInfo, programInfo) (inj [ function' ])
|
||||
where
|
||||
function' = merge (Just (FunctionDeclaration "foo" mempty Nothing) :. emptyInfo, Just (FunctionDeclaration "foo" mempty Nothing) :. emptyInfo) (inj (Declaration.Function [] name' [] (merge (Nothing :. emptyInfo, Nothing :. emptyInfo) (inj [ inserting body ]))))
|
||||
name' = let info = Nothing :. emptyInfo in merge (info, info) (inj (Syntax.Identifier "foo"))
|
||||
name' = let info = Nothing :. emptyInfo in merge (info, info) (inj (Syntax.Identifier (name "foo")))
|
||||
|
||||
-- Return a diff where term is inserted in the program, below a function found on both sides of the diff.
|
||||
programWithChangeOutsideFunction :: Term' -> Diff'
|
||||
programWithChangeOutsideFunction term = merge (programInfo, programInfo) (inj [ function', term' ])
|
||||
where
|
||||
function' = merge (Just (FunctionDeclaration "foo" mempty Nothing) :. emptyInfo, Just (FunctionDeclaration "foo" mempty Nothing) :. emptyInfo) (inj (Declaration.Function [] name' [] (merge (Nothing :. emptyInfo, Nothing :. emptyInfo) (inj []))))
|
||||
name' = let info = Nothing :. emptyInfo in merge (info, info) (inj (Syntax.Identifier "foo"))
|
||||
name' = let info = Nothing :. emptyInfo in merge (info, info) (inj (Syntax.Identifier (name "foo")))
|
||||
term' = inserting term
|
||||
|
||||
programWithInsert :: Text -> Term' -> Diff'
|
||||
@ -211,9 +215,9 @@ programOf :: Diff' -> Diff'
|
||||
programOf diff = merge (programInfo, programInfo) (inj [ diff ])
|
||||
|
||||
functionOf :: Text -> Term' -> Term'
|
||||
functionOf name body = termIn (Just (FunctionDeclaration name mempty Nothing) :. emptyInfo) (inj (Declaration.Function [] name' [] (termIn (Nothing :. emptyInfo) (inj [body]))))
|
||||
functionOf n body = termIn (Just (FunctionDeclaration n mempty Nothing) :. emptyInfo) (inj (Declaration.Function [] name' [] (termIn (Nothing :. emptyInfo) (inj [body]))))
|
||||
where
|
||||
name' = termIn (Nothing :. emptyInfo) (inj (Syntax.Identifier (encodeUtf8 name)))
|
||||
name' = termIn (Nothing :. emptyInfo) (inj (Syntax.Identifier (name (encodeUtf8 n))))
|
||||
|
||||
programInfo :: Record '[Maybe Declaration, Range, Span]
|
||||
programInfo = Nothing :. emptyInfo
|
||||
@ -240,7 +244,7 @@ blobsForPaths :: Both FilePath -> IO BlobPair
|
||||
blobsForPaths = readFilePair . fmap ("test/fixtures/toc/" <>)
|
||||
|
||||
blankDiff :: Diff'
|
||||
blankDiff = merge (arrayInfo, arrayInfo) (inj [ inserting (termIn literalInfo (inj (Syntax.Identifier "\"a\""))) ])
|
||||
blankDiff = merge (arrayInfo, arrayInfo) (inj [ inserting (termIn literalInfo (inj (Syntax.Identifier (name "\"a\"")))) ])
|
||||
where
|
||||
arrayInfo = Nothing :. Range 0 3 :. Span (Pos 1 1) (Pos 1 5) :. Nil
|
||||
literalInfo = Nothing :. Range 1 2 :. Span (Pos 1 2) (Pos 1 4) :. Nil
|
||||
|
@ -25,11 +25,13 @@
|
||||
(
|
||||
(Integer)
|
||||
(Integer))))
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Times
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Times
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Integer)))
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Plus
|
||||
@ -78,11 +80,6 @@
|
||||
{+(KeyValue
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+})+})+})+})+}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(Times
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(Plus
|
||||
|
@ -25,11 +25,13 @@
|
||||
(
|
||||
(Integer)
|
||||
(Integer))))
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Times
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Times
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Integer)))
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Plus
|
||||
@ -40,11 +42,15 @@
|
||||
{+(LShift
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(RShift
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Plus
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})
|
||||
->(RShift
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Integer)+}) })
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(DividedBy
|
||||
@ -55,15 +61,11 @@
|
||||
{+(BXOr
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Times
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})
|
||||
->(Modulo
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Modulo
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+}) })
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Not
|
||||
@ -82,11 +84,6 @@
|
||||
{+(KeyValue
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+})+})+})+})+}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(Plus
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(LShift
|
||||
|
11
test/fixtures/go/binary-expressions.diffA-B.txt
vendored
11
test/fixtures/go/binary-expressions.diffA-B.txt
vendored
@ -22,11 +22,9 @@
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
||||
(Equal
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{+(Equal
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Not
|
||||
{+(Equal
|
||||
{+(Identifier)+}
|
||||
@ -76,6 +74,9 @@
|
||||
{+(BAnd
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{-(Equal
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Not
|
||||
{-(Equal
|
||||
{-(Identifier)-}
|
||||
|
11
test/fixtures/go/binary-expressions.diffB-A.txt
vendored
11
test/fixtures/go/binary-expressions.diffB-A.txt
vendored
@ -22,11 +22,9 @@
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
||||
(Equal
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{+(Equal
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Not
|
||||
{+(Equal
|
||||
{+(Identifier)+}
|
||||
@ -76,6 +74,9 @@
|
||||
{+(BAnd
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{-(Equal
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Not
|
||||
{-(Equal
|
||||
{-(Identifier)-}
|
||||
|
84
test/fixtures/go/channel-types.diffA-B.txt
vendored
84
test/fixtures/go/channel-types.diffA-B.txt
vendored
@ -6,38 +6,58 @@
|
||||
(Identifier)
|
||||
([])
|
||||
(
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(BidirectionalChannel
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(SendChannel
|
||||
{+(SendChannel
|
||||
{+(Constructor
|
||||
{+(Empty)+}
|
||||
{+([])+})+})+})+})+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(SendChannel
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+})+})+}
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(BidirectionalChannel
|
||||
(ReceiveChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(SendChannel
|
||||
(SendChannel
|
||||
(Constructor
|
||||
(Empty)
|
||||
([])))))
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(SendChannel
|
||||
(ReceiveChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(Type
|
||||
(Identifier)
|
||||
(ReceiveChannel
|
||||
(ReceiveChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(Type
|
||||
(Identifier)
|
||||
(BidirectionalChannel
|
||||
(Parenthesized
|
||||
(ReceiveChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })))))))
|
||||
{ (BidirectionalChannel
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})
|
||||
->(ReceiveChannel
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+}) })
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(BidirectionalChannel
|
||||
{+(Parenthesized
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+})+})+})+}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(SendChannel
|
||||
{-(SendChannel
|
||||
{-(Constructor
|
||||
{-(Empty)-}
|
||||
{-([])-})-})-})-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(SendChannel
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(ReceiveChannel
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(BidirectionalChannel
|
||||
{-(Parenthesized
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})-})-})-})))
|
||||
|
91
test/fixtures/go/channel-types.diffB-A.txt
vendored
91
test/fixtures/go/channel-types.diffB-A.txt
vendored
@ -6,38 +6,59 @@
|
||||
(Identifier)
|
||||
([])
|
||||
(
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(BidirectionalChannel
|
||||
(ReceiveChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(SendChannel
|
||||
(SendChannel
|
||||
(Constructor
|
||||
(Empty)
|
||||
([])))))
|
||||
(Type
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(SendChannel
|
||||
(ReceiveChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(Type
|
||||
(Identifier)
|
||||
(ReceiveChannel
|
||||
(ReceiveChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(Type
|
||||
(Identifier)
|
||||
(BidirectionalChannel
|
||||
(Parenthesized
|
||||
(ReceiveChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })))))))
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(BidirectionalChannel
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(SendChannel
|
||||
{+(SendChannel
|
||||
{+(Constructor
|
||||
{+(Empty)+}
|
||||
{+([])+})+})+})+})+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(SendChannel
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(ReceiveChannel
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(Type
|
||||
{+(Identifier)+}
|
||||
{+(BidirectionalChannel
|
||||
{+(Parenthesized
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+})+})+})+}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(BidirectionalChannel
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(SendChannel
|
||||
{-(SendChannel
|
||||
{-(Constructor
|
||||
{-(Empty)-}
|
||||
{-([])-})-})-})-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(SendChannel
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(ReceiveChannel
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(Type
|
||||
{-(Identifier)-}
|
||||
{-(BidirectionalChannel
|
||||
{-(Parenthesized
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})-})-})-})))
|
||||
|
@ -20,9 +20,9 @@
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
([]))
|
||||
@ -32,8 +32,10 @@
|
||||
->(Identifier) }
|
||||
([])
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)))
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
|
@ -20,9 +20,9 @@
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
([]))
|
||||
@ -32,8 +32,10 @@
|
||||
->(Identifier) }
|
||||
([])
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)))
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
|
@ -18,9 +18,9 @@
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
([]))
|
||||
@ -29,8 +29,10 @@
|
||||
(Identifier)
|
||||
([])
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)))
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
|
@ -18,9 +18,9 @@
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
([]))
|
||||
@ -29,8 +29,10 @@
|
||||
(Identifier)
|
||||
([])
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)))
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
|
10
test/fixtures/go/function-literals.diffA-B.txt
vendored
10
test/fixtures/go/function-literals.diffA-B.txt
vendored
@ -16,10 +16,12 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
||||
(Return
|
||||
(
|
||||
(Integer)
|
||||
|
10
test/fixtures/go/function-literals.diffB-A.txt
vendored
10
test/fixtures/go/function-literals.diffB-A.txt
vendored
@ -16,10 +16,12 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
||||
(Return
|
||||
(
|
||||
(Integer)
|
||||
|
@ -14,8 +14,10 @@
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)))
|
||||
(Return
|
||||
(
|
||||
(Integer)
|
||||
|
@ -14,8 +14,10 @@
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)))
|
||||
(Return
|
||||
(
|
||||
(Integer)
|
||||
|
23
test/fixtures/go/function-types.diffA-B.txt
vendored
23
test/fixtures/go/function-types.diffA-B.txt
vendored
@ -10,8 +10,9 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Function
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
||||
(Type
|
||||
@ -19,13 +20,17 @@
|
||||
->(Identifier) }
|
||||
(Function
|
||||
(
|
||||
{-(Identifier)-}
|
||||
(Identifier)
|
||||
{+(Identifier)+})
|
||||
(
|
||||
{-(
|
||||
{-(Identifier)-})-}
|
||||
(
|
||||
(Identifier))
|
||||
{+(
|
||||
{+(Identifier)+})+})
|
||||
(
|
||||
(
|
||||
{+(BidirectionalChannel
|
||||
{+(Identifier)+})+})+}
|
||||
{-(Identifier)-}
|
||||
(Identifier))
|
||||
{+(Identifier)+})+}
|
||||
{-(Identifier)-})
|
||||
(
|
||||
(Identifier)))
|
||||
(Empty))))))
|
||||
|
23
test/fixtures/go/function-types.diffB-A.txt
vendored
23
test/fixtures/go/function-types.diffB-A.txt
vendored
@ -10,8 +10,9 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Function
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
||||
(Type
|
||||
@ -19,13 +20,17 @@
|
||||
->(Identifier) }
|
||||
(Function
|
||||
(
|
||||
{-(Identifier)-}
|
||||
(Identifier)
|
||||
{+(Identifier)+})
|
||||
(
|
||||
{+(Identifier)+}
|
||||
{-(
|
||||
{-(Identifier)-})-}
|
||||
(
|
||||
(Identifier))
|
||||
{+(
|
||||
{+(Identifier)+})+})
|
||||
(
|
||||
(
|
||||
{+(Identifier)+}
|
||||
{-(BidirectionalChannel
|
||||
{-(Identifier)-})-})-}
|
||||
(Identifier))
|
||||
{-(Identifier)-})-})
|
||||
(
|
||||
(Identifier)))
|
||||
(Empty))))))
|
||||
|
15
test/fixtures/go/function-types.parseA.txt
vendored
15
test/fixtures/go/function-types.parseA.txt
vendored
@ -9,15 +9,20 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Function
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier))
|
||||
(Identifier)))
|
||||
(Type
|
||||
(Identifier)
|
||||
(Function
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)))
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)))
|
||||
(Empty))))))
|
||||
|
12
test/fixtures/go/function-types.parseB.txt
vendored
12
test/fixtures/go/function-types.parseB.txt
vendored
@ -9,17 +9,21 @@
|
||||
(Type
|
||||
(Identifier)
|
||||
(Function
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier))
|
||||
(Identifier)))
|
||||
(Type
|
||||
(Identifier)
|
||||
(Function
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)))
|
||||
(
|
||||
(
|
||||
(BidirectionalChannel
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)))
|
||||
(Empty))))))
|
||||
|
@ -2,18 +2,23 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(
|
||||
(Import
|
||||
(QualifiedImport
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Empty))
|
||||
(Import
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Empty))
|
||||
(Import
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Identifier)))
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{+(WildcardImport
|
||||
{+(TextElement)+}
|
||||
{+(Empty)+})+}
|
||||
{+(QualifiedImport
|
||||
{+(TextElement)+}
|
||||
{+(Identifier)+})+}
|
||||
{-(WildcardImport
|
||||
{-(TextElement)-}
|
||||
{-(Empty)-})-}
|
||||
{-(QualifiedImport
|
||||
{-(TextElement)-}
|
||||
{-(Identifier)-})-})
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -2,18 +2,23 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(
|
||||
(Import
|
||||
(QualifiedImport
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Empty))
|
||||
(Import
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Empty))
|
||||
(Import
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Identifier)))
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{+(WildcardImport
|
||||
{+(TextElement)+}
|
||||
{+(Empty)+})+}
|
||||
{+(QualifiedImport
|
||||
{+(TextElement)+}
|
||||
{+(Identifier)+})+}
|
||||
{-(WildcardImport
|
||||
{-(TextElement)-}
|
||||
{-(Empty)-})-}
|
||||
{-(QualifiedImport
|
||||
{-(TextElement)-}
|
||||
{-(Identifier)-})-})
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
|
@ -2,13 +2,13 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(
|
||||
(Import
|
||||
(QualifiedImport
|
||||
(TextElement)
|
||||
(Identifier))
|
||||
(WildcardImport
|
||||
(TextElement)
|
||||
(Empty))
|
||||
(Import
|
||||
(TextElement)
|
||||
(Empty))
|
||||
(Import
|
||||
(QualifiedImport
|
||||
(TextElement)
|
||||
(Identifier)))
|
||||
(Function
|
||||
|
@ -2,13 +2,13 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(
|
||||
(Import
|
||||
(QualifiedImport
|
||||
(TextElement)
|
||||
(Identifier))
|
||||
(WildcardImport
|
||||
(TextElement)
|
||||
(Empty))
|
||||
(Import
|
||||
(TextElement)
|
||||
(Empty))
|
||||
(Import
|
||||
(QualifiedImport
|
||||
(TextElement)
|
||||
(Identifier)))
|
||||
(Function
|
||||
|
@ -4,10 +4,10 @@
|
||||
(
|
||||
(Comment)
|
||||
(Comment)
|
||||
(Import
|
||||
(QualifiedImport
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Empty))
|
||||
(Identifier))
|
||||
(Comment))
|
||||
(Function
|
||||
(Empty)
|
||||
|
@ -4,10 +4,10 @@
|
||||
(
|
||||
(Comment)
|
||||
(Comment)
|
||||
(Import
|
||||
(QualifiedImport
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Empty))
|
||||
(Identifier))
|
||||
(Comment))
|
||||
(Function
|
||||
(Empty)
|
||||
|
@ -4,9 +4,9 @@
|
||||
(
|
||||
(Comment)
|
||||
(Comment)
|
||||
(Import
|
||||
(QualifiedImport
|
||||
(TextElement)
|
||||
(Empty))
|
||||
(Identifier))
|
||||
(Comment))
|
||||
(Function
|
||||
(Empty)
|
||||
|
@ -4,9 +4,9 @@
|
||||
(
|
||||
(Comment)
|
||||
(Comment)
|
||||
(Import
|
||||
(QualifiedImport
|
||||
(TextElement)
|
||||
(Empty))
|
||||
(Identifier))
|
||||
(Comment))
|
||||
(Function
|
||||
(Empty)
|
||||
|
@ -127,8 +127,7 @@
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)))
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier))
|
||||
([])))
|
||||
|
@ -127,8 +127,7 @@
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)))
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier))
|
||||
([])))
|
||||
|
@ -92,7 +92,6 @@
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
([])))
|
||||
|
@ -106,7 +106,6 @@
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
([])))
|
||||
|
@ -1,15 +1,16 @@
|
||||
(Program
|
||||
(Module
|
||||
(Identifier))
|
||||
(Import
|
||||
(QualifiedImport
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(WildcardImport
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Empty))
|
||||
(Import
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Empty))
|
||||
(Import
|
||||
(QualifiedImport
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Identifier))
|
||||
|
@ -1,15 +1,16 @@
|
||||
(Program
|
||||
(Module
|
||||
(Identifier))
|
||||
(Import
|
||||
(QualifiedImport
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(WildcardImport
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Empty))
|
||||
(Import
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Empty))
|
||||
(Import
|
||||
(QualifiedImport
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(Identifier))
|
||||
|
@ -1,13 +1,13 @@
|
||||
(Program
|
||||
(Module
|
||||
(Identifier))
|
||||
(Import
|
||||
(QualifiedImport
|
||||
(TextElement)
|
||||
(Identifier))
|
||||
(WildcardImport
|
||||
(TextElement)
|
||||
(Empty))
|
||||
(Import
|
||||
(TextElement)
|
||||
(Empty))
|
||||
(Import
|
||||
(QualifiedImport
|
||||
(TextElement)
|
||||
(Identifier))
|
||||
(Function
|
||||
|
@ -1,13 +1,13 @@
|
||||
(Program
|
||||
(Module
|
||||
(Identifier))
|
||||
(Import
|
||||
(QualifiedImport
|
||||
(TextElement)
|
||||
(Identifier))
|
||||
(WildcardImport
|
||||
(TextElement)
|
||||
(Empty))
|
||||
(Import
|
||||
(TextElement)
|
||||
(Empty))
|
||||
(Import
|
||||
(QualifiedImport
|
||||
(TextElement)
|
||||
(Identifier))
|
||||
(Function
|
||||
|
@ -6,11 +6,12 @@
|
||||
(Identifier)
|
||||
([])
|
||||
(
|
||||
(TypeConversion
|
||||
(Pointer
|
||||
(Identifier))
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Pointer
|
||||
(Call
|
||||
(Identifier)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty)))
|
||||
(Call
|
||||
(Pointer
|
||||
(Identifier))
|
||||
|
@ -6,11 +6,12 @@
|
||||
(Identifier)
|
||||
([])
|
||||
(
|
||||
(TypeConversion
|
||||
(Pointer
|
||||
(Identifier))
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Pointer
|
||||
(Call
|
||||
(Identifier)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty)))
|
||||
(Call
|
||||
(Pointer
|
||||
(Identifier))
|
||||
|
@ -6,10 +6,11 @@
|
||||
(Identifier)
|
||||
([])
|
||||
(
|
||||
(TypeConversion
|
||||
(Pointer
|
||||
(Identifier))
|
||||
(Identifier))
|
||||
(Pointer
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(Call
|
||||
(Pointer
|
||||
(Identifier))
|
||||
|
@ -6,10 +6,11 @@
|
||||
(Identifier)
|
||||
([])
|
||||
(
|
||||
(TypeConversion
|
||||
(Pointer
|
||||
(Identifier))
|
||||
(Identifier))
|
||||
(Pointer
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(Call
|
||||
(Pointer
|
||||
(Identifier))
|
||||
|
@ -28,7 +28,8 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier))
|
||||
(Variadic
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
|
@ -28,7 +28,8 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier))
|
||||
(Variadic
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
|
@ -25,7 +25,8 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier))
|
||||
(Variadic
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
|
@ -25,7 +25,8 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier))
|
||||
(Variadic
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
|
20
test/fixtures/javascript/export.diffA-B.txt
vendored
20
test/fixtures/javascript/export.diffA-B.txt
vendored
@ -5,18 +5,22 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty))
|
||||
{+(ImportExportSpecifier
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
(ImportExportSpecifier
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty))
|
||||
(ImportExportSpecifier
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty))
|
||||
(ImportExportSpecifier
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty))))
|
||||
{+(ImportExportSpecifier
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{-(ImportExportSpecifier
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(ImportExportSpecifier
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}))
|
||||
(Export
|
||||
(ExportClause
|
||||
{-(ImportExportSpecifier
|
||||
|
41
test/fixtures/javascript/export.diffB-A.txt
vendored
41
test/fixtures/javascript/export.diffB-A.txt
vendored
@ -5,18 +5,22 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty))
|
||||
{+(ImportExportSpecifier
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
(ImportExportSpecifier
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty))
|
||||
(ImportExportSpecifier
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty))
|
||||
(ImportExportSpecifier
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty))))
|
||||
{+(ImportExportSpecifier
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{-(ImportExportSpecifier
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(ImportExportSpecifier
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}))
|
||||
(Export
|
||||
(ExportClause
|
||||
{+(ImportExportSpecifier
|
||||
@ -133,14 +137,17 @@
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(ImportExportSpecifier
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(ImportExportSpecifier
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty)))
|
||||
{+(ImportExportSpecifier
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(ImportExportSpecifier
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{-(ImportExportSpecifier
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(ImportExportSpecifier
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})
|
||||
{ (TextElement)
|
||||
->(TextElement) }))
|
||||
|
8
test/fixtures/javascript/import.diffA-B.txt
vendored
8
test/fixtures/javascript/import.diffA-B.txt
vendored
@ -4,14 +4,14 @@
|
||||
{+(QualifiedImport
|
||||
{+(TextElement)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Import
|
||||
{+(TextElement)+})+}
|
||||
{+(Import
|
||||
{+(TextElement)+})+}
|
||||
{ (Import
|
||||
{-(TextElement)-})
|
||||
->(Import
|
||||
{+(TextElement)+}) }
|
||||
{+(Import
|
||||
{+(TextElement)+})+}
|
||||
{+(Import
|
||||
{+(TextElement)+})+}
|
||||
{+(
|
||||
{+(Import
|
||||
{+(TextElement)+})+}
|
||||
|
18
test/fixtures/python/assignment.diffA-B.txt
vendored
18
test/fixtures/python/assignment.diffA-B.txt
vendored
@ -10,18 +10,14 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Integer))
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(
|
||||
{+(Integer)+}
|
||||
{+(Integer)+})+})+}
|
||||
{-(Assignment
|
||||
{-(
|
||||
(Assignment
|
||||
{ (
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(
|
||||
{-(Integer)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Identifier)-})
|
||||
->(Identifier) }
|
||||
(
|
||||
(Integer)
|
||||
(Integer)))
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(
|
||||
|
14
test/fixtures/python/call.diffA-B.txt
vendored
14
test/fixtures/python/call.diffA-B.txt
vendored
@ -1,25 +1,19 @@
|
||||
(Program
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
{-(Identifier)-}
|
||||
(Empty))
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
{+(Identifier)+}
|
||||
(Empty))
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
{-(Identifier)-}
|
||||
(Identifier)
|
||||
{+(Identifier)+}
|
||||
(Empty))
|
||||
{+(Call
|
||||
{+(QualifiedIdentifier
|
||||
{+(
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+}
|
||||
{+(Empty)+})+})
|
||||
|
14
test/fixtures/python/call.diffB-A.txt
vendored
14
test/fixtures/python/call.diffB-A.txt
vendored
@ -1,25 +1,19 @@
|
||||
(Program
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
{+(Identifier)+}
|
||||
(Empty))
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
{-(Identifier)-}
|
||||
(Empty))
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
{-(Identifier)-}
|
||||
(Identifier)
|
||||
{+(Identifier)+}
|
||||
(Empty))
|
||||
{-(Call
|
||||
{-(QualifiedIdentifier
|
||||
{-(
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-}
|
||||
{-(Empty)-})-})
|
||||
|
9
test/fixtures/python/call.parseA.txt
vendored
9
test/fixtures/python/call.parseA.txt
vendored
@ -1,16 +1,13 @@
|
||||
(Program
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
|
18
test/fixtures/python/call.parseB.txt
vendored
18
test/fixtures/python/call.parseB.txt
vendored
@ -1,23 +1,17 @@
|
||||
(Program
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Integer)
|
||||
(Empty)))
|
||||
|
@ -27,16 +27,18 @@
|
||||
{+(Equal
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
(Not
|
||||
(Member
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
||||
{+(Not
|
||||
{+(Member
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+})+}
|
||||
{+(Not
|
||||
{+(Equal
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+})+}
|
||||
{-(Not
|
||||
{-(Member
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-})-}
|
||||
{-(Equal
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
|
@ -9,13 +9,11 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
{ (Identifier)
|
||||
->(Call
|
||||
{+(QualifiedIdentifier
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+}) })
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
|
@ -2,8 +2,7 @@
|
||||
{+(If
|
||||
{+(Identifier)+}
|
||||
{+(Call
|
||||
{+(QualifiedIdentifier
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Identifier)+})+}
|
||||
(Assignment
|
||||
@ -19,10 +18,8 @@
|
||||
{-(If
|
||||
{-(Identifier)-}
|
||||
{-(Call
|
||||
{-(QualifiedIdentifier
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Call
|
||||
{-(QualifiedIdentifier
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})-})
|
||||
|
@ -2,8 +2,7 @@
|
||||
(If
|
||||
(Identifier)
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Identifier))
|
||||
(Assignment
|
||||
|
@ -8,10 +8,8 @@
|
||||
(If
|
||||
(Identifier)
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Call
|
||||
(QualifiedIdentifier
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty))))
|
||||
|
@ -1,32 +1,26 @@
|
||||
(Program
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Class
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
([])
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{+(Identifier)+}
|
||||
{-(Integer)-}
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{+(Identifier)+}
|
||||
{-(
|
||||
{-(Integer)-}
|
||||
{-(Integer)-})-}
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
{+(
|
||||
{+(Integer)+}
|
||||
{+(Assignment
|
||||
@ -38,16 +32,13 @@
|
||||
{-(Identifier)-}
|
||||
{-(Boolean)-})-}
|
||||
{ (Decorator
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Decorator
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Decorator
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(
|
||||
{-(Integer)-}
|
||||
{-(Assignment
|
||||
|
@ -1,32 +1,26 @@
|
||||
(Program
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Class
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
([])
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{+(Integer)+}
|
||||
{-(Identifier)-}
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{+(
|
||||
{+(Integer)+}
|
||||
{+(Integer)+})+}
|
||||
{-(Identifier)-}
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Boolean)+})+}
|
||||
@ -43,16 +37,13 @@
|
||||
{-(Identifier)-})-}
|
||||
{-(Empty)-})
|
||||
->(Decorator
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Decorator
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Decorator
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(
|
||||
{+(Integer)+}
|
||||
{+(Assignment
|
||||
|
@ -1,41 +1,32 @@
|
||||
(Program
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Class
|
||||
(Identifier)
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
([])
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Integer)
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(
|
||||
(Integer)
|
||||
(Integer))
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Boolean))
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(
|
||||
(Integer)
|
||||
(Assignment
|
||||
|
@ -1,25 +1,19 @@
|
||||
(Program
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Class
|
||||
(Identifier)
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
([])
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(
|
||||
(Integer)
|
||||
(Assignment
|
||||
|
@ -1,44 +1,33 @@
|
||||
(Program
|
||||
{+(QualifiedImport
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(QualifiedImport
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(WildcardImport
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(QualifiedImport
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(QualifiedImport
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(QualifiedImport
|
||||
{+(Empty)+}
|
||||
{+(Empty)+})+}
|
||||
{-(QualifiedImport
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(QualifiedImport
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(WildcardImport
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(QualifiedImport
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(QualifiedImport
|
||||
{-(Empty)-}
|
||||
|
@ -1,44 +1,33 @@
|
||||
(Program
|
||||
{+(QualifiedImport
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(QualifiedImport
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(WildcardImport
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(QualifiedImport
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(QualifiedImport
|
||||
{+(Empty)+}
|
||||
{+(Empty)+})+}
|
||||
{-(QualifiedImport
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(QualifiedImport
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(WildcardImport
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(QualifiedImport
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(QualifiedImport
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(QualifiedImport
|
||||
{-(Empty)-}
|
||||
|
@ -1,20 +1,15 @@
|
||||
(Program
|
||||
(QualifiedImport
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(QualifiedImport
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(WildcardImport
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(QualifiedImport
|
||||
(ScopeResolution
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(QualifiedImport
|
||||
(Empty)
|
||||
|
@ -1,24 +1,18 @@
|
||||
(Program
|
||||
(QualifiedImport
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(QualifiedImport
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(WildcardImport
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(QualifiedImport
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(QualifiedImport
|
||||
(ScopeResolution
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(QualifiedImport
|
||||
(Empty)
|
||||
|
@ -7,38 +7,21 @@
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
{-(QualifiedImport
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-})
|
||||
{+(QualifiedImport
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(QualifiedImport
|
||||
{+(
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{-(
|
||||
{-(QualifiedImport
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(QualifiedImport
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-})-}
|
||||
{-(QualifiedImport
|
||||
{-(
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-})-})
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-})
|
||||
|
@ -7,38 +7,20 @@
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
{+(QualifiedImport
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+})
|
||||
{+(
|
||||
{+(QualifiedImport
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(QualifiedImport
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+})+}
|
||||
{+(QualifiedImport
|
||||
{+(
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+})+}
|
||||
(QualifiedImport
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{-(QualifiedImport
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-})-}
|
||||
{-(QualifiedImport
|
||||
{-(
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-})-})
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-})
|
||||
|
17
test/fixtures/python/import-statement.parseA.txt
vendored
17
test/fixtures/python/import-statement.parseA.txt
vendored
@ -4,24 +4,15 @@
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(QualifiedImport
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(
|
||||
(QualifiedImport
|
||||
(ScopeResolution
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(QualifiedImport
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(QualifiedImport
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))))
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
|
14
test/fixtures/python/import-statement.parseB.txt
vendored
14
test/fixtures/python/import-statement.parseB.txt
vendored
@ -7,16 +7,8 @@
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(QualifiedImport
|
||||
(ScopeResolution
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(QualifiedImport
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))))
|
||||
(Identifier)
|
||||
(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