mirror of
https://github.com/github/semantic.git
synced 2024-11-24 08:54:07 +03:00
Introduce place to put all these directives
This commit is contained in:
parent
15e1b6c505
commit
da89a11fae
@ -94,6 +94,7 @@ library
|
||||
, Data.Syntax
|
||||
, Data.Syntax.Comment
|
||||
, Data.Syntax.Declaration
|
||||
, Data.Syntax.Directive
|
||||
, Data.Syntax.Expression
|
||||
, Data.Syntax.Literal
|
||||
, Data.Syntax.Statement
|
||||
|
18
src/Data/Syntax/Directive.hs
Normal file
18
src/Data/Syntax/Directive.hs
Normal file
@ -0,0 +1,18 @@
|
||||
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances #-}
|
||||
module Data.Syntax.Directive where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Module (ModuleInfo(..))
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import Diffing.Algorithm
|
||||
import Prologue
|
||||
|
||||
data FileDirective a = FileDirective
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance Eq1 FileDirective where liftEq = genericLiftEq
|
||||
instance Ord1 FileDirective where liftCompare = genericLiftCompare
|
||||
instance Show1 FileDirective where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable FileDirective where
|
||||
eval FileDirective{} = currentModule >>= string . BC.pack . modulePath
|
@ -17,6 +17,7 @@ import qualified Assigning.Assignment as Assignment
|
||||
import qualified Data.Syntax as Syntax
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
import qualified Data.Syntax.Directive as Directive
|
||||
import qualified Data.Syntax.Expression as Expression
|
||||
import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
@ -28,6 +29,7 @@ type Syntax = '[
|
||||
Comment.Comment
|
||||
, Declaration.Function
|
||||
, Declaration.Method
|
||||
, Directive.FileDirective
|
||||
, Expression.Arithmetic
|
||||
, Expression.Bitwise
|
||||
, Expression.Boolean
|
||||
@ -74,7 +76,6 @@ type Syntax = '[
|
||||
, Syntax.Identifier
|
||||
, Syntax.Program
|
||||
, Ruby.Syntax.Class
|
||||
, Ruby.Syntax.FileDirective
|
||||
, Ruby.Syntax.Load
|
||||
, Ruby.Syntax.LowPrecedenceBoolean
|
||||
, Ruby.Syntax.Module
|
||||
@ -179,7 +180,7 @@ identifier =
|
||||
vcallOrLocal = do
|
||||
(loc, ident, locals) <- identWithLocals
|
||||
case ident of
|
||||
"__FILE__" -> pure $ makeTerm loc (Ruby.Syntax.FileDirective ident)
|
||||
"__FILE__" -> pure $ makeTerm loc Directive.FileDirective
|
||||
_ -> do
|
||||
let identTerm = makeTerm loc (Syntax.Identifier (name ident))
|
||||
if ident `elem` locals
|
||||
|
@ -106,16 +106,6 @@ doLoad path shouldWrap = do
|
||||
|
||||
-- TODO: autoload
|
||||
|
||||
newtype FileDirective a = FileDirective ByteString
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance Eq1 FileDirective where liftEq = genericLiftEq
|
||||
instance Ord1 FileDirective where liftCompare = genericLiftCompare
|
||||
instance Show1 FileDirective where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable FileDirective where
|
||||
eval (FileDirective _) = currentModule >>= string . BC.pack . modulePath
|
||||
|
||||
|
||||
data Class a = Class { classIdentifier :: !a, classSuperClasses :: ![a], classBody :: !a }
|
||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
Loading…
Reference in New Issue
Block a user