mirror of
https://github.com/github/semantic.git
synced 2024-12-26 00:12:29 +03:00
Merge remote-tracking branch 'origin/module-resolution' into repo-import-graph
This commit is contained in:
commit
bc91a5f320
@ -241,7 +241,6 @@ test-suite test
|
|||||||
, Diffing.Interpreter.Spec
|
, Diffing.Interpreter.Spec
|
||||||
, Integration.Spec
|
, Integration.Spec
|
||||||
, Matching.Go.Spec
|
, Matching.Go.Spec
|
||||||
, Rendering.Imports.Spec
|
|
||||||
, Rendering.TOC.Spec
|
, Rendering.TOC.Spec
|
||||||
, Semantic.Spec
|
, Semantic.Spec
|
||||||
, Semantic.CLI.Spec
|
, Semantic.CLI.Spec
|
||||||
|
@ -1,4 +1,4 @@
|
|||||||
{-# LANGUAGE GeneralizedNewtypeDeriving, RankNTypes, TypeFamilies, UndecidableInstances #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving, RankNTypes, TypeFamilies, UndecidableInstances, ScopedTypeVariables #-}
|
||||||
module Analysis.Abstract.Evaluating
|
module Analysis.Abstract.Evaluating
|
||||||
( Evaluating
|
( Evaluating
|
||||||
, EvaluatingState(..)
|
, EvaluatingState(..)
|
||||||
@ -49,17 +49,18 @@ data EvaluatingState location term value = EvaluatingState
|
|||||||
, modules :: ModuleTable (Environment location value, value)
|
, modules :: ModuleTable (Environment location value, value)
|
||||||
, exports :: Exports location value
|
, exports :: Exports location value
|
||||||
, jumps :: IntMap.IntMap term
|
, jumps :: IntMap.IntMap term
|
||||||
|
, origin :: SomeOrigin term
|
||||||
}
|
}
|
||||||
|
|
||||||
deriving instance (Eq (Cell location value), Eq location, Eq term, Eq value) => Eq (EvaluatingState location term value)
|
deriving instance (Eq (Cell location value), Eq location, Eq term, Eq value, Eq (Base term ())) => Eq (EvaluatingState location term value)
|
||||||
deriving instance (Ord (Cell location value), Ord location, Ord term, Ord value) => Ord (EvaluatingState location term value)
|
deriving instance (Ord (Cell location value), Ord location, Ord term, Ord value, Ord (Base term ())) => Ord (EvaluatingState location term value)
|
||||||
deriving instance (Show (Cell location value), Show location, Show term, Show value) => Show (EvaluatingState location term value)
|
deriving instance (Show (Cell location value), Show location, Show term, Show value, Show (Base term ())) => Show (EvaluatingState location term value)
|
||||||
|
|
||||||
instance (Ord location, Semigroup (Cell location value)) => Semigroup (EvaluatingState location term value) where
|
instance (Ord location, Semigroup (Cell location value)) => Semigroup (EvaluatingState location term value) where
|
||||||
EvaluatingState e1 h1 m1 x1 j1 <> EvaluatingState e2 h2 m2 x2 j2 = EvaluatingState (e1 <> e2) (h1 <> h2) (m1 <> m2) (x1 <> x2) (j1 <> j2)
|
EvaluatingState e1 h1 m1 x1 j1 o1 <> EvaluatingState e2 h2 m2 x2 j2 o2 = EvaluatingState (e1 <> e2) (h1 <> h2) (m1 <> m2) (x1 <> x2) (j1 <> j2) (o1 <> o2)
|
||||||
|
|
||||||
instance (Ord location, Semigroup (Cell location value)) => Monoid (EvaluatingState location term value) where
|
instance (Ord location, Semigroup (Cell location value)) => Monoid (EvaluatingState location term value) where
|
||||||
mempty = EvaluatingState mempty mempty mempty mempty mempty
|
mempty = EvaluatingState mempty mempty mempty mempty mempty mempty
|
||||||
mappend = (<>)
|
mappend = (<>)
|
||||||
|
|
||||||
_environment :: Lens' (EvaluatingState location term value) (Environment location value)
|
_environment :: Lens' (EvaluatingState location term value) (Environment location value)
|
||||||
@ -77,6 +78,9 @@ _exports = lens exports (\ s e -> s {exports = e})
|
|||||||
_jumps :: Lens' (EvaluatingState location term value) (IntMap.IntMap term)
|
_jumps :: Lens' (EvaluatingState location term value) (IntMap.IntMap term)
|
||||||
_jumps = lens jumps (\ s j -> s {jumps = j})
|
_jumps = lens jumps (\ s j -> s {jumps = j})
|
||||||
|
|
||||||
|
_origin :: Lens' (EvaluatingState location term value) (SomeOrigin term)
|
||||||
|
_origin = lens origin (\ s o -> s {origin = o})
|
||||||
|
|
||||||
|
|
||||||
(.=) :: Member (State (EvaluatingState location term value)) effects => ASetter (EvaluatingState location term value) (EvaluatingState location term value) a b -> b -> Evaluating location term value effects ()
|
(.=) :: Member (State (EvaluatingState location term value)) effects => ASetter (EvaluatingState location term value) (EvaluatingState location term value) a b -> b -> Evaluating location term value effects ()
|
||||||
lens .= val = raise (modify' (lens .~ val))
|
lens .= val = raise (modify' (lens .~ val))
|
||||||
@ -126,7 +130,11 @@ instance Member (State (EvaluatingState location term value)) effects
|
|||||||
getHeap = view _heap
|
getHeap = view _heap
|
||||||
putHeap = (_heap .=)
|
putHeap = (_heap .=)
|
||||||
|
|
||||||
instance Members '[Reader (ModuleTable [Module term]), State (EvaluatingState location term value)] effects
|
instance Members '[ Reader (ModuleTable [Module term])
|
||||||
|
, State (EvaluatingState location term value)
|
||||||
|
, Reader (SomeOrigin term)
|
||||||
|
, Fail
|
||||||
|
] effects
|
||||||
=> MonadModuleTable location term value (Evaluating location term value effects) where
|
=> MonadModuleTable location term value (Evaluating location term value effects) where
|
||||||
getModuleTable = view _modules
|
getModuleTable = view _modules
|
||||||
putModuleTable = (_modules .=)
|
putModuleTable = (_modules .=)
|
||||||
@ -134,6 +142,10 @@ instance Members '[Reader (ModuleTable [Module term]), State (EvaluatingState lo
|
|||||||
askModuleTable = raise ask
|
askModuleTable = raise ask
|
||||||
localModuleTable f a = raise (local f (lower a))
|
localModuleTable f a = raise (local f (lower a))
|
||||||
|
|
||||||
|
currentModule = do
|
||||||
|
o <- raise ask
|
||||||
|
maybeFail "unable to get currentModule" $ withSomeOrigin (originModule @term) o
|
||||||
|
|
||||||
instance Members (EvaluatingEffects location term value) effects
|
instance Members (EvaluatingEffects location term value) effects
|
||||||
=> MonadEvaluator location term value (Evaluating location term value effects) where
|
=> MonadEvaluator location term value (Evaluating location term value effects) where
|
||||||
getConfiguration term = Configuration term mempty <$> getEnv <*> getHeap
|
getConfiguration term = Configuration term mempty <$> getEnv <*> getHeap
|
||||||
|
@ -11,18 +11,18 @@ import Algebra.Graph.Class
|
|||||||
import Algebra.Graph.Export.Dot
|
import Algebra.Graph.Export.Dot
|
||||||
import Control.Abstract.Analysis
|
import Control.Abstract.Analysis
|
||||||
import Data.Abstract.Evaluatable (LoadError (..))
|
import Data.Abstract.Evaluatable (LoadError (..))
|
||||||
import Data.Abstract.FreeVariables
|
|
||||||
import Data.Abstract.Module
|
import Data.Abstract.Module
|
||||||
import Data.Abstract.Origin
|
import Data.Abstract.Origin
|
||||||
|
import qualified Data.ByteString.Char8 as BC
|
||||||
import Prologue hiding (empty)
|
import Prologue hiding (empty)
|
||||||
|
|
||||||
-- | The graph of function definitions to symbols used in a given program.
|
-- | The graph of function definitions to symbols used in a given program.
|
||||||
newtype ImportGraph = ImportGraph { unImportGraph :: G.Graph Name }
|
newtype ImportGraph = ImportGraph { unImportGraph :: G.Graph FilePath }
|
||||||
deriving (Eq, Graph, Show)
|
deriving (Eq, Graph, Show)
|
||||||
|
|
||||||
-- | Render a 'ImportGraph' to a 'ByteString' in DOT notation.
|
-- | Render a 'ImportGraph' to a 'ByteString' in DOT notation.
|
||||||
renderImportGraph :: ImportGraph -> ByteString
|
renderImportGraph :: ImportGraph -> ByteString
|
||||||
renderImportGraph = export (defaultStyle friendlyName) . unImportGraph
|
renderImportGraph = export (defaultStyle BC.pack) . unImportGraph
|
||||||
|
|
||||||
newtype ImportGraphing m (effects :: [* -> *]) a = ImportGraphing (m effects a)
|
newtype ImportGraphing m (effects :: [* -> *]) a = ImportGraphing (m effects a)
|
||||||
deriving (Alternative, Applicative, Functor, Effectful, Monad, MonadFail, MonadFresh, MonadNonDet)
|
deriving (Alternative, Applicative, Functor, Effectful, Monad, MonadFail, MonadFresh, MonadNonDet)
|
||||||
@ -49,7 +49,7 @@ instance ( Effectful m
|
|||||||
(\yield (LoadError name) -> insertVertexName name >> yield [])
|
(\yield (LoadError name) -> insertVertexName name >> yield [])
|
||||||
|
|
||||||
analyzeModule recur m = do
|
analyzeModule recur m = do
|
||||||
insertVertexName (moduleName (moduleInfo m))
|
insertVertexName (modulePath (moduleInfo m))
|
||||||
liftAnalyze analyzeModule recur m
|
liftAnalyze analyzeModule recur m
|
||||||
|
|
||||||
insertVertexName :: forall m location term value effects
|
insertVertexName :: forall m location term value effects
|
||||||
@ -58,11 +58,11 @@ insertVertexName :: forall m location term value effects
|
|||||||
, Member (State ImportGraph) effects
|
, Member (State ImportGraph) effects
|
||||||
, MonadEvaluator location term value (m effects)
|
, MonadEvaluator location term value (m effects)
|
||||||
)
|
)
|
||||||
=> NonEmpty ByteString
|
=> FilePath
|
||||||
-> ImportGraphing m effects ()
|
-> ImportGraphing m effects ()
|
||||||
insertVertexName name = do
|
insertVertexName name = do
|
||||||
o <- raise ask
|
o <- raise ask
|
||||||
let parent = maybe empty (vertex . moduleName) (withSomeOrigin (originModule @term) o)
|
let parent = maybe empty (vertex . modulePath) (withSomeOrigin (originModule @term) o)
|
||||||
modifyImportGraph (parent >< vertex name <>)
|
modifyImportGraph (parent >< vertex name <>)
|
||||||
|
|
||||||
(><) :: Graph a => a -> a -> a
|
(><) :: Graph a => a -> a -> a
|
||||||
|
@ -26,7 +26,7 @@ buildCallGraph = foldSubterms callGraphAlgebra
|
|||||||
|
|
||||||
-- | Render a 'CallGraph' to a 'ByteString' in DOT notation.
|
-- | Render a 'CallGraph' to a 'ByteString' in DOT notation.
|
||||||
renderCallGraph :: CallGraph -> ByteString
|
renderCallGraph :: CallGraph -> ByteString
|
||||||
renderCallGraph = export (defaultStyle friendlyName) . unCallGraph
|
renderCallGraph = export (defaultStyle id) . unCallGraph
|
||||||
|
|
||||||
|
|
||||||
-- | Types which contribute to a 'CallGraph'. There is exactly one instance of this typeclass; customizing the 'CallGraph's for a new type is done by defining an instance of 'CustomCallGraphAlgebra' instead.
|
-- | Types which contribute to a 'CallGraph'. There is exactly one instance of this typeclass; customizing the 'CallGraph's for a new type is done by defining an instance of 'CustomCallGraphAlgebra' instead.
|
||||||
|
@ -14,7 +14,6 @@ import Data.Record
|
|||||||
import Data.Source as Source
|
import Data.Source as Source
|
||||||
import Data.Span
|
import Data.Span
|
||||||
import Data.Term
|
import Data.Term
|
||||||
import Data.Abstract.FreeVariables
|
|
||||||
import qualified Data.Syntax as Syntax
|
import qualified Data.Syntax as Syntax
|
||||||
import qualified Data.Syntax.Declaration as Declaration
|
import qualified Data.Syntax.Declaration as Declaration
|
||||||
import qualified Data.Syntax.Expression as Expression
|
import qualified Data.Syntax.Expression as Expression
|
||||||
@ -123,44 +122,13 @@ instance CustomHasDeclaration whole Ruby.Syntax.Class where
|
|||||||
customToDeclaration blob@Blob{..} ann decl@(Ruby.Syntax.Class (Term (In identifierAnn _), _) _ _)
|
customToDeclaration blob@Blob{..} ann decl@(Ruby.Syntax.Class (Term (In identifierAnn _), _) _ _)
|
||||||
= Just $ ClassDeclaration (getSource blobSource identifierAnn) (getRubyClassSource blob (In ann decl)) blobLanguage
|
= Just $ ClassDeclaration (getSource blobSource identifierAnn) (getRubyClassSource blob (In ann decl)) blobLanguage
|
||||||
|
|
||||||
instance CustomHasDeclaration (Union fs) Declaration.Import where
|
|
||||||
customToDeclaration Blob{..} _ (Declaration.Import (Term (In fromAnn _), _) symbols _)
|
|
||||||
= Just $ ImportDeclaration ((stripQuotes . getSource blobSource) fromAnn) "" (fmap getSymbol symbols) blobLanguage
|
|
||||||
where
|
|
||||||
getSymbol = let f = (T.decodeUtf8 . friendlyName) in bimap f f
|
|
||||||
|
|
||||||
instance (Syntax.Identifier :< fs) => CustomHasDeclaration (Union fs) Declaration.QualifiedImport where
|
|
||||||
customToDeclaration Blob{..} _ (Declaration.QualifiedImport (Term (In fromAnn _), _) (Term (In aliasAnn aliasF), _) symbols)
|
|
||||||
| Just (Syntax.Identifier alias) <- prj aliasF = Just $ ImportDeclaration ((stripQuotes . getSource blobSource) fromAnn) (toName alias) (fmap getSymbol symbols) blobLanguage
|
|
||||||
| otherwise = Just $ ImportDeclaration ((stripQuotes . getSource blobSource) fromAnn) (getSource blobSource aliasAnn) (fmap getSymbol symbols) blobLanguage
|
|
||||||
where
|
|
||||||
getSymbol = bimap toName toName
|
|
||||||
toName = T.decodeUtf8 . friendlyName
|
|
||||||
|
|
||||||
instance CustomHasDeclaration (Union fs) Declaration.SideEffectImport where
|
|
||||||
customToDeclaration Blob{..} _ (Declaration.SideEffectImport (Term (In fromAnn _), _) _)
|
|
||||||
= Just $ ImportDeclaration ((stripQuotes . getSource blobSource) fromAnn) "" [] blobLanguage
|
|
||||||
|
|
||||||
instance CustomHasDeclaration (Union fs) Ruby.Syntax.Require where
|
|
||||||
customToDeclaration Blob{..} _ (Ruby.Syntax.Require _ (Term (In fromAnn _), _))
|
|
||||||
= Just $ ImportDeclaration ((stripQuotes . getSource blobSource) fromAnn) "" [] blobLanguage
|
|
||||||
|
|
||||||
instance CustomHasDeclaration (Union fs) Ruby.Syntax.Load where
|
|
||||||
customToDeclaration Blob{..} _ (Ruby.Syntax.Load ((Term (In fromArgs _), _):_))
|
|
||||||
= Just $ ImportDeclaration ((stripQuotes . getSource blobSource) fromArgs) "" [] blobLanguage
|
|
||||||
customToDeclaration Blob{..} _ (Ruby.Syntax.Load _)
|
|
||||||
= Nothing
|
|
||||||
|
|
||||||
getSource :: HasField fields Range => Source -> Record fields -> Text
|
getSource :: HasField fields Range => Source -> Record fields -> Text
|
||||||
getSource blobSource = toText . flip Source.slice blobSource . getField
|
getSource blobSource = toText . flip Source.slice blobSource . getField
|
||||||
|
|
||||||
stripQuotes :: Text -> Text
|
|
||||||
stripQuotes = T.dropAround (`elem` ['"', '\''])
|
|
||||||
|
|
||||||
instance (Syntax.Identifier :< fs, Expression.MemberAccess :< fs) => CustomHasDeclaration (Union fs) Expression.Call where
|
instance (Syntax.Identifier :< fs, Expression.MemberAccess :< fs) => CustomHasDeclaration (Union fs) Expression.Call where
|
||||||
customToDeclaration Blob{..} _ (Expression.Call _ (Term (In fromAnn fromF), _) _ _)
|
customToDeclaration Blob{..} _ (Expression.Call _ (Term (In fromAnn fromF), _) _ _)
|
||||||
| Just (Expression.MemberAccess (Term (In leftAnn leftF)) (Term (In idenAnn _))) <- prj fromF = Just $ CallReference (getSource idenAnn) (memberAccess leftAnn leftF)
|
| Just (Expression.MemberAccess (Term (In leftAnn leftF)) (Term (In idenAnn _))) <- prj fromF = Just $ CallReference (getSource idenAnn) (memberAccess leftAnn leftF)
|
||||||
| Just (Syntax.Identifier name) <- prj fromF = Just $ CallReference (T.decodeUtf8 (friendlyName name)) []
|
| Just (Syntax.Identifier name) <- prj fromF = Just $ CallReference (T.decodeUtf8 name) []
|
||||||
| otherwise = Just $ CallReference (getSource fromAnn) []
|
| otherwise = Just $ CallReference (getSource fromAnn) []
|
||||||
where
|
where
|
||||||
memberAccess modAnn termFOut
|
memberAccess modAnn termFOut
|
||||||
@ -191,12 +159,8 @@ class HasDeclarationWithStrategy (strategy :: Strategy) whole syntax where
|
|||||||
-- If you’re seeing errors about missing a 'CustomHasDeclaration' instance for a given type, you’ve probably listed it in here but not defined a 'CustomHasDeclaration' instance for it, or else you’ve listed the wrong type in here. Conversely, if your 'customHasDeclaration' method is never being called, you may have forgotten to list the type in here.
|
-- If you’re seeing errors about missing a 'CustomHasDeclaration' instance for a given type, you’ve probably listed it in here but not defined a 'CustomHasDeclaration' instance for it, or else you’ve listed the wrong type in here. Conversely, if your 'customHasDeclaration' method is never being called, you may have forgotten to list the type in here.
|
||||||
type family DeclarationStrategy syntax where
|
type family DeclarationStrategy syntax where
|
||||||
DeclarationStrategy Declaration.Class = 'Custom
|
DeclarationStrategy Declaration.Class = 'Custom
|
||||||
DeclarationStrategy Declaration.Function = 'Custom
|
|
||||||
DeclarationStrategy Declaration.Import = 'Custom
|
|
||||||
DeclarationStrategy Declaration.QualifiedImport = 'Custom
|
|
||||||
DeclarationStrategy Declaration.SideEffectImport = 'Custom
|
|
||||||
DeclarationStrategy Ruby.Syntax.Class = 'Custom
|
DeclarationStrategy Ruby.Syntax.Class = 'Custom
|
||||||
DeclarationStrategy Ruby.Syntax.Require = 'Custom
|
DeclarationStrategy Declaration.Function = 'Custom
|
||||||
DeclarationStrategy Declaration.Method = 'Custom
|
DeclarationStrategy Declaration.Method = 'Custom
|
||||||
DeclarationStrategy Markdown.Heading = 'Custom
|
DeclarationStrategy Markdown.Heading = 'Custom
|
||||||
DeclarationStrategy Expression.Call = 'Custom
|
DeclarationStrategy Expression.Call = 'Custom
|
||||||
|
@ -5,7 +5,6 @@ module Analysis.IdentifierName
|
|||||||
, identifierLabel
|
, identifierLabel
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Abstract.FreeVariables
|
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
import Data.JSON.Fields
|
import Data.JSON.Fields
|
||||||
import qualified Data.Syntax
|
import qualified Data.Syntax
|
||||||
@ -40,7 +39,7 @@ instance Apply IdentifierName fs => CustomIdentifierName (Union fs) where
|
|||||||
customIdentifierName = apply (Proxy :: Proxy IdentifierName) identifierName
|
customIdentifierName = apply (Proxy :: Proxy IdentifierName) identifierName
|
||||||
|
|
||||||
instance CustomIdentifierName Data.Syntax.Identifier where
|
instance CustomIdentifierName Data.Syntax.Identifier where
|
||||||
customIdentifierName (Data.Syntax.Identifier name) = Just (friendlyName name)
|
customIdentifierName (Data.Syntax.Identifier name) = Just name
|
||||||
|
|
||||||
data Strategy = Default | Custom
|
data Strategy = Default | Custom
|
||||||
|
|
||||||
|
@ -1,4 +1,4 @@
|
|||||||
{-# LANGUAGE ConstrainedClassMethods, DataKinds, FunctionalDependencies, TypeFamilies, UndecidableInstances #-}
|
{-# LANGUAGE ConstrainedClassMethods, DataKinds, FunctionalDependencies, RankNTypes, TypeFamilies, UndecidableInstances #-}
|
||||||
module Control.Abstract.Evaluator
|
module Control.Abstract.Evaluator
|
||||||
( MonadEvaluator(..)
|
( MonadEvaluator(..)
|
||||||
, MonadEnvironment(..)
|
, MonadEnvironment(..)
|
||||||
@ -46,7 +46,6 @@ class ( MonadControl term m
|
|||||||
-- | Get the current 'Configuration' with a passed-in term.
|
-- | Get the current 'Configuration' with a passed-in term.
|
||||||
getConfiguration :: Ord location => term -> m (Configuration location term value)
|
getConfiguration :: Ord location => term -> m (Configuration location term value)
|
||||||
|
|
||||||
|
|
||||||
-- | A 'Monad' abstracting local and global environments.
|
-- | A 'Monad' abstracting local and global environments.
|
||||||
class Monad m => MonadEnvironment location value m | m -> value, m -> location where
|
class Monad m => MonadEnvironment location value m | m -> value, m -> location where
|
||||||
-- | Retrieve the environment.
|
-- | Retrieve the environment.
|
||||||
@ -148,6 +147,9 @@ class Monad m => MonadModuleTable location term value m | m -> location, m -> te
|
|||||||
-- | Run an action with a locally-modified table of unevaluated modules.
|
-- | Run an action with a locally-modified table of unevaluated modules.
|
||||||
localModuleTable :: (ModuleTable [Module term] -> ModuleTable [Module term]) -> m a -> m a
|
localModuleTable :: (ModuleTable [Module term] -> ModuleTable [Module term]) -> m a -> m a
|
||||||
|
|
||||||
|
-- | Get the currently evaluating 'ModuleInfo'.
|
||||||
|
currentModule :: m ModuleInfo
|
||||||
|
|
||||||
-- | Update the evaluated module table.
|
-- | Update the evaluated module table.
|
||||||
modifyModuleTable :: MonadModuleTable location term value m => (ModuleTable (Environment location value, value) -> ModuleTable (Environment location value, value)) -> m ()
|
modifyModuleTable :: MonadModuleTable location term value m => (ModuleTable (Environment location value, value) -> ModuleTable (Environment location value, value)) -> m ()
|
||||||
modifyModuleTable f = do
|
modifyModuleTable f = do
|
||||||
|
@ -27,8 +27,8 @@ import GHC.Exts (IsList (..))
|
|||||||
import Prologue
|
import Prologue
|
||||||
|
|
||||||
-- $setup
|
-- $setup
|
||||||
-- >>> let bright = push (insert (name "foo") (Address (Precise 0)) mempty)
|
-- >>> let bright = push (insert "foo" (Address (Precise 0)) mempty)
|
||||||
-- >>> let shadowed = insert (name "foo") (Address (Precise 1)) bright
|
-- >>> let shadowed = insert "foo" (Address (Precise 1)) bright
|
||||||
|
|
||||||
-- | A LIFO stack of maps of names to addresses, representing a lexically-scoped evaluation environment.
|
-- | A LIFO stack of maps of names to addresses, representing a lexically-scoped evaluation environment.
|
||||||
-- All behaviors can be assumed to be frontmost-biased: looking up "a" will check the most specific
|
-- All behaviors can be assumed to be frontmost-biased: looking up "a" will check the most specific
|
||||||
@ -85,13 +85,13 @@ mergeNewer (Environment (a :| as)) (Environment (b :| bs)) =
|
|||||||
-- | Extract an association list of bindings from an 'Environment'.
|
-- | Extract an association list of bindings from an 'Environment'.
|
||||||
--
|
--
|
||||||
-- >>> pairs shadowed
|
-- >>> pairs shadowed
|
||||||
-- [("foo" :| [],Address {unAddress = Precise {unPrecise = 1}})]
|
-- [("foo",Address {unAddress = Precise {unPrecise = 1}})]
|
||||||
pairs :: Environment l a -> [(Name, Address l a)]
|
pairs :: Environment l a -> [(Name, Address l a)]
|
||||||
pairs = Map.toList . fold . unEnvironment
|
pairs = Map.toList . fold . unEnvironment
|
||||||
|
|
||||||
-- | Lookup a 'Name' in the environment.
|
-- | Lookup a 'Name' in the environment.
|
||||||
--
|
--
|
||||||
-- >>> lookup (name "foo") shadowed
|
-- >>> lookup "foo" shadowed
|
||||||
-- Just (Address {unAddress = Precise {unPrecise = 1}})
|
-- Just (Address {unAddress = Precise {unPrecise = 1}})
|
||||||
lookup :: Name -> Environment l a -> Maybe (Address l a)
|
lookup :: Name -> Environment l a -> Maybe (Address l a)
|
||||||
lookup k = foldMapA (Map.lookup k) . unEnvironment
|
lookup k = foldMapA (Map.lookup k) . unEnvironment
|
||||||
@ -102,7 +102,7 @@ insert name value (Environment (a :| as)) = Environment (Map.insert name value a
|
|||||||
|
|
||||||
-- | Remove a 'Name' from the environment.
|
-- | Remove a 'Name' from the environment.
|
||||||
--
|
--
|
||||||
-- >>> delete (name "foo") shadowed
|
-- >>> delete "foo" shadowed
|
||||||
-- Environment {unEnvironment = fromList [] :| []}
|
-- Environment {unEnvironment = fromList [] :| []}
|
||||||
delete :: Name -> Environment l a -> Environment l a
|
delete :: Name -> Environment l a -> Environment l a
|
||||||
delete name = trim . Environment . fmap (Map.delete name) . unEnvironment
|
delete name = trim . Environment . fmap (Map.delete name) . unEnvironment
|
||||||
|
@ -12,6 +12,8 @@ module Data.Abstract.Evaluatable
|
|||||||
, evaluateModules
|
, evaluateModules
|
||||||
, evaluatePackage
|
, evaluatePackage
|
||||||
, throwLoadError
|
, throwLoadError
|
||||||
|
, resolve
|
||||||
|
, listModulesInDir
|
||||||
, require
|
, require
|
||||||
, load
|
, load
|
||||||
, pushOrigin
|
, pushOrigin
|
||||||
@ -51,7 +53,7 @@ type MonadEvaluatable location term value m =
|
|||||||
|
|
||||||
-- | An error thrown when loading a module from the list of provided modules. Indicates we weren't able to find a module with the given name.
|
-- | An error thrown when loading a module from the list of provided modules. Indicates we weren't able to find a module with the given name.
|
||||||
data LoadError term value resume where
|
data LoadError term value resume where
|
||||||
LoadError :: ModuleName -> LoadError term value [Module term]
|
LoadError :: ModulePath -> LoadError term value [Module term]
|
||||||
|
|
||||||
deriving instance Eq (LoadError term a b)
|
deriving instance Eq (LoadError term a b)
|
||||||
deriving instance Show (LoadError term a b)
|
deriving instance Show (LoadError term a b)
|
||||||
@ -117,11 +119,24 @@ instance Evaluatable [] where
|
|||||||
-- 'nonEmpty' and 'foldMap1' enable us to return the last statement’s result instead of 'unit' for non-empty lists.
|
-- 'nonEmpty' and 'foldMap1' enable us to return the last statement’s result instead of 'unit' for non-empty lists.
|
||||||
eval = maybe unit (runApp . foldMap1 (App . subtermValue)) . nonEmpty
|
eval = maybe unit (runApp . foldMap1 (App . subtermValue)) . nonEmpty
|
||||||
|
|
||||||
|
-- Resolve a list of module paths to a possible module table entry.
|
||||||
|
resolve :: MonadEvaluatable location term value m
|
||||||
|
=> [FilePath]
|
||||||
|
-> m (Maybe ModulePath)
|
||||||
|
resolve names = do
|
||||||
|
tbl <- askModuleTable
|
||||||
|
pure $ find (`ModuleTable.member` tbl) names
|
||||||
|
|
||||||
|
listModulesInDir :: MonadEvaluatable location term value m
|
||||||
|
=> FilePath
|
||||||
|
-> m [ModulePath]
|
||||||
|
listModulesInDir dir = ModuleTable.modulePathsInDir dir <$> askModuleTable
|
||||||
|
|
||||||
-- | Require/import another module by name and return it's environment and value.
|
-- | Require/import another module by name and return it's environment and value.
|
||||||
--
|
--
|
||||||
-- Looks up the term's name in the cache of evaluated modules first, returns if found, otherwise loads/evaluates the module.
|
-- Looks up the term's name in the cache of evaluated modules first, returns if found, otherwise loads/evaluates the module.
|
||||||
require :: MonadEvaluatable location term value m
|
require :: MonadEvaluatable location term value m
|
||||||
=> ModuleName
|
=> ModulePath
|
||||||
-> m (Environment location value, value)
|
-> m (Environment location value, value)
|
||||||
require name = getModuleTable >>= maybeM (load name) . ModuleTable.lookup name
|
require name = getModuleTable >>= maybeM (load name) . ModuleTable.lookup name
|
||||||
|
|
||||||
@ -129,7 +144,7 @@ require name = getModuleTable >>= maybeM (load name) . ModuleTable.lookup name
|
|||||||
--
|
--
|
||||||
-- Always loads/evaluates.
|
-- Always loads/evaluates.
|
||||||
load :: MonadEvaluatable location term value m
|
load :: MonadEvaluatable location term value m
|
||||||
=> ModuleName
|
=> ModulePath
|
||||||
-> m (Environment location value, value)
|
-> m (Environment location value, value)
|
||||||
load name = askModuleTable >>= maybeM notFound . ModuleTable.lookup name >>= evalAndCache
|
load name = askModuleTable >>= maybeM notFound . ModuleTable.lookup name >>= evalAndCache
|
||||||
where
|
where
|
||||||
|
@ -3,24 +3,9 @@ module Data.Abstract.FreeVariables where
|
|||||||
|
|
||||||
import Prologue
|
import Prologue
|
||||||
import Data.Term
|
import Data.Term
|
||||||
import Data.ByteString (intercalate)
|
|
||||||
import qualified Data.List.NonEmpty as NonEmpty
|
|
||||||
|
|
||||||
-- | The type of variable names.
|
-- | The type of variable names.
|
||||||
type Name = NonEmpty ByteString
|
type Name = ByteString
|
||||||
|
|
||||||
-- | Construct a qualified name from a 'ByteString'
|
|
||||||
name :: ByteString -> Name
|
|
||||||
name x = x :| []
|
|
||||||
|
|
||||||
-- | Construct a qualified name from a list of 'ByteString's
|
|
||||||
qualifiedName :: [ByteString] -> Name
|
|
||||||
qualifiedName = NonEmpty.fromList
|
|
||||||
|
|
||||||
-- | User friendly 'ByteString' of a qualified 'Name'.
|
|
||||||
friendlyName :: Name -> ByteString
|
|
||||||
friendlyName xs = intercalate "." (NonEmpty.toList xs)
|
|
||||||
|
|
||||||
|
|
||||||
-- | The type of labels.
|
-- | The type of labels.
|
||||||
-- TODO: This should be rolled into 'Name' and tracked in the environment, both so that we can abstract over labels like any other location, and so that we can garbage collect unreachable labels.
|
-- TODO: This should be rolled into 'Name' and tracked in the environment, both so that we can abstract over labels like any other location, and so that we can garbage collect unreachable labels.
|
||||||
@ -49,7 +34,7 @@ freeVariables1 = liftFreeVariables freeVariables
|
|||||||
freeVariable :: (HasCallStack, FreeVariables term) => term -> Name
|
freeVariable :: (HasCallStack, FreeVariables term) => term -> Name
|
||||||
freeVariable term = case freeVariables term of
|
freeVariable term = case freeVariables term of
|
||||||
[n] -> n
|
[n] -> n
|
||||||
xs -> Prelude.fail ("expected single free variable, but got: " <> show xs <> prettyCallStack callStack)
|
xs -> error ("expected single free variable, but got: " <> show xs)
|
||||||
|
|
||||||
instance (FreeVariables1 syntax, Functor syntax) => FreeVariables (Term syntax ann) where
|
instance (FreeVariables1 syntax, Functor syntax) => FreeVariables (Term syntax ann) where
|
||||||
freeVariables = cata (liftFreeVariables id)
|
freeVariables = cata (liftFreeVariables id)
|
||||||
|
@ -1,20 +1,17 @@
|
|||||||
module Data.Abstract.Module
|
module Data.Abstract.Module
|
||||||
( Module(..)
|
( Module(..)
|
||||||
, ModuleInfo(..)
|
, ModuleInfo(..)
|
||||||
, ModuleName
|
, ModulePath
|
||||||
, moduleForBlob
|
, moduleForBlob
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Abstract.FreeVariables
|
|
||||||
import Data.Blob
|
import Data.Blob
|
||||||
import qualified Data.ByteString.Char8 as BC
|
import Prologue
|
||||||
import Data.Language
|
|
||||||
import Data.List.Split (splitWhen)
|
|
||||||
import System.FilePath.Posix
|
import System.FilePath.Posix
|
||||||
|
|
||||||
type ModuleName = Name
|
type ModulePath = FilePath
|
||||||
|
|
||||||
data ModuleInfo = ModuleInfo { moduleName :: ModuleName, modulePath :: FilePath }
|
data ModuleInfo = ModuleInfo { modulePath :: FilePath, moduleRoot :: FilePath }
|
||||||
deriving (Eq, Ord, Show)
|
deriving (Eq, Ord, Show)
|
||||||
|
|
||||||
data Module term = Module { moduleInfo :: ModuleInfo, moduleBody :: term }
|
data Module term = Module { moduleInfo :: ModuleInfo, moduleBody :: term }
|
||||||
@ -26,12 +23,8 @@ moduleForBlob :: Maybe FilePath -- ^ The root directory relative to which the mo
|
|||||||
-> Blob -- ^ The 'Blob' containing the module.
|
-> Blob -- ^ The 'Blob' containing the module.
|
||||||
-> term -- ^ The @term@ representing the body of the module.
|
-> term -- ^ The @term@ representing the body of the module.
|
||||||
-> Module term -- ^ A 'Module' named appropriate for the 'Blob', holding the @term@, and constructed relative to the root 'FilePath', if any.
|
-> Module term -- ^ A 'Module' named appropriate for the 'Blob', holding the @term@, and constructed relative to the root 'FilePath', if any.
|
||||||
moduleForBlob rootDir blob = Module info
|
moduleForBlob rootDir Blob{..} = Module info
|
||||||
where modulePathForBlob Blob{..} | Just Go <- blobLanguage = takeDirectory (modulePath blobPath)
|
where
|
||||||
| otherwise = modulePath blobPath
|
root = fromMaybe (takeDirectory blobPath) rootDir
|
||||||
-- TODO: Need a better way to handle module registration and resolution
|
modulePath = maybe takeFileName makeRelative rootDir
|
||||||
modulePath = dropExtensions . maybe takeFileName makeRelative rootDir
|
info = ModuleInfo (modulePath blobPath) root
|
||||||
info = ModuleInfo (moduleNameForPath (modulePathForBlob blob)) (blobPath blob)
|
|
||||||
|
|
||||||
moduleNameForPath :: FilePath -> ModuleName
|
|
||||||
moduleNameForPath = qualifiedName . map BC.pack . splitWhen (== pathSeparator)
|
|
||||||
|
@ -1,9 +1,11 @@
|
|||||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
module Data.Abstract.ModuleTable
|
module Data.Abstract.ModuleTable
|
||||||
( ModuleName
|
( ModulePath
|
||||||
, ModuleTable (..)
|
, ModuleTable (..)
|
||||||
, singleton
|
, singleton
|
||||||
, lookup
|
, lookup
|
||||||
|
, member
|
||||||
|
, modulePathsInDir
|
||||||
, insert
|
, insert
|
||||||
, fromModules
|
, fromModules
|
||||||
, toPairs
|
, toPairs
|
||||||
@ -12,26 +14,34 @@ module Data.Abstract.ModuleTable
|
|||||||
import Data.Abstract.Module
|
import Data.Abstract.Module
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
import Data.Semigroup
|
import Data.Semigroup
|
||||||
|
import Prologue
|
||||||
|
import System.FilePath.Posix
|
||||||
import GHC.Generics (Generic1)
|
import GHC.Generics (Generic1)
|
||||||
import Prelude hiding (lookup)
|
import Prelude hiding (lookup)
|
||||||
|
|
||||||
newtype ModuleTable a = ModuleTable { unModuleTable :: Map.Map ModuleName a }
|
newtype ModuleTable a = ModuleTable { unModuleTable :: Map.Map ModulePath a }
|
||||||
deriving (Eq, Foldable, Functor, Generic1, Monoid, Ord, Semigroup, Show, Traversable)
|
deriving (Eq, Foldable, Functor, Generic1, Monoid, Ord, Semigroup, Show, Traversable)
|
||||||
|
|
||||||
singleton :: ModuleName -> a -> ModuleTable a
|
singleton :: ModulePath -> a -> ModuleTable a
|
||||||
singleton name = ModuleTable . Map.singleton name
|
singleton name = ModuleTable . Map.singleton name
|
||||||
|
|
||||||
lookup :: ModuleName -> ModuleTable a -> Maybe a
|
modulePathsInDir :: FilePath -> ModuleTable a -> [ModulePath]
|
||||||
|
modulePathsInDir k = filter (\e -> k == takeDirectory e) . Map.keys . unModuleTable
|
||||||
|
|
||||||
|
lookup :: ModulePath -> ModuleTable a -> Maybe a
|
||||||
lookup k = Map.lookup k . unModuleTable
|
lookup k = Map.lookup k . unModuleTable
|
||||||
|
|
||||||
insert :: ModuleName -> a -> ModuleTable a -> ModuleTable a
|
member :: ModulePath -> ModuleTable a -> Bool
|
||||||
insert k v ModuleTable{..} = ModuleTable (Map.insert k v unModuleTable)
|
member k = Map.member k . unModuleTable
|
||||||
|
|
||||||
|
insert :: ModulePath -> a -> ModuleTable a -> ModuleTable a
|
||||||
|
insert k v = ModuleTable . Map.insert k v . unModuleTable
|
||||||
|
|
||||||
|
|
||||||
-- | Construct a 'ModuleTable' from a list of 'Module's.
|
-- | Construct a 'ModuleTable' from a list of 'Module's.
|
||||||
fromModules :: [Module term] -> ModuleTable [Module term]
|
fromModules :: [Module term] -> ModuleTable [Module term]
|
||||||
fromModules = ModuleTable . Map.fromListWith (<>) . map toEntry
|
fromModules = ModuleTable . Map.fromListWith (<>) . map toEntry
|
||||||
where toEntry m = (moduleName (moduleInfo m), [m])
|
where toEntry m = (modulePath (moduleInfo m), [m])
|
||||||
|
|
||||||
toPairs :: ModuleTable a -> [(ModuleName, a)]
|
toPairs :: ModuleTable a -> [(ModulePath, a)]
|
||||||
toPairs = Map.toList . unModuleTable
|
toPairs = Map.toList . unModuleTable
|
||||||
|
@ -33,4 +33,4 @@ data Package term = Package
|
|||||||
fromModules :: [Module term] -> PackageBody term
|
fromModules :: [Module term] -> PackageBody term
|
||||||
fromModules [] = PackageBody mempty mempty
|
fromModules [] = PackageBody mempty mempty
|
||||||
fromModules (m:ms) = PackageBody (ModuleTable.fromModules (m:ms)) entryPoints
|
fromModules (m:ms) = PackageBody (ModuleTable.fromModules (m:ms)) entryPoints
|
||||||
where entryPoints = ModuleTable.singleton (moduleName (moduleInfo m)) Nothing
|
where entryPoints = ModuleTable.singleton (modulePath (moduleInfo m)) Nothing
|
||||||
|
@ -232,7 +232,7 @@ instance (Monad m, MonadEvaluatable location term (Value location) m) => MonadVa
|
|||||||
|
|
||||||
asString v
|
asString v
|
||||||
| Just (String n) <- prjValue v = pure n
|
| Just (String n) <- prjValue v = pure n
|
||||||
| otherwise = fail ("expected " <> show v <> " to be a string")
|
| otherwise = fail ("expected " <> show v <> " to be a string")
|
||||||
|
|
||||||
ifthenelse cond if' else'
|
ifthenelse cond if' else'
|
||||||
| Just (Boolean b) <- prjValue cond = if b then if' else else'
|
| Just (Boolean b) <- prjValue cond = if b then if' else else'
|
||||||
|
@ -4,7 +4,6 @@ module Data.Syntax.Declaration where
|
|||||||
import qualified Data.Abstract.Environment as Env
|
import qualified Data.Abstract.Environment as Env
|
||||||
import Data.Abstract.Evaluatable
|
import Data.Abstract.Evaluatable
|
||||||
import Diffing.Algorithm
|
import Diffing.Algorithm
|
||||||
import Prelude hiding (fail)
|
|
||||||
import Prologue
|
import Prologue
|
||||||
|
|
||||||
data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a }
|
data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a }
|
||||||
@ -203,113 +202,6 @@ instance Show1 Comprehension where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable Comprehension
|
instance Evaluatable Comprehension
|
||||||
|
|
||||||
|
|
||||||
-- | Qualified Export declarations
|
|
||||||
newtype QualifiedExport a = QualifiedExport { qualifiedExportSymbols :: [(Name, Name)] }
|
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
|
||||||
|
|
||||||
instance Eq1 QualifiedExport where liftEq = genericLiftEq
|
|
||||||
instance Ord1 QualifiedExport where liftCompare = genericLiftCompare
|
|
||||||
instance Show1 QualifiedExport where liftShowsPrec = genericLiftShowsPrec
|
|
||||||
|
|
||||||
instance Evaluatable QualifiedExport where
|
|
||||||
eval (QualifiedExport exportSymbols) = do
|
|
||||||
-- Insert the aliases with no addresses.
|
|
||||||
for_ exportSymbols $ \(name, alias) ->
|
|
||||||
addExport name alias Nothing
|
|
||||||
unit
|
|
||||||
|
|
||||||
|
|
||||||
-- | Qualified Export declarations that export from another module.
|
|
||||||
data QualifiedExportFrom a = QualifiedExportFrom { qualifiedExportFrom :: !a, qualifiedExportFromSymbols :: ![(Name, Name)]}
|
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
|
||||||
|
|
||||||
instance Eq1 QualifiedExportFrom where liftEq = genericLiftEq
|
|
||||||
instance Ord1 QualifiedExportFrom where liftCompare = genericLiftCompare
|
|
||||||
instance Show1 QualifiedExportFrom where liftShowsPrec = genericLiftShowsPrec
|
|
||||||
|
|
||||||
instance Evaluatable QualifiedExportFrom where
|
|
||||||
eval (QualifiedExportFrom from exportSymbols) = do
|
|
||||||
let moduleName = freeVariable (subterm from)
|
|
||||||
(importedEnv, _) <- isolate (require moduleName)
|
|
||||||
-- Look up addresses in importedEnv and insert the aliases with addresses into the exports.
|
|
||||||
for_ exportSymbols $ \(name, alias) -> do
|
|
||||||
let address = Env.lookup name importedEnv
|
|
||||||
maybe (cannotExport moduleName name) (addExport name alias . Just) address
|
|
||||||
unit
|
|
||||||
where
|
|
||||||
cannotExport moduleName name = fail $
|
|
||||||
"module " <> show (friendlyName moduleName) <> " does not export " <> show (friendlyName name)
|
|
||||||
|
|
||||||
|
|
||||||
newtype DefaultExport a = DefaultExport { defaultExport :: a }
|
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
|
||||||
|
|
||||||
instance Eq1 DefaultExport where liftEq = genericLiftEq
|
|
||||||
instance Ord1 DefaultExport where liftCompare = genericLiftCompare
|
|
||||||
instance Show1 DefaultExport where liftShowsPrec = genericLiftShowsPrec
|
|
||||||
|
|
||||||
instance Evaluatable DefaultExport where
|
|
||||||
|
|
||||||
|
|
||||||
-- | Qualified Import declarations (symbols are qualified in calling environment).
|
|
||||||
--
|
|
||||||
-- If the list of symbols is empty copy and qualify everything to the 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)
|
|
||||||
|
|
||||||
instance Eq1 QualifiedImport where liftEq = genericLiftEq
|
|
||||||
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
|
|
||||||
instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec
|
|
||||||
|
|
||||||
instance Evaluatable QualifiedImport where
|
|
||||||
eval (QualifiedImport from alias xs) = do
|
|
||||||
(importedEnv, _) <- isolate (require moduleName)
|
|
||||||
modifyEnv (mappend (Env.overwrite (renames importedEnv) importedEnv))
|
|
||||||
unit
|
|
||||||
where
|
|
||||||
moduleName = freeVariable (subterm from)
|
|
||||||
renames importedEnv
|
|
||||||
| Prologue.null xs = fmap prepend (Env.names importedEnv)
|
|
||||||
| otherwise = xs
|
|
||||||
prefix = freeVariable (subterm alias)
|
|
||||||
prepend n = (n, prefix <> n)
|
|
||||||
|
|
||||||
-- | Import declarations (symbols are added directly to the calling environment).
|
|
||||||
--
|
|
||||||
-- If the list of symbols is empty copy everything to the calling environment.
|
|
||||||
data Import a = Import { importFrom :: !a, importSymbols :: ![(Name, Name)], importWildcardToken :: !a }
|
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
|
||||||
|
|
||||||
instance Eq1 Import where liftEq = genericLiftEq
|
|
||||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
|
||||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
|
||||||
|
|
||||||
instance Evaluatable Import where
|
|
||||||
eval (Import from xs _) = do
|
|
||||||
(importedEnv, _) <- isolate (require moduleName)
|
|
||||||
modifyEnv (mappend (renamed importedEnv))
|
|
||||||
unit
|
|
||||||
where
|
|
||||||
moduleName = freeVariable (subterm from)
|
|
||||||
renamed importedEnv
|
|
||||||
| Prologue.null xs = importedEnv
|
|
||||||
| otherwise = Env.overwrite xs importedEnv
|
|
||||||
|
|
||||||
-- | Side effect only imports (no symbols made available to the calling environment).
|
|
||||||
data SideEffectImport a = SideEffectImport { sideEffectImportFrom :: !a, sideEffectImportToken :: !a }
|
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
|
||||||
|
|
||||||
instance Eq1 SideEffectImport where liftEq = genericLiftEq
|
|
||||||
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
|
|
||||||
instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec
|
|
||||||
|
|
||||||
instance Evaluatable SideEffectImport where
|
|
||||||
eval (SideEffectImport from _) = do
|
|
||||||
let moduleName = freeVariable (subterm from)
|
|
||||||
void $ isolate (require moduleName)
|
|
||||||
unit
|
|
||||||
|
|
||||||
|
|
||||||
-- | A declared type (e.g. `a []int` in Go).
|
-- | A declared type (e.g. `a []int` in Go).
|
||||||
data Type a = Type { typeName :: !a, typeKind :: !a }
|
data Type a = Type { typeName :: !a, typeKind :: !a }
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
@ -7,8 +7,6 @@ module Language.Go.Assignment
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import Assigning.Assignment hiding (Assignment, Error)
|
import Assigning.Assignment hiding (Assignment, Error)
|
||||||
import Data.Abstract.FreeVariables
|
|
||||||
import Data.Abstract.Path
|
|
||||||
import Data.Record
|
import Data.Record
|
||||||
import Data.Syntax (contextualize, emptyTerm, parseError, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1)
|
import Data.Syntax (contextualize, emptyTerm, parseError, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1)
|
||||||
import Language.Go.Grammar as Grammar
|
import Language.Go.Grammar as Grammar
|
||||||
@ -29,9 +27,6 @@ type Syntax =
|
|||||||
'[ Comment.Comment
|
'[ Comment.Comment
|
||||||
, Declaration.Constructor
|
, Declaration.Constructor
|
||||||
, Declaration.Function
|
, Declaration.Function
|
||||||
, Declaration.Import
|
|
||||||
, Declaration.QualifiedImport
|
|
||||||
, Declaration.SideEffectImport
|
|
||||||
, Declaration.Method
|
, Declaration.Method
|
||||||
, Declaration.MethodSignature
|
, Declaration.MethodSignature
|
||||||
, Declaration.Type
|
, Declaration.Type
|
||||||
@ -66,6 +61,9 @@ type Syntax =
|
|||||||
, Go.Type.BidirectionalChannel
|
, Go.Type.BidirectionalChannel
|
||||||
, Go.Type.ReceiveChannel
|
, Go.Type.ReceiveChannel
|
||||||
, Go.Type.SendChannel
|
, Go.Type.SendChannel
|
||||||
|
, Go.Syntax.Import
|
||||||
|
, Go.Syntax.QualifiedImport
|
||||||
|
, Go.Syntax.SideEffectImport
|
||||||
, Literal.Array
|
, Literal.Array
|
||||||
, Literal.Complex
|
, Literal.Complex
|
||||||
, Literal.Float
|
, Literal.Float
|
||||||
@ -225,13 +223,13 @@ element :: Assignment
|
|||||||
element = symbol Element *> children expression
|
element = symbol Element *> children expression
|
||||||
|
|
||||||
fieldIdentifier :: Assignment
|
fieldIdentifier :: Assignment
|
||||||
fieldIdentifier = makeTerm <$> symbol FieldIdentifier <*> (Syntax.Identifier <$> (name <$> source))
|
fieldIdentifier = makeTerm <$> symbol FieldIdentifier <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
floatLiteral :: Assignment
|
floatLiteral :: Assignment
|
||||||
floatLiteral = makeTerm <$> symbol FloatLiteral <*> (source >>= Literal.normalizeFloatString [Literal.padWithLeadingZero, Literal.dropAlphaSuffix])
|
floatLiteral = makeTerm <$> symbol FloatLiteral <*> (source >>= Literal.normalizeFloatString [Literal.padWithLeadingZero, Literal.dropAlphaSuffix])
|
||||||
|
|
||||||
identifier :: Assignment
|
identifier :: Assignment
|
||||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> (name <$> source))
|
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
imaginaryLiteral :: Assignment
|
imaginaryLiteral :: Assignment
|
||||||
imaginaryLiteral = makeTerm <$> symbol ImaginaryLiteral <*> (Literal.Complex <$> source)
|
imaginaryLiteral = makeTerm <$> symbol ImaginaryLiteral <*> (Literal.Complex <$> source)
|
||||||
@ -246,7 +244,7 @@ literalValue :: Assignment
|
|||||||
literalValue = makeTerm <$> symbol LiteralValue <*> children (manyTerm expression)
|
literalValue = makeTerm <$> symbol LiteralValue <*> children (manyTerm expression)
|
||||||
|
|
||||||
packageIdentifier :: Assignment
|
packageIdentifier :: Assignment
|
||||||
packageIdentifier = makeTerm <$> symbol PackageIdentifier <*> (Syntax.Identifier <$> (name <$> source))
|
packageIdentifier = makeTerm <$> symbol PackageIdentifier <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
parenthesizedType :: Assignment
|
parenthesizedType :: Assignment
|
||||||
parenthesizedType = makeTerm <$> symbol Grammar.ParenthesizedType <*> children (Type.Parenthesized <$> expression)
|
parenthesizedType = makeTerm <$> symbol Grammar.ParenthesizedType <*> children (Type.Parenthesized <$> expression)
|
||||||
@ -258,7 +256,7 @@ runeLiteral :: Assignment
|
|||||||
runeLiteral = makeTerm <$> symbol Grammar.RuneLiteral <*> (Go.Syntax.Rune <$> source)
|
runeLiteral = makeTerm <$> symbol Grammar.RuneLiteral <*> (Go.Syntax.Rune <$> source)
|
||||||
|
|
||||||
typeIdentifier :: Assignment
|
typeIdentifier :: Assignment
|
||||||
typeIdentifier = makeTerm <$> symbol TypeIdentifier <*> (Syntax.Identifier <$> (name <$> source))
|
typeIdentifier = makeTerm <$> symbol TypeIdentifier <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
|
|
||||||
-- Primitive Types
|
-- Primitive Types
|
||||||
@ -373,7 +371,7 @@ expressionSwitchStatement :: Assignment
|
|||||||
expressionSwitchStatement = makeTerm <$> symbol ExpressionSwitchStatement <*> children (Statement.Match <$> (makeTerm <$> location <*> manyTermsTill expression (void (symbol ExpressionCaseClause)) <|> emptyTerm) <*> expressions)
|
expressionSwitchStatement = makeTerm <$> symbol ExpressionSwitchStatement <*> children (Statement.Match <$> (makeTerm <$> location <*> manyTermsTill expression (void (symbol ExpressionCaseClause)) <|> emptyTerm) <*> expressions)
|
||||||
|
|
||||||
fallThroughStatement :: Assignment
|
fallThroughStatement :: Assignment
|
||||||
fallThroughStatement = makeTerm <$> symbol FallthroughStatement <*> (Statement.Pattern <$> (makeTerm <$> location <*> (Syntax.Identifier <$> (name <$> source))) <*> emptyTerm)
|
fallThroughStatement = makeTerm <$> symbol FallthroughStatement <*> (Statement.Pattern <$> (makeTerm <$> location <*> (Syntax.Identifier <$> source)) <*> emptyTerm)
|
||||||
|
|
||||||
functionDeclaration :: Assignment
|
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))
|
functionDeclaration = makeTerm <$> (symbol FunctionDeclaration <|> symbol FuncLiteral) <*> children (mkFunctionDeclaration <$> (term identifier <|> emptyTerm) <*> manyTerm parameters <*> (term types <|> term identifier <|> term returnParameters <|> emptyTerm) <*> (term block <|> emptyTerm))
|
||||||
@ -385,29 +383,22 @@ importDeclaration :: Assignment
|
|||||||
importDeclaration = makeTerm'' <$> symbol ImportDeclaration <*> children (manyTerm (importSpec <|> importSpecList))
|
importDeclaration = makeTerm'' <$> symbol ImportDeclaration <*> children (manyTerm (importSpec <|> importSpecList))
|
||||||
where
|
where
|
||||||
-- `import . "lib/Math"`
|
-- `import . "lib/Math"`
|
||||||
dotImport = inj <$> (makeImport <$> dot <*> importFromPath)
|
dotImport = inj <$> (flip Go.Syntax.Import <$> dot <*> importFromPath)
|
||||||
-- dotImport = inj <$> (flip Declaration.Import <$> (symbol Dot *> source *> pure []) <*> importFromPath)
|
|
||||||
-- `import _ "lib/Math"`
|
-- `import _ "lib/Math"`
|
||||||
sideEffectImport = inj <$> (flip Declaration.SideEffectImport <$> underscore <*> importFromPath)
|
sideEffectImport = inj <$> (flip Go.Syntax.SideEffectImport <$> underscore <*> importFromPath)
|
||||||
-- `import m "lib/Math"`
|
-- `import m "lib/Math"`
|
||||||
namedImport = inj <$> (flip Declaration.QualifiedImport <$> packageIdentifier <*> importFromPath <*> pure [])
|
namedImport = inj <$> (flip Go.Syntax.QualifiedImport <$> packageIdentifier <*> importFromPath)
|
||||||
-- `import "lib/Math"`
|
-- `import "lib/Math"`
|
||||||
plainImport = inj <$> (symbol InterpretedStringLiteral >>= \loc -> do
|
plainImport = inj <$> (symbol InterpretedStringLiteral >>= \loc -> do
|
||||||
names <- toName <$> source
|
from <- importPath <$> source
|
||||||
let from = makeTerm loc (Syntax.Identifier (qualifiedName names))
|
let alias = makeTerm loc (Syntax.Identifier (defaultAlias from)) -- Go takes `import "lib/Math"` and uses `Math` as the qualified name (e.g. `Math.Sin()`)
|
||||||
let alias = makeTerm loc (Syntax.Identifier (name (last names))) -- Go takes `import "lib/Math"` and uses `Math` as the qualified name (e.g. `Math.Sin()`)
|
Go.Syntax.QualifiedImport <$> pure from <*> pure alias)
|
||||||
Declaration.QualifiedImport <$> pure from <*> pure alias <*> pure [])
|
|
||||||
|
|
||||||
makeImport dot path = Declaration.Import path [] dot
|
|
||||||
dot = makeTerm <$> symbol Dot <*> (Literal.TextElement <$> source)
|
dot = makeTerm <$> symbol Dot <*> (Literal.TextElement <$> source)
|
||||||
underscore = makeTerm <$> symbol BlankIdentifier <*> (Literal.TextElement <$> source)
|
underscore = makeTerm <$> symbol BlankIdentifier <*> (Literal.TextElement <$> source)
|
||||||
importSpec = makeTerm' <$> symbol ImportSpec <*> children (sideEffectImport <|> dotImport <|> namedImport <|> plainImport)
|
importSpec = makeTerm' <$> symbol ImportSpec <*> children (sideEffectImport <|> dotImport <|> namedImport <|> plainImport)
|
||||||
importSpecList = makeTerm <$> symbol ImportSpecList <*> children (manyTerm (importSpec <|> comment))
|
importSpecList = makeTerm <$> symbol ImportSpecList <*> children (manyTerm (importSpec <|> comment))
|
||||||
importFromPath = makeTerm <$> symbol InterpretedStringLiteral <*> (Syntax.Identifier <$> (toQualifiedName <$> source))
|
importFromPath = symbol InterpretedStringLiteral *> (importPath <$> source)
|
||||||
|
|
||||||
toQualifiedName = qualifiedName . toName
|
|
||||||
toName = splitOnPathSeparator . dropRelativePrefix . stripQuotes
|
|
||||||
|
|
||||||
|
|
||||||
indexExpression :: Assignment
|
indexExpression :: Assignment
|
||||||
indexExpression = makeTerm <$> symbol IndexExpression <*> children (Expression.Subscript <$> expression <*> manyTerm expression)
|
indexExpression = makeTerm <$> symbol IndexExpression <*> children (Expression.Subscript <$> expression <*> manyTerm expression)
|
||||||
@ -571,7 +562,7 @@ keyedElement :: Assignment
|
|||||||
keyedElement = makeTerm <$> symbol KeyedElement <*> children (Literal.KeyValue <$> expression <*> expression)
|
keyedElement = makeTerm <$> symbol KeyedElement <*> children (Literal.KeyValue <$> expression <*> expression)
|
||||||
|
|
||||||
labelName :: Assignment
|
labelName :: Assignment
|
||||||
labelName = makeTerm <$> symbol LabelName <*> (Syntax.Identifier <$> (name <$> source))
|
labelName = makeTerm <$> symbol LabelName <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
labeledStatement :: Assignment
|
labeledStatement :: Assignment
|
||||||
labeledStatement = makeTerm <$> (symbol LabeledStatement <|> symbol LabeledStatement') <*> children (Go.Syntax.Label <$> expression <*> (expression <|> emptyTerm))
|
labeledStatement = makeTerm <$> (symbol LabeledStatement <|> symbol LabeledStatement') <*> children (Go.Syntax.Label <$> expression <*> (expression <|> emptyTerm))
|
||||||
|
@ -2,9 +2,85 @@
|
|||||||
module Language.Go.Syntax where
|
module Language.Go.Syntax where
|
||||||
|
|
||||||
import Data.Abstract.Evaluatable hiding (Label)
|
import Data.Abstract.Evaluatable hiding (Label)
|
||||||
|
import Data.Abstract.Module
|
||||||
import Diffing.Algorithm
|
import Diffing.Algorithm
|
||||||
|
import qualified Data.ByteString.Char8 as BC
|
||||||
|
import qualified Data.ByteString as B
|
||||||
|
import System.FilePath.Posix
|
||||||
import Prologue
|
import Prologue
|
||||||
|
|
||||||
|
newtype ImportPath = ImportPath { unPath :: FilePath }
|
||||||
|
deriving (Eq, Ord, Show)
|
||||||
|
|
||||||
|
importPath :: ByteString -> ImportPath
|
||||||
|
importPath str = let path = stripQuotes str in ImportPath (BC.unpack path)
|
||||||
|
where stripQuotes = B.filter (`B.notElem` "\'\"")
|
||||||
|
|
||||||
|
defaultAlias :: ImportPath -> Name
|
||||||
|
defaultAlias = BC.pack . takeFileName . unPath
|
||||||
|
|
||||||
|
-- TODO: need to delineate between relative and absolute Go imports
|
||||||
|
resolveGoImport :: MonadEvaluatable location term value m => FilePath -> m [ModulePath]
|
||||||
|
resolveGoImport relImportPath = do
|
||||||
|
ModuleInfo{..} <- currentModule
|
||||||
|
let relRootDir = takeDirectory (makeRelative moduleRoot modulePath)
|
||||||
|
listModulesInDir $ normalise (relRootDir </> normalise relImportPath)
|
||||||
|
|
||||||
|
-- | Import declarations (symbols are added directly to the calling environment).
|
||||||
|
--
|
||||||
|
-- If the list of symbols is empty copy everything to the calling environment.
|
||||||
|
data Import a = Import { importFrom :: ImportPath, importWildcardToken :: !a }
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
|
||||||
|
instance Eq1 Import where liftEq = genericLiftEq
|
||||||
|
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance Evaluatable Import where
|
||||||
|
eval (Import (ImportPath name) _) = do
|
||||||
|
paths <- resolveGoImport name
|
||||||
|
for_ paths $ \path -> do
|
||||||
|
(importedEnv, _) <- isolate (require path)
|
||||||
|
modifyEnv (mappend importedEnv)
|
||||||
|
unit
|
||||||
|
|
||||||
|
|
||||||
|
-- | Qualified Import declarations (symbols are qualified in calling environment).
|
||||||
|
--
|
||||||
|
-- If the list of symbols is empty copy and qualify everything to the calling environment.
|
||||||
|
data QualifiedImport a = QualifiedImport { qualifiedImportFrom :: !ImportPath, qualifiedImportAlias :: !a}
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
|
||||||
|
instance Eq1 QualifiedImport where liftEq = genericLiftEq
|
||||||
|
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance Evaluatable QualifiedImport where
|
||||||
|
eval (QualifiedImport (ImportPath name) aliasTerm) = do
|
||||||
|
paths <- resolveGoImport name
|
||||||
|
let alias = freeVariable (subterm aliasTerm)
|
||||||
|
void $ letrec' alias $ \addr -> do
|
||||||
|
for_ paths $ \path -> do
|
||||||
|
(importedEnv, _) <- isolate (require path)
|
||||||
|
modifyEnv (mappend importedEnv)
|
||||||
|
|
||||||
|
makeNamespace alias addr []
|
||||||
|
unit
|
||||||
|
|
||||||
|
-- | Side effect only imports (no symbols made available to the calling environment).
|
||||||
|
data SideEffectImport a = SideEffectImport { sideEffectImportFrom :: !ImportPath, sideEffectImportToken :: !a }
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
|
||||||
|
instance Eq1 SideEffectImport where liftEq = genericLiftEq
|
||||||
|
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance Evaluatable SideEffectImport where
|
||||||
|
eval (SideEffectImport (ImportPath name) _) = do
|
||||||
|
paths <- resolveGoImport name
|
||||||
|
for_ paths (isolate . require)
|
||||||
|
unit
|
||||||
|
|
||||||
-- A composite literal in Go
|
-- A composite literal in Go
|
||||||
data Composite a = Composite { compositeType :: !a, compositeElement :: !a }
|
data Composite a = Composite { compositeType :: !a, compositeElement :: !a }
|
||||||
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||||
@ -169,7 +245,7 @@ instance Show1 Package where liftShowsPrec = genericLiftShowsPrec
|
|||||||
|
|
||||||
instance Evaluatable Package where
|
instance Evaluatable Package where
|
||||||
eval (Package _ xs) = eval xs
|
eval (Package _ xs) = eval xs
|
||||||
|
|
||||||
|
|
||||||
-- | A type assertion in Go (e.g. `x.(T)` where the value of `x` is not nil and is of type `T`).
|
-- | A type assertion in Go (e.g. `x.(T)` where the value of `x` is not nil and is of type `T`).
|
||||||
data TypeAssertion a = TypeAssertion { typeAssertionSubject :: !a, typeAssertionType :: !a }
|
data TypeAssertion a = TypeAssertion { typeAssertionSubject :: !a, typeAssertionType :: !a }
|
||||||
|
@ -12,7 +12,7 @@ import Data.Syntax (emptyTerm, handleError, parseError, infixContext, makeTerm,
|
|||||||
import Language.PHP.Grammar as Grammar
|
import Language.PHP.Grammar as Grammar
|
||||||
import Prologue
|
import Prologue
|
||||||
import qualified Assigning.Assignment as Assignment
|
import qualified Assigning.Assignment as Assignment
|
||||||
import qualified Data.Abstract.FreeVariables as FV
|
-- import qualified Data.Abstract.FreeVariables as FV
|
||||||
import qualified Data.Syntax as Syntax
|
import qualified Data.Syntax as Syntax
|
||||||
import qualified Data.Syntax.Comment as Comment
|
import qualified Data.Syntax.Comment as Comment
|
||||||
import qualified Data.Syntax.Declaration as Declaration
|
import qualified Data.Syntax.Declaration as Declaration
|
||||||
@ -429,7 +429,7 @@ classConstDeclaration :: Assignment
|
|||||||
classConstDeclaration = makeTerm <$> symbol ClassConstDeclaration <*> children (Syntax.ClassConstDeclaration <$> (term visibilityModifier <|> emptyTerm) <*> manyTerm constElement)
|
classConstDeclaration = makeTerm <$> symbol ClassConstDeclaration <*> children (Syntax.ClassConstDeclaration <$> (term visibilityModifier <|> emptyTerm) <*> manyTerm constElement)
|
||||||
|
|
||||||
visibilityModifier :: Assignment
|
visibilityModifier :: Assignment
|
||||||
visibilityModifier = makeTerm <$> symbol VisibilityModifier <*> (Syntax.Identifier <$> (FV.name <$> source))
|
visibilityModifier = makeTerm <$> symbol VisibilityModifier <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
constElement :: Assignment
|
constElement :: Assignment
|
||||||
constElement = makeTerm <$> symbol ConstElement <*> children (Statement.Assignment [] <$> term name <*> term expression)
|
constElement = makeTerm <$> symbol ConstElement <*> children (Statement.Assignment [] <$> term name <*> term expression)
|
||||||
@ -635,7 +635,7 @@ propertyDeclaration :: Assignment
|
|||||||
propertyDeclaration = makeTerm <$> symbol PropertyDeclaration <*> children (Syntax.PropertyDeclaration <$> term propertyModifier <*> someTerm propertyElement)
|
propertyDeclaration = makeTerm <$> symbol PropertyDeclaration <*> children (Syntax.PropertyDeclaration <$> term propertyModifier <*> someTerm propertyElement)
|
||||||
|
|
||||||
propertyModifier :: Assignment
|
propertyModifier :: Assignment
|
||||||
propertyModifier = (makeTerm <$> symbol PropertyModifier <*> children (Syntax.PropertyModifier <$> (term visibilityModifier <|> emptyTerm) <*> (term staticModifier <|> emptyTerm))) <|> term (makeTerm <$> symbol PropertyModifier <*> (Syntax.Identifier <$> (FV.name <$> source)))
|
propertyModifier = (makeTerm <$> symbol PropertyModifier <*> children (Syntax.PropertyModifier <$> (term visibilityModifier <|> emptyTerm) <*> (term staticModifier <|> emptyTerm))) <|> term (makeTerm <$> symbol PropertyModifier <*> (Syntax.Identifier <$> source))
|
||||||
|
|
||||||
propertyElement :: Assignment
|
propertyElement :: Assignment
|
||||||
propertyElement = makeTerm <$> symbol PropertyElement <*> children (Statement.Assignment [] <$> term variableName <*> term propertyInitializer) <|> (symbol PropertyElement *> children (term variableName))
|
propertyElement = makeTerm <$> symbol PropertyElement <*> children (Statement.Assignment [] <$> term variableName <*> term propertyInitializer) <|> (symbol PropertyElement *> children (term variableName))
|
||||||
@ -696,7 +696,7 @@ namespaceAliasingClause = makeTerm <$> symbol NamespaceAliasingClause <*> childr
|
|||||||
|
|
||||||
-- | TODO Do something better than Identifier
|
-- | TODO Do something better than Identifier
|
||||||
namespaceFunctionOrConst :: Assignment
|
namespaceFunctionOrConst :: Assignment
|
||||||
namespaceFunctionOrConst = makeTerm <$> symbol NamespaceFunctionOrConst <*> (Syntax.Identifier <$> (FV.name <$> source))
|
namespaceFunctionOrConst = makeTerm <$> symbol NamespaceFunctionOrConst <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
globalDeclaration :: Assignment
|
globalDeclaration :: Assignment
|
||||||
globalDeclaration = makeTerm <$> symbol GlobalDeclaration <*> children (Syntax.GlobalDeclaration <$> manyTerm simpleVariable')
|
globalDeclaration = makeTerm <$> symbol GlobalDeclaration <*> children (Syntax.GlobalDeclaration <$> manyTerm simpleVariable')
|
||||||
@ -732,7 +732,7 @@ variableName :: Assignment
|
|||||||
variableName = makeTerm <$> symbol VariableName <*> children (Syntax.VariableName <$> term name)
|
variableName = makeTerm <$> symbol VariableName <*> children (Syntax.VariableName <$> term name)
|
||||||
|
|
||||||
name :: Assignment
|
name :: Assignment
|
||||||
name = makeTerm <$> (symbol Name <|> symbol Name') <*> (Syntax.Identifier <$> (FV.name <$> source))
|
name = makeTerm <$> (symbol Name <|> symbol Name') <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
functionStaticDeclaration :: Assignment
|
functionStaticDeclaration :: Assignment
|
||||||
functionStaticDeclaration = makeTerm <$> symbol FunctionStaticDeclaration <*> children (Declaration.VariableDeclaration <$> manyTerm staticVariableDeclaration)
|
functionStaticDeclaration = makeTerm <$> symbol FunctionStaticDeclaration <*> children (Declaration.VariableDeclaration <$> manyTerm staticVariableDeclaration)
|
||||||
|
@ -1,12 +1,13 @@
|
|||||||
{-# LANGUAGE DeriveAnyClass, ViewPatterns #-}
|
{-# LANGUAGE DeriveAnyClass, ViewPatterns #-}
|
||||||
module Language.PHP.Syntax where
|
module Language.PHP.Syntax where
|
||||||
|
|
||||||
import Data.Abstract.Evaluatable
|
import Data.Abstract.Evaluatable
|
||||||
import Data.Abstract.Path
|
import Data.Abstract.Module
|
||||||
import Diffing.Algorithm
|
import Data.Abstract.Path
|
||||||
import Prelude hiding (fail)
|
import qualified Data.ByteString.Char8 as BC
|
||||||
import Prologue hiding (Text)
|
import Diffing.Algorithm
|
||||||
|
import Prelude hiding (fail)
|
||||||
|
import Prologue hiding (Text)
|
||||||
|
|
||||||
newtype Text a = Text ByteString
|
newtype Text a = Text ByteString
|
||||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||||
@ -33,23 +34,28 @@ instance Evaluatable VariableName
|
|||||||
-- file, the complete contents of the included file are treated as though it
|
-- file, the complete contents of the included file are treated as though it
|
||||||
-- were defined inside that function.
|
-- were defined inside that function.
|
||||||
|
|
||||||
|
resolvePHPName :: MonadEvaluatable location term value m => ByteString -> m ModulePath
|
||||||
|
resolvePHPName n = resolve [name] >>= maybeFail notFound
|
||||||
|
where name = toName n
|
||||||
|
notFound = "Unable to resolve: " <> name
|
||||||
|
toName = BC.unpack . dropRelativePrefix . stripQuotes
|
||||||
|
|
||||||
doInclude :: MonadEvaluatable location term value m => Subterm t (m value) -> m value
|
doInclude :: MonadEvaluatable location term value m => Subterm t (m value) -> m value
|
||||||
doInclude path = do
|
doInclude pathTerm = do
|
||||||
name <- toQualifiedName <$> (subtermValue path >>= asString)
|
name <- subtermValue pathTerm >>= asString
|
||||||
(importedEnv, v) <- isolate (load name)
|
path <- resolvePHPName name
|
||||||
|
(importedEnv, v) <- isolate (load path)
|
||||||
modifyEnv (mappend importedEnv)
|
modifyEnv (mappend importedEnv)
|
||||||
pure v
|
pure v
|
||||||
|
|
||||||
doIncludeOnce :: MonadEvaluatable location term value m => Subterm t (m value) -> m value
|
doIncludeOnce :: MonadEvaluatable location term value m => Subterm t (m value) -> m value
|
||||||
doIncludeOnce path = do
|
doIncludeOnce pathTerm = do
|
||||||
name <- toQualifiedName <$> (subtermValue path >>= asString)
|
name <- subtermValue pathTerm >>= asString
|
||||||
(importedEnv, v) <- isolate (require name)
|
path <- resolvePHPName name
|
||||||
|
(importedEnv, v) <- isolate (require path)
|
||||||
modifyEnv (mappend importedEnv)
|
modifyEnv (mappend importedEnv)
|
||||||
pure v
|
pure v
|
||||||
|
|
||||||
toQualifiedName :: ByteString -> Name
|
|
||||||
toQualifiedName = qualifiedName . splitOnPathSeparator . dropExtension . dropRelativePrefix . stripQuotes
|
|
||||||
|
|
||||||
newtype Require a = Require a
|
newtype Require a = Require a
|
||||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||||
|
|
||||||
|
@ -8,7 +8,6 @@ module Language.Python.Assignment
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import Assigning.Assignment hiding (Assignment, Error)
|
import Assigning.Assignment hiding (Assignment, Error)
|
||||||
import Data.Abstract.FreeVariables
|
|
||||||
import Data.Record
|
import Data.Record
|
||||||
import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize)
|
import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize)
|
||||||
import GHC.Stack
|
import GHC.Stack
|
||||||
@ -33,8 +32,6 @@ type Syntax =
|
|||||||
, Declaration.Comprehension
|
, Declaration.Comprehension
|
||||||
, Declaration.Decorator
|
, Declaration.Decorator
|
||||||
, Declaration.Function
|
, Declaration.Function
|
||||||
, Declaration.Import
|
|
||||||
, Declaration.QualifiedImport
|
|
||||||
, Declaration.Variable
|
, Declaration.Variable
|
||||||
, Expression.Arithmetic
|
, Expression.Arithmetic
|
||||||
, Expression.Boolean
|
, Expression.Boolean
|
||||||
@ -73,6 +70,9 @@ type Syntax =
|
|||||||
, Statement.While
|
, Statement.While
|
||||||
, Statement.Yield
|
, Statement.Yield
|
||||||
, Python.Syntax.Ellipsis
|
, Python.Syntax.Ellipsis
|
||||||
|
, Python.Syntax.Import
|
||||||
|
, Python.Syntax.QualifiedImport
|
||||||
|
, Python.Syntax.QualifiedAliasedImport
|
||||||
, Syntax.Context
|
, Syntax.Context
|
||||||
, Syntax.Empty
|
, Syntax.Empty
|
||||||
, Syntax.Error
|
, Syntax.Error
|
||||||
@ -179,10 +179,10 @@ expressionList :: Assignment
|
|||||||
expressionList = makeTerm'' <$> symbol ExpressionList <*> children (someTerm expression)
|
expressionList = makeTerm'' <$> symbol ExpressionList <*> children (someTerm expression)
|
||||||
|
|
||||||
listSplat :: Assignment
|
listSplat :: Assignment
|
||||||
listSplat = makeTerm <$> symbol ListSplat <*> (Syntax.Identifier <$> (name <$> source))
|
listSplat = makeTerm <$> symbol ListSplat <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
dictionarySplat :: Assignment
|
dictionarySplat :: Assignment
|
||||||
dictionarySplat = makeTerm <$> symbol DictionarySplat <*> (Syntax.Identifier <$> (name <$> source))
|
dictionarySplat = makeTerm <$> symbol DictionarySplat <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
keywordArgument :: Assignment
|
keywordArgument :: Assignment
|
||||||
keywordArgument = makeTerm <$> symbol KeywordArgument <*> children (Statement.Assignment [] <$> term expression <*> term expression)
|
keywordArgument = makeTerm <$> symbol KeywordArgument <*> children (Statement.Assignment [] <$> term expression <*> term expression)
|
||||||
@ -249,7 +249,7 @@ functionDefinition
|
|||||||
makeAsyncFunctionDeclaration loc (async', functionName', functionParameters, ty, functionBody) = makeTerm loc $ Type.Annotation (makeTerm loc $ Type.Annotation (makeTerm loc $ Declaration.Function [] functionName' functionParameters functionBody) (fromMaybe (makeTerm loc Syntax.Empty) ty)) async'
|
makeAsyncFunctionDeclaration loc (async', functionName', functionParameters, ty, functionBody) = makeTerm loc $ Type.Annotation (makeTerm loc $ Type.Annotation (makeTerm loc $ Declaration.Function [] functionName' functionParameters functionBody) (fromMaybe (makeTerm loc Syntax.Empty) ty)) async'
|
||||||
|
|
||||||
async' :: Assignment
|
async' :: Assignment
|
||||||
async' = makeTerm <$> symbol AnonAsync <*> (Syntax.Identifier <$> (name <$> source))
|
async' = makeTerm <$> symbol AnonAsync <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
classDefinition :: Assignment
|
classDefinition :: Assignment
|
||||||
classDefinition = makeTerm <$> symbol ClassDefinition <*> children (Declaration.Class <$> pure [] <*> term expression <*> argumentList <*> expressions)
|
classDefinition = makeTerm <$> symbol ClassDefinition <*> children (Declaration.Class <$> pure [] <*> term expression <*> argumentList <*> expressions)
|
||||||
@ -337,14 +337,8 @@ assignment' = makeTerm <$> symbol Assignment <*> children (Statement.Assignmen
|
|||||||
yield :: Assignment
|
yield :: Assignment
|
||||||
yield = makeTerm <$> symbol Yield <*> (Statement.Yield <$> children (term ( expression <|> emptyTerm )))
|
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 :: Assignment
|
||||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> (name <$> source))
|
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier' <|> symbol DottedName) <*> (Syntax.Identifier <$> source)
|
||||||
<|> makeQualifiedIdentifier <$> symbol DottedName <*> children (some identifier')
|
|
||||||
<|> symbol DottedName *> children identifier
|
|
||||||
where
|
|
||||||
identifier' = (symbol Identifier <|> symbol Identifier') *> source
|
|
||||||
makeQualifiedIdentifier loc xs = makeTerm loc (Syntax.Identifier (qualifiedName xs))
|
|
||||||
|
|
||||||
set :: Assignment
|
set :: Assignment
|
||||||
set = makeTerm <$> symbol Set <*> children (Literal.Set <$> manyTerm expression)
|
set = makeTerm <$> symbol Set <*> children (Literal.Set <$> manyTerm expression)
|
||||||
@ -379,29 +373,31 @@ comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
|||||||
|
|
||||||
import' :: Assignment
|
import' :: Assignment
|
||||||
import' = makeTerm'' <$> symbol ImportStatement <*> children (manyTerm (aliasedImport <|> plainImport))
|
import' = makeTerm'' <$> symbol ImportStatement <*> children (manyTerm (aliasedImport <|> plainImport))
|
||||||
<|> makeTerm <$> symbol ImportFromStatement <*> children (Declaration.Import <$> (identifier <|> emptyTerm) <*> (wildcard <|> some (aliasImportSymbol <|> importSymbol)) <*> emptyTerm)
|
<|> makeTerm <$> symbol ImportFromStatement <*> children (Python.Syntax.Import <$> importPath <*> (wildcard <|> some (aliasImportSymbol <|> importSymbol)))
|
||||||
where
|
where
|
||||||
-- `import a as b`
|
-- `import a as b`
|
||||||
aliasedImport = makeImport <$> symbol AliasedImport <*> children ((,) <$> expression <*> (Just <$> expression))
|
aliasedImport = makeTerm <$> symbol AliasedImport <*> children (Python.Syntax.QualifiedAliasedImport <$> importPath <*> expression)
|
||||||
-- `import a`
|
-- `import a`
|
||||||
plainImport = makeImport <$> location <*> ((,) <$> identifier <*> pure Nothing)
|
plainImport = makeTerm <$> location <*> (Python.Syntax.QualifiedImport <$> importPath)
|
||||||
-- `from a import foo `
|
-- `from a import foo `
|
||||||
importSymbol = makeNameAliasPair <$> rawIdentifier <*> pure Nothing
|
importSymbol = makeNameAliasPair <$> aliasIdentifier <*> pure Nothing
|
||||||
-- `from a import foo as bar`
|
-- `from a import foo as bar`
|
||||||
aliasImportSymbol = symbol AliasedImport *> children (makeNameAliasPair <$> rawIdentifier <*> (Just <$> rawIdentifier))
|
aliasImportSymbol = symbol AliasedImport *> children (makeNameAliasPair <$> aliasIdentifier <*> (Just <$> aliasIdentifier))
|
||||||
-- `from a import *`
|
-- `from a import *`
|
||||||
wildcard = symbol WildcardImport *> source $> []
|
wildcard = symbol WildcardImport *> source $> []
|
||||||
|
|
||||||
rawIdentifier = (name <$> identifier') <|> (qualifiedName <$> dottedName')
|
importPath = importIden <|> importDottedName <|> importRelative
|
||||||
dottedName' = symbol DottedName *> children (some identifier')
|
importIden = moduleName <$> identifierSource
|
||||||
identifier' = (symbol Identifier <|> symbol Identifier') *> source
|
importDottedName = symbol DottedName *> (qualifiedModuleName <$> children (some identifierSource))
|
||||||
|
importRelative = symbol RelativeImport *> (qualifiedModuleName <$> ((:) <$> source <*> children (many identifierSource)))
|
||||||
|
identifierSource = (symbol Identifier <|> symbol Identifier') *> source
|
||||||
|
|
||||||
|
aliasIdentifier = (symbol Identifier <|> symbol Identifier') *> source <|> symbol DottedName *> source
|
||||||
makeNameAliasPair from (Just alias) = (from, alias)
|
makeNameAliasPair from (Just alias) = (from, alias)
|
||||||
makeNameAliasPair from Nothing = (from, from)
|
makeNameAliasPair from Nothing = (from, from)
|
||||||
makeImport loc (from, Just alias) = makeTerm loc (Declaration.QualifiedImport from alias [])
|
|
||||||
makeImport loc (from, Nothing) = makeTerm loc (Declaration.QualifiedImport from from [])
|
|
||||||
|
|
||||||
assertStatement :: Assignment
|
assertStatement :: Assignment
|
||||||
assertStatement = makeTerm <$> symbol AssertStatement <*> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier <$> (name <$> source))) <*> manyTerm expression <*> emptyTerm)
|
assertStatement = makeTerm <$> symbol AssertStatement <*> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier <$> source)) <*> manyTerm expression <*> emptyTerm)
|
||||||
|
|
||||||
printStatement :: Assignment
|
printStatement :: Assignment
|
||||||
printStatement = do
|
printStatement = do
|
||||||
@ -410,25 +406,25 @@ printStatement = do
|
|||||||
print <- term printKeyword
|
print <- term printKeyword
|
||||||
term (redirectCallTerm location print <|> printCallTerm location print)
|
term (redirectCallTerm location print <|> printCallTerm location print)
|
||||||
where
|
where
|
||||||
printKeyword = makeTerm <$> symbol AnonPrint <*> (Syntax.Identifier <$> (name <$> source))
|
printKeyword = makeTerm <$> symbol AnonPrint <*> (Syntax.Identifier <$> source)
|
||||||
redirectCallTerm location identifier = makeTerm location <$ symbol Chevron <*> (flip Python.Syntax.Redirect <$> children (term expression) <*> term (printCallTerm location identifier))
|
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)
|
printCallTerm location identifier = makeTerm location <$> (Expression.Call [] identifier <$> manyTerm expression <*> emptyTerm)
|
||||||
|
|
||||||
nonlocalStatement :: Assignment
|
nonlocalStatement :: Assignment
|
||||||
nonlocalStatement = makeTerm <$> symbol NonlocalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonNonlocal <*> (Syntax.Identifier <$> (name <$> source))) <*> manyTerm expression <*> emptyTerm)
|
nonlocalStatement = makeTerm <$> symbol NonlocalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonNonlocal <*> (Syntax.Identifier <$> source)) <*> manyTerm expression <*> emptyTerm)
|
||||||
|
|
||||||
globalStatement :: Assignment
|
globalStatement :: Assignment
|
||||||
globalStatement = makeTerm <$> symbol GlobalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonGlobal <*> (Syntax.Identifier <$> (name <$> source))) <*> manyTerm expression <*> emptyTerm)
|
globalStatement = makeTerm <$> symbol GlobalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonGlobal <*> (Syntax.Identifier <$> source)) <*> manyTerm expression <*> emptyTerm)
|
||||||
|
|
||||||
await :: Assignment
|
await :: Assignment
|
||||||
await = makeTerm <$> symbol Await <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier <$> (name <$> source))) <*> manyTerm expression <*> emptyTerm)
|
await = makeTerm <$> symbol Await <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier <$> source)) <*> manyTerm expression <*> emptyTerm)
|
||||||
|
|
||||||
returnStatement :: Assignment
|
returnStatement :: Assignment
|
||||||
returnStatement = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> term (expressionList <|> emptyTerm))
|
returnStatement = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> term (expressionList <|> emptyTerm))
|
||||||
|
|
||||||
deleteStatement :: Assignment
|
deleteStatement :: Assignment
|
||||||
deleteStatement = makeTerm <$> symbol DeleteStatement <*> children (Expression.Call <$> pure [] <*> term deleteIdentifier <* symbol ExpressionList <*> children (manyTerm expression) <*> emptyTerm)
|
deleteStatement = makeTerm <$> symbol DeleteStatement <*> children (Expression.Call <$> pure [] <*> term deleteIdentifier <* symbol ExpressionList <*> children (manyTerm expression) <*> emptyTerm)
|
||||||
where deleteIdentifier = makeTerm <$> symbol AnonDel <*> (Syntax.Identifier <$> (name <$> source))
|
where deleteIdentifier = makeTerm <$> symbol AnonDel <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
raiseStatement :: Assignment
|
raiseStatement :: Assignment
|
||||||
raiseStatement = makeTerm <$> symbol RaiseStatement <*> children (Statement.Throw <$> expressions)
|
raiseStatement = makeTerm <$> symbol RaiseStatement <*> children (Statement.Throw <$> expressions)
|
||||||
@ -439,7 +435,7 @@ ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> ter
|
|||||||
makeElif (loc, makeIf) rest = makeTerm loc (makeIf rest)
|
makeElif (loc, makeIf) rest = makeTerm loc (makeIf rest)
|
||||||
|
|
||||||
execStatement :: Assignment
|
execStatement :: Assignment
|
||||||
execStatement = makeTerm <$> symbol ExecStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> location <*> (Syntax.Identifier <$> (name <$> source))) <*> manyTerm (string <|> expression) <*> emptyTerm)
|
execStatement = makeTerm <$> symbol ExecStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> location <*> (Syntax.Identifier <$> source)) <*> manyTerm (string <|> expression) <*> emptyTerm)
|
||||||
|
|
||||||
passStatement :: Assignment
|
passStatement :: Assignment
|
||||||
passStatement = makeTerm <$> symbol PassStatement <*> (Statement.NoOp <$> emptyTerm <* advance)
|
passStatement = makeTerm <$> symbol PassStatement <*> (Statement.NoOp <$> emptyTerm <* advance)
|
||||||
|
@ -1,12 +1,155 @@
|
|||||||
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses #-}
|
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses #-}
|
||||||
module Language.Python.Syntax where
|
module Language.Python.Syntax where
|
||||||
|
|
||||||
import Data.Abstract.Evaluatable
|
import Data.Abstract.Environment as Env
|
||||||
import Data.Align.Generic
|
import Data.Abstract.Evaluatable
|
||||||
import Data.Functor.Classes.Generic
|
import Data.Abstract.Module
|
||||||
import Data.Mergeable
|
import Data.Align.Generic
|
||||||
import Diffing.Algorithm
|
import qualified Data.ByteString.Char8 as BC
|
||||||
import GHC.Generics
|
import Data.Functor.Classes.Generic
|
||||||
|
import Data.List (intercalate)
|
||||||
|
import qualified Data.List.NonEmpty as NonEmpty
|
||||||
|
import Data.Mergeable
|
||||||
|
import Diffing.Algorithm
|
||||||
|
import GHC.Generics
|
||||||
|
import Prologue
|
||||||
|
import System.FilePath.Posix
|
||||||
|
|
||||||
|
|
||||||
|
-- TODO: Model relative imports. E.g.:
|
||||||
|
-- import .a
|
||||||
|
-- import ..a
|
||||||
|
|
||||||
|
newtype QualifiedModuleName = QualifiedModuleName { unQualifiedModuleName :: NonEmpty FilePath }
|
||||||
|
deriving (Eq, Ord, Show)
|
||||||
|
|
||||||
|
moduleName :: ByteString -> QualifiedModuleName
|
||||||
|
moduleName x = QualifiedModuleName $ BC.unpack x :| []
|
||||||
|
|
||||||
|
qualifiedModuleName :: [ByteString] -> QualifiedModuleName
|
||||||
|
qualifiedModuleName xs = QualifiedModuleName $ NonEmpty.fromList (BC.unpack <$> xs)
|
||||||
|
|
||||||
|
friendlyName :: QualifiedModuleName -> String
|
||||||
|
friendlyName (QualifiedModuleName xs) = intercalate "." (NonEmpty.toList xs)
|
||||||
|
|
||||||
|
-- Python module resolution.
|
||||||
|
--
|
||||||
|
-- https://docs.python.org/3/reference/import.html#importsystem
|
||||||
|
--
|
||||||
|
-- Regular packages resolution:
|
||||||
|
--
|
||||||
|
-- parent/
|
||||||
|
-- __init__.py
|
||||||
|
-- one/
|
||||||
|
-- __init__.py
|
||||||
|
-- two/
|
||||||
|
-- __init__.py
|
||||||
|
-- three/
|
||||||
|
-- __init__.py
|
||||||
|
--
|
||||||
|
-- `import parent.one` will implicitly execute:
|
||||||
|
-- `parent/__init__.py` and
|
||||||
|
-- `parent/one/__init__.py`
|
||||||
|
-- Subsequent imports of `parent.two` or `parent.three` will execute
|
||||||
|
-- `parent/two/__init__.py` and
|
||||||
|
-- `parent/three/__init__.py` respectively.
|
||||||
|
resolvePythonModules :: MonadEvaluatable location term value m => QualifiedModuleName -> m (NonEmpty ModulePath)
|
||||||
|
resolvePythonModules q@(QualifiedModuleName qualifiedName) = do
|
||||||
|
ModuleInfo{..} <- currentModule
|
||||||
|
let relRootDir = takeDirectory (makeRelative moduleRoot modulePath)
|
||||||
|
for (moduleNames qualifiedName) $ \name -> do
|
||||||
|
go relRootDir name
|
||||||
|
where
|
||||||
|
moduleNames = NonEmpty.scanl1 (</>)
|
||||||
|
notFound xs = "Unable to resolve module import: " <> friendlyName q <> ", searched: " <> show xs
|
||||||
|
go rootDir x = do
|
||||||
|
let path = normalise (rootDir </> normalise x)
|
||||||
|
let searchPaths = [ path </> "__init__.py"
|
||||||
|
, path <.> ".py"
|
||||||
|
]
|
||||||
|
trace ("searched: " <> show searchPaths) $
|
||||||
|
resolve searchPaths >>= maybeFail (notFound searchPaths)
|
||||||
|
|
||||||
|
|
||||||
|
-- | Import declarations (symbols are added directly to the calling environment).
|
||||||
|
--
|
||||||
|
-- If the list of symbols is empty copy everything to the calling environment.
|
||||||
|
data Import a = Import { importFrom :: QualifiedModuleName, importSymbols :: ![(Name, Name)] }
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
|
||||||
|
instance Eq1 Import where liftEq = genericLiftEq
|
||||||
|
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
-- from a import b
|
||||||
|
-- from a import b as c
|
||||||
|
-- from a import *
|
||||||
|
instance Evaluatable Import where
|
||||||
|
eval (Import name xs) = do
|
||||||
|
modulePaths <- resolvePythonModules name
|
||||||
|
|
||||||
|
-- Eval parent modules first
|
||||||
|
for_ (NonEmpty.init modulePaths) (isolate . require)
|
||||||
|
|
||||||
|
-- Last module path is the one we want to import
|
||||||
|
let path = NonEmpty.last modulePaths
|
||||||
|
(importedEnv, _) <- isolate (require path)
|
||||||
|
modifyEnv (mappend (select importedEnv))
|
||||||
|
unit
|
||||||
|
where
|
||||||
|
select importedEnv
|
||||||
|
| Prologue.null xs = importedEnv
|
||||||
|
| otherwise = Env.overwrite xs importedEnv
|
||||||
|
|
||||||
|
|
||||||
|
newtype QualifiedImport a = QualifiedImport { qualifiedImportFrom :: QualifiedModuleName }
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
|
||||||
|
instance Eq1 QualifiedImport where liftEq = genericLiftEq
|
||||||
|
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
-- import a.b.c
|
||||||
|
instance Evaluatable QualifiedImport where
|
||||||
|
eval (QualifiedImport name@QualifiedModuleName{..}) = do
|
||||||
|
modulePaths <- resolvePythonModules name
|
||||||
|
go (NonEmpty.zip (BC.pack <$> unQualifiedModuleName) modulePaths)
|
||||||
|
where
|
||||||
|
-- Evaluate and import the last module, updating the environment
|
||||||
|
go ((name, path) :| []) = letrec' name $ \addr -> do
|
||||||
|
(importedEnv, _) <- isolate (require path)
|
||||||
|
modifyEnv (mappend importedEnv)
|
||||||
|
void $ makeNamespace name addr []
|
||||||
|
unit
|
||||||
|
-- Evaluate each parent module, creating a just namespace
|
||||||
|
go ((name, path) :| xs) = letrec' name $ \addr -> do
|
||||||
|
void $ isolate (require path)
|
||||||
|
void $ go (NonEmpty.fromList xs)
|
||||||
|
makeNamespace name addr []
|
||||||
|
|
||||||
|
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportFrom :: QualifiedModuleName, qualifiedAliasedImportAlias :: !a }
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
|
||||||
|
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
|
||||||
|
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 QualifiedAliasedImport where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
-- import a.b.c as e
|
||||||
|
instance Evaluatable QualifiedAliasedImport where
|
||||||
|
eval (QualifiedAliasedImport name aliasTerm) = do
|
||||||
|
modulePaths <- resolvePythonModules name
|
||||||
|
|
||||||
|
-- Evaluate each parent module
|
||||||
|
for_ (NonEmpty.init modulePaths) (isolate . require)
|
||||||
|
|
||||||
|
-- Evaluate and import the last module, aliasing and updating the environment
|
||||||
|
let alias = freeVariable (subterm aliasTerm)
|
||||||
|
letrec' alias $ \addr -> do
|
||||||
|
let path = NonEmpty.last modulePaths
|
||||||
|
(importedEnv, _) <- isolate (require path)
|
||||||
|
modifyEnv (mappend importedEnv)
|
||||||
|
void $ makeNamespace alias addr []
|
||||||
|
unit
|
||||||
|
|
||||||
-- | Ellipsis (used in splice expressions and alternatively can be used as a fill in expression, like `undefined` in Haskell)
|
-- | Ellipsis (used in splice expressions and alternatively can be used as a fill in expression, like `undefined` in Haskell)
|
||||||
data Ellipsis a = Ellipsis
|
data Ellipsis a = Ellipsis
|
||||||
|
@ -7,7 +7,6 @@ module Language.Ruby.Assignment
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import Assigning.Assignment hiding (Assignment, Error)
|
import Assigning.Assignment hiding (Assignment, Error)
|
||||||
import Data.Abstract.FreeVariables
|
|
||||||
import Data.List (elem)
|
import Data.List (elem)
|
||||||
import Data.Record
|
import Data.Record
|
||||||
import Data.Syntax (contextualize, postContextualize, emptyTerm, parseError, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1)
|
import Data.Syntax (contextualize, postContextualize, emptyTerm, parseError, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1)
|
||||||
@ -159,7 +158,7 @@ identifier =
|
|||||||
<|> mk BlockArgument
|
<|> mk BlockArgument
|
||||||
<|> mk ReservedIdentifier
|
<|> mk ReservedIdentifier
|
||||||
<|> mk Uninterpreted
|
<|> mk Uninterpreted
|
||||||
where mk s = makeTerm <$> symbol s <*> (Syntax.Identifier <$> (name <$> source))
|
where mk s = makeTerm <$> symbol s <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
-- TODO: Handle interpolation in all literals that support it (strings, regexes, symbols, subshells, etc).
|
-- TODO: Handle interpolation in all literals that support it (strings, regexes, symbols, subshells, etc).
|
||||||
literal :: Assignment
|
literal :: Assignment
|
||||||
@ -213,7 +212,7 @@ parameter =
|
|||||||
<|> mk OptionalParameter
|
<|> mk OptionalParameter
|
||||||
<|> makeTerm <$> symbol DestructuredParameter <*> children (many parameter)
|
<|> makeTerm <$> symbol DestructuredParameter <*> children (many parameter)
|
||||||
<|> expression
|
<|> expression
|
||||||
where mk s = makeTerm <$> symbol s <*> (Syntax.Identifier <$> (name <$> source))
|
where mk s = makeTerm <$> symbol s <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
method :: Assignment
|
method :: Assignment
|
||||||
method = makeTerm <$> symbol Method <*> children (Declaration.Method <$> pure [] <*> emptyTerm <*> expression <*> params <*> expressions')
|
method = makeTerm <$> symbol Method <*> children (Declaration.Method <$> pure [] <*> emptyTerm <*> expression <*> params <*> expressions')
|
||||||
@ -240,11 +239,11 @@ comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
|||||||
|
|
||||||
alias :: Assignment
|
alias :: Assignment
|
||||||
alias = makeTerm <$> symbol Alias <*> children (Expression.Call <$> pure [] <*> name' <*> some expression <*> emptyTerm)
|
alias = makeTerm <$> symbol Alias <*> children (Expression.Call <$> pure [] <*> name' <*> some expression <*> emptyTerm)
|
||||||
where name' = makeTerm <$> location <*> (Syntax.Identifier <$> (name <$> source))
|
where name' = makeTerm <$> location <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
undef :: Assignment
|
undef :: Assignment
|
||||||
undef = makeTerm <$> symbol Undef <*> children (Expression.Call <$> pure [] <*> name' <*> some expression <*> emptyTerm)
|
undef = makeTerm <$> symbol Undef <*> children (Expression.Call <$> pure [] <*> name' <*> some expression <*> emptyTerm)
|
||||||
where name' = makeTerm <$> location <*> (Syntax.Identifier <$> (name <$> source))
|
where name' = makeTerm <$> location <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
if' :: Assignment
|
if' :: Assignment
|
||||||
if' = ifElsif If
|
if' = ifElsif If
|
||||||
@ -347,7 +346,7 @@ assignment' = makeTerm <$> symbol Assignment <*> children (Statement.As
|
|||||||
|
|
||||||
lhs = makeTerm <$> symbol LeftAssignmentList <*> children (many expr) <|> expr
|
lhs = makeTerm <$> symbol LeftAssignmentList <*> children (many expr) <|> expr
|
||||||
rhs = makeTerm <$> symbol RightAssignmentList <*> children (many expr) <|> expr
|
rhs = makeTerm <$> symbol RightAssignmentList <*> children (many expr) <|> expr
|
||||||
expr = makeTerm <$> symbol RestAssignment <*> (Syntax.Identifier <$> (name <$> source))
|
expr = makeTerm <$> symbol RestAssignment <*> (Syntax.Identifier <$> source)
|
||||||
<|> makeTerm <$> symbol DestructuredLeftAssignment <*> children (many expr)
|
<|> makeTerm <$> symbol DestructuredLeftAssignment <*> children (many expr)
|
||||||
<|> expression
|
<|> expression
|
||||||
|
|
||||||
@ -356,7 +355,7 @@ unary = symbol Unary >>= \ location ->
|
|||||||
makeTerm location . Expression.Complement <$> children ( symbol AnonTilde *> expression )
|
makeTerm location . Expression.Complement <$> children ( symbol AnonTilde *> expression )
|
||||||
<|> makeTerm location . Expression.Not <$> children ( symbol AnonBang *> expression )
|
<|> makeTerm location . Expression.Not <$> children ( symbol AnonBang *> expression )
|
||||||
<|> makeTerm location . Expression.Not <$> children ( symbol AnonNot *> expression )
|
<|> makeTerm location . Expression.Not <$> children ( symbol AnonNot *> expression )
|
||||||
<|> makeTerm location <$> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonDefinedQuestion <*> (Syntax.Identifier <$> (name <$> source))) <*> some expression <*> emptyTerm)
|
<|> makeTerm location <$> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonDefinedQuestion <*> (Syntax.Identifier <$> source)) <*> some expression <*> emptyTerm)
|
||||||
<|> makeTerm location . Expression.Negate <$> children ( symbol AnonMinus' *> expression )
|
<|> makeTerm location . Expression.Negate <$> children ( symbol AnonMinus' *> expression )
|
||||||
<|> children ( symbol AnonPlus *> expression )
|
<|> children ( symbol AnonPlus *> expression )
|
||||||
|
|
||||||
|
@ -1,13 +1,34 @@
|
|||||||
{-# LANGUAGE DeriveAnyClass #-}
|
{-# LANGUAGE DeriveAnyClass #-}
|
||||||
module Language.Ruby.Syntax where
|
module Language.Ruby.Syntax where
|
||||||
|
|
||||||
import Control.Monad (unless)
|
import Control.Monad (unless)
|
||||||
import Data.Abstract.Evaluatable
|
import Data.Abstract.Evaluatable
|
||||||
import Data.Abstract.ModuleTable as ModuleTable
|
import Data.Abstract.Module (ModulePath)
|
||||||
import Data.Abstract.Path
|
import Data.Abstract.ModuleTable as ModuleTable
|
||||||
import Diffing.Algorithm
|
import Data.Abstract.Path
|
||||||
import Prelude hiding (fail)
|
import qualified Data.ByteString.Char8 as BC
|
||||||
import Prologue
|
import Diffing.Algorithm
|
||||||
|
import Prelude hiding (fail)
|
||||||
|
import Prologue
|
||||||
|
import System.FilePath.Posix
|
||||||
|
|
||||||
|
|
||||||
|
-- TODO: Fully sort out ruby require/load mechanics
|
||||||
|
--
|
||||||
|
-- require "json"
|
||||||
|
resolveRubyName :: MonadEvaluatable location term value m => ByteString -> m ModulePath
|
||||||
|
resolveRubyName name = let n = cleanNameOrPath name in resolve [n <.> "rb"] >>= maybeFailNotFound n
|
||||||
|
|
||||||
|
-- load "/root/src/file.rb"
|
||||||
|
resolveRubyPath :: MonadEvaluatable location term value m => ByteString -> m ModulePath
|
||||||
|
resolveRubyPath path = let n = cleanNameOrPath path in resolve [n] >>= maybeFailNotFound n
|
||||||
|
|
||||||
|
maybeFailNotFound :: MonadFail m => String -> Maybe a -> m a
|
||||||
|
maybeFailNotFound name = maybeFail notFound
|
||||||
|
where notFound = "Unable to resolve: " <> name
|
||||||
|
|
||||||
|
cleanNameOrPath :: ByteString -> String
|
||||||
|
cleanNameOrPath = BC.unpack . dropRelativePrefix . stripQuotes
|
||||||
|
|
||||||
data Require a = Require { requireRelative :: Bool, requirePath :: !a }
|
data Require a = Require { requireRelative :: Bool, requirePath :: !a }
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
@ -18,15 +39,14 @@ instance Show1 Require where liftShowsPrec = genericLiftShowsPrec
|
|||||||
|
|
||||||
instance Evaluatable Require where
|
instance Evaluatable Require where
|
||||||
eval (Require _ x) = do
|
eval (Require _ x) = do
|
||||||
name <- toName <$> (subtermValue x >>= asString)
|
name <- subtermValue x >>= asString
|
||||||
(importedEnv, v) <- isolate (doRequire name)
|
path <- resolveRubyName name
|
||||||
|
(importedEnv, v) <- isolate (doRequire path)
|
||||||
modifyEnv (mappend importedEnv)
|
modifyEnv (mappend importedEnv)
|
||||||
pure v -- Returns True if the file was loaded, False if it was already loaded. http://ruby-doc.org/core-2.5.0/Kernel.html#method-i-require
|
pure v -- Returns True if the file was loaded, False if it was already loaded. http://ruby-doc.org/core-2.5.0/Kernel.html#method-i-require
|
||||||
where
|
|
||||||
toName = qualifiedName . splitOnPathSeparator . dropRelativePrefix . stripQuotes
|
|
||||||
|
|
||||||
doRequire :: MonadEvaluatable location term value m
|
doRequire :: MonadEvaluatable location term value m
|
||||||
=> ModuleName
|
=> ModulePath
|
||||||
-> m (Environment location value, value)
|
-> m (Environment location value, value)
|
||||||
doRequire name = do
|
doRequire name = do
|
||||||
moduleTable <- getModuleTable
|
moduleTable <- getModuleTable
|
||||||
@ -54,11 +74,10 @@ instance Evaluatable Load where
|
|||||||
|
|
||||||
doLoad :: MonadEvaluatable location term value m => ByteString -> Bool -> m value
|
doLoad :: MonadEvaluatable location term value m => ByteString -> Bool -> m value
|
||||||
doLoad path shouldWrap = do
|
doLoad path shouldWrap = do
|
||||||
(importedEnv, _) <- isolate (load (toName path))
|
path' <- resolveRubyPath path
|
||||||
|
(importedEnv, _) <- isolate (load path')
|
||||||
unless shouldWrap $ modifyEnv (mappend importedEnv)
|
unless shouldWrap $ modifyEnv (mappend importedEnv)
|
||||||
boolean Prelude.True -- load always returns true. http://ruby-doc.org/core-2.5.0/Kernel.html#method-i-load
|
boolean Prelude.True -- load always returns true. http://ruby-doc.org/core-2.5.0/Kernel.html#method-i-load
|
||||||
where
|
|
||||||
toName = qualifiedName . splitOnPathSeparator . dropExtension . dropRelativePrefix . stripQuotes
|
|
||||||
|
|
||||||
-- TODO: autoload
|
-- TODO: autoload
|
||||||
|
|
||||||
|
@ -8,8 +8,6 @@ module Language.TypeScript.Assignment
|
|||||||
|
|
||||||
import Assigning.Assignment hiding (Assignment, Error)
|
import Assigning.Assignment hiding (Assignment, Error)
|
||||||
import qualified Assigning.Assignment as Assignment
|
import qualified Assigning.Assignment as Assignment
|
||||||
import Data.Abstract.FreeVariables
|
|
||||||
import Data.Abstract.Path
|
|
||||||
import Data.Record
|
import Data.Record
|
||||||
import Data.Syntax (emptyTerm, handleError, parseError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, contextualize, postContextualize)
|
import Data.Syntax (emptyTerm, handleError, parseError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, contextualize, postContextualize)
|
||||||
import qualified Data.Syntax as Syntax
|
import qualified Data.Syntax as Syntax
|
||||||
@ -35,12 +33,6 @@ type Syntax = '[
|
|||||||
, Declaration.PublicFieldDefinition
|
, Declaration.PublicFieldDefinition
|
||||||
, Declaration.VariableDeclaration
|
, Declaration.VariableDeclaration
|
||||||
, Declaration.TypeAlias
|
, Declaration.TypeAlias
|
||||||
, Declaration.Import
|
|
||||||
, Declaration.QualifiedImport
|
|
||||||
, Declaration.SideEffectImport
|
|
||||||
, Declaration.DefaultExport
|
|
||||||
, Declaration.QualifiedExport
|
|
||||||
, Declaration.QualifiedExportFrom
|
|
||||||
, Expression.Arithmetic
|
, Expression.Arithmetic
|
||||||
, Expression.Bitwise
|
, Expression.Bitwise
|
||||||
, Expression.Boolean
|
, Expression.Boolean
|
||||||
@ -165,6 +157,12 @@ type Syntax = '[
|
|||||||
, TypeScript.Syntax.Update
|
, TypeScript.Syntax.Update
|
||||||
, TypeScript.Syntax.ComputedPropertyName
|
, TypeScript.Syntax.ComputedPropertyName
|
||||||
, TypeScript.Syntax.Decorator
|
, TypeScript.Syntax.Decorator
|
||||||
|
, TypeScript.Syntax.Import
|
||||||
|
, TypeScript.Syntax.QualifiedAliasedImport
|
||||||
|
, TypeScript.Syntax.SideEffectImport
|
||||||
|
, TypeScript.Syntax.DefaultExport
|
||||||
|
, TypeScript.Syntax.QualifiedExport
|
||||||
|
, TypeScript.Syntax.QualifiedExportFrom
|
||||||
, []
|
, []
|
||||||
]
|
]
|
||||||
|
|
||||||
@ -338,7 +336,7 @@ false :: Assignment
|
|||||||
false = makeTerm <$> symbol Grammar.False <*> (Literal.false <$ source)
|
false = makeTerm <$> symbol Grammar.False <*> (Literal.false <$ source)
|
||||||
|
|
||||||
identifier :: Assignment
|
identifier :: Assignment
|
||||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> (name <$> source))
|
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
class' :: Assignment
|
class' :: Assignment
|
||||||
class' = makeClass <$> symbol Class <*> children ((,,,,) <$> manyTerm decorator <*> term identifier <*> (symbol TypeParameters *> children (manyTerm typeParameter') <|> pure []) <*> (classHeritage' <|> pure []) <*> classBodyStatements)
|
class' = makeClass <$> symbol Class <*> children ((,,,,) <$> manyTerm decorator <*> term identifier <*> (symbol TypeParameters *> children (manyTerm typeParameter') <|> pure []) <*> (classHeritage' <|> pure []) <*> classBodyStatements)
|
||||||
@ -391,7 +389,7 @@ jsxAttribute = makeTerm <$> symbol Grammar.JsxAttribute <*> children (TypeScript
|
|||||||
where jsxAttributeValue = choice [ string, jsxExpression', jsxElement', jsxFragment ]
|
where jsxAttributeValue = choice [ string, jsxExpression', jsxElement', jsxFragment ]
|
||||||
|
|
||||||
propertyIdentifier :: Assignment
|
propertyIdentifier :: Assignment
|
||||||
propertyIdentifier = makeTerm <$> symbol PropertyIdentifier <*> (Syntax.Identifier <$> (name <$> source))
|
propertyIdentifier = makeTerm <$> symbol PropertyIdentifier <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
sequenceExpression :: Assignment
|
sequenceExpression :: Assignment
|
||||||
sequenceExpression = makeTerm <$> symbol Grammar.SequenceExpression <*> children (Expression.SequenceExpression <$> term expression <*> term expressions)
|
sequenceExpression = makeTerm <$> symbol Grammar.SequenceExpression <*> children (Expression.SequenceExpression <$> term expression <*> term expressions)
|
||||||
@ -406,7 +404,7 @@ parameter =
|
|||||||
<|> optionalParameter
|
<|> optionalParameter
|
||||||
|
|
||||||
accessibilityModifier' :: Assignment
|
accessibilityModifier' :: Assignment
|
||||||
accessibilityModifier' = makeTerm <$> symbol AccessibilityModifier <*> children (Syntax.Identifier <$> (name <$> source))
|
accessibilityModifier' = makeTerm <$> symbol AccessibilityModifier <*> children (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
destructuringPattern :: Assignment
|
destructuringPattern :: Assignment
|
||||||
destructuringPattern = object <|> array
|
destructuringPattern = object <|> array
|
||||||
@ -629,22 +627,22 @@ labeledStatement :: Assignment
|
|||||||
labeledStatement = makeTerm <$> symbol Grammar.LabeledStatement <*> children (TypeScript.Syntax.LabeledStatement <$> statementIdentifier <*> term statement)
|
labeledStatement = makeTerm <$> symbol Grammar.LabeledStatement <*> children (TypeScript.Syntax.LabeledStatement <$> statementIdentifier <*> term statement)
|
||||||
|
|
||||||
statementIdentifier :: Assignment
|
statementIdentifier :: Assignment
|
||||||
statementIdentifier = makeTerm <$> symbol StatementIdentifier <*> (Syntax.Identifier <$> (name <$> source))
|
statementIdentifier = makeTerm <$> symbol StatementIdentifier <*> (Syntax.Identifier <$> source)
|
||||||
|
|
||||||
importStatement :: Assignment
|
importStatement :: Assignment
|
||||||
importStatement = makeImportTerm <$> symbol Grammar.ImportStatement <*> children ((,) <$> importClause <*> term fromClause)
|
importStatement = makeImportTerm <$> symbol Grammar.ImportStatement <*> children ((,) <$> importClause <*> fromClause)
|
||||||
<|> makeTerm' <$> symbol Grammar.ImportStatement <*> children (requireImport <|> sideEffectImport)
|
<|> makeTerm' <$> symbol Grammar.ImportStatement <*> children (requireImport <|> sideEffectImport)
|
||||||
where
|
where
|
||||||
-- `import foo = require "./foo"`
|
-- `import foo = require "./foo"`
|
||||||
requireImport = inj <$> (symbol Grammar.ImportRequireClause *> children (flip Declaration.QualifiedImport <$> term identifier <*> term fromClause <*> pure []))
|
requireImport = inj <$> (symbol Grammar.ImportRequireClause *> children (TypeScript.Syntax.QualifiedAliasedImport <$> term identifier <*> fromClause))
|
||||||
-- `import "./foo"`
|
-- `import "./foo"`
|
||||||
sideEffectImport = inj <$> (Declaration.SideEffectImport <$> term fromClause <*> emptyTerm)
|
sideEffectImport = inj <$> (TypeScript.Syntax.SideEffectImport <$> fromClause)
|
||||||
-- `import { bar } from "./foo"`
|
-- `import { bar } from "./foo"`
|
||||||
namedImport = (,,,) <$> pure Prelude.False <*> pure Nothing <*> (symbol Grammar.NamedImports *> children (many importSymbol)) <*> emptyTerm
|
namedImport = (,) Nothing <$> (symbol Grammar.NamedImports *> children (many importSymbol))
|
||||||
-- `import defaultMember from "./foo"`
|
-- `import defaultMember from "./foo"`
|
||||||
defaultImport = (,,,) <$> pure Prelude.False <*> pure Nothing <*> (pure <$> (makeNameAliasPair <$> rawIdentifier <*> pure Nothing)) <*> emptyTerm
|
defaultImport = (,) Nothing <$> (pure <$> (makeNameAliasPair <$> rawIdentifier <*> pure Nothing))
|
||||||
-- `import * as name from "./foo"`
|
-- `import * as name from "./foo"`
|
||||||
namespaceImport = symbol Grammar.NamespaceImport *> children ((,,,) <$> pure Prelude.True <*> (Just <$> term identifier) <*> pure [] <*> emptyTerm)
|
namespaceImport = symbol Grammar.NamespaceImport *> children ((,) . Just <$> term identifier <*> pure [])
|
||||||
|
|
||||||
-- Combinations of the above.
|
-- Combinations of the above.
|
||||||
importClause = symbol Grammar.ImportClause *>
|
importClause = symbol Grammar.ImportClause *>
|
||||||
@ -654,20 +652,17 @@ importStatement = makeImportTerm <$> symbol Grammar.ImportStatement <*> childr
|
|||||||
<|> ((\a b -> [a, b]) <$> defaultImport <*> (namedImport <|> namespaceImport))
|
<|> ((\a b -> [a, b]) <$> defaultImport <*> (namedImport <|> namespaceImport))
|
||||||
<|> (pure <$> defaultImport))
|
<|> (pure <$> defaultImport))
|
||||||
|
|
||||||
makeImportTerm1 loc from (Prelude.True, Just alias, symbols, _) = makeTerm loc (Declaration.QualifiedImport from alias symbols)
|
makeImportTerm1 loc from (Just alias, _) = makeTerm loc (TypeScript.Syntax.QualifiedAliasedImport alias from)
|
||||||
makeImportTerm1 loc from (Prelude.True, Nothing, symbols, _) = makeTerm loc (Declaration.QualifiedImport from from symbols)
|
makeImportTerm1 loc from (Nothing, symbols) = makeTerm loc (TypeScript.Syntax.Import symbols from)
|
||||||
makeImportTerm1 loc from (_, _, symbols, extra) = makeTerm loc (Declaration.Import from symbols extra)
|
|
||||||
makeImportTerm loc ([x], from) = makeImportTerm1 loc from x
|
makeImportTerm loc ([x], from) = makeImportTerm1 loc from x
|
||||||
makeImportTerm loc (xs, from) = makeTerm loc $ fmap (makeImportTerm1 loc from) xs
|
makeImportTerm loc (xs, from) = makeTerm loc $ fmap (makeImportTerm1 loc from) xs
|
||||||
importSymbol = symbol Grammar.ImportSpecifier *> children (makeNameAliasPair <$> rawIdentifier <*> ((Just <$> rawIdentifier) <|> pure Nothing))
|
importSymbol = symbol Grammar.ImportSpecifier *> children (makeNameAliasPair <$> rawIdentifier <*> ((Just <$> rawIdentifier) <|> pure Nothing))
|
||||||
rawIdentifier = (symbol Identifier <|> symbol Identifier') *> (name <$> source)
|
rawIdentifier = (symbol Identifier <|> symbol Identifier') *> source
|
||||||
makeNameAliasPair from (Just alias) = (from, alias)
|
makeNameAliasPair from (Just alias) = (from, alias)
|
||||||
makeNameAliasPair from Nothing = (from, from)
|
makeNameAliasPair from Nothing = (from, from)
|
||||||
|
|
||||||
fromClause :: Assignment
|
-- TODO: Need to validate that inline comments are still handled with this change in assigning to Path and not a Term.
|
||||||
fromClause = makeTerm <$> symbol Grammar.String <*> (Syntax.Identifier <$> (toName <$> source))
|
fromClause = symbol Grammar.String *> (TypeScript.Syntax.importPath <$> source)
|
||||||
where
|
|
||||||
toName = qualifiedName . splitOnPathSeparator . dropRelativePrefix . stripQuotes
|
|
||||||
|
|
||||||
debuggerStatement :: Assignment
|
debuggerStatement :: Assignment
|
||||||
debuggerStatement = makeTerm <$> symbol Grammar.DebuggerStatement <*> (TypeScript.Syntax.Debugger <$ source)
|
debuggerStatement = makeTerm <$> symbol Grammar.DebuggerStatement <*> (TypeScript.Syntax.Debugger <$ source)
|
||||||
@ -712,23 +707,25 @@ ambientDeclaration :: Assignment
|
|||||||
ambientDeclaration = makeTerm <$> symbol Grammar.AmbientDeclaration <*> children (TypeScript.Syntax.AmbientDeclaration <$> term (choice [declaration, statementBlock]))
|
ambientDeclaration = makeTerm <$> symbol Grammar.AmbientDeclaration <*> children (TypeScript.Syntax.AmbientDeclaration <$> term (choice [declaration, statementBlock]))
|
||||||
|
|
||||||
exportStatement :: Assignment
|
exportStatement :: Assignment
|
||||||
exportStatement = makeTerm <$> symbol Grammar.ExportStatement <*> children (flip Declaration.QualifiedExportFrom <$> exportClause <*> term fromClause)
|
exportStatement = makeTerm <$> symbol Grammar.ExportStatement <*> children (flip TypeScript.Syntax.QualifiedExportFrom <$> exportClause <*> fromClause)
|
||||||
<|> makeTerm <$> symbol Grammar.ExportStatement <*> children (Declaration.QualifiedExport <$> exportClause)
|
<|> makeTerm <$> symbol Grammar.ExportStatement <*> children (TypeScript.Syntax.QualifiedExport <$> exportClause)
|
||||||
<|> makeTerm <$> symbol Grammar.ExportStatement <*> children (Declaration.DefaultExport <$> contextualize decorator (term (declaration <|> expression <|> identifier <|> importAlias')))
|
<|> makeTerm <$> symbol Grammar.ExportStatement <*> children (TypeScript.Syntax.DefaultExport <$> contextualize decorator (term (declaration <|> expression <|> identifier <|> importAlias')))
|
||||||
where
|
where
|
||||||
exportClause = symbol Grammar.ExportClause *> children (many exportSymbol)
|
exportClause = symbol Grammar.ExportClause *> children (many exportSymbol)
|
||||||
exportSymbol = symbol Grammar.ExportSpecifier *> children (makeNameAliasPair <$> rawIdentifier <*> (Just <$> rawIdentifier))
|
exportSymbol = symbol Grammar.ExportSpecifier *> children (makeNameAliasPair <$> rawIdentifier <*> (Just <$> rawIdentifier))
|
||||||
<|> symbol Grammar.ExportSpecifier *> children (makeNameAliasPair <$> rawIdentifier <*> pure Nothing)
|
<|> symbol Grammar.ExportSpecifier *> children (makeNameAliasPair <$> rawIdentifier <*> pure Nothing)
|
||||||
makeNameAliasPair from (Just alias) = (from, alias)
|
makeNameAliasPair from (Just alias) = (from, alias)
|
||||||
makeNameAliasPair from Nothing = (from, from)
|
makeNameAliasPair from Nothing = (from, from)
|
||||||
rawIdentifier = (symbol Identifier <|> symbol Identifier') *> (name <$> source)
|
rawIdentifier = (symbol Identifier <|> symbol Identifier') *> source
|
||||||
|
-- TODO: Need to validate that inline comments are still handled with this change in assigning to Path and not a Term.
|
||||||
|
fromClause = symbol Grammar.String *> (TypeScript.Syntax.importPath <$> source)
|
||||||
|
|
||||||
propertySignature :: Assignment
|
propertySignature :: Assignment
|
||||||
propertySignature = makePropertySignature <$> symbol Grammar.PropertySignature <*> children ((,,,) <$> (term accessibilityModifier' <|> emptyTerm) <*> (term readonly' <|> emptyTerm) <*> term propertyName <*> (term typeAnnotation' <|> emptyTerm))
|
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)
|
where makePropertySignature loc (modifier, readonly, propertyName, annotation) = makeTerm loc (TypeScript.Syntax.PropertySignature [modifier, readonly, annotation] propertyName)
|
||||||
|
|
||||||
propertyName :: Assignment
|
propertyName :: Assignment
|
||||||
propertyName = (makeTerm <$> symbol PropertyIdentifier <*> (Syntax.Identifier <$> (name <$> source))) <|> term string <|> term number <|> term computedPropertyName
|
propertyName = (makeTerm <$> symbol PropertyIdentifier <*> (Syntax.Identifier <$> source)) <|> term string <|> term number <|> term computedPropertyName
|
||||||
|
|
||||||
computedPropertyName :: Assignment
|
computedPropertyName :: Assignment
|
||||||
computedPropertyName = makeTerm <$> symbol Grammar.ComputedPropertyName <*> children (TypeScript.Syntax.ComputedPropertyName <$> term expression)
|
computedPropertyName = makeTerm <$> symbol Grammar.ComputedPropertyName <*> children (TypeScript.Syntax.ComputedPropertyName <$> term expression)
|
||||||
|
@ -1,9 +1,184 @@
|
|||||||
{-# LANGUAGE DeriveAnyClass #-}
|
{-# LANGUAGE DeriveAnyClass #-}
|
||||||
module Language.TypeScript.Syntax where
|
module Language.TypeScript.Syntax where
|
||||||
|
|
||||||
import Prologue
|
import qualified Data.Abstract.Environment as Env
|
||||||
import Data.Abstract.Evaluatable
|
import Data.Abstract.Evaluatable
|
||||||
import Diffing.Algorithm
|
import qualified Data.ByteString.Char8 as BC
|
||||||
|
import qualified Data.ByteString as B
|
||||||
|
import Data.Abstract.Module (ModulePath, ModuleInfo(..))
|
||||||
|
import Diffing.Algorithm
|
||||||
|
import Prelude hiding (fail)
|
||||||
|
import Prologue
|
||||||
|
import System.FilePath.Posix
|
||||||
|
|
||||||
|
data Relative = Relative | NonRelative
|
||||||
|
deriving (Eq, Ord, Show)
|
||||||
|
|
||||||
|
data ImportPath = ImportPath { unPath :: FilePath, pathIsRelative :: Relative }
|
||||||
|
deriving (Eq, Ord, Show)
|
||||||
|
|
||||||
|
importPath :: ByteString -> ImportPath
|
||||||
|
importPath str = let path = stripQuotes str in ImportPath (BC.unpack path) (pathType path)
|
||||||
|
where
|
||||||
|
stripQuotes = B.filter (`B.notElem` "\'\"")
|
||||||
|
pathType xs | not (B.null xs), BC.head xs == '.' = Relative
|
||||||
|
| otherwise = NonRelative
|
||||||
|
|
||||||
|
toName :: ImportPath -> Name
|
||||||
|
toName = BC.pack . unPath
|
||||||
|
|
||||||
|
resolveTypeScriptModule :: MonadEvaluatable location term value m => ImportPath -> m ModulePath
|
||||||
|
resolveTypeScriptModule (ImportPath path Relative) = resolveRelativeTSModule path
|
||||||
|
resolveTypeScriptModule (ImportPath path NonRelative) = resolveNonRelativeTSModule path
|
||||||
|
|
||||||
|
-- | Resolve a relative TypeScript import to a known 'ModuleName' or fail.
|
||||||
|
--
|
||||||
|
-- import { b } from "./moduleB" in /root/src/moduleA.ts
|
||||||
|
--
|
||||||
|
-- /root/src/moduleB.ts
|
||||||
|
-- /root/src/moduleB/package.json (if it specifies a "types" property)
|
||||||
|
-- /root/src/moduleB/index.ts
|
||||||
|
resolveRelativeTSModule :: MonadEvaluatable location term value m => FilePath -> m ModulePath
|
||||||
|
resolveRelativeTSModule relImportPath = do
|
||||||
|
ModuleInfo{..} <- currentModule
|
||||||
|
let relRootDir = takeDirectory (makeRelative moduleRoot modulePath)
|
||||||
|
let path = normalise (relRootDir </> normalise relImportPath)
|
||||||
|
resolveTSModule path >>= either notFound pure
|
||||||
|
where
|
||||||
|
notFound xs = fail $ "Unable to resolve relative module import: " <> show relImportPath <> ", looked for it in: " <> show xs
|
||||||
|
|
||||||
|
-- | Resolve a non-relative TypeScript import to a known 'ModuleName' or fail.
|
||||||
|
--
|
||||||
|
-- import { b } from "moduleB" in source file /root/src/moduleA.ts
|
||||||
|
--
|
||||||
|
-- /root/src/node_modules/moduleB.ts
|
||||||
|
-- /root/src/node_modules/moduleB/package.json (if it specifies a "types" property)
|
||||||
|
-- /root/src/node_modules/moduleB/index.ts
|
||||||
|
--
|
||||||
|
-- /root/node_modules/moduleB.ts, etc
|
||||||
|
-- /node_modules/moduleB.ts, etc
|
||||||
|
resolveNonRelativeTSModule :: MonadEvaluatable location term value m => FilePath -> m ModulePath
|
||||||
|
resolveNonRelativeTSModule name = do
|
||||||
|
ModuleInfo{..} <- currentModule
|
||||||
|
go "." (makeRelative moduleRoot modulePath) mempty
|
||||||
|
where
|
||||||
|
nodeModulesPath dir = takeDirectory dir </> "node_modules" </> name
|
||||||
|
-- Recursively search in a 'node_modules' directory, stepping up a directory each time.
|
||||||
|
go root path searched = do
|
||||||
|
res <- resolveTSModule (nodeModulesPath path)
|
||||||
|
case res of
|
||||||
|
Left xs | parentDir <- takeDirectory path , root /= parentDir -> go root parentDir (searched <> xs)
|
||||||
|
| otherwise -> notFound (searched <> xs)
|
||||||
|
Right m -> pure m
|
||||||
|
notFound xs = fail $ "Unable to resolve non-relative module import: " <> show name <> ", looked for it in: " <> show xs
|
||||||
|
|
||||||
|
resolveTSModule :: MonadEvaluatable location term value m => FilePath -> m (Either [FilePath] ModulePath)
|
||||||
|
resolveTSModule path = maybe (Left searchPaths) Right <$> resolve searchPaths
|
||||||
|
where exts = ["ts", "tsx", "d.ts"]
|
||||||
|
searchPaths =
|
||||||
|
((path <.>) <$> exts)
|
||||||
|
-- TODO: Requires parsing package.json, getting the path of the
|
||||||
|
-- "types" property and adding that value to the search Paths.
|
||||||
|
-- <> [searchDir </> "package.json"]
|
||||||
|
<> (((path </> "index") <.>) <$> exts)
|
||||||
|
|
||||||
|
|
||||||
|
data Import a = Import { importSymbols :: ![(Name, Name)], importFrom :: ImportPath }
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
|
||||||
|
instance Eq1 Import where liftEq = genericLiftEq
|
||||||
|
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
-- http://www.typescriptlang.org/docs/handbook/module-resolution.html
|
||||||
|
instance Evaluatable Import where
|
||||||
|
eval (Import symbols importPath) = do
|
||||||
|
modulePath <- resolveTypeScriptModule importPath
|
||||||
|
(importedEnv, _) <- isolate (require modulePath)
|
||||||
|
modifyEnv (mappend (renamed importedEnv)) *> unit
|
||||||
|
where
|
||||||
|
renamed importedEnv
|
||||||
|
| Prologue.null symbols = importedEnv
|
||||||
|
| otherwise = Env.overwrite symbols importedEnv
|
||||||
|
|
||||||
|
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportAlias :: !a, qualifiedAliasedImportFrom :: ImportPath }
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
|
||||||
|
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
|
||||||
|
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 QualifiedAliasedImport where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance Evaluatable QualifiedAliasedImport where
|
||||||
|
eval (QualifiedAliasedImport aliasTerm importPath ) = do
|
||||||
|
modulePath <- resolveTypeScriptModule importPath
|
||||||
|
let alias = freeVariable (subterm aliasTerm)
|
||||||
|
letrec' alias $ \addr -> do
|
||||||
|
(importedEnv, _) <- isolate (require modulePath)
|
||||||
|
modifyEnv (mappend importedEnv)
|
||||||
|
void $ makeNamespace alias addr []
|
||||||
|
unit
|
||||||
|
|
||||||
|
newtype SideEffectImport a = SideEffectImport { sideEffectImportFrom :: ImportPath }
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
|
||||||
|
instance Eq1 SideEffectImport where liftEq = genericLiftEq
|
||||||
|
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance Evaluatable SideEffectImport where
|
||||||
|
eval (SideEffectImport importPath) = do
|
||||||
|
modulePath <- resolveTypeScriptModule importPath
|
||||||
|
void $ isolate (require modulePath)
|
||||||
|
unit
|
||||||
|
|
||||||
|
|
||||||
|
-- | Qualified Export declarations
|
||||||
|
newtype QualifiedExport a = QualifiedExport { qualifiedExportSymbols :: [(Name, Name)] }
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
|
||||||
|
instance Eq1 QualifiedExport where liftEq = genericLiftEq
|
||||||
|
instance Ord1 QualifiedExport where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 QualifiedExport where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance Evaluatable QualifiedExport where
|
||||||
|
eval (QualifiedExport exportSymbols) = do
|
||||||
|
-- Insert the aliases with no addresses.
|
||||||
|
for_ exportSymbols $ \(name, alias) ->
|
||||||
|
addExport name alias Nothing
|
||||||
|
unit
|
||||||
|
|
||||||
|
|
||||||
|
-- | Qualified Export declarations that export from another module.
|
||||||
|
data QualifiedExportFrom a = QualifiedExportFrom { qualifiedExportFrom :: ImportPath, qualifiedExportFromSymbols :: ![(Name, Name)]}
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
|
||||||
|
instance Eq1 QualifiedExportFrom where liftEq = genericLiftEq
|
||||||
|
instance Ord1 QualifiedExportFrom where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 QualifiedExportFrom where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance Evaluatable QualifiedExportFrom where
|
||||||
|
eval (QualifiedExportFrom importPath exportSymbols) = do
|
||||||
|
modulePath <- resolveTypeScriptModule importPath
|
||||||
|
(importedEnv, _) <- isolate (require modulePath)
|
||||||
|
-- Look up addresses in importedEnv and insert the aliases with addresses into the exports.
|
||||||
|
for_ exportSymbols $ \(name, alias) -> do
|
||||||
|
let address = Env.lookup name importedEnv
|
||||||
|
maybe (cannotExport modulePath name) (addExport name alias . Just) address
|
||||||
|
unit
|
||||||
|
where
|
||||||
|
cannotExport moduleName name = fail $
|
||||||
|
"module " <> show moduleName <> " does not export " <> show name
|
||||||
|
|
||||||
|
|
||||||
|
newtype DefaultExport a = DefaultExport { defaultExport :: a }
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
|
||||||
|
instance Eq1 DefaultExport where liftEq = genericLiftEq
|
||||||
|
instance Ord1 DefaultExport where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 DefaultExport where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
instance Evaluatable DefaultExport where
|
||||||
|
|
||||||
|
|
||||||
-- | Lookup type for a type-level key in a typescript map.
|
-- | Lookup type for a type-level key in a typescript map.
|
||||||
data LookupType a = LookupType { lookupTypeIdentifier :: a, lookupTypeKey :: a }
|
data LookupType a = LookupType { lookupTypeIdentifier :: a, lookupTypeKey :: a }
|
||||||
|
@ -29,6 +29,7 @@ import Data.Span
|
|||||||
import Data.Term
|
import Data.Term
|
||||||
import Diffing.Algorithm
|
import Diffing.Algorithm
|
||||||
import Diffing.Interpreter
|
import Diffing.Interpreter
|
||||||
|
import System.FilePath.Glob
|
||||||
import qualified GHC.TypeLits as TypeLevel
|
import qualified GHC.TypeLits as TypeLevel
|
||||||
import Language.Preluded
|
import Language.Preluded
|
||||||
import Parsing.Parser
|
import Parsing.Parser
|
||||||
@ -44,31 +45,68 @@ import qualified Language.Ruby.Assignment as Ruby
|
|||||||
import qualified Language.TypeScript.Assignment as TypeScript
|
import qualified Language.TypeScript.Assignment as TypeScript
|
||||||
|
|
||||||
-- Ruby
|
-- Ruby
|
||||||
evaluateRubyFile = evaluateWithPrelude rubyParser
|
evalRubyProject = evaluateProjectWithPrelude rubyParser ["rb"]
|
||||||
evaluateRubyFiles = evaluateFilesWithPrelude rubyParser
|
evalRubyFile = evaluateWithPrelude rubyParser
|
||||||
evaluateRubyImportGraph paths = runAnalysis @(ImportGraphing (BadVariables (BadValues (Quietly (Evaluating Precise Ruby.Term (Value Precise)))))) . evaluateModules <$> parseFiles rubyParser paths
|
evaluateRubyImportGraph paths = runAnalysis @(ImportGraphing (BadVariables (BadValues (Quietly (Evaluating Precise Ruby.Term (Value Precise)))))) . evaluateModules <$> parseFiles rubyParser (dropFileName (head paths)) paths
|
||||||
evaluateRubyBadVariables paths = runAnalysis @(BadVariables (Evaluating Precise Ruby.Term (Value Precise))) . evaluateModules <$> parseFiles rubyParser paths
|
evaluateRubyBadVariables paths = runAnalysis @(BadVariables (Evaluating Precise Ruby.Term (Value Precise))) . evaluateModules <$> parseFiles rubyParser (dropFileName (head paths)) paths
|
||||||
|
|
||||||
-- Go
|
-- Go
|
||||||
evaluateGoFile = evaluateFile goParser
|
evalGoProject = evaluateProject goParser ["go"]
|
||||||
evaluateGoFiles = evaluateFiles goParser
|
evalGoFile = evaluateFile goParser
|
||||||
typecheckGoFile path = runAnalysis @(Caching (Evaluating Monovariant Go.Term Type)) . evaluateModule <$> parseFile goParser Nothing path
|
typecheckGoFile path = runAnalysis @(Caching (Evaluating Monovariant Go.Term Type)) . evaluateModule <$> parseFile goParser Nothing path
|
||||||
|
|
||||||
-- Python
|
-- Python
|
||||||
evaluatePythonFile = evaluateWithPrelude pythonParser
|
evalPythonProject = evaluateProject pythonParser ["py"]
|
||||||
evaluatePythonFiles = evaluateFilesWithPrelude pythonParser
|
evalPythonFile = evaluateWithPrelude pythonParser
|
||||||
typecheckPythonFile path = runAnalysis @(Caching (Evaluating Monovariant Python.Term Type)) . evaluateModule <$> parseFile pythonParser Nothing path
|
typecheckPythonFile path = runAnalysis @(Caching (Evaluating Monovariant Python.Term Type)) . evaluateModule <$> parseFile pythonParser Nothing path
|
||||||
tracePythonFile path = runAnalysis @(Tracing [] (Evaluating Precise Python.Term (Value Precise))) . evaluateModule <$> parseFile pythonParser Nothing path
|
tracePythonFile path = runAnalysis @(Tracing [] (Evaluating Precise Python.Term (Value Precise))) . evaluateModule <$> parseFile pythonParser Nothing path
|
||||||
evaluateDeadTracePythonFile path = runAnalysis @(DeadCode (Tracing [] (Evaluating Precise Python.Term (Value Precise)))) . evaluateModule <$> parseFile pythonParser Nothing path
|
evaluateDeadTracePythonFile path = runAnalysis @(DeadCode (Tracing [] (Evaluating Precise Python.Term (Value Precise)))) . evaluateModule <$> parseFile pythonParser Nothing path
|
||||||
|
|
||||||
-- PHP
|
-- PHP
|
||||||
evaluatePHPFile = evaluateFile phpParser
|
evalPHPProject = evaluateProject phpParser ["php"]
|
||||||
evaluatePHPFiles = evaluateFiles phpParser
|
evalPHPFile = evaluateFile phpParser
|
||||||
|
|
||||||
-- TypeScript
|
-- TypeScript
|
||||||
|
evalTypeScriptProject = evaluateProject typescriptParser ["ts", "tsx"]
|
||||||
|
evalTypeScriptFile = evaluateFile typescriptParser
|
||||||
typecheckTypeScriptFile path = runAnalysis @(Caching (Evaluating Monovariant TypeScript.Term Type)) . evaluateModule <$> parseFile typescriptParser Nothing path
|
typecheckTypeScriptFile path = runAnalysis @(Caching (Evaluating Monovariant TypeScript.Term Type)) . evaluateModule <$> parseFile typescriptParser Nothing path
|
||||||
evaluateTypeScriptFile = evaluateFile typescriptParser
|
|
||||||
evaluateTypeScriptFiles = evaluateFiles typescriptParser
|
evaluateProject :: forall term effects
|
||||||
|
. ( Corecursive term
|
||||||
|
, Evaluatable (Base term)
|
||||||
|
, FreeVariables term
|
||||||
|
, effects ~ Effects Precise term (Value Precise) (Evaluating Precise term (Value Precise) effects)
|
||||||
|
, MonadAddressable Precise (Evaluating Precise term (Value Precise) effects)
|
||||||
|
, Recursive term
|
||||||
|
)
|
||||||
|
=> Parser term
|
||||||
|
-> [FilePath]
|
||||||
|
-> FilePath
|
||||||
|
-> IO (Final effects (Value Precise))
|
||||||
|
evaluateProject parser exts entryPoint = do
|
||||||
|
let rootDir = takeDirectory entryPoint
|
||||||
|
paths <- filter (/= entryPoint) <$> getPaths exts rootDir
|
||||||
|
evaluateFiles parser rootDir (entryPoint : paths)
|
||||||
|
|
||||||
|
evaluateProjectWithPrelude :: forall term effects
|
||||||
|
. ( Corecursive term
|
||||||
|
, Evaluatable (Base term)
|
||||||
|
, FreeVariables term
|
||||||
|
, effects ~ Effects Precise term (Value Precise) (Evaluating Precise term (Value Precise) effects)
|
||||||
|
, MonadAddressable Precise (Evaluating Precise term (Value Precise) effects)
|
||||||
|
, Recursive term
|
||||||
|
, TypeLevel.KnownSymbol (PreludePath term)
|
||||||
|
)
|
||||||
|
=> Parser term
|
||||||
|
-> [FilePath]
|
||||||
|
-> FilePath
|
||||||
|
-> IO (Final effects (Value Precise))
|
||||||
|
evaluateProjectWithPrelude parser exts entryPoint = do
|
||||||
|
let rootDir = takeDirectory entryPoint
|
||||||
|
paths <- filter (/= entryPoint) <$> getPaths exts rootDir
|
||||||
|
evaluateFilesWithPrelude parser rootDir (entryPoint : paths)
|
||||||
|
|
||||||
|
getPaths exts = fmap fold . globDir (compile . mappend "**/*." <$> exts)
|
||||||
|
|
||||||
-- Evalute a single file.
|
-- Evalute a single file.
|
||||||
evaluateFile :: forall term effects
|
evaluateFile :: forall term effects
|
||||||
@ -136,9 +174,10 @@ evaluateFiles :: forall term effects
|
|||||||
, Recursive term
|
, Recursive term
|
||||||
)
|
)
|
||||||
=> Parser term
|
=> Parser term
|
||||||
|
-> FilePath
|
||||||
-> [FilePath]
|
-> [FilePath]
|
||||||
-> IO (Final effects (Value Precise))
|
-> IO (Final effects (Value Precise))
|
||||||
evaluateFiles parser paths = runAnalysis @(Evaluating Precise term (Value Precise)) . evaluateModules <$> parseFiles parser paths
|
evaluateFiles parser rootDir paths = runAnalysis @(Evaluating Precise term (Value Precise)) . evaluateModules <$> parseFiles parser rootDir paths
|
||||||
|
|
||||||
-- | Evaluate terms and an entry point to a value with a given prelude.
|
-- | Evaluate terms and an entry point to a value with a given prelude.
|
||||||
evaluatesWith :: forall location value term effects
|
evaluatesWith :: forall location value term effects
|
||||||
@ -169,26 +208,26 @@ evaluateFilesWithPrelude :: forall term effects
|
|||||||
, TypeLevel.KnownSymbol (PreludePath term)
|
, TypeLevel.KnownSymbol (PreludePath term)
|
||||||
)
|
)
|
||||||
=> Parser term
|
=> Parser term
|
||||||
|
-> FilePath
|
||||||
-> [FilePath]
|
-> [FilePath]
|
||||||
-> IO (Final effects (Value Precise))
|
-> IO (Final effects (Value Precise))
|
||||||
evaluateFilesWithPrelude parser paths = do
|
evaluateFilesWithPrelude parser rootDir paths = do
|
||||||
let preludePath = TypeLevel.symbolVal (Proxy :: Proxy (PreludePath term))
|
let preludePath = TypeLevel.symbolVal (Proxy :: Proxy (PreludePath term))
|
||||||
prelude <- parseFile parser Nothing preludePath
|
prelude <- parseFile parser Nothing preludePath
|
||||||
xs <- traverse (parseFile parser Nothing) paths
|
xs <- parseFiles parser rootDir paths
|
||||||
pure $ evaluatesWith @Precise @(Value Precise) prelude xs
|
pure $ evaluatesWith @Precise @(Value Precise) prelude xs
|
||||||
|
|
||||||
|
|
||||||
-- Read and parse a file.
|
-- Read and parse a file.
|
||||||
parseFile :: Parser term -> Maybe FilePath -> FilePath -> IO (Module term)
|
parseFile :: Parser term -> Maybe FilePath -> FilePath -> IO (Module term)
|
||||||
parseFile parser rootDir path = runTask $ do
|
parseFile parser rootDir path = runTask $ do
|
||||||
blob <- file path
|
blob <- file path
|
||||||
moduleForBlob rootDir blob <$> parse parser blob
|
moduleForBlob rootDir blob <$> parse parser blob
|
||||||
|
|
||||||
parseFiles :: Parser term -> [FilePath] -> IO [Module term]
|
parseFiles :: Parser term -> FilePath -> [FilePath] -> IO [Module term]
|
||||||
parseFiles parser paths = traverse (parseFile parser (Just (dropFileName (head paths)))) paths
|
parseFiles parser rootDir = traverse (parseFile parser (Just rootDir))
|
||||||
|
|
||||||
parsePackage :: PackageName -> Parser term -> [FilePath] -> IO (Package term)
|
parsePackage :: PackageName -> Parser term -> FilePath -> [FilePath] -> IO (Package term)
|
||||||
parsePackage name parser files = Package (PackageInfo name Nothing) . Package.fromModules <$> parseFiles parser files
|
parsePackage name parser rootDir files = Package (PackageInfo name Nothing) . Package.fromModules <$> parseFiles parser rootDir files
|
||||||
|
|
||||||
|
|
||||||
-- Read a file from the filesystem into a Blob.
|
-- Read a file from the filesystem into a Blob.
|
||||||
|
@ -1,35 +1,30 @@
|
|||||||
{-# LANGUAGE OverloadedLists #-}
|
{-# LANGUAGE OverloadedLists #-}
|
||||||
module Analysis.Go.Spec (spec) where
|
module Analysis.Go.Spec (spec) where
|
||||||
|
|
||||||
import Data.Abstract.Value
|
|
||||||
import SpecHelpers
|
import SpecHelpers
|
||||||
|
|
||||||
|
|
||||||
spec :: Spec
|
spec :: Spec
|
||||||
spec = parallel $ do
|
spec = parallel $ do
|
||||||
describe "evalutes Go" $ do
|
describe "evaluates Go" $ do
|
||||||
it "imports and wildcard imports" $ do
|
it "imports and wildcard imports" $ do
|
||||||
env <- environment . snd <$> evaluate "main.go"
|
res <- snd <$> evaluate "main.go"
|
||||||
env `shouldBe` [ (qualifiedName ["foo", "New"], addr 0)
|
environment res `shouldBe` [ ("foo", addr 0)
|
||||||
, (qualifiedName ["Rab"], addr 1)
|
, ("Bar", addr 2)
|
||||||
, (qualifiedName ["Bar"], addr 2)
|
, ("Rab", addr 3)
|
||||||
, (qualifiedName ["main"], addr 3)
|
, ("main", addr 4)
|
||||||
]
|
]
|
||||||
|
|
||||||
|
heapLookup (Address (Precise 0)) (heap res) `shouldBe` ns "foo" [ ("New", addr 1) ]
|
||||||
|
|
||||||
it "imports with aliases (and side effects only)" $ do
|
it "imports with aliases (and side effects only)" $ do
|
||||||
env <- environment . snd <$> evaluate "main1.go"
|
res <- snd <$> evaluate "main1.go"
|
||||||
env `shouldBe` [ (qualifiedName ["f", "New"], addr 0)
|
environment res `shouldBe` [ ("f", addr 0)
|
||||||
, (qualifiedName ["main"], addr 3) -- addr 3 is due to side effects of
|
, ("main", addr 4) -- addr 4 is due to side effects of eval'ing `import _ "./bar"` which used addr 2 & 3. f defines New which got addr 1.
|
||||||
-- eval'ing `import _ "./bar"` which
|
]
|
||||||
-- used addr 1 & 2.
|
|
||||||
]
|
heapLookup (Address (Precise 0)) (heap res) `shouldBe` ns "f" [ ("New", addr 1) ]
|
||||||
|
|
||||||
where
|
where
|
||||||
addr = Address . Precise
|
|
||||||
fixtures = "test/fixtures/go/analysis/"
|
fixtures = "test/fixtures/go/analysis/"
|
||||||
evaluate entry = evaluateFiles goParser
|
evaluate entry = evalGoProject (fixtures <> entry)
|
||||||
[ fixtures <> entry
|
|
||||||
, fixtures <> "foo/foo.go"
|
|
||||||
, fixtures <> "bar/bar.go"
|
|
||||||
, fixtures <> "bar/rab.go"
|
|
||||||
]
|
|
||||||
|
@ -1,7 +1,6 @@
|
|||||||
{-# LANGUAGE OverloadedLists #-}
|
{-# LANGUAGE OverloadedLists #-}
|
||||||
module Analysis.PHP.Spec (spec) where
|
module Analysis.PHP.Spec (spec) where
|
||||||
|
|
||||||
import Data.Abstract.Value
|
|
||||||
import SpecHelpers
|
import SpecHelpers
|
||||||
|
|
||||||
|
|
||||||
@ -10,32 +9,26 @@ spec = parallel $ do
|
|||||||
describe "PHP" $ do
|
describe "PHP" $ do
|
||||||
it "evaluates include and require" $ do
|
it "evaluates include and require" $ do
|
||||||
env <- environment . snd <$> evaluate "main.php"
|
env <- environment . snd <$> evaluate "main.php"
|
||||||
env `shouldBe` [ (name "foo", addr 0)
|
env `shouldBe` [ ("foo", addr 0)
|
||||||
, (name "bar", addr 1) ]
|
, ("bar", addr 1) ]
|
||||||
|
|
||||||
it "evaluates include_once and require_once" $ do
|
it "evaluates include_once and require_once" $ do
|
||||||
env <- environment . snd <$> evaluate "main_once.php"
|
env <- environment . snd <$> evaluate "main_once.php"
|
||||||
env `shouldBe` [ (name "foo", addr 0)
|
env `shouldBe` [ ("foo", addr 0)
|
||||||
, (name "bar", addr 1) ]
|
, ("bar", addr 1) ]
|
||||||
|
|
||||||
it "evaluates namespaces" $ do
|
it "evaluates namespaces" $ do
|
||||||
res <- snd <$> evaluate "namespaces.php"
|
res <- snd <$> evaluate "namespaces.php"
|
||||||
environment res `shouldBe` [ (name "NS1", addr 0)
|
environment res `shouldBe` [ ("NS1", addr 0)
|
||||||
, (name "Foo", addr 6) ]
|
, ("Foo", addr 6) ]
|
||||||
|
|
||||||
heapLookup (Address (Precise 0)) (heap res) `shouldBe` ns "NS1" [ (name "Sub1", addr 1)
|
heapLookup (Address (Precise 0)) (heap res) `shouldBe` ns "NS1" [ ("Sub1", addr 1)
|
||||||
, (name "b", addr 4)
|
, ("b", addr 4)
|
||||||
, (name "c", addr 5)
|
, ("c", addr 5)
|
||||||
]
|
]
|
||||||
heapLookup (Address (Precise 1)) (heap res) `shouldBe` ns "Sub1" [ (name "Sub2", addr 2) ]
|
heapLookup (Address (Precise 1)) (heap res) `shouldBe` ns "Sub1" [ ("Sub2", addr 2) ]
|
||||||
heapLookup (Address (Precise 2)) (heap res) `shouldBe` ns "Sub2" [ (name "f", addr 3) ]
|
heapLookup (Address (Precise 2)) (heap res) `shouldBe` ns "Sub2" [ ("f", addr 3) ]
|
||||||
|
|
||||||
where
|
where
|
||||||
ns n = Just . Latest . Just . injValue . Namespace (name n)
|
|
||||||
addr = Address . Precise
|
|
||||||
fixtures = "test/fixtures/php/analysis/"
|
fixtures = "test/fixtures/php/analysis/"
|
||||||
evaluate entry = evaluateFiles phpParser
|
evaluate entry = evalPHPProject (fixtures <> entry)
|
||||||
[ fixtures <> entry
|
|
||||||
, fixtures <> "foo.php"
|
|
||||||
, fixtures <> "bar.php"
|
|
||||||
]
|
|
||||||
|
@ -1,4 +1,4 @@
|
|||||||
{-# LANGUAGE OverloadedLists #-}
|
{-# LANGUAGE OverloadedLists, OverloadedStrings #-}
|
||||||
module Analysis.Python.Spec (spec) where
|
module Analysis.Python.Spec (spec) where
|
||||||
|
|
||||||
import Data.Abstract.Value
|
import Data.Abstract.Value
|
||||||
@ -9,23 +9,27 @@ import SpecHelpers
|
|||||||
|
|
||||||
spec :: Spec
|
spec :: Spec
|
||||||
spec = parallel $ do
|
spec = parallel $ do
|
||||||
describe "evalutes Python" $ do
|
describe "evaluates Python" $ do
|
||||||
it "imports" $ do
|
it "imports" $ do
|
||||||
env <- environment . snd <$> evaluate "main.py"
|
res <- snd <$> evaluate "main.py"
|
||||||
env `shouldBe` [ (qualifiedName ["a", "foo"], addr 0)
|
environment res `shouldBe` [ ("a", addr 0)
|
||||||
, (qualifiedName ["b", "c", "baz"], addr 1)
|
, ("b", addr 2)
|
||||||
]
|
]
|
||||||
|
|
||||||
|
heapLookup (Address (Precise 0)) (heap res) `shouldBe` ns "a" [ ("foo", addr 1) ]
|
||||||
|
heapLookup (Address (Precise 2)) (heap res) `shouldBe` ns "b" [ ("c", addr 3) ]
|
||||||
|
heapLookup (Address (Precise 3)) (heap res) `shouldBe` ns "c" [ ("baz", addr 4) ]
|
||||||
|
|
||||||
it "imports with aliases" $ do
|
it "imports with aliases" $ do
|
||||||
env <- environment . snd <$> evaluate "main1.py"
|
env <- environment . snd <$> evaluate "main1.py"
|
||||||
env `shouldBe` [ (qualifiedName ["b", "foo"], addr 0)
|
env `shouldBe` [ ("b", addr 0)
|
||||||
, (qualifiedName ["e", "baz"], addr 1)
|
, ("e", addr 2)
|
||||||
]
|
]
|
||||||
|
|
||||||
it "imports using 'from' syntax" $ do
|
it "imports using 'from' syntax" $ do
|
||||||
env <- environment . snd <$> evaluate "main2.py"
|
env <- environment . snd <$> evaluate "main2.py"
|
||||||
env `shouldBe` [ (qualifiedName ["foo"], addr 0)
|
env `shouldBe` [ ("foo", addr 0)
|
||||||
, (qualifiedName ["bar"], addr 1)
|
, ("bar", addr 1)
|
||||||
]
|
]
|
||||||
|
|
||||||
it "subclasses" $ do
|
it "subclasses" $ do
|
||||||
@ -37,10 +41,7 @@ spec = parallel $ do
|
|||||||
v `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"foo!\""))))))
|
v `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"foo!\""))))))
|
||||||
|
|
||||||
where
|
where
|
||||||
|
ns n = Just . Latest . Just . injValue . Namespace n
|
||||||
addr = Address . Precise
|
addr = Address . Precise
|
||||||
fixtures = "test/fixtures/python/analysis/"
|
fixtures = "test/fixtures/python/analysis/"
|
||||||
evaluate entry = evaluateFiles pythonParser
|
evaluate entry = evalPythonProject (fixtures <> entry)
|
||||||
[ fixtures <> entry
|
|
||||||
, fixtures <> "a.py"
|
|
||||||
, fixtures <> "b/c.py"
|
|
||||||
]
|
|
||||||
|
@ -17,46 +17,43 @@ spec = parallel $ do
|
|||||||
describe "Ruby" $ do
|
describe "Ruby" $ do
|
||||||
it "evaluates require_relative" $ do
|
it "evaluates require_relative" $ do
|
||||||
env <- environment . snd <$> evaluate "main.rb"
|
env <- environment . snd <$> evaluate "main.rb"
|
||||||
env `shouldBe` [ (name "Object", addr 0)
|
env `shouldBe` [ ("Object", addr 0)
|
||||||
, (name "foo", addr 3) ]
|
, ("foo", addr 3) ]
|
||||||
|
|
||||||
it "evaluates load" $ do
|
it "evaluates load" $ do
|
||||||
env <- environment . snd <$> evaluate "load.rb"
|
env <- environment . snd <$> evaluate "load.rb"
|
||||||
env `shouldBe` [ (name "Object", addr 0)
|
env `shouldBe` [ ("Object", addr 0)
|
||||||
, (name "foo", addr 3) ]
|
, ("foo", addr 3) ]
|
||||||
|
|
||||||
it "evaluates load with wrapper" $ do
|
it "evaluates load with wrapper" $ do
|
||||||
res <- evaluate "load-wrap.rb"
|
res <- evaluate "load-wrap.rb"
|
||||||
fst res `shouldBe` Right (Right (Right (Right (Left (SomeExc (FreeVariableError ("foo" :| [])))))))
|
fst res `shouldBe` Right (Right (Right (Right (Left (SomeExc (FreeVariableError "foo"))))))
|
||||||
environment (snd res) `shouldBe` [ (name "Object", addr 0) ]
|
environment (snd res) `shouldBe` [ ("Object", addr 0) ]
|
||||||
|
|
||||||
it "evaluates subclass" $ do
|
it "evaluates subclass" $ do
|
||||||
res <- evaluate "subclass.rb"
|
res <- evaluate "subclass.rb"
|
||||||
fst res `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"<bar>\""))))))
|
fst res `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"<bar>\""))))))
|
||||||
environment (snd res) `shouldBe` [ (name "Bar", addr 6)
|
environment (snd res) `shouldBe` [ ("Bar", addr 6)
|
||||||
, (name "Foo", addr 3)
|
, ("Foo", addr 3)
|
||||||
, (name "Object", addr 0) ]
|
, ("Object", addr 0) ]
|
||||||
|
|
||||||
heapLookup (Address (Precise 6)) (heap (snd res))
|
heapLookup (Address (Precise 6)) (heap (snd res))
|
||||||
`shouldBe` ns "Bar" [ (name "baz", addr 8)
|
`shouldBe` ns "Bar" [ ("baz", addr 8)
|
||||||
, (name "foo", addr 5)
|
, ("foo", addr 5)
|
||||||
, (name "inspect", addr 7) ]
|
, ("inspect", addr 7) ]
|
||||||
|
|
||||||
it "evaluates modules" $ do
|
it "evaluates modules" $ do
|
||||||
res <- evaluate "modules.rb"
|
res <- evaluate "modules.rb"
|
||||||
fst res `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"<hello>\""))))))
|
fst res `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"<hello>\""))))))
|
||||||
environment (snd res) `shouldBe` [ (name "Object", addr 0)
|
environment (snd res) `shouldBe` [ ("Object", addr 0)
|
||||||
, (name "Bar", addr 3) ]
|
, ("Bar", addr 3) ]
|
||||||
|
|
||||||
it "has prelude" $ do
|
it "has prelude" $ do
|
||||||
res <- fst <$> evaluate "preluded.rb"
|
res <- fst <$> evaluate "preluded.rb"
|
||||||
res `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"<foo>\""))))))
|
res `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"<foo>\""))))))
|
||||||
|
|
||||||
where
|
where
|
||||||
ns n = Just . Latest . Just . injValue . Namespace (name n)
|
ns n = Just . Latest . Just . injValue . Namespace n
|
||||||
addr = Address . Precise
|
addr = Address . Precise
|
||||||
fixtures = "test/fixtures/ruby/analysis/"
|
fixtures = "test/fixtures/ruby/analysis/"
|
||||||
evaluate entry = evaluateFilesWithPrelude rubyParser
|
evaluate entry = evalRubyProject (fixtures <> entry)
|
||||||
[ fixtures <> entry
|
|
||||||
, fixtures <> "foo.rb"
|
|
||||||
]
|
|
||||||
|
@ -1,26 +1,27 @@
|
|||||||
{-# LANGUAGE OverloadedLists #-}
|
{-# LANGUAGE OverloadedLists #-}
|
||||||
module Analysis.TypeScript.Spec (spec) where
|
module Analysis.TypeScript.Spec (spec) where
|
||||||
|
|
||||||
import Data.Abstract.Value
|
|
||||||
import Data.Map
|
|
||||||
|
|
||||||
import SpecHelpers
|
import SpecHelpers
|
||||||
|
|
||||||
|
|
||||||
spec :: Spec
|
spec :: Spec
|
||||||
spec = parallel $ do
|
spec = parallel $ do
|
||||||
describe "evalutes TypeScript" $ do
|
describe "evaluates TypeScript" $ do
|
||||||
it "imports with aliased symbols" $ do
|
it "imports with aliased symbols" $ do
|
||||||
env <- environment . snd <$> evaluate "main.ts"
|
env <- environment . snd <$> evaluate "main.ts"
|
||||||
env `shouldBe` [ (qualifiedName ["bar"], addr 0) ]
|
env `shouldBe` [ ("bar", addr 0)
|
||||||
|
, ("quz", addr 3)]
|
||||||
|
|
||||||
it "imports with qualified names" $ do
|
it "imports with qualified names" $ do
|
||||||
env <- environment . snd <$> evaluate "main1.ts"
|
res <- snd <$> evaluate "main1.ts"
|
||||||
env `shouldBe` [ (qualifiedName ["b", "baz"], addr 0)
|
environment res `shouldBe` [ ("b", addr 0)
|
||||||
, (qualifiedName ["b", "foo"], addr 2)
|
, ("z", addr 4)
|
||||||
, (qualifiedName ["z", "baz"], addr 0)
|
]
|
||||||
, (qualifiedName ["z", "foo"], addr 2)
|
|
||||||
]
|
heapLookup (Address (Precise 0)) (heap res) `shouldBe` ns "b" [ ("baz", addr 1)
|
||||||
|
, ("foo", addr 3) ]
|
||||||
|
heapLookup (Address (Precise 4)) (heap res) `shouldBe` ns "z" [ ("baz", addr 1)
|
||||||
|
, ("foo", addr 3) ]
|
||||||
|
|
||||||
it "side effect only imports" $ do
|
it "side effect only imports" $ do
|
||||||
env <- environment . snd <$> evaluate "main2.ts"
|
env <- environment . snd <$> evaluate "main2.ts"
|
||||||
@ -28,14 +29,8 @@ spec = parallel $ do
|
|||||||
|
|
||||||
it "fails exporting symbols not defined in the module" $ do
|
it "fails exporting symbols not defined in the module" $ do
|
||||||
v <- fst <$> evaluate "bad-export.ts"
|
v <- fst <$> evaluate "bad-export.ts"
|
||||||
v `shouldBe` Left "module \"foo\" does not export \"pip\""
|
v `shouldBe` Left "module \"foo.ts\" does not export \"pip\""
|
||||||
|
|
||||||
where
|
where
|
||||||
addr = Address . Precise
|
|
||||||
fixtures = "test/fixtures/typescript/analysis/"
|
fixtures = "test/fixtures/typescript/analysis/"
|
||||||
evaluate entry = evaluateFiles typescriptParser
|
evaluate entry = evalTypeScriptProject (fixtures <> entry)
|
||||||
[ fixtures <> entry
|
|
||||||
, fixtures <> "a.ts"
|
|
||||||
, fixtures <> "foo.ts"
|
|
||||||
, fixtures <> "pip.ts"
|
|
||||||
]
|
|
||||||
|
@ -47,7 +47,6 @@ import qualified Data.Syntax as Syntax
|
|||||||
import qualified Data.Syntax.Comment as Comment
|
import qualified Data.Syntax.Comment as Comment
|
||||||
import qualified Data.Syntax.Declaration as Declaration
|
import qualified Data.Syntax.Declaration as Declaration
|
||||||
import qualified Data.Syntax.Statement as Statement
|
import qualified Data.Syntax.Statement as Statement
|
||||||
import qualified Data.Abstract.FreeVariables as FV
|
|
||||||
import Data.Term
|
import Data.Term
|
||||||
import Data.Text as T (Text, pack)
|
import Data.Text as T (Text, pack)
|
||||||
import qualified Data.Text.Encoding as T
|
import qualified Data.Text.Encoding as T
|
||||||
@ -257,9 +256,6 @@ type ListableSyntax = Union
|
|||||||
, []
|
, []
|
||||||
]
|
]
|
||||||
|
|
||||||
instance Listable FV.Name where
|
|
||||||
tiers = cons1 FV.name
|
|
||||||
|
|
||||||
instance Listable1 Gram where
|
instance Listable1 Gram where
|
||||||
liftTiers tiers = liftCons2 (liftTiers (liftTiers tiers)) (liftTiers (liftTiers tiers)) Gram
|
liftTiers tiers = liftCons2 (liftTiers (liftTiers tiers)) (liftTiers (liftTiers tiers)) Gram
|
||||||
|
|
||||||
|
@ -37,7 +37,7 @@ spec = parallel $ do
|
|||||||
(beforeTerm diff, afterTerm diff) `shouldBe` (Just (wrap (stripTerm <$> tas)), Just (wrap (stripTerm <$> tbs)))
|
(beforeTerm diff, afterTerm diff) `shouldBe` (Just (wrap (stripTerm <$> tas)), Just (wrap (stripTerm <$> tbs)))
|
||||||
|
|
||||||
it "produces unbiased insertions within branches" $
|
it "produces unbiased insertions within branches" $
|
||||||
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
|
let (a, b) = (decorate (termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier "a")) ])), decorate (termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier "b")) ]))) in
|
||||||
fmap (bimap stripTerm stripTerm) (rws comparableTerms (equalTerms comparableTerms) [ b ] [ a, b ]) `shouldBe` fmap (bimap stripTerm stripTerm) [ That a, These b b ]
|
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
|
where decorate = defaultFeatureVectorDecorator constructorNameAndConstantFields
|
||||||
|
@ -19,8 +19,8 @@ spec :: Spec
|
|||||||
spec = parallel $ do
|
spec = parallel $ do
|
||||||
describe "diffTerms" $ do
|
describe "diffTerms" $ do
|
||||||
it "returns a replacement when comparing two unicode equivalent terms" $
|
it "returns a replacement when comparing two unicode equivalent terms" $
|
||||||
let termA = termIn Nil (inj (Syntax.Identifier (name "t\776")))
|
let termA = termIn Nil (inj (Syntax.Identifier "t\776"))
|
||||||
termB = termIn Nil (inj (Syntax.Identifier (name "\7831"))) in
|
termB = termIn Nil (inj (Syntax.Identifier "\7831")) in
|
||||||
diffTerms termA termB `shouldBe` replacing termA (termB :: Term ListableSyntax (Record '[]))
|
diffTerms termA termB `shouldBe` replacing termA (termB :: Term ListableSyntax (Record '[]))
|
||||||
|
|
||||||
prop "produces correct diffs" $
|
prop "produces correct diffs" $
|
||||||
@ -32,7 +32,7 @@ spec = parallel $ do
|
|||||||
length (diffPatches diff) `shouldBe` 0
|
length (diffPatches diff) `shouldBe` 0
|
||||||
|
|
||||||
it "produces unbiased insertions within branches" $
|
it "produces unbiased insertions within branches" $
|
||||||
let term s = termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier (name s))) ]) :: Term ListableSyntax (Record '[])
|
let term s = termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier s)) ]) :: Term ListableSyntax (Record '[])
|
||||||
wrap = termIn Nil . inj in
|
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") ])
|
diffTerms (wrap [ term "b" ]) (wrap [ term "a", term "b" ]) `shouldBe` merge (Nil, Nil) (inj [ inserting (term "a"), merging (term "b") ])
|
||||||
|
|
||||||
|
@ -1,37 +0,0 @@
|
|||||||
module Rendering.Imports.Spec (spec) where
|
|
||||||
|
|
||||||
import Analysis.Declaration (declarationAlgebra)
|
|
||||||
import Analysis.PackageDef (packageDefAlgebra)
|
|
||||||
import Rendering.Imports
|
|
||||||
|
|
||||||
import SpecHelpers
|
|
||||||
|
|
||||||
|
|
||||||
spec :: Spec
|
|
||||||
spec = parallel $ do
|
|
||||||
describe "renderToImports" $ do
|
|
||||||
it "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
|
|
||||||
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
|
|
||||||
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
|
|
||||||
output <- parseToImports typescriptParser "test/fixtures/typescript/import-graph/app.ts"
|
|
||||||
expected <- readFileVerbatim "test/fixtures/typescript/import-graph/app.json"
|
|
||||||
toVerbatimOutput output `shouldBe` expected
|
|
||||||
|
|
||||||
where
|
|
||||||
toVerbatimOutput = verbatim . toOutput
|
|
||||||
parseToImports parser path = do
|
|
||||||
blob <- file path
|
|
||||||
runTask (parse parser blob >>= decorate (declarationAlgebra blob) >>= decorate (packageDefAlgebra blob) >>= render (renderToImports blob))
|
|
@ -166,14 +166,14 @@ programWithChange :: Term' -> Diff'
|
|||||||
programWithChange body = merge (programInfo, programInfo) (inj [ function' ])
|
programWithChange body = merge (programInfo, programInfo) (inj [ function' ])
|
||||||
where
|
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 ]))))
|
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 (name "foo")))
|
name' = let info = Nothing :. emptyInfo in merge (info, info) (inj (Syntax.Identifier "foo"))
|
||||||
|
|
||||||
-- Return a diff where term is inserted in the program, below a function found on both sides of the diff.
|
-- 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' -> Diff'
|
||||||
programWithChangeOutsideFunction term = merge (programInfo, programInfo) (inj [ function', term' ])
|
programWithChangeOutsideFunction term = merge (programInfo, programInfo) (inj [ function', term' ])
|
||||||
where
|
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 []))))
|
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 (name "foo")))
|
name' = let info = Nothing :. emptyInfo in merge (info, info) (inj (Syntax.Identifier "foo"))
|
||||||
term' = inserting term
|
term' = inserting term
|
||||||
|
|
||||||
programWithInsert :: Text -> Term' -> Diff'
|
programWithInsert :: Text -> Term' -> Diff'
|
||||||
@ -191,7 +191,7 @@ programOf diff = merge (programInfo, programInfo) (inj [ diff ])
|
|||||||
functionOf :: Text -> Term' -> Term'
|
functionOf :: Text -> Term' -> Term'
|
||||||
functionOf n body = termIn (Just (FunctionDeclaration n 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
|
where
|
||||||
name' = termIn (Nothing :. emptyInfo) (inj (Syntax.Identifier (name (encodeUtf8 n))))
|
name' = termIn (Nothing :. emptyInfo) (inj (Syntax.Identifier (encodeUtf8 n)))
|
||||||
|
|
||||||
programInfo :: Record '[Maybe Declaration, Range, Span]
|
programInfo :: Record '[Maybe Declaration, Range, Span]
|
||||||
programInfo = Nothing :. emptyInfo
|
programInfo = Nothing :. emptyInfo
|
||||||
@ -218,7 +218,7 @@ blobsForPaths :: Both FilePath -> IO BlobPair
|
|||||||
blobsForPaths = readFilePair . fmap ("test/fixtures/toc/" <>)
|
blobsForPaths = readFilePair . fmap ("test/fixtures/toc/" <>)
|
||||||
|
|
||||||
blankDiff :: Diff'
|
blankDiff :: Diff'
|
||||||
blankDiff = merge (arrayInfo, arrayInfo) (inj [ inserting (termIn literalInfo (inj (Syntax.Identifier (name "\"a\"")))) ])
|
blankDiff = merge (arrayInfo, arrayInfo) (inj [ inserting (termIn literalInfo (inj (Syntax.Identifier "\"a\""))) ])
|
||||||
where
|
where
|
||||||
arrayInfo = Nothing :. Range 0 3 :. Span (Pos 1 1) (Pos 1 5) :. Nil
|
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
|
literalInfo = Nothing :. Range 1 2 :. Span (Pos 1 2) (Pos 1 4) :. Nil
|
||||||
|
@ -17,7 +17,6 @@ import qualified Diffing.Interpreter.Spec
|
|||||||
import qualified Integration.Spec
|
import qualified Integration.Spec
|
||||||
import qualified Matching.Go.Spec
|
import qualified Matching.Go.Spec
|
||||||
import qualified Rendering.TOC.Spec
|
import qualified Rendering.TOC.Spec
|
||||||
import qualified Rendering.Imports.Spec
|
|
||||||
import qualified Semantic.Spec
|
import qualified Semantic.Spec
|
||||||
import qualified Semantic.CLI.Spec
|
import qualified Semantic.CLI.Spec
|
||||||
import qualified Semantic.IO.Spec
|
import qualified Semantic.IO.Spec
|
||||||
@ -44,7 +43,6 @@ main = hspec $ do
|
|||||||
describe "Diffing.Interpreter" Diffing.Interpreter.Spec.spec
|
describe "Diffing.Interpreter" Diffing.Interpreter.Spec.spec
|
||||||
describe "Matching" Matching.Go.Spec.spec
|
describe "Matching" Matching.Go.Spec.spec
|
||||||
describe "Rendering.TOC" Rendering.TOC.Spec.spec
|
describe "Rendering.TOC" Rendering.TOC.Spec.spec
|
||||||
describe "Rendering.Imports" Rendering.Imports.Spec.spec
|
|
||||||
describe "Semantic" Semantic.Spec.spec
|
describe "Semantic" Semantic.Spec.spec
|
||||||
describe "Semantic.CLI" Semantic.CLI.Spec.spec
|
describe "Semantic.CLI" Semantic.CLI.Spec.spec
|
||||||
describe "Semantic.IO" Semantic.IO.Spec.spec
|
describe "Semantic.IO" Semantic.IO.Spec.spec
|
||||||
|
@ -5,6 +5,8 @@ module SpecHelpers (
|
|||||||
, parseFilePath
|
, parseFilePath
|
||||||
, readFilePair
|
, readFilePair
|
||||||
, readFileVerbatim
|
, readFileVerbatim
|
||||||
|
, addr
|
||||||
|
, ns
|
||||||
, verbatim
|
, verbatim
|
||||||
, Verbatim(..)
|
, Verbatim(..)
|
||||||
, ) where
|
, ) where
|
||||||
@ -44,7 +46,7 @@ import Test.LeanCheck as X
|
|||||||
|
|
||||||
import qualified Data.ByteString as B
|
import qualified Data.ByteString as B
|
||||||
import qualified Semantic.IO as IO
|
import qualified Semantic.IO as IO
|
||||||
|
import Data.Abstract.Value
|
||||||
|
|
||||||
-- | Returns an s-expression formatted diff for the specified FilePath pair.
|
-- | Returns an s-expression formatted diff for the specified FilePath pair.
|
||||||
diffFilePaths :: Both FilePath -> IO ByteString
|
diffFilePaths :: Both FilePath -> IO ByteString
|
||||||
@ -52,7 +54,7 @@ diffFilePaths paths = readFilePair paths >>= runTask . diffBlobPair SExpressionD
|
|||||||
|
|
||||||
-- | Returns an s-expression parse tree for the specified FilePath.
|
-- | Returns an s-expression parse tree for the specified FilePath.
|
||||||
parseFilePath :: FilePath -> IO ByteString
|
parseFilePath :: FilePath -> IO ByteString
|
||||||
parseFilePath path = IO.readFile path (IO.languageForFilePath path) >>= pure . fromJust >>= runTask . parseBlob SExpressionTermRenderer
|
parseFilePath path = (fromJust <$> IO.readFile path (IO.languageForFilePath path)) >>= runTask . parseBlob SExpressionTermRenderer
|
||||||
|
|
||||||
-- | Read two files to a BlobPair.
|
-- | Read two files to a BlobPair.
|
||||||
readFilePair :: Both FilePath -> IO BlobPair
|
readFilePair :: Both FilePath -> IO BlobPair
|
||||||
@ -62,6 +64,9 @@ readFilePair paths = let paths' = fmap (\p -> (p, IO.languageForFilePath p)) pat
|
|||||||
readFileVerbatim :: FilePath -> IO Verbatim
|
readFileVerbatim :: FilePath -> IO Verbatim
|
||||||
readFileVerbatim = fmap verbatim . B.readFile
|
readFileVerbatim = fmap verbatim . B.readFile
|
||||||
|
|
||||||
|
ns n = Just . Latest . Just . injValue . Namespace n
|
||||||
|
addr = Address . Precise
|
||||||
|
|
||||||
newtype Verbatim = Verbatim ByteString
|
newtype Verbatim = Verbatim ByteString
|
||||||
deriving (Eq)
|
deriving (Eq)
|
||||||
|
|
||||||
|
2
test/fixtures/go/analysis/main1.go
vendored
2
test/fixtures/go/analysis/main1.go
vendored
@ -2,7 +2,7 @@ package main
|
|||||||
|
|
||||||
import (
|
import (
|
||||||
f "./foo"
|
f "./foo"
|
||||||
_ "./bar"
|
_ "./bar"
|
||||||
)
|
)
|
||||||
|
|
||||||
func main() {
|
func main() {
|
||||||
|
@ -25,13 +25,11 @@
|
|||||||
(
|
(
|
||||||
(Integer)
|
(Integer)
|
||||||
(Integer))))
|
(Integer))))
|
||||||
(Assignment
|
{+(Assignment
|
||||||
{ (Identifier)
|
{+(Identifier)+}
|
||||||
->(Identifier) }
|
{+(Times
|
||||||
(Times
|
{+(Identifier)+}
|
||||||
{ (Identifier)
|
{+(Integer)+})+})+}
|
||||||
->(Identifier) }
|
|
||||||
(Integer)))
|
|
||||||
{+(Assignment
|
{+(Assignment
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Plus
|
{+(Plus
|
||||||
@ -80,6 +78,11 @@
|
|||||||
{+(KeyValue
|
{+(KeyValue
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Integer)+})+})+})+})+})+})+}
|
{+(Integer)+})+})+})+})+})+})+}
|
||||||
|
{-(Assignment
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(Times
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(Integer)-})-})-}
|
||||||
{-(Assignment
|
{-(Assignment
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
{-(Plus
|
{-(Plus
|
||||||
|
@ -25,13 +25,11 @@
|
|||||||
(
|
(
|
||||||
(Integer)
|
(Integer)
|
||||||
(Integer))))
|
(Integer))))
|
||||||
(Assignment
|
{+(Assignment
|
||||||
{ (Identifier)
|
{+(Identifier)+}
|
||||||
->(Identifier) }
|
{+(Times
|
||||||
(Times
|
{+(Identifier)+}
|
||||||
{ (Identifier)
|
{+(Integer)+})+})+}
|
||||||
->(Identifier) }
|
|
||||||
(Integer)))
|
|
||||||
{+(Assignment
|
{+(Assignment
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Plus
|
{+(Plus
|
||||||
@ -42,15 +40,11 @@
|
|||||||
{+(LShift
|
{+(LShift
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Integer)+})+})+}
|
{+(Integer)+})+})+}
|
||||||
(Assignment
|
{+(Assignment
|
||||||
{ (Identifier)
|
{+(Identifier)+}
|
||||||
->(Identifier) }
|
{+(RShift
|
||||||
{ (Plus
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Integer)-})
|
|
||||||
->(RShift
|
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Integer)+}) })
|
{+(Integer)+})+})+}
|
||||||
{+(Assignment
|
{+(Assignment
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(DividedBy
|
{+(DividedBy
|
||||||
@ -61,11 +55,15 @@
|
|||||||
{+(BXOr
|
{+(BXOr
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Integer)+})+})+}
|
{+(Integer)+})+})+}
|
||||||
{+(Assignment
|
(Assignment
|
||||||
{+(Identifier)+}
|
{ (Identifier)
|
||||||
{+(Modulo
|
->(Identifier) }
|
||||||
|
{ (Times
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(Integer)-})
|
||||||
|
->(Modulo
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Integer)+})+})+}
|
{+(Integer)+}) })
|
||||||
{+(Assignment
|
{+(Assignment
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Not
|
{+(Not
|
||||||
@ -84,6 +82,11 @@
|
|||||||
{+(KeyValue
|
{+(KeyValue
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Integer)+})+})+})+})+})+})+}
|
{+(Integer)+})+})+})+})+})+})+}
|
||||||
|
{-(Assignment
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(Plus
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(Integer)-})-})-}
|
||||||
{-(Assignment
|
{-(Assignment
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
{-(LShift
|
{-(LShift
|
||||||
|
11
test/fixtures/go/binary-expressions.diffA-B.txt
vendored
11
test/fixtures/go/binary-expressions.diffA-B.txt
vendored
@ -22,9 +22,11 @@
|
|||||||
->(Identifier) }
|
->(Identifier) }
|
||||||
{ (Identifier)
|
{ (Identifier)
|
||||||
->(Identifier) }))
|
->(Identifier) }))
|
||||||
{+(Equal
|
(Equal
|
||||||
{+(Identifier)+}
|
{ (Identifier)
|
||||||
{+(Identifier)+})+}
|
->(Identifier) }
|
||||||
|
{ (Identifier)
|
||||||
|
->(Identifier) })
|
||||||
{+(Not
|
{+(Not
|
||||||
{+(Equal
|
{+(Equal
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
@ -74,9 +76,6 @@
|
|||||||
{+(BAnd
|
{+(BAnd
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Identifier)+})+}
|
{+(Identifier)+})+}
|
||||||
{-(Equal
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-}
|
|
||||||
{-(Not
|
{-(Not
|
||||||
{-(Equal
|
{-(Equal
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
|
11
test/fixtures/go/binary-expressions.diffB-A.txt
vendored
11
test/fixtures/go/binary-expressions.diffB-A.txt
vendored
@ -22,9 +22,11 @@
|
|||||||
->(Identifier) }
|
->(Identifier) }
|
||||||
{ (Identifier)
|
{ (Identifier)
|
||||||
->(Identifier) }))
|
->(Identifier) }))
|
||||||
{+(Equal
|
(Equal
|
||||||
{+(Identifier)+}
|
{ (Identifier)
|
||||||
{+(Identifier)+})+}
|
->(Identifier) }
|
||||||
|
{ (Identifier)
|
||||||
|
->(Identifier) })
|
||||||
{+(Not
|
{+(Not
|
||||||
{+(Equal
|
{+(Equal
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
@ -74,9 +76,6 @@
|
|||||||
{+(BAnd
|
{+(BAnd
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Identifier)+})+}
|
{+(Identifier)+})+}
|
||||||
{-(Equal
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-}
|
|
||||||
{-(Not
|
{-(Not
|
||||||
{-(Equal
|
{-(Equal
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
|
84
test/fixtures/go/channel-types.diffA-B.txt
vendored
84
test/fixtures/go/channel-types.diffA-B.txt
vendored
@ -6,58 +6,38 @@
|
|||||||
(Identifier)
|
(Identifier)
|
||||||
([])
|
([])
|
||||||
(
|
(
|
||||||
{+(Type
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(BidirectionalChannel
|
|
||||||
{+(ReceiveChannel
|
|
||||||
{+(Identifier)+})+})+})+}
|
|
||||||
{+(Type
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(SendChannel
|
|
||||||
{+(SendChannel
|
|
||||||
{+(Constructor
|
|
||||||
{+(Empty)+}
|
|
||||||
{+([])+})+})+})+})+}
|
|
||||||
{+(Type
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(SendChannel
|
|
||||||
{+(ReceiveChannel
|
|
||||||
{+(Identifier)+})+})+})+}
|
|
||||||
(Type
|
(Type
|
||||||
{ (Identifier)
|
{ (Identifier)
|
||||||
->(Identifier) }
|
->(Identifier) }
|
||||||
{ (BidirectionalChannel
|
(BidirectionalChannel
|
||||||
{-(ReceiveChannel
|
(ReceiveChannel
|
||||||
{-(Identifier)-})-})
|
{ (Identifier)
|
||||||
->(ReceiveChannel
|
->(Identifier) })))
|
||||||
{+(ReceiveChannel
|
(Type
|
||||||
{+(Identifier)+})+}) })
|
{ (Identifier)
|
||||||
{+(Type
|
->(Identifier) }
|
||||||
{+(Identifier)+}
|
(SendChannel
|
||||||
{+(BidirectionalChannel
|
(SendChannel
|
||||||
{+(Parenthesized
|
(Constructor
|
||||||
{+(ReceiveChannel
|
(Empty)
|
||||||
{+(Identifier)+})+})+})+})+}
|
([])))))
|
||||||
{-(Type
|
(Type
|
||||||
{-(Identifier)-}
|
{ (Identifier)
|
||||||
{-(SendChannel
|
->(Identifier) }
|
||||||
{-(SendChannel
|
(SendChannel
|
||||||
{-(Constructor
|
(ReceiveChannel
|
||||||
{-(Empty)-}
|
{ (Identifier)
|
||||||
{-([])-})-})-})-})-}
|
->(Identifier) })))
|
||||||
{-(Type
|
(Type
|
||||||
{-(Identifier)-}
|
(Identifier)
|
||||||
{-(SendChannel
|
(ReceiveChannel
|
||||||
{-(ReceiveChannel
|
(ReceiveChannel
|
||||||
{-(Identifier)-})-})-})-}
|
{ (Identifier)
|
||||||
{-(Type
|
->(Identifier) })))
|
||||||
{-(Identifier)-}
|
(Type
|
||||||
{-(ReceiveChannel
|
(Identifier)
|
||||||
{-(ReceiveChannel
|
(BidirectionalChannel
|
||||||
{-(Identifier)-})-})-})-}
|
(Parenthesized
|
||||||
{-(Type
|
(ReceiveChannel
|
||||||
{-(Identifier)-}
|
{ (Identifier)
|
||||||
{-(BidirectionalChannel
|
->(Identifier) })))))))
|
||||||
{-(Parenthesized
|
|
||||||
{-(ReceiveChannel
|
|
||||||
{-(Identifier)-})-})-})-})-})))
|
|
||||||
|
91
test/fixtures/go/channel-types.diffB-A.txt
vendored
91
test/fixtures/go/channel-types.diffB-A.txt
vendored
@ -6,59 +6,38 @@
|
|||||||
(Identifier)
|
(Identifier)
|
||||||
([])
|
([])
|
||||||
(
|
(
|
||||||
{+(Type
|
(Type
|
||||||
{+(Identifier)+}
|
{ (Identifier)
|
||||||
{+(BidirectionalChannel
|
->(Identifier) }
|
||||||
{+(ReceiveChannel
|
(BidirectionalChannel
|
||||||
{+(Identifier)+})+})+})+}
|
(ReceiveChannel
|
||||||
{+(Type
|
{ (Identifier)
|
||||||
{+(Identifier)+}
|
->(Identifier) })))
|
||||||
{+(SendChannel
|
(Type
|
||||||
{+(SendChannel
|
{ (Identifier)
|
||||||
{+(Constructor
|
->(Identifier) }
|
||||||
{+(Empty)+}
|
(SendChannel
|
||||||
{+([])+})+})+})+})+}
|
(SendChannel
|
||||||
{+(Type
|
(Constructor
|
||||||
{+(Identifier)+}
|
(Empty)
|
||||||
{+(SendChannel
|
([])))))
|
||||||
{+(ReceiveChannel
|
(Type
|
||||||
{+(Identifier)+})+})+})+}
|
{ (Identifier)
|
||||||
{+(Type
|
->(Identifier) }
|
||||||
{+(Identifier)+}
|
(SendChannel
|
||||||
{+(ReceiveChannel
|
(ReceiveChannel
|
||||||
{+(ReceiveChannel
|
{ (Identifier)
|
||||||
{+(Identifier)+})+})+})+}
|
->(Identifier) })))
|
||||||
{+(Type
|
(Type
|
||||||
{+(Identifier)+}
|
(Identifier)
|
||||||
{+(BidirectionalChannel
|
(ReceiveChannel
|
||||||
{+(Parenthesized
|
(ReceiveChannel
|
||||||
{+(ReceiveChannel
|
{ (Identifier)
|
||||||
{+(Identifier)+})+})+})+})+}
|
->(Identifier) })))
|
||||||
{-(Type
|
(Type
|
||||||
{-(Identifier)-}
|
(Identifier)
|
||||||
{-(BidirectionalChannel
|
(BidirectionalChannel
|
||||||
{-(ReceiveChannel
|
(Parenthesized
|
||||||
{-(Identifier)-})-})-})-}
|
(ReceiveChannel
|
||||||
{-(Type
|
{ (Identifier)
|
||||||
{-(Identifier)-}
|
->(Identifier) })))))))
|
||||||
{-(SendChannel
|
|
||||||
{-(SendChannel
|
|
||||||
{-(Constructor
|
|
||||||
{-(Empty)-}
|
|
||||||
{-([])-})-})-})-})-}
|
|
||||||
{-(Type
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(SendChannel
|
|
||||||
{-(ReceiveChannel
|
|
||||||
{-(Identifier)-})-})-})-}
|
|
||||||
{-(Type
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(ReceiveChannel
|
|
||||||
{-(ReceiveChannel
|
|
||||||
{-(Identifier)-})-})-})-}
|
|
||||||
{-(Type
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(BidirectionalChannel
|
|
||||||
{-(Parenthesized
|
|
||||||
{-(ReceiveChannel
|
|
||||||
{-(Identifier)-})-})-})-})-})))
|
|
||||||
|
@ -2,23 +2,18 @@
|
|||||||
(Package
|
(Package
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(
|
(
|
||||||
(QualifiedImport
|
{ (QualifiedImport
|
||||||
{ (Identifier)
|
{-(Identifier)-})
|
||||||
->(Identifier) }
|
->(QualifiedImport
|
||||||
{ (Identifier)
|
{+(Identifier)+}) }
|
||||||
->(Identifier) })
|
{ (Import
|
||||||
{+(Import
|
{-(TextElement)-})
|
||||||
{+(Identifier)+}
|
->(Import
|
||||||
{+(TextElement)+})+}
|
{+(TextElement)+}) }
|
||||||
{+(QualifiedImport
|
{ (QualifiedImport
|
||||||
{+(Identifier)+}
|
{-(Identifier)-})
|
||||||
{+(Identifier)+})+}
|
->(QualifiedImport
|
||||||
{-(Import
|
{+(Identifier)+}) })
|
||||||
{-(Identifier)-}
|
|
||||||
{-(TextElement)-})-}
|
|
||||||
{-(QualifiedImport
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-})
|
|
||||||
(Function
|
(Function
|
||||||
(Empty)
|
(Empty)
|
||||||
(Identifier)
|
(Identifier)
|
||||||
|
@ -2,23 +2,18 @@
|
|||||||
(Package
|
(Package
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(
|
(
|
||||||
(QualifiedImport
|
{ (QualifiedImport
|
||||||
{ (Identifier)
|
{-(Identifier)-})
|
||||||
->(Identifier) }
|
->(QualifiedImport
|
||||||
{ (Identifier)
|
{+(Identifier)+}) }
|
||||||
->(Identifier) })
|
{ (Import
|
||||||
{+(Import
|
{-(TextElement)-})
|
||||||
{+(Identifier)+}
|
->(Import
|
||||||
{+(TextElement)+})+}
|
{+(TextElement)+}) }
|
||||||
{+(QualifiedImport
|
{ (QualifiedImport
|
||||||
{+(Identifier)+}
|
{-(Identifier)-})
|
||||||
{+(Identifier)+})+}
|
->(QualifiedImport
|
||||||
{-(Import
|
{+(Identifier)+}) })
|
||||||
{-(Identifier)-}
|
|
||||||
{-(TextElement)-})-}
|
|
||||||
{-(QualifiedImport
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-})
|
|
||||||
(Function
|
(Function
|
||||||
(Empty)
|
(Empty)
|
||||||
(Identifier)
|
(Identifier)
|
||||||
|
@ -3,13 +3,10 @@
|
|||||||
(Identifier))
|
(Identifier))
|
||||||
(
|
(
|
||||||
(QualifiedImport
|
(QualifiedImport
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Import
|
(Import
|
||||||
(Identifier)
|
|
||||||
(TextElement))
|
(TextElement))
|
||||||
(QualifiedImport
|
(QualifiedImport
|
||||||
(Identifier)
|
|
||||||
(Identifier)))
|
(Identifier)))
|
||||||
(Function
|
(Function
|
||||||
(Empty)
|
(Empty)
|
||||||
|
@ -3,13 +3,10 @@
|
|||||||
(Identifier))
|
(Identifier))
|
||||||
(
|
(
|
||||||
(QualifiedImport
|
(QualifiedImport
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Import
|
(Import
|
||||||
(Identifier)
|
|
||||||
(TextElement))
|
(TextElement))
|
||||||
(QualifiedImport
|
(QualifiedImport
|
||||||
(Identifier)
|
|
||||||
(Identifier)))
|
(Identifier)))
|
||||||
(Function
|
(Function
|
||||||
(Empty)
|
(Empty)
|
||||||
|
@ -4,10 +4,10 @@
|
|||||||
(
|
(
|
||||||
(Comment)
|
(Comment)
|
||||||
(Comment)
|
(Comment)
|
||||||
(QualifiedImport
|
{ (QualifiedImport
|
||||||
{ (Identifier)
|
{-(Identifier)-})
|
||||||
->(Identifier) }
|
->(QualifiedImport
|
||||||
(Identifier))
|
{+(Identifier)+}) }
|
||||||
(Comment))
|
(Comment))
|
||||||
(Function
|
(Function
|
||||||
(Empty)
|
(Empty)
|
||||||
|
@ -4,10 +4,10 @@
|
|||||||
(
|
(
|
||||||
(Comment)
|
(Comment)
|
||||||
(Comment)
|
(Comment)
|
||||||
(QualifiedImport
|
{ (QualifiedImport
|
||||||
{ (Identifier)
|
{-(Identifier)-})
|
||||||
->(Identifier) }
|
->(QualifiedImport
|
||||||
(Identifier))
|
{+(Identifier)+}) }
|
||||||
(Comment))
|
(Comment))
|
||||||
(Function
|
(Function
|
||||||
(Empty)
|
(Empty)
|
||||||
|
@ -5,7 +5,6 @@
|
|||||||
(Comment)
|
(Comment)
|
||||||
(Comment)
|
(Comment)
|
||||||
(QualifiedImport
|
(QualifiedImport
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Comment))
|
(Comment))
|
||||||
(Function
|
(Function
|
||||||
|
@ -5,7 +5,6 @@
|
|||||||
(Comment)
|
(Comment)
|
||||||
(Comment)
|
(Comment)
|
||||||
(QualifiedImport
|
(QualifiedImport
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Comment))
|
(Comment))
|
||||||
(Function
|
(Function
|
||||||
|
@ -1,19 +1,18 @@
|
|||||||
(Program
|
(Program
|
||||||
(Package
|
(Package
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(QualifiedImport
|
{ (QualifiedImport
|
||||||
{ (Identifier)
|
{-(Identifier)-})
|
||||||
->(Identifier) }
|
->(QualifiedImport
|
||||||
{ (Identifier)
|
{+(Identifier)+}) }
|
||||||
->(Identifier) })
|
{ (Import
|
||||||
(Import
|
{-(TextElement)-})
|
||||||
{ (Identifier)
|
->(Import
|
||||||
->(Identifier) }
|
{+(TextElement)+}) }
|
||||||
(TextElement))
|
{ (QualifiedImport
|
||||||
(QualifiedImport
|
{-(Identifier)-})
|
||||||
{ (Identifier)
|
->(QualifiedImport
|
||||||
->(Identifier) }
|
{+(Identifier)+}) }
|
||||||
(Identifier))
|
|
||||||
(Function
|
(Function
|
||||||
(Empty)
|
(Empty)
|
||||||
(Identifier)
|
(Identifier)
|
||||||
|
@ -1,19 +1,18 @@
|
|||||||
(Program
|
(Program
|
||||||
(Package
|
(Package
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(QualifiedImport
|
{ (QualifiedImport
|
||||||
{ (Identifier)
|
{-(Identifier)-})
|
||||||
->(Identifier) }
|
->(QualifiedImport
|
||||||
{ (Identifier)
|
{+(Identifier)+}) }
|
||||||
->(Identifier) })
|
{ (Import
|
||||||
(Import
|
{-(TextElement)-})
|
||||||
{ (Identifier)
|
->(Import
|
||||||
->(Identifier) }
|
{+(TextElement)+}) }
|
||||||
(TextElement))
|
{ (QualifiedImport
|
||||||
(QualifiedImport
|
{-(Identifier)-})
|
||||||
{ (Identifier)
|
->(QualifiedImport
|
||||||
->(Identifier) }
|
{+(Identifier)+}) }
|
||||||
(Identifier))
|
|
||||||
(Function
|
(Function
|
||||||
(Empty)
|
(Empty)
|
||||||
(Identifier)
|
(Identifier)
|
||||||
|
@ -2,13 +2,10 @@
|
|||||||
(Package
|
(Package
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(QualifiedImport
|
(QualifiedImport
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Import
|
(Import
|
||||||
(Identifier)
|
|
||||||
(TextElement))
|
(TextElement))
|
||||||
(QualifiedImport
|
(QualifiedImport
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Function
|
(Function
|
||||||
(Empty)
|
(Empty)
|
||||||
|
@ -2,13 +2,10 @@
|
|||||||
(Package
|
(Package
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(QualifiedImport
|
(QualifiedImport
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Import
|
(Import
|
||||||
(Identifier)
|
|
||||||
(TextElement))
|
(TextElement))
|
||||||
(QualifiedImport
|
(QualifiedImport
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Function
|
(Function
|
||||||
(Empty)
|
(Empty)
|
||||||
|
12
test/fixtures/javascript/export.diffA-B.txt
vendored
12
test/fixtures/javascript/export.diffA-B.txt
vendored
@ -62,10 +62,8 @@
|
|||||||
{+(QualifiedExport)+}
|
{+(QualifiedExport)+}
|
||||||
{+(DefaultExport
|
{+(DefaultExport
|
||||||
{+(TextElement)+})+}
|
{+(TextElement)+})+}
|
||||||
{+(QualifiedExportFrom
|
{+(QualifiedExportFrom)+}
|
||||||
{+(Identifier)+})+}
|
{+(QualifiedExportFrom)+}
|
||||||
{+(QualifiedExportFrom
|
|
||||||
{+(Identifier)+})+}
|
|
||||||
{-(DefaultExport
|
{-(DefaultExport
|
||||||
{-(Function
|
{-(Function
|
||||||
{-(Empty)-}
|
{-(Empty)-}
|
||||||
@ -75,7 +73,5 @@
|
|||||||
{-(QualifiedExport)-}
|
{-(QualifiedExport)-}
|
||||||
{-(DefaultExport
|
{-(DefaultExport
|
||||||
{-(TextElement)-})-}
|
{-(TextElement)-})-}
|
||||||
{-(QualifiedExportFrom
|
{-(QualifiedExportFrom)-}
|
||||||
{-(Identifier)-})-}
|
{-(QualifiedExportFrom)-})
|
||||||
{-(QualifiedExportFrom
|
|
||||||
{-(Identifier)-})-})
|
|
||||||
|
12
test/fixtures/javascript/export.diffB-A.txt
vendored
12
test/fixtures/javascript/export.diffB-A.txt
vendored
@ -73,11 +73,7 @@
|
|||||||
(DefaultExport
|
(DefaultExport
|
||||||
{ (TextElement)
|
{ (TextElement)
|
||||||
->(TextElement) })
|
->(TextElement) })
|
||||||
{ (QualifiedExportFrom
|
{ (QualifiedExportFrom)
|
||||||
{-(Identifier)-})
|
->(QualifiedExportFrom) }
|
||||||
->(QualifiedExportFrom
|
{ (QualifiedExportFrom)
|
||||||
{+(Identifier)+}) }
|
->(QualifiedExportFrom) })
|
||||||
{ (QualifiedExportFrom
|
|
||||||
{-(Identifier)-})
|
|
||||||
->(QualifiedExportFrom
|
|
||||||
{+(Identifier)+}) })
|
|
||||||
|
6
test/fixtures/javascript/export.parseA.txt
vendored
6
test/fixtures/javascript/export.parseA.txt
vendored
@ -50,7 +50,5 @@
|
|||||||
(QualifiedExport)
|
(QualifiedExport)
|
||||||
(DefaultExport
|
(DefaultExport
|
||||||
(TextElement))
|
(TextElement))
|
||||||
(QualifiedExportFrom
|
(QualifiedExportFrom)
|
||||||
(Identifier))
|
(QualifiedExportFrom))
|
||||||
(QualifiedExportFrom
|
|
||||||
(Identifier)))
|
|
||||||
|
6
test/fixtures/javascript/export.parseB.txt
vendored
6
test/fixtures/javascript/export.parseB.txt
vendored
@ -50,7 +50,5 @@
|
|||||||
(QualifiedExport)
|
(QualifiedExport)
|
||||||
(DefaultExport
|
(DefaultExport
|
||||||
(TextElement))
|
(TextElement))
|
||||||
(QualifiedExportFrom
|
(QualifiedExportFrom)
|
||||||
(Identifier))
|
(QualifiedExportFrom))
|
||||||
(QualifiedExportFrom
|
|
||||||
(Identifier)))
|
|
||||||
|
80
test/fixtures/javascript/import.diffA-B.txt
vendored
80
test/fixtures/javascript/import.diffA-B.txt
vendored
@ -1,65 +1,29 @@
|
|||||||
(Program
|
(Program
|
||||||
{+(Import
|
{ (Import)
|
||||||
{+(Identifier)+}
|
->(Import) }
|
||||||
{+(Empty)+})+}
|
{ (QualifiedAliasedImport
|
||||||
{+(QualifiedImport
|
{-(Identifier)-})
|
||||||
{+(Identifier)+}
|
->(QualifiedAliasedImport
|
||||||
{+(Identifier)+})+}
|
{+(Identifier)+}) }
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{ (Import)
|
||||||
{+(Empty)+})+}
|
->(Import) }
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(Import
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(
|
{+(
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{+(Import)+})+}
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(Import
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+})+}
|
|
||||||
{+(
|
{+(
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{+(QualifiedAliasedImport
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(QualifiedImport
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Identifier)+})+})+}
|
{+(Identifier)+})+})+}
|
||||||
{+(SideEffectImport
|
{+(SideEffectImport)+}
|
||||||
{+(Identifier)+}
|
{-(Import)-}
|
||||||
{+(Empty)+})+}
|
{-(Import)-}
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(QualifiedImport
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(
|
{-(
|
||||||
{-(Import
|
{-(Import)-}
|
||||||
{-(Identifier)-}
|
{-(Import)-})-}
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-})-}
|
|
||||||
{-(
|
{-(
|
||||||
{-(Import
|
{-(Import)-}
|
||||||
{-(Identifier)-}
|
{-(QualifiedAliasedImport
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(QualifiedImport
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-})-}
|
{-(Identifier)-})-})-}
|
||||||
{-(SideEffectImport
|
{-(SideEffectImport)-})
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-})
|
|
||||||
|
80
test/fixtures/javascript/import.diffB-A.txt
vendored
80
test/fixtures/javascript/import.diffB-A.txt
vendored
@ -1,65 +1,29 @@
|
|||||||
(Program
|
(Program
|
||||||
{+(Import
|
{ (Import)
|
||||||
{+(Identifier)+}
|
->(Import) }
|
||||||
{+(Empty)+})+}
|
{ (QualifiedAliasedImport
|
||||||
{+(QualifiedImport
|
{-(Identifier)-})
|
||||||
{+(Identifier)+}
|
->(QualifiedAliasedImport
|
||||||
{+(Identifier)+})+}
|
{+(Identifier)+}) }
|
||||||
{ (Import
|
{+(Import)+}
|
||||||
{-(Identifier)-}
|
{+(Import)+}
|
||||||
{-(Empty)-})
|
{ (Import)
|
||||||
->(Import
|
->(Import) }
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+}) }
|
|
||||||
{+(Import
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(Import
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(
|
{+(
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{+(Import)+})+}
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(Import
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+})+}
|
|
||||||
{+(
|
{+(
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{+(QualifiedAliasedImport
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(QualifiedImport
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Identifier)+})+})+}
|
{+(Identifier)+})+})+}
|
||||||
{+(SideEffectImport
|
{+(SideEffectImport)+}
|
||||||
{+(Identifier)+}
|
{-(Import)-}
|
||||||
{+(Empty)+})+}
|
{-(Import)-}
|
||||||
{-(QualifiedImport
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(
|
{-(
|
||||||
{-(Import
|
{-(Import)-}
|
||||||
{-(Identifier)-}
|
{-(Import)-})-}
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-})-}
|
|
||||||
{-(
|
{-(
|
||||||
{-(Import
|
{-(Import)-}
|
||||||
{-(Identifier)-}
|
{-(QualifiedAliasedImport
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(QualifiedImport
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-})-}
|
{-(Identifier)-})-})-}
|
||||||
{-(SideEffectImport
|
{-(SideEffectImport)-})
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-})
|
|
||||||
|
38
test/fixtures/javascript/import.parseA.txt
vendored
38
test/fixtures/javascript/import.parseA.txt
vendored
@ -1,33 +1,15 @@
|
|||||||
(Program
|
(Program
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(QualifiedAliasedImport
|
||||||
(Empty))
|
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(Import)
|
||||||
(Empty))
|
(Import)
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty))
|
|
||||||
(
|
(
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(Import))
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty)))
|
|
||||||
(
|
(
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(QualifiedAliasedImport
|
||||||
(Empty))
|
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier)))
|
(Identifier)))
|
||||||
(SideEffectImport
|
(SideEffectImport))
|
||||||
(Identifier)
|
|
||||||
(Empty)))
|
|
||||||
|
38
test/fixtures/javascript/import.parseB.txt
vendored
38
test/fixtures/javascript/import.parseB.txt
vendored
@ -1,33 +1,15 @@
|
|||||||
(Program
|
(Program
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(QualifiedAliasedImport
|
||||||
(Empty))
|
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(Import)
|
||||||
(Empty))
|
(Import)
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty))
|
|
||||||
(
|
(
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(Import))
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty)))
|
|
||||||
(
|
(
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(QualifiedAliasedImport
|
||||||
(Empty))
|
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier)))
|
(Identifier)))
|
||||||
(SideEffectImport
|
(SideEffectImport))
|
||||||
(Identifier)
|
|
||||||
(Empty)))
|
|
||||||
|
18
test/fixtures/python/assignment.diffA-B.txt
vendored
18
test/fixtures/python/assignment.diffA-B.txt
vendored
@ -10,14 +10,18 @@
|
|||||||
{ (Identifier)
|
{ (Identifier)
|
||||||
->(Identifier) }
|
->(Identifier) }
|
||||||
(Integer))
|
(Integer))
|
||||||
(Assignment
|
{+(Assignment
|
||||||
{ (
|
{+(Identifier)+}
|
||||||
|
{+(
|
||||||
|
{+(Integer)+}
|
||||||
|
{+(Integer)+})+})+}
|
||||||
|
{-(Assignment
|
||||||
|
{-(
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
{-(Identifier)-})
|
{-(Identifier)-})-}
|
||||||
->(Identifier) }
|
{-(
|
||||||
(
|
{-(Integer)-}
|
||||||
(Integer)
|
{-(Integer)-})-})-}
|
||||||
(Integer)))
|
|
||||||
{-(Assignment
|
{-(Assignment
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
{-(
|
{-(
|
||||||
|
@ -27,18 +27,16 @@
|
|||||||
{+(Equal
|
{+(Equal
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Identifier)+})+}
|
{+(Identifier)+})+}
|
||||||
{+(Not
|
(Not
|
||||||
{+(Member
|
(Member
|
||||||
{+(Identifier)+}
|
{ (Identifier)
|
||||||
{+(Identifier)+})+})+}
|
->(Identifier) }
|
||||||
|
{ (Identifier)
|
||||||
|
->(Identifier) }))
|
||||||
{+(Not
|
{+(Not
|
||||||
{+(Equal
|
{+(Equal
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Identifier)+})+})+}
|
{+(Identifier)+})+})+}
|
||||||
{-(Not
|
|
||||||
{-(Member
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-})-}
|
|
||||||
{-(Equal
|
{-(Equal
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
{-(Identifier)-})-}
|
{-(Identifier)-})-}
|
||||||
|
@ -1,34 +1,12 @@
|
|||||||
(Program
|
(Program
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{+(Import)+}
|
||||||
{+(Empty)+})+}
|
{+(Import)+}
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{+(Import)+}
|
||||||
{+(Empty)+})+}
|
{+(Import)+}
|
||||||
{ (Import
|
{-(Import)-}
|
||||||
{-(Identifier)-}
|
{-(Import)-}
|
||||||
{-(Empty)-})
|
{-(Import)-}
|
||||||
->(Import
|
{-(Import)-}
|
||||||
{+(Identifier)+}
|
{-(Import)-})
|
||||||
{+(Empty)+}) }
|
|
||||||
{+(Import
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(Import
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+}
|
|
||||||
{ (Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})
|
|
||||||
->(Import
|
|
||||||
{+(Empty)+}
|
|
||||||
{+(Empty)+}) }
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Empty)-}
|
|
||||||
{-(Empty)-})-})
|
|
||||||
|
@ -1,34 +1,12 @@
|
|||||||
(Program
|
(Program
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{+(Import)+}
|
||||||
{+(Empty)+})+}
|
{ (Import)
|
||||||
{+(Import
|
->(Import) }
|
||||||
{+(Identifier)+}
|
{ (Import)
|
||||||
{+(Empty)+})+}
|
->(Import) }
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{-(Import)-}
|
||||||
{+(Empty)+})+}
|
{-(Import)-}
|
||||||
{+(Import
|
{-(Import)-}
|
||||||
{+(Identifier)+}
|
{-(Import)-})
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(Import
|
|
||||||
{+(Empty)+}
|
|
||||||
{+(Empty)+})+}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Empty)-}
|
|
||||||
{-(Empty)-})-})
|
|
||||||
|
@ -1,16 +1,6 @@
|
|||||||
(Program
|
(Program
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(Import)
|
||||||
(Empty))
|
(Import)
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(Import))
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Empty)
|
|
||||||
(Empty)))
|
|
||||||
|
@ -1,19 +1,7 @@
|
|||||||
(Program
|
(Program
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(Import)
|
||||||
(Empty))
|
(Import)
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(Import)
|
||||||
(Empty))
|
(Import))
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Empty)
|
|
||||||
(Empty)))
|
|
||||||
|
@ -1,27 +1,14 @@
|
|||||||
(Program
|
(Program
|
||||||
(
|
(
|
||||||
{+(QualifiedImport
|
{+(QualifiedImport)+}
|
||||||
{+(Identifier)+}
|
(QualifiedImport)
|
||||||
{+(Identifier)+})+}
|
{-(QualifiedAliasedImport
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
|
||||||
{-(QualifiedImport
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-})
|
{-(Identifier)-})-})
|
||||||
{+(QualifiedImport
|
{+(QualifiedAliasedImport
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Identifier)+})+}
|
|
||||||
{+(QualifiedImport
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Identifier)+})+}
|
{+(Identifier)+})+}
|
||||||
|
{+(QualifiedImport)+}
|
||||||
{-(
|
{-(
|
||||||
{-(QualifiedImport
|
{-(QualifiedAliasedImport
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-}
|
{-(Identifier)-})-}
|
||||||
{-(QualifiedImport
|
{-(QualifiedImport)-})-}
|
||||||
{-(Identifier)-}
|
{-(QualifiedImport)-})
|
||||||
{-(Identifier)-})-})-}
|
|
||||||
{-(QualifiedImport
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-})
|
|
||||||
|
@ -1,26 +1,14 @@
|
|||||||
(Program
|
(Program
|
||||||
(
|
(
|
||||||
{-(QualifiedImport
|
{-(QualifiedImport)-}
|
||||||
{-(Identifier)-}
|
(QualifiedImport)
|
||||||
{-(Identifier)-})-}
|
{+(QualifiedAliasedImport
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
|
||||||
{+(QualifiedImport
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Identifier)+})+})
|
{+(Identifier)+})+})
|
||||||
{+(
|
{+(
|
||||||
{+(QualifiedImport
|
{+(QualifiedAliasedImport
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Identifier)+})+}
|
{+(Identifier)+})+}
|
||||||
{+(QualifiedImport
|
{+(QualifiedImport)+})+}
|
||||||
{+(Identifier)+}
|
{+(QualifiedImport)+}
|
||||||
{+(Identifier)+})+})+}
|
{-(QualifiedAliasedImport
|
||||||
(QualifiedImport
|
{-(Identifier)-})-}
|
||||||
{ (Identifier)
|
{-(QualifiedImport)-})
|
||||||
->(Identifier) }
|
|
||||||
{ (Identifier)
|
|
||||||
->(Identifier) })
|
|
||||||
{-(QualifiedImport
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-})
|
|
||||||
|
18
test/fixtures/python/import-statement.parseA.txt
vendored
18
test/fixtures/python/import-statement.parseA.txt
vendored
@ -1,18 +1,10 @@
|
|||||||
(Program
|
(Program
|
||||||
(
|
(
|
||||||
(QualifiedImport
|
(QualifiedImport)
|
||||||
(Identifier)
|
(QualifiedAliasedImport
|
||||||
(Identifier))
|
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier)))
|
(Identifier)))
|
||||||
(
|
(
|
||||||
(QualifiedImport
|
(QualifiedAliasedImport
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(QualifiedImport
|
(QualifiedImport))
|
||||||
(Identifier)
|
(QualifiedImport))
|
||||||
(Identifier)))
|
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier)))
|
|
||||||
|
15
test/fixtures/python/import-statement.parseB.txt
vendored
15
test/fixtures/python/import-statement.parseB.txt
vendored
@ -1,14 +1,7 @@
|
|||||||
(Program
|
(Program
|
||||||
(
|
(
|
||||||
(QualifiedImport
|
(QualifiedImport)
|
||||||
(Identifier)
|
(QualifiedImport))
|
||||||
(Identifier))
|
(QualifiedAliasedImport
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier)))
|
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(QualifiedImport
|
(QualifiedImport))
|
||||||
(Identifier)
|
|
||||||
(Identifier)))
|
|
||||||
|
@ -2,10 +2,9 @@
|
|||||||
{+(Negate
|
{+(Negate
|
||||||
{+(Identifier)+})+}
|
{+(Identifier)+})+}
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Complement
|
(Complement
|
||||||
{+(Identifier)+})+}
|
{ (Identifier)
|
||||||
{-(Complement
|
->(Identifier) })
|
||||||
{-(Identifier)-})-}
|
|
||||||
{-(Negate
|
{-(Negate
|
||||||
{-(Identifier)-})-}
|
{-(Identifier)-})-}
|
||||||
{-(Identifier)-})
|
{-(Identifier)-})
|
||||||
|
33
test/fixtures/ruby/hash.diffA-B.txt
vendored
33
test/fixtures/ruby/hash.diffA-B.txt
vendored
@ -1,20 +1,23 @@
|
|||||||
(Program
|
(Program
|
||||||
(Hash
|
(Hash
|
||||||
(KeyValue
|
{+(KeyValue
|
||||||
{ (Symbol)
|
{+(Identifier)+}
|
||||||
->(Identifier) }
|
{+(TextElement)+})+}
|
||||||
{ (TextElement)
|
{+(KeyValue
|
||||||
->(TextElement) })
|
{+(Identifier)+}
|
||||||
(KeyValue
|
{+(Integer)+})+}
|
||||||
{ (Symbol)
|
{+(KeyValue
|
||||||
->(Identifier) }
|
{+(Identifier)+}
|
||||||
{ (Integer)
|
{+(Boolean)+})+}
|
||||||
->(Integer) })
|
{-(KeyValue
|
||||||
(KeyValue
|
{-(Symbol)-}
|
||||||
{ (TextElement)
|
{-(TextElement)-})-}
|
||||||
->(Identifier) }
|
{-(KeyValue
|
||||||
{ (Boolean)
|
{-(Symbol)-}
|
||||||
->(Boolean) })
|
{-(Integer)-})-}
|
||||||
|
{-(KeyValue
|
||||||
|
{-(TextElement)-}
|
||||||
|
{-(Boolean)-})-}
|
||||||
{-(KeyValue
|
{-(KeyValue
|
||||||
{-(Symbol)-}
|
{-(Symbol)-}
|
||||||
{-(Integer)-})-})
|
{-(Integer)-})-})
|
||||||
|
26
test/fixtures/ruby/hash.diffB-A.txt
vendored
26
test/fixtures/ruby/hash.diffB-A.txt
vendored
@ -1,23 +1,25 @@
|
|||||||
(Program
|
(Program
|
||||||
(Hash
|
(Hash
|
||||||
(KeyValue
|
{+(KeyValue
|
||||||
{ (Identifier)
|
{+(Symbol)+}
|
||||||
->(Symbol) }
|
{+(TextElement)+})+}
|
||||||
{ (TextElement)
|
{+(KeyValue
|
||||||
->(TextElement) })
|
{+(Symbol)+}
|
||||||
(KeyValue
|
{+(Integer)+})+}
|
||||||
{ (Identifier)
|
|
||||||
->(Symbol) }
|
|
||||||
{ (Integer)
|
|
||||||
->(Integer) })
|
|
||||||
(KeyValue
|
(KeyValue
|
||||||
{ (Identifier)
|
{ (Identifier)
|
||||||
->(TextElement) }
|
->(TextElement) }
|
||||||
{ (Boolean)
|
{ (TextElement)
|
||||||
->(Boolean) })
|
->(Boolean) })
|
||||||
{+(KeyValue
|
{+(KeyValue
|
||||||
{+(Symbol)+}
|
{+(Symbol)+}
|
||||||
{+(Integer)+})+})
|
{+(Integer)+})+}
|
||||||
|
{-(KeyValue
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(Integer)-})-}
|
||||||
|
{-(KeyValue
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(Boolean)-})-})
|
||||||
{+(Hash)+}
|
{+(Hash)+}
|
||||||
{+(Hash
|
{+(Hash
|
||||||
{+(Context
|
{+(Context
|
||||||
|
8
test/fixtures/typescript/analysis/foo/b.ts
vendored
Normal file
8
test/fixtures/typescript/analysis/foo/b.ts
vendored
Normal file
@ -0,0 +1,8 @@
|
|||||||
|
// import { baz } from "../foo";
|
||||||
|
export { quz }
|
||||||
|
|
||||||
|
function quz() {
|
||||||
|
return "this is the quz function"
|
||||||
|
}
|
||||||
|
|
||||||
|
// baz()
|
2
test/fixtures/typescript/analysis/main.ts
vendored
2
test/fixtures/typescript/analysis/main.ts
vendored
@ -1,5 +1,7 @@
|
|||||||
// Use `tsc main.ts && node main.js` to test evaluation
|
// Use `tsc main.ts && node main.js` to test evaluation
|
||||||
|
|
||||||
import { baz as bar } from "./foo";
|
import { baz as bar } from "./foo";
|
||||||
|
import { quz } from "./foo/b"
|
||||||
|
|
||||||
|
quz()
|
||||||
bar()
|
bar()
|
||||||
|
12
test/fixtures/typescript/export.diffA-B.txt
vendored
12
test/fixtures/typescript/export.diffA-B.txt
vendored
@ -62,10 +62,8 @@
|
|||||||
{+(QualifiedExport)+}
|
{+(QualifiedExport)+}
|
||||||
{+(DefaultExport
|
{+(DefaultExport
|
||||||
{+(TextElement)+})+}
|
{+(TextElement)+})+}
|
||||||
{+(QualifiedExportFrom
|
{+(QualifiedExportFrom)+}
|
||||||
{+(Identifier)+})+}
|
{+(QualifiedExportFrom)+}
|
||||||
{+(QualifiedExportFrom
|
|
||||||
{+(Identifier)+})+}
|
|
||||||
{-(DefaultExport
|
{-(DefaultExport
|
||||||
{-(Function
|
{-(Function
|
||||||
{-(Empty)-}
|
{-(Empty)-}
|
||||||
@ -75,7 +73,5 @@
|
|||||||
{-(QualifiedExport)-}
|
{-(QualifiedExport)-}
|
||||||
{-(DefaultExport
|
{-(DefaultExport
|
||||||
{-(TextElement)-})-}
|
{-(TextElement)-})-}
|
||||||
{-(QualifiedExportFrom
|
{-(QualifiedExportFrom)-}
|
||||||
{-(Identifier)-})-}
|
{-(QualifiedExportFrom)-})
|
||||||
{-(QualifiedExportFrom
|
|
||||||
{-(Identifier)-})-})
|
|
||||||
|
12
test/fixtures/typescript/export.diffB-A.txt
vendored
12
test/fixtures/typescript/export.diffB-A.txt
vendored
@ -73,11 +73,7 @@
|
|||||||
(DefaultExport
|
(DefaultExport
|
||||||
{ (TextElement)
|
{ (TextElement)
|
||||||
->(TextElement) })
|
->(TextElement) })
|
||||||
{ (QualifiedExportFrom
|
{ (QualifiedExportFrom)
|
||||||
{-(Identifier)-})
|
->(QualifiedExportFrom) }
|
||||||
->(QualifiedExportFrom
|
{ (QualifiedExportFrom)
|
||||||
{+(Identifier)+}) }
|
->(QualifiedExportFrom) })
|
||||||
{ (QualifiedExportFrom
|
|
||||||
{-(Identifier)-})
|
|
||||||
->(QualifiedExportFrom
|
|
||||||
{+(Identifier)+}) })
|
|
||||||
|
6
test/fixtures/typescript/export.parseA.txt
vendored
6
test/fixtures/typescript/export.parseA.txt
vendored
@ -50,7 +50,5 @@
|
|||||||
(QualifiedExport)
|
(QualifiedExport)
|
||||||
(DefaultExport
|
(DefaultExport
|
||||||
(TextElement))
|
(TextElement))
|
||||||
(QualifiedExportFrom
|
(QualifiedExportFrom)
|
||||||
(Identifier))
|
(QualifiedExportFrom))
|
||||||
(QualifiedExportFrom
|
|
||||||
(Identifier)))
|
|
||||||
|
6
test/fixtures/typescript/export.parseB.txt
vendored
6
test/fixtures/typescript/export.parseB.txt
vendored
@ -50,7 +50,5 @@
|
|||||||
(QualifiedExport)
|
(QualifiedExport)
|
||||||
(DefaultExport
|
(DefaultExport
|
||||||
(TextElement))
|
(TextElement))
|
||||||
(QualifiedExportFrom
|
(QualifiedExportFrom)
|
||||||
(Identifier))
|
(QualifiedExportFrom))
|
||||||
(QualifiedExportFrom
|
|
||||||
(Identifier)))
|
|
||||||
|
83
test/fixtures/typescript/import.diffA-B.txt
vendored
83
test/fixtures/typescript/import.diffA-B.txt
vendored
@ -1,68 +1,31 @@
|
|||||||
(Program
|
(Program
|
||||||
{+(Import
|
{ (Import)
|
||||||
{+(Identifier)+}
|
->(Import) }
|
||||||
{+(Empty)+})+}
|
{ (QualifiedAliasedImport
|
||||||
{+(QualifiedImport
|
{-(Identifier)-})
|
||||||
{+(Identifier)+}
|
->(QualifiedAliasedImport
|
||||||
{+(Identifier)+})+}
|
{+(Identifier)+}) }
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{ (Import)
|
||||||
{+(Empty)+})+}
|
->(Import) }
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(Import
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(
|
{+(
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{+(Import)+})+}
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(Import
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+})+}
|
|
||||||
{+(
|
{+(
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{+(QualifiedAliasedImport
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(QualifiedImport
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Identifier)+})+})+}
|
{+(Identifier)+})+})+}
|
||||||
{+(SideEffectImport
|
{+(SideEffectImport)+}
|
||||||
{+(Identifier)+}
|
{-(Import)-}
|
||||||
{+(Empty)+})+}
|
{-(Import)-}
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(QualifiedImport
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(
|
{-(
|
||||||
{-(Import
|
{-(Import)-}
|
||||||
{-(Identifier)-}
|
{-(Import)-})-}
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-})-}
|
|
||||||
{-(
|
{-(
|
||||||
{-(Import
|
{-(Import)-}
|
||||||
{-(Identifier)-}
|
{-(QualifiedAliasedImport
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(QualifiedImport
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-})-}
|
{-(Identifier)-})-})-}
|
||||||
{-(SideEffectImport
|
{-(SideEffectImport)-}
|
||||||
{-(Identifier)-}
|
{-(QualifiedAliasedImport
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(QualifiedImport
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-})
|
{-(Identifier)-})-})
|
||||||
|
83
test/fixtures/typescript/import.diffB-A.txt
vendored
83
test/fixtures/typescript/import.diffB-A.txt
vendored
@ -1,68 +1,31 @@
|
|||||||
(Program
|
(Program
|
||||||
{+(Import
|
{ (Import)
|
||||||
{+(Identifier)+}
|
->(Import) }
|
||||||
{+(Empty)+})+}
|
{ (QualifiedAliasedImport
|
||||||
{+(QualifiedImport
|
{-(Identifier)-})
|
||||||
{+(Identifier)+}
|
->(QualifiedAliasedImport
|
||||||
{+(Identifier)+})+}
|
{+(Identifier)+}) }
|
||||||
{ (Import
|
{+(Import)+}
|
||||||
{-(Identifier)-}
|
{+(Import)+}
|
||||||
{-(Empty)-})
|
{ (Import)
|
||||||
->(Import
|
->(Import) }
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+}) }
|
|
||||||
{+(Import
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(Import
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(
|
{+(
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{+(Import)+})+}
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(Import
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Empty)+})+})+}
|
|
||||||
{+(
|
{+(
|
||||||
{+(Import
|
{+(Import)+}
|
||||||
{+(Identifier)+}
|
{+(QualifiedAliasedImport
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(QualifiedImport
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Identifier)+})+})+}
|
{+(Identifier)+})+})+}
|
||||||
{+(SideEffectImport
|
{+(SideEffectImport)+}
|
||||||
{+(Identifier)+}
|
{+(QualifiedAliasedImport
|
||||||
{+(Empty)+})+}
|
|
||||||
{+(QualifiedImport
|
|
||||||
{+(Identifier)+}
|
|
||||||
{+(Identifier)+})+}
|
{+(Identifier)+})+}
|
||||||
{-(QualifiedImport
|
{-(Import)-}
|
||||||
{-(Identifier)-}
|
{-(Import)-}
|
||||||
{-(Identifier)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(
|
{-(
|
||||||
{-(Import
|
{-(Import)-}
|
||||||
{-(Identifier)-}
|
{-(Import)-})-}
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(Import
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-})-}
|
|
||||||
{-(
|
{-(
|
||||||
{-(Import
|
{-(Import)-}
|
||||||
{-(Identifier)-}
|
{-(QualifiedAliasedImport
|
||||||
{-(Empty)-})-}
|
|
||||||
{-(QualifiedImport
|
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Identifier)-})-})-}
|
{-(Identifier)-})-})-}
|
||||||
{-(SideEffectImport
|
{-(SideEffectImport)-})
|
||||||
{-(Identifier)-}
|
|
||||||
{-(Empty)-})-})
|
|
||||||
|
41
test/fixtures/typescript/import.parseA.txt
vendored
41
test/fixtures/typescript/import.parseA.txt
vendored
@ -1,36 +1,17 @@
|
|||||||
(Program
|
(Program
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(QualifiedAliasedImport
|
||||||
(Empty))
|
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(Import)
|
||||||
(Empty))
|
(Import)
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty))
|
|
||||||
(
|
(
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(Import))
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty)))
|
|
||||||
(
|
(
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(QualifiedAliasedImport
|
||||||
(Empty))
|
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier)))
|
(Identifier)))
|
||||||
(SideEffectImport
|
(SideEffectImport)
|
||||||
(Identifier)
|
(QualifiedAliasedImport
|
||||||
(Empty))
|
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier)))
|
(Identifier)))
|
||||||
|
38
test/fixtures/typescript/import.parseB.txt
vendored
38
test/fixtures/typescript/import.parseB.txt
vendored
@ -1,33 +1,15 @@
|
|||||||
(Program
|
(Program
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(QualifiedAliasedImport
|
||||||
(Empty))
|
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(Import)
|
||||||
(Empty))
|
(Import)
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty))
|
|
||||||
(
|
(
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(Import))
|
||||||
(Empty))
|
|
||||||
(Import
|
|
||||||
(Identifier)
|
|
||||||
(Empty)))
|
|
||||||
(
|
(
|
||||||
(Import
|
(Import)
|
||||||
(Identifier)
|
(QualifiedAliasedImport
|
||||||
(Empty))
|
|
||||||
(QualifiedImport
|
|
||||||
(Identifier)
|
|
||||||
(Identifier)))
|
(Identifier)))
|
||||||
(SideEffectImport
|
(SideEffectImport))
|
||||||
(Identifier)
|
|
||||||
(Empty)))
|
|
||||||
|
2
vendor/haskell-tree-sitter
vendored
2
vendor/haskell-tree-sitter
vendored
@ -1 +1 @@
|
|||||||
Subproject commit 8c59597af18d6db53f4059367883eee391ecfb0b
|
Subproject commit 09109e6087f53fce23452d4718c2ce5ae3782bad
|
Loading…
Reference in New Issue
Block a user