mirror of
https://github.com/github/semantic.git
synced 2024-11-28 01:47:01 +03:00
Update assignment for PHP include and eval it
This commit is contained in:
parent
67a7a8c358
commit
9ca7b7f983
@ -13,6 +13,7 @@ import Language.PHP.Grammar as Grammar
|
||||
import Prologue
|
||||
import qualified Assigning.Assignment as Assignment
|
||||
import qualified Data.Abstract.FreeVariables as FV
|
||||
import qualified Data.Abstract.Path as Path
|
||||
import qualified Data.Syntax as Syntax
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
@ -715,8 +716,11 @@ arrayElementInitializer :: Assignment
|
||||
arrayElementInitializer = makeTerm <$> symbol ArrayElementInitializer <*> children (Literal.KeyValue <$> term expression <*> term expression) <|> (symbol ArrayElementInitializer *> children (term expression))
|
||||
|
||||
includeExpression :: Assignment
|
||||
includeExpression = makeTerm <$> symbol IncludeExpression <*> children (Syntax.Include <$> term expression)
|
||||
includeExpression = makeTerm <$> symbol IncludeExpression <*> children (Syntax.Include <$> term includePath)
|
||||
|
||||
-- TODO: Dropping the .php file extension here means we loose diff-ability.
|
||||
includePath :: Assignment
|
||||
includePath = makeTerm <$> symbol Grammar.String <*> (Syntax.Identifier . FV.pathToQualifiedName . Path.dropExtension <$> source)
|
||||
|
||||
includeOnceExpression :: Assignment
|
||||
includeOnceExpression = makeTerm <$> symbol IncludeOnceExpression <*> children (Syntax.IncludeOnce <$> term expression)
|
||||
|
@ -1,9 +1,11 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
module Language.PHP.Syntax where
|
||||
|
||||
import Data.Abstract.Environment
|
||||
import Data.Abstract.Evaluatable
|
||||
import Diffing.Algorithm
|
||||
import Prologue hiding (Text)
|
||||
import qualified Data.Map as Map
|
||||
|
||||
newtype Text a = Text ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
@ -45,7 +47,21 @@ newtype Include a = Include a
|
||||
instance Eq1 Include where liftEq = genericLiftEq
|
||||
instance Ord1 Include where liftCompare = genericLiftCompare
|
||||
instance Show1 Include where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Include
|
||||
|
||||
instance Evaluatable Include where
|
||||
eval (Include path) = do
|
||||
let name = freeVariable (subterm path)
|
||||
importedEnv <- isolate (require name)
|
||||
modifyGlobalEnv (flip (Map.foldrWithKey envInsert) (unEnvironment importedEnv))
|
||||
unit
|
||||
|
||||
data IncludePath a = IncludePath { includePath :: a, includePathExtension :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 IncludePath where liftEq = genericLiftEq
|
||||
instance Ord1 IncludePath where liftCompare = genericLiftCompare
|
||||
instance Show1 IncludePath where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable IncludePath
|
||||
|
||||
newtype IncludeOnce a = IncludeOnce a
|
||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
Loading…
Reference in New Issue
Block a user