1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 08:54:07 +03:00

Merge branch 'master' into java-assignment-part-2

This commit is contained in:
Rob Rix 2018-06-05 09:26:31 -04:00 committed by GitHub
commit 1d8fcf3ecf
79 changed files with 551 additions and 633 deletions

View File

@ -21,23 +21,23 @@ import Data.Abstract.Name
import Data.Abstract.Package (PackageInfo(..))
import Data.Aeson hiding (Result)
import Data.ByteString.Builder
import qualified Data.ByteString.Char8 as BC
import Data.Graph
import Data.Sum
import qualified Data.Syntax as Syntax
import Data.Term
import Data.Text.Encoding as T
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Prologue hiding (packageName, project)
-- | A vertex of some specific type.
data Vertex
= Package { vertexName :: ByteString }
| Module { vertexName :: ByteString }
| Variable { vertexName :: ByteString }
= Package { vertexName :: Text }
| Module { vertexName :: Text }
| Variable { vertexName :: Text }
deriving (Eq, Ord, Show)
style :: Style Vertex Builder
style = (defaultStyle (byteString . vertexName))
style = (defaultStyle (T.encodeUtf8Builder . vertexName))
{ vertexAttributes = vertexAttributes
, edgeAttributes = edgeAttributes
}
@ -93,7 +93,7 @@ packageVertex :: PackageInfo -> Vertex
packageVertex = Package . unName . packageName
moduleVertex :: ModuleInfo -> Vertex
moduleVertex = Module . BC.pack . modulePath
moduleVertex = Module . T.pack . modulePath
-- | Add an edge from the current package to the passed vertex.
packageInclusion :: ( Effectful m
@ -137,7 +137,7 @@ instance ToJSON Vertex where
toJSON v = object [ "name" .= vertexToText v, "type" .= vertexToType v ]
vertexToText :: Vertex -> Text
vertexToText = decodeUtf8 . vertexName
vertexToText = vertexName
vertexToType :: Vertex -> Text
vertexToType Package{} = "package"

View File

@ -19,7 +19,6 @@ import qualified Data.Syntax.Declaration as Declaration
import qualified Data.Syntax.Expression as Expression
import Data.Term
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Language.Markdown.Syntax as Markdown
import qualified Language.Ruby.Syntax as Ruby.Syntax
import Prologue hiding (project)
@ -130,7 +129,7 @@ getSource blobSource = toText . flip Source.slice blobSource . getField
instance (Syntax.Identifier :< fs, Expression.MemberAccess :< fs) => CustomHasDeclaration (Sum fs) Expression.Call where
customToDeclaration Blob{..} _ (Expression.Call _ (Term (In fromAnn fromF), _) _ _)
| Just (Expression.MemberAccess (Term (In leftAnn leftF)) (Term (In idenAnn _))) <- project fromF = Just $ CallReference (getSource idenAnn) mempty blobLanguage (memberAccess leftAnn leftF)
| Just (Syntax.Identifier name) <- project fromF = Just $ CallReference (T.decodeUtf8 (unName name)) mempty blobLanguage []
| Just (Syntax.Identifier name) <- project fromF = Just $ CallReference (unName name) mempty blobLanguage []
| otherwise = Just $ CallReference (getSource fromAnn) mempty blobLanguage []
where
memberAccess modAnn termFOut

View File

@ -69,6 +69,7 @@ module Assigning.Assignment
, location
, currentNode
, symbol
, rawSource
, source
, children
, advance
@ -104,6 +105,8 @@ import Data.Record
import qualified Data.Source as Source (Source, slice, sourceBytes)
import Data.Span
import Data.Term
import Data.Text (Text)
import Data.Text.Encoding (decodeUtf8')
import Text.Parser.Combinators as Parsers hiding (choice)
import TreeSitter.Language
@ -123,8 +126,8 @@ data AssignmentF ast grammar a where
Alt :: [a] -> AssignmentF ast grammar a
Label :: Assignment ast grammar a -> String -> AssignmentF ast grammar a
Fail :: String -> AssignmentF ast grammar a
GetRubyLocals :: AssignmentF ast grammar [ByteString]
PutRubyLocals :: [ByteString] -> AssignmentF ast grammar ()
GetRubyLocals :: AssignmentF ast grammar [Text]
PutRubyLocals :: [Text] -> AssignmentF ast grammar ()
data Tracing f a where
Tracing :: { tracingCallSite :: Maybe (String, SrcLoc), runTracing :: f a } -> Tracing f a
@ -144,10 +147,10 @@ tracing f = case getCallStack callStack of
location :: HasCallStack => Assignment ast grammar (Record Location)
location = tracing Location `Then` return
getRubyLocals :: HasCallStack => Assignment ast grammar [ByteString]
getRubyLocals :: HasCallStack => Assignment ast grammar [Text]
getRubyLocals = tracing GetRubyLocals `Then` return
putRubyLocals :: (HasCallStack, Enum grammar, Eq1 ast, Ix grammar) => [ByteString] -> Assignment ast grammar ()
putRubyLocals :: (HasCallStack, Enum grammar, Eq1 ast, Ix grammar) => [Text] -> Assignment ast grammar ()
putRubyLocals l = (tracing (PutRubyLocals l) `Then` return)
<|> (tracing End `Then` return)
@ -160,8 +163,13 @@ symbol :: (Enum grammar, Ix grammar, HasCallStack) => grammar -> Assignment ast
symbol s = tracing (Choose (Table.singleton s location) Nothing Nothing) `Then` return
-- | A rule to produce a nodes source as a ByteString.
source :: HasCallStack => Assignment ast grammar ByteString
source = tracing Source `Then` return
-- You probably want to use 'source', unless you're throwing away the result.
rawSource :: HasCallStack => Assignment ast grammar ByteString
rawSource = tracing Source `Then` return
-- | A rule to produce a node's source as Text. Fails if the node's source can't be parsed as UTF-8.
source :: HasCallStack => Assignment ast grammar Text
source = fmap decodeUtf8' rawSource >>= either (\e -> fail ("UTF-8 decoding failed: " <> show e)) pure
-- | Match a node by applying an assignment to its children.
children :: HasCallStack => Assignment ast grammar a -> Assignment ast grammar a
@ -299,7 +307,7 @@ data State ast grammar = State
, statePos :: {-# UNPACK #-} !Pos -- ^ The (1-indexed) line/column position in the Source thus far reached.
, stateCallSites :: ![(String, SrcLoc)] -- ^ The symbols & source locations of the calls thus far.
, stateNodes :: ![AST ast grammar] -- ^ The remaining nodes to assign. Note that 'children' rules recur into subterms, and thus this does not necessarily reflect all of the terms remaining to be assigned in the overall algorithm, only those “in scope.”
, stateRubyLocals :: ![ByteString] -- Special state necessary for the Ruby assignment. When we refactor Assignment to use effects we should pull this out into Language.Ruby.Assignment
, stateRubyLocals :: ![Text] -- Special state necessary for the Ruby assignment. When we refactor Assignment to use effects we should pull this out into Language.Ruby.Assignment
}
deriving instance (Eq grammar, Eq1 ast) => Eq (State ast grammar)

View File

@ -6,8 +6,8 @@ import Control.Abstract.Evaluator
import Control.Abstract.Heap
import Control.Abstract.Value
import Data.Abstract.Name
import Data.ByteString.Char8 (pack, unpack)
import Data.Semilattice.Lower
import Data.Text (pack, unpack)
import Prologue
builtin :: ( HasCallStack
@ -20,7 +20,7 @@ builtin :: ( HasCallStack
-> Evaluator address value effects value
-> Evaluator address value effects ()
builtin s def = withCurrentCallStack callStack $ do
let name' = name (pack ("__semantic_" <> s))
let name' = name ("__semantic_" <> pack s)
addr <- alloc name'
bind name' addr
def >>= assign addr

View File

@ -55,11 +55,11 @@ class Show value => AbstractIntro value where
boolean :: Bool -> value
-- | Construct an abstract string value.
string :: ByteString -> value
string :: Text -> value
-- | Construct a self-evaluating symbol value.
-- TODO: Should these be interned in some table to provide stronger uniqueness guarantees?
symbol :: ByteString -> value
symbol :: Text -> value
-- | Construct an abstract integral value.
integer :: Integer -> value
@ -117,8 +117,8 @@ class (AbstractFunction address value effects, AbstractIntro value) => AbstractV
-- | Extract the contents of a key-value pair as a tuple.
asPair :: value -> Evaluator address value effects (value, value)
-- | Extract a 'ByteString' from a given value.
asString :: value -> Evaluator address value effects ByteString
-- | Extract a 'Text' from a given value.
asString :: value -> Evaluator address value effects Text
-- | Eliminate boolean values. TODO: s/boolean/truthy
ifthenelse :: value -> Evaluator address value effects a -> Evaluator address value effects a -> Evaluator address value effects a

View File

@ -5,27 +5,26 @@ import Data.Range
import Data.Record
import Data.Span
import Data.Term
import Data.Aeson
import Data.ByteString.Char8 (pack)
import Data.Text (pack)
import Data.JSON.Fields
import Data.Text.Encoding (decodeUtf8)
-- | An AST node labelled with symbols and source location.
type AST syntax grammar = Term syntax (Node grammar)
data Node grammar = Node
{ nodeSymbol :: !grammar
{ nodeSymbol :: !grammar
, nodeByteRange :: {-# UNPACK #-} !Range
, nodeSpan :: {-# UNPACK #-} !Span
, nodeSpan :: {-# UNPACK #-} !Span
}
deriving (Eq, Show)
instance Show grammar => ToJSONFields (Node grammar) where
toJSONFields Node{..} =
[ "symbol" .= decodeUtf8 (pack (show nodeSymbol))
, "span" .= nodeSpan ]
[ "symbol" .= pack (show nodeSymbol)
, "span" .= nodeSpan
]
-- | A location specified as possibly-empty intervals of bytes and line/column positions.
type Location = '[Range, Span]

View File

@ -142,9 +142,9 @@ traceResolve name path = trace ("resolved " <> show name <> " -> " <> show path)
data EvalError return where
FreeVariablesError :: [Name] -> EvalError Name
-- Indicates that our evaluator wasn't able to make sense of these literals.
IntegerFormatError :: ByteString -> EvalError Integer
FloatFormatError :: ByteString -> EvalError Scientific
RationalFormatError :: ByteString -> EvalError Rational
IntegerFormatError :: Text -> EvalError Integer
FloatFormatError :: Text -> EvalError Scientific
RationalFormatError :: Text -> EvalError Rational
DefaultExportError :: EvalError ()
ExportError :: ModulePath -> Name -> EvalError ()

View File

@ -7,36 +7,35 @@ module Data.Abstract.Name
) where
import Data.Aeson
import qualified Data.ByteString.Char8 as BC
import qualified Data.Char as Char
import Data.String
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Data.String
import Prologue
-- | The type of variable names.
data Name
= Name ByteString
= Name Text
| I Int
deriving (Eq, Ord)
-- | Construct a 'Name' from a 'ByteString'.
name :: ByteString -> Name
-- | Construct a 'Name' from a 'Text'.
name :: Text -> Name
name = Name
-- | Construct a 'Name' from an 'Int'. This is suitable for automatic generation, e.g. using a Fresh effect, but should not be used for human-generated names.
nameI :: Int -> Name
nameI = I
-- | Extract a human-readable 'ByteString' from a 'Name'.
unName :: Name -> ByteString
-- | Extract a human-readable 'Text' from a 'Name'.
unName :: Name -> Text
unName (Name name) = name
unName (I i) = Text.encodeUtf8 . Text.pack $ '_' : (alphabet !! a) : replicate n 'ʹ'
unName (I i) = Text.pack $ '_' : (alphabet !! a) : replicate n 'ʹ'
where alphabet = ['a'..'z']
(n, a) = i `divMod` length alphabet
instance IsString Name where
fromString = Name . BC.pack
fromString = Name . Text.pack
-- $
-- >>> I 0
@ -44,7 +43,7 @@ instance IsString Name where
-- >>> I 26
-- "_aʹ"
instance Show Name where
showsPrec _ = prettyShowString . Text.unpack . Text.decodeUtf8 . unName
showsPrec _ = prettyShowString . Text.unpack . unName
where prettyShowString str = showChar '"' . foldr ((.) . prettyChar) id str . showChar '"'
prettyChar c
| c `elem` ['\\', '\"'] = Char.showLitChar c
@ -56,5 +55,5 @@ instance Hashable Name where
hashWithSalt salt (I i) = salt `hashWithSalt` (1 :: Int) `hashWithSalt` i
instance ToJSON Name where
toJSON = toJSON . Text.decodeUtf8 . unName
toEncoding = toEncoding . Text.decodeUtf8 . unName
toJSON = toJSON . unName
toEncoding = toEncoding . unName

View File

@ -1,8 +1,7 @@
module Data.Abstract.Path where
import Prologue
import qualified Data.ByteString.Char8 as BC
import qualified Data.ByteString as B
import qualified Data.Text as T
import System.FilePath.Posix
-- | Join two paths a and b. Handles walking up relative directories in b. e.g.
@ -19,8 +18,8 @@ joinPaths a b = let bs = splitPath (normalise b)
walkup 0 str = str
walkup n str = walkup (pred n) (takeDirectory str)
stripQuotes :: ByteString -> ByteString
stripQuotes = B.filter (`B.notElem` "\'\"")
stripQuotes :: Text -> Text
stripQuotes = T.dropAround (`elem` ("\'\"" :: String))
dropRelativePrefix :: ByteString -> ByteString
dropRelativePrefix = BC.dropWhile (== '/') . BC.dropWhile (== '.')
dropRelativePrefix :: Text -> Text
dropRelativePrefix = T.dropWhile (== '/') . T.dropWhile (== '.')

View File

@ -20,8 +20,8 @@ data Value address body
| Integer (Number.Number Integer)
| Rational (Number.Number Rational)
| Float (Number.Number Scientific)
| String ByteString
| Symbol ByteString
| String Text
| Symbol Text
| Tuple [Value address body]
| Array [Value address body]
| Class Name (Environment address)
@ -225,7 +225,7 @@ instance ( Coercible body (Eff effects)
-- | The type of exceptions that can be thrown when constructing values in 'Value's 'MonadValue' instance.
data ValueError address body resume where
StringError :: Value address body -> ValueError address body ByteString
StringError :: Value address body -> ValueError address body Text
BoolError :: Value address body -> ValueError address body Bool
IndexError :: Value address body -> Value address body -> ValueError address body (Value address body)
NamespaceError :: Prelude.String -> ValueError address body (Environment address)

View File

@ -42,7 +42,7 @@ formatError includeSource colourize Blob{..} Error{..}
. showString (replicate (succ (posColumn (spanStart errorSpan) + lineNumberDigits)) ' ') . withSGRCode colourize [SetColor Foreground Vivid Green] (showChar '^' . showChar '\n')
else id)
. showCallStack colourize callStack . showChar '\n'
where context = maybe "\n" (sourceBytes . sconcat) (nonEmpty [ fromBytes (pack (showLineNumber i)) <> fromBytes ": " <> l | (i, l) <- zip [1..] (sourceLines blobSource), inRange (posLine (spanStart errorSpan) - 2, posLine (spanStart errorSpan)) i ])
where context = maybe "\n" (sourceBytes . sconcat) (nonEmpty [ fromUTF8 (pack (showLineNumber i)) <> fromUTF8 ": " <> l | (i, l) <- zip [1..] (sourceLines blobSource), inRange (posLine (spanStart errorSpan) - 2, posLine (spanStart errorSpan)) i ])
showLineNumber n = let s = show n in replicate (lineNumberDigits - length s) ' ' <> s
lineNumberDigits = succ (floor (logBase 10 (fromIntegral (posLine (spanStart errorSpan)) :: Double)))

View File

@ -12,7 +12,6 @@ import Data.Aeson
import qualified Data.Map as Map
import Data.Sum (Apply (..), Sum)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Prologue
class ToJSONFields a where
@ -130,13 +129,7 @@ instance ToJSON1 f => GSelectorJSONValue1 (Rec1 f) where
instance ToJSON k => GSelectorJSONValue1 (K1 r k) where
gselectorJSONValue1 k x = (fromMaybe "value" k, [SomeJSON (unK1 x)])
-- TODO: Fix this orphan instance.
instance ToJSON ByteString where
toJSON = toJSON . Text.decodeUtf8
toEncoding = toEncoding . Text.decodeUtf8
-- | An existential type wrapping an JSON-compatible data type.
data SomeJSON where
SomeJSON :: ToJSON a => a -> SomeJSON

View File

@ -1,28 +1,28 @@
module Data.Project where
import Data.ByteString.Char8 as BC (pack)
import Data.Language
import Prologue
import System.FilePath.Posix
import Data.Text as T (pack)
import Data.Language
import Prologue
import System.FilePath.Posix
data Project = Project
{ projectRootDir :: FilePath
, projectFiles :: [File]
, projectLanguage :: Language
{ projectRootDir :: FilePath
, projectFiles :: [File]
, projectLanguage :: Language
, projectEntryPoints :: [File]
, projectExcludeDirs :: [FilePath]
}
deriving (Eq, Ord, Show)
projectName :: Project -> ByteString
projectName = BC.pack . dropExtensions . takeFileName . projectRootDir
projectName :: Project -> Text
projectName = T.pack . dropExtensions . takeFileName . projectRootDir
projectExtensions :: Project -> [String]
projectExtensions = extensionsForLanguage . projectLanguage
data File = File
{ filePath :: FilePath
{ filePath :: FilePath
, fileLanguage :: Maybe Language
}
deriving (Eq, Ord, Show)

View File

@ -7,9 +7,9 @@ module Data.Scientific.Exts
import Control.Applicative
import Control.Exception as Exc (evaluate, try)
import Control.Monad hiding (fail)
import Data.Attoparsec.ByteString.Char8
import Data.ByteString.Char8 hiding (readInt, takeWhile)
import Data.Char (isOctDigit)
import Data.Attoparsec.Text
import Data.Text hiding (takeWhile)
import Data.Char (isDigit, isOctDigit)
import Data.Scientific
import Numeric
import Prelude hiding (fail, filter, null, takeWhile)
@ -17,7 +17,7 @@ import Prologue hiding (null)
import Text.Read (readMaybe)
import System.IO.Unsafe
parseScientific :: ByteString -> Either String Scientific
parseScientific :: Text -> Either String Scientific
parseScientific = parseOnly parser
-- | This is a very flexible and forgiving parser for Scientific values.

View File

@ -2,7 +2,7 @@
module Data.Source
( Source
, sourceBytes
, fromBytes
, fromUTF8
-- Measurement
, sourceLength
, nullSource
@ -38,12 +38,14 @@ import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Proto3.Suite
-- | The contents of a source file, represented as a 'ByteString'.
-- | The contents of a source file. This is represented as a UTF-8
-- 'ByteString' under the hood. Construct these with 'fromUTF8'; obviously,
-- passing 'fromUTF8' non-UTF8 bytes will cause crashes.
newtype Source = Source { sourceBytes :: B.ByteString }
deriving (Eq, IsString, Show, Generic, MessageField)
fromBytes :: B.ByteString -> Source
fromBytes = Source
fromUTF8 :: B.ByteString -> Source
fromUTF8 = Source
-- Measurement

View File

@ -149,7 +149,7 @@ instance Declarations1 Identifier where
liftDeclaredName _ (Identifier x) = pure x
-- | An accessibility modifier, e.g. private, public, protected, etc.
newtype AccessibilityModifier a = AccessibilityModifier ByteString
newtype AccessibilityModifier a = AccessibilityModifier Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 AccessibilityModifier where liftEq = genericLiftEq

View File

@ -7,7 +7,7 @@ import Data.JSON.Fields
import Diffing.Algorithm
-- | An unnested comment (line or block).
newtype Comment a = Comment { commentContent :: ByteString }
newtype Comment a = Comment { commentContent :: Text }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 Comment where liftEq = genericLiftEq
@ -21,3 +21,14 @@ instance Evaluatable Comment where
-- TODO: documentation comment types
-- TODO: literate programming comment types? alternatively, consider those as markup
-- TODO: Differentiate between line/block comments?
-- | HashBang line (e.g. `#!/usr/bin/env node`)
newtype HashBang a = HashBang Text
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 HashBang where liftEq = genericLiftEq
instance Ord1 HashBang where liftCompare = genericLiftCompare
instance Show1 HashBang where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for HashBang
instance Evaluatable HashBang

View File

@ -3,7 +3,7 @@ module Data.Syntax.Directive where
import Data.Abstract.Evaluatable
import Data.Abstract.Module (ModuleInfo(..))
import qualified Data.ByteString.Char8 as BC
import qualified Data.Text as T
import Data.JSON.Fields
import Data.Span
import Diffing.Algorithm
@ -18,7 +18,7 @@ instance Ord1 File where liftCompare = genericLiftCompare
instance Show1 File where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable File where
eval File = Rval . string . BC.pack . modulePath <$> currentModule
eval File = Rval . string . T.pack . modulePath <$> currentModule
-- A line directive like the Ruby constant `__LINE__`.

View File

@ -2,10 +2,9 @@
module Data.Syntax.Literal where
import Data.Abstract.Evaluatable
import Data.ByteString.Char8 (readInteger, unpack)
import qualified Data.ByteString.Char8 as B
import Data.JSON.Fields
import Data.Scientific.Exts
import qualified Data.Text as T
import Diffing.Algorithm
import Prelude hiding (Float, null)
import Prologue hiding (Set, hash, null)
@ -33,7 +32,7 @@ instance Evaluatable Boolean where
-- Numeric
-- | A literal integer of unspecified width. No particular base is implied.
newtype Integer a = Integer { integerContent :: ByteString }
newtype Integer a = Integer { integerContent :: Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 Data.Syntax.Literal.Integer where liftEq = genericLiftEq
@ -41,15 +40,13 @@ instance Ord1 Data.Syntax.Literal.Integer where liftCompare = genericLiftCompare
instance Show1 Data.Syntax.Literal.Integer where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Data.Syntax.Literal.Integer where
-- TODO: This instance probably shouldn't have readInteger?
-- TODO: We should use something more robust than shelling out to readMaybe.
eval (Data.Syntax.Literal.Integer x) =
Rval . integer <$> maybeM (throwEvalError (IntegerFormatError x)) (fst <$> readInteger x)
-- TODO: Should IntegerLiteral hold an Integer instead of a ByteString?
-- TODO: Consider a Numeric datatype with FloatingPoint/Integral/etc constructors.
Rval . integer <$> maybeM (throwEvalError (IntegerFormatError x)) (readMaybe (T.unpack x))
-- | A literal float of unspecified width.
newtype Float a = Float { floatContent :: ByteString }
newtype Float a = Float { floatContent :: Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 Data.Syntax.Literal.Float where liftEq = genericLiftEq
@ -61,7 +58,7 @@ instance Evaluatable Data.Syntax.Literal.Float where
Rval . float <$> either (const (throwEvalError (FloatFormatError s))) pure (parseScientific s)
-- Rational literals e.g. `2/3r`
newtype Rational a = Rational ByteString
newtype Rational a = Rational Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 Data.Syntax.Literal.Rational where liftEq = genericLiftEq
@ -71,12 +68,12 @@ instance Show1 Data.Syntax.Literal.Rational where liftShowsPrec = genericLiftSho
instance Evaluatable Data.Syntax.Literal.Rational where
eval (Rational r) =
let
trimmed = B.takeWhile (/= 'r') r
parsed = readMaybe @Prelude.Integer (unpack trimmed)
trimmed = T.takeWhile (/= 'r') r
parsed = readMaybe @Prelude.Integer (T.unpack trimmed)
in Rval . rational <$> maybe (throwEvalError (RationalFormatError r)) (pure . toRational) parsed
-- Complex literals e.g. `3 + 2i`
newtype Complex a = Complex ByteString
newtype Complex a = Complex Text
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 Data.Syntax.Literal.Complex where liftEq = genericLiftEq
@ -100,7 +97,7 @@ instance Show1 Data.Syntax.Literal.String where liftShowsPrec = genericLiftShows
-- TODO: Implement Eval instance for String
instance Evaluatable Data.Syntax.Literal.String
newtype Character a = Character { characterContent :: ByteString }
newtype Character a = Character { characterContent :: Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 Data.Syntax.Literal.Character where liftEq = genericLiftEq
@ -121,7 +118,7 @@ instance Show1 InterpolationElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable InterpolationElement
-- | A sequence of textual contents within a string literal.
newtype TextElement a = TextElement { textElementContent :: ByteString }
newtype TextElement a = TextElement { textElementContent :: Text }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 TextElement where liftEq = genericLiftEq
@ -140,7 +137,7 @@ instance Show1 Null where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Null where eval _ = pure (Rval null)
newtype Symbol a = Symbol { symbolContent :: ByteString }
newtype Symbol a = Symbol { symbolContent :: Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 Symbol where liftEq = genericLiftEq
@ -150,7 +147,7 @@ instance Show1 Symbol where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Symbol where
eval (Symbol s) = pure (Rval (symbol s))
newtype Regex a = Regex { regexContent :: ByteString }
newtype Regex a = Regex { regexContent :: Text }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 Regex where liftEq = genericLiftEq
@ -162,7 +159,6 @@ instance Show1 Regex where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for Regex
instance Evaluatable Regex
-- Collections
newtype Array a = Array { arrayElements :: [a] }

View File

@ -357,14 +357,3 @@ instance Show1 ScopeExit where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for ScopeExit
instance Evaluatable ScopeExit
-- | HashBang line (e.g. `#!/usr/bin/env node`)
newtype HashBang a = HashBang ByteString
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 HashBang where liftEq = genericLiftEq
instance Ord1 HashBang where liftCompare = genericLiftCompare
instance Show1 HashBang where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for HashBang
instance Evaluatable HashBang

View File

@ -355,7 +355,7 @@ defaultCase :: Assignment
defaultCase = makeTerm <$> symbol DefaultCase <*> children (Go.Syntax.DefaultPattern <$> (expressions <|> emptyTerm))
defaultExpressionCase :: Assignment
defaultExpressionCase = makeTerm <$> symbol DefaultCase <*> (Go.Syntax.DefaultPattern <$ source <*> (expressions <|> emptyTerm))
defaultExpressionCase = makeTerm <$> symbol DefaultCase <*> (Go.Syntax.DefaultPattern <$ rawSource <*> (expressions <|> emptyTerm))
callExpression :: Assignment
callExpression = makeTerm <$> symbol CallExpression <*> children (Expression.Call <$> pure [] <*> expression <*> manyTerm expression <*> emptyTerm)

View File

@ -6,9 +6,8 @@ import Data.Abstract.Module
import qualified Data.Abstract.Package as Package
import Data.Abstract.Path
import Data.Aeson
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import Data.JSON.Fields
import qualified Data.Text as T
import Diffing.Algorithm
import Prologue
import System.FilePath.Posix
@ -19,15 +18,14 @@ data Relative = Relative | NonRelative
data ImportPath = ImportPath { unPath :: FilePath, pathIsRelative :: Relative }
deriving (Eq, Generic, Hashable, Ord, Show, ToJSON)
importPath :: ByteString -> ImportPath
importPath str = let path = stripQuotes str in ImportPath (BC.unpack path) (pathType path)
importPath :: Text -> ImportPath
importPath str = let path = stripQuotes str in ImportPath (T.unpack path) (pathType path)
where
stripQuotes = B.filter (`B.notElem` "\'\"")
pathType xs | not (B.null xs), BC.head xs == '.' = Relative
pathType xs | not (T.null xs), T.head xs == '.' = Relative -- head call here is safe
| otherwise = NonRelative
defaultAlias :: ImportPath -> Name
defaultAlias = name . BC.pack . takeFileName . unPath
defaultAlias = name . T.pack . takeFileName . unPath
resolveGoImport :: ( Member (Modules address value) effects
, Member (Reader ModuleInfo) effects
@ -44,14 +42,14 @@ resolveGoImport (ImportPath path Relative) = do
[] -> throwResumable $ GoImportError path
_ -> pure paths
resolveGoImport (ImportPath path NonRelative) = do
package <- BC.unpack . unName . Package.packageName <$> currentPackage
package <- T.unpack . unName . Package.packageName <$> currentPackage
trace ("attempting to resolve " <> show path <> " for package " <> package)
case splitDirectories path of
-- Import an absolute path that's defined in this package being analyzed.
-- First two are source, next is package name, remaining are path to package
-- (e.g. github.com/golang/<package>/path...).
(_ : _ : p : xs) | p == package -> listModulesInDir (joinPath xs)
_ -> throwResumable $ GoImportError path
_ -> throwResumable $ GoImportError path
-- | Import declarations (symbols are added directly to the calling environment).
--
@ -166,7 +164,7 @@ instance Show1 Label where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Label
-- | A rune literal in Go (e.g. `'⌘'`).
newtype Rune a = Rune { _runeLiteral :: ByteString }
newtype Rune a = Rune { _runeLiteral :: Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
-- TODO: Implement Eval instance for Rune

View File

@ -182,7 +182,7 @@ strictType = makeTerm' <$> symbol StrictType <*> children ((inject <$> (Syntax.S
<|> (inject <$> (Syntax.StrictTypeVariable <$> typeVariableIdentifier)))
tuplingConstructor :: Assignment
tuplingConstructor = makeTerm <$> symbol TuplingConstructor <*> (tupleWithArity <$> source)
tuplingConstructor = makeTerm <$> symbol TuplingConstructor <*> (tupleWithArity <$> rawSource)
-- a tuple (,) has arity two, but only one comma, so apply the successor to the count of commas for the correct arity.
where tupleWithArity = Syntax.TupleConstructor . succ . count ','

View File

@ -111,7 +111,7 @@ instance ToJSONFields1 Field
instance Evaluatable Field
newtype Pragma a = Pragma ByteString deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
newtype Pragma a = Pragma Text deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
instance Eq1 Pragma where liftEq = genericLiftEq
instance Ord1 Pragma where liftCompare = genericLiftCompare

View File

@ -55,8 +55,8 @@ string :: Assignment
string = makeTerm <$> symbol String <*> (Literal.TextElement <$> source)
boolean :: Assignment
boolean = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source)
<|> makeTerm <$> symbol Grammar.False <*> (Literal.false <$ source)
boolean = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ rawSource)
<|> makeTerm <$> symbol Grammar.False <*> (Literal.false <$ rawSource)
none :: Assignment
none = makeTerm <$> symbol Null <*> (Literal.Null <$ source)
none = makeTerm <$> symbol Null <*> (Literal.Null <$ rawSource)

View File

@ -10,11 +10,9 @@ import Assigning.Assignment hiding (Assignment, Error)
import Data.Record
import Data.Syntax (makeTerm)
import Data.Term as Term (Term(..), TermF(..), termFAnnotation, termFOut, termIn)
import Data.Text.Encoding (encodeUtf8)
import Parsing.CMark as Grammar (Grammar(..))
import qualified Assigning.Assignment as Assignment
import qualified CMarkGFM
import qualified Data.ByteString as B
import Data.Sum
import qualified Data.Syntax as Syntax
import qualified Data.Text as Text
@ -148,14 +146,14 @@ htmlInline = makeTerm <$> symbol HTMLInline <*> (Markup.HTMLBlock <$> source)
link :: Assignment
link = makeTerm <$> symbol Link <*> (makeLink . termFAnnotation . termFOut <$> currentNode) <* advance
where
makeLink (CMarkGFM.LINK url title) = Markup.Link (encodeUtf8 url) (nullText title)
makeLink _ = Markup.Link B.empty Nothing
makeLink (CMarkGFM.LINK url title) = Markup.Link url (nullText title)
makeLink _ = Markup.Link mempty Nothing
image :: Assignment
image = makeTerm <$> symbol Image <*> (makeImage . termFAnnotation . termFOut <$> currentNode) <* advance
where
makeImage (CMarkGFM.IMAGE url title) = Markup.Image (encodeUtf8 url) (nullText title)
makeImage _ = Markup.Image B.empty Nothing
makeImage (CMarkGFM.IMAGE url title) = Markup.Image url (nullText title)
makeImage _ = Markup.Image mempty Nothing
code :: Assignment
code = makeTerm <$> symbol Code <*> (Markup.Code Nothing <$> source)
@ -169,5 +167,5 @@ softBreak = makeTerm <$> token SoftBreak <*> pure Markup.LineBreak
-- Implementation details
nullText :: Text.Text -> Maybe ByteString
nullText text = if Text.null text then Nothing else Just (encodeUtf8 text)
nullText :: Text.Text -> Maybe Text.Text
nullText text = if Text.null text then Nothing else Just text

View File

@ -3,6 +3,7 @@ module Language.Markdown.Syntax where
import Prologue hiding (Text)
import Data.JSON.Fields
import qualified Data.Text as T
import Diffing.Algorithm
newtype Document a = Document [a]
@ -57,7 +58,7 @@ instance Eq1 ThematicBreak where liftEq = genericLiftEq
instance Ord1 ThematicBreak where liftCompare = genericLiftCompare
instance Show1 ThematicBreak where liftShowsPrec = genericLiftShowsPrec
newtype HTMLBlock a = HTMLBlock ByteString
newtype HTMLBlock a = HTMLBlock T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
instance Eq1 HTMLBlock where liftEq = genericLiftEq
@ -102,28 +103,28 @@ instance Eq1 Emphasis where liftEq = genericLiftEq
instance Ord1 Emphasis where liftCompare = genericLiftCompare
instance Show1 Emphasis where liftShowsPrec = genericLiftShowsPrec
newtype Text a = Text ByteString
newtype Text a = Text T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
instance Eq1 Text where liftEq = genericLiftEq
instance Ord1 Text where liftCompare = genericLiftCompare
instance Show1 Text where liftShowsPrec = genericLiftShowsPrec
data Link a = Link { linkURL :: ByteString, linkTitle :: Maybe ByteString }
data Link a = Link { linkURL :: T.Text, linkTitle :: Maybe T.Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
instance Eq1 Link where liftEq = genericLiftEq
instance Ord1 Link where liftCompare = genericLiftCompare
instance Show1 Link where liftShowsPrec = genericLiftShowsPrec
data Image a = Image { imageURL :: ByteString, imageTitle :: Maybe ByteString }
data Image a = Image { imageURL :: T.Text, imageTitle :: Maybe T.Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
instance Eq1 Image where liftEq = genericLiftEq
instance Ord1 Image where liftCompare = genericLiftCompare
instance Show1 Image where liftShowsPrec = genericLiftShowsPrec
data Code a = Code { codeLanguage :: Maybe ByteString, codeContent :: ByteString }
data Code a = Code { codeLanguage :: Maybe T.Text, codeContent :: T.Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
instance Eq1 Code where liftEq = genericLiftEq

View File

@ -4,14 +4,14 @@ module Language.PHP.Syntax where
import Data.Abstract.Evaluatable
import Data.Abstract.Module
import Data.Abstract.Path
import qualified Data.ByteString.Char8 as BC
import qualified Data.Text as T
import Data.JSON.Fields
import qualified Data.Language as Language
import Diffing.Algorithm
import Prelude hiding (fail)
import Prologue hiding (Text)
newtype Text a = Text ByteString
newtype Text a = Text T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 Text where liftEq = genericLiftEq
@ -39,13 +39,13 @@ instance Evaluatable VariableName
resolvePHPName :: ( Member (Modules address value) effects
, Member (Resumable ResolutionError) effects
)
=> ByteString
=> T.Text
-> Evaluator address value effects ModulePath
resolvePHPName n = do
modulePath <- resolve [name]
maybeM (throwResumable $ NotFoundError name [name] Language.PHP) modulePath
where name = toName n
toName = BC.unpack . dropRelativePrefix . stripQuotes
toName = T.unpack . dropRelativePrefix . stripQuotes
include :: ( AbstractValue address value effects
, Member (Allocator address value) effects
@ -136,7 +136,7 @@ instance Evaluatable SimpleVariable
-- | TODO: Unify with TypeScript's PredefinedType
newtype CastType a = CastType { _castType :: ByteString }
newtype CastType a = CastType { _castType :: T.Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 CastType where liftEq = genericLiftEq
@ -160,7 +160,7 @@ instance Ord1 Clone where liftCompare = genericLiftCompare
instance Show1 Clone where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Clone
newtype ShellCommand a = ShellCommand ByteString
newtype ShellCommand a = ShellCommand T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 ShellCommand where liftEq = genericLiftEq
@ -185,7 +185,7 @@ instance Ord1 NewVariable where liftCompare = genericLiftCompare
instance Show1 NewVariable where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable NewVariable
newtype RelativeScope a = RelativeScope ByteString
newtype RelativeScope a = RelativeScope T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 RelativeScope where liftEq = genericLiftEq
@ -279,7 +279,7 @@ instance Ord1 BaseTypeDeclaration where liftCompare = genericLiftCompare
instance Show1 BaseTypeDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable BaseTypeDeclaration
newtype ScalarType a = ScalarType ByteString
newtype ScalarType a = ScalarType T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 ScalarType where liftEq = genericLiftEq
@ -426,7 +426,7 @@ instance Ord1 DestructorDeclaration where liftCompare = genericLiftCompare
instance Show1 DestructorDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DestructorDeclaration
newtype Static a = Static ByteString
newtype Static a = Static T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 Static where liftEq = genericLiftEq
@ -434,7 +434,7 @@ instance Ord1 Static where liftCompare = genericLiftCompare
instance Show1 Static where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Static
newtype ClassModifier a = ClassModifier ByteString
newtype ClassModifier a = ClassModifier T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 ClassModifier where liftEq = genericLiftEq

View File

@ -464,7 +464,7 @@ boolean = makeTerm <$> token Grammar.True <*> pure Literal.true
<|> makeTerm <$> token Grammar.False <*> pure Literal.false
none :: Assignment
none = makeTerm <$> symbol None <*> (Literal.Null <$ source)
none = makeTerm <$> symbol None <*> (Literal.Null <$ rawSource)
comprehension :: Assignment
comprehension = makeTerm <$> symbol ListComprehension <*> children (Declaration.Comprehension <$> term expression <*> expressions)

View File

@ -7,27 +7,27 @@ import Data.Abstract.Module
import Data.Aeson
import Data.Functor.Classes.Generic
import Data.JSON.Fields
import qualified Data.Language as Language
import qualified Data.List.NonEmpty as NonEmpty
import Data.Mergeable
import qualified Data.Text as T
import Diffing.Algorithm
import GHC.Generics
import Prelude hiding (fail)
import Prologue
import System.FilePath.Posix
import qualified Data.ByteString.Char8 as BC
import qualified Data.Language as Language
import qualified Data.List.NonEmpty as NonEmpty
data QualifiedName
= QualifiedName (NonEmpty FilePath)
| RelativeQualifiedName FilePath (Maybe QualifiedName)
deriving (Eq, Generic, Hashable, Ord, Show, ToJSON)
qualifiedName :: NonEmpty ByteString -> QualifiedName
qualifiedName xs = QualifiedName (BC.unpack <$> xs)
qualifiedName :: NonEmpty Text -> QualifiedName
qualifiedName xs = QualifiedName (T.unpack <$> xs)
relativeQualifiedName :: ByteString -> [ByteString] -> QualifiedName
relativeQualifiedName prefix [] = RelativeQualifiedName (BC.unpack prefix) Nothing
relativeQualifiedName prefix paths = RelativeQualifiedName (BC.unpack prefix) (Just (qualifiedName (NonEmpty.fromList paths)))
relativeQualifiedName :: Text -> [Text] -> QualifiedName
relativeQualifiedName prefix [] = RelativeQualifiedName (T.unpack prefix) Nothing
relativeQualifiedName prefix paths = RelativeQualifiedName (T.unpack prefix) (Just (qualifiedName (NonEmpty.fromList paths)))
-- Python module resolution.
-- https://docs.python.org/3/reference/import.html#importsystem
@ -147,7 +147,7 @@ instance Evaluatable QualifiedImport where
eval (QualifiedImport (RelativeQualifiedName _ _)) = raiseEff (fail "technically this is not allowed in python")
eval (QualifiedImport qname@(QualifiedName qualifiedName)) = do
modulePaths <- resolvePythonModules qname
Rval <$> go (NonEmpty.zip (name . BC.pack <$> qualifiedName) modulePaths)
Rval <$> go (NonEmpty.zip (name . T.pack <$> qualifiedName) modulePaths)
where
-- Evaluate and import the last module, updating the environment
go ((name, path) :| []) = evalQualifiedImport name path

View File

@ -361,11 +361,11 @@ methodCall = makeTerm' <$> symbol MethodCall <*> children (require <|> load <|>
selector = Just <$> term methodSelector
require = inject <$> (symbol Identifier *> do
s <- source
s <- rawSource
guard (s `elem` ["require", "require_relative"])
Ruby.Syntax.Require (s == "require_relative") <$> nameExpression)
load = inject <$> (symbol Identifier *> do
s <- source
s <- rawSource
guard (s == "load")
Ruby.Syntax.Load <$> loadArgs)
loadArgs = (symbol ArgumentList <|> symbol ArgumentListWithParens) *> children (some expression)
@ -427,7 +427,7 @@ assignment' = makeTerm <$> symbol Assignment <*> children (Statement.As
<|> lhsIdent
<|> expression
identWithLocals :: Assignment' (Record Location, ByteString, [ByteString])
identWithLocals :: Assignment' (Record Location, Text, [Text])
identWithLocals = do
loc <- symbol Identifier
-- source advances, so it's important we call getRubyLocals first
@ -488,7 +488,7 @@ conditional :: Assignment
conditional = makeTerm <$> symbol Conditional <*> children (Statement.If <$> expression <*> expression <*> expression)
emptyStatement :: Assignment
emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ source <|> pure Syntax.Empty)
emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ rawSource <|> pure Syntax.Empty)
-- Helpers

View File

@ -5,7 +5,7 @@ import Control.Monad (unless)
import Data.Abstract.Evaluatable
import qualified Data.Abstract.Module as M
import Data.Abstract.Path
import qualified Data.ByteString.Char8 as BC
import qualified Data.Text as T
import Data.JSON.Fields
import qualified Data.Language as Language
import Diffing.Algorithm
@ -20,7 +20,7 @@ import System.FilePath.Posix
resolveRubyName :: ( Member (Modules address value) effects
, Member (Resumable ResolutionError) effects
)
=> ByteString
=> Text
-> Evaluator address value effects M.ModulePath
resolveRubyName name = do
let name' = cleanNameOrPath name
@ -32,15 +32,15 @@ resolveRubyName name = do
resolveRubyPath :: ( Member (Modules address value) effects
, Member (Resumable ResolutionError) effects
)
=> ByteString
=> Text
-> Evaluator address value effects M.ModulePath
resolveRubyPath path = do
let name' = cleanNameOrPath path
modulePath <- resolve [name']
maybeM (throwResumable $ NotFoundError name' [name'] Language.Ruby) modulePath
cleanNameOrPath :: ByteString -> String
cleanNameOrPath = BC.unpack . dropRelativePrefix . stripQuotes
cleanNameOrPath :: Text -> String
cleanNameOrPath = T.unpack . dropRelativePrefix . stripQuotes
data Send a = Send { sendReceiver :: Maybe a, sendSelector :: Maybe a, sendArgs :: [a], sendBlock :: Maybe a }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
@ -108,7 +108,7 @@ doLoad :: ( AbstractValue address value effects
, Member (Resumable ResolutionError) effects
, Member Trace effects
)
=> ByteString
=> Text
-> Bool
-> Evaluator address value effects value
doLoad path shouldWrap = do

View File

@ -38,6 +38,7 @@ import Prologue
-- | The type of TypeScript syntax.
type Syntax = '[
Comment.Comment
, Comment.HashBang
, Declaration.Class
, Declaration.Function
, Declaration.Method
@ -83,7 +84,6 @@ type Syntax = '[
, Statement.Finally
, Statement.For
, Statement.ForEach
, Statement.HashBang
, Statement.If
, Statement.Match
, Statement.Pattern
@ -232,7 +232,7 @@ expression = handleError everything
]
undefined' :: Assignment
undefined' = makeTerm <$> symbol Grammar.Undefined <*> (TypeScript.Syntax.Undefined <$ source)
undefined' = makeTerm <$> symbol Grammar.Undefined <*> (TypeScript.Syntax.Undefined <$ rawSource)
assignmentExpression :: Assignment
assignmentExpression = makeTerm <$> symbol AssignmentExpression <*> children (Statement.Assignment [] <$> term (memberExpression <|> subscriptExpression <|> identifier <|> destructuringPattern) <*> expression)
@ -282,13 +282,13 @@ yieldExpression :: Assignment
yieldExpression = makeTerm <$> symbol Grammar.YieldExpression <*> children (Statement.Yield <$> term (expression <|> emptyTerm))
this :: Assignment
this = makeTerm <$> symbol Grammar.This <*> (TypeScript.Syntax.This <$ source)
this = makeTerm <$> symbol Grammar.This <*> (TypeScript.Syntax.This <$ rawSource)
regex :: Assignment
regex = makeTerm <$> symbol Grammar.Regex <*> (Literal.Regex <$> source)
null' :: Assignment
null' = makeTerm <$> symbol Null <*> (Literal.Null <$ source)
null' = makeTerm <$> symbol Null <*> (Literal.Null <$ rawSource)
anonymousClass :: Assignment
anonymousClass = makeTerm <$> symbol Grammar.AnonymousClass <*> children (Declaration.Class <$> pure [] <*> emptyTerm <*> (classHeritage' <|> pure []) <*> classBodyStatements)
@ -313,7 +313,7 @@ implementsClause' :: Assignment
implementsClause' = makeTerm <$> symbol Grammar.ImplementsClause <*> children (TypeScript.Syntax.ImplementsClause <$> manyTerm ty)
super :: Assignment
super = makeTerm <$> symbol Grammar.Super <*> (TypeScript.Syntax.Super <$ source)
super = makeTerm <$> symbol Grammar.Super <*> (TypeScript.Syntax.Super <$ rawSource)
typeAssertion :: Assignment
typeAssertion = makeTerm <$> symbol Grammar.TypeAssertion <*> children (TypeScript.Syntax.TypeAssertion <$> term typeArguments' <*> term expression)
@ -340,10 +340,10 @@ string :: Assignment
string = makeTerm <$> symbol Grammar.String <*> (Literal.TextElement <$> source)
true :: Assignment
true = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source)
true = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ rawSource)
false :: Assignment
false = makeTerm <$> symbol Grammar.False <*> (Literal.false <$ source)
false = makeTerm <$> symbol Grammar.False <*> (Literal.false <$ rawSource)
identifier :: Assignment
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier . name <$> source)
@ -423,7 +423,7 @@ spreadElement :: Assignment
spreadElement = symbol SpreadElement *> children (term expression)
readonly' :: Assignment
readonly' = makeTerm <$> symbol Readonly <*> (Type.Readonly <$ source)
readonly' = makeTerm <$> symbol Readonly <*> (Type.Readonly <$ rawSource)
methodDefinition :: Assignment
methodDefinition = makeMethod <$>
@ -636,7 +636,7 @@ throwStatement :: Assignment
throwStatement = makeTerm <$> symbol Grammar.ThrowStatement <*> children (Statement.Throw <$> term expressions)
hashBang :: Assignment
hashBang = makeTerm <$> symbol HashBangLine <*> (Statement.HashBang <$> source)
hashBang = makeTerm <$> symbol HashBangLine <*> (Comment.HashBang <$> source)
labeledStatement :: Assignment
labeledStatement = makeTerm <$> symbol Grammar.LabeledStatement <*> children (TypeScript.Syntax.LabeledStatement <$> statementIdentifier <*> term statement)
@ -680,7 +680,7 @@ importStatement = makeImportTerm <$> symbol Grammar.ImportStatement <*> childr
fromClause = symbol Grammar.String *> (TypeScript.Syntax.importPath <$> source)
debuggerStatement :: Assignment
debuggerStatement = makeTerm <$> symbol Grammar.DebuggerStatement <*> (TypeScript.Syntax.Debugger <$ source)
debuggerStatement = makeTerm <$> symbol Grammar.DebuggerStatement <*> (TypeScript.Syntax.Debugger <$ rawSource)
expressionStatement' :: Assignment
expressionStatement' = symbol ExpressionStatement *> children (term expressions)
@ -873,7 +873,7 @@ term :: Assignment -> Assignment
term term = contextualize comment (postContextualize comment term)
emptyStatement :: Assignment
emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ source <|> pure Syntax.Empty)
emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ rawSource <|> pure Syntax.Empty)
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.
infixTerm :: Assignment

View File

@ -7,11 +7,10 @@ import qualified Data.Abstract.Module as M
import Data.Abstract.Package
import Data.Abstract.Path
import Data.Aeson
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import Data.JSON.Fields
import qualified Data.Language as Language
import qualified Data.Map as Map
import qualified Data.Text as T
import Diffing.Algorithm
import Prelude
import Prologue
@ -23,15 +22,15 @@ data Relative = Relative | NonRelative
data ImportPath = ImportPath { unPath :: FilePath, pathIsRelative :: Relative }
deriving (Eq, Generic, Hashable, Ord, Show, ToJSON)
importPath :: ByteString -> ImportPath
importPath str = let path = stripQuotes str in ImportPath (BC.unpack path) (pathType path)
-- TODO: fix the duplication present in this and Python
importPath :: Text -> ImportPath
importPath str = let path = stripQuotes str in ImportPath (T.unpack path) (pathType path)
where
stripQuotes = B.filter (`B.notElem` "\'\"")
pathType xs | not (B.null xs), BC.head xs == '.' = Relative
pathType xs | not (T.null xs), T.head xs == '.' = Relative -- TODO: fix partiality
| otherwise = NonRelative
toName :: ImportPath -> Name
toName = name . BC.pack . unPath
toName = name . T.pack . unPath
-- Node.js resolution algorithm: https://nodejs.org/api/modules.html#modules_all_together
--
@ -268,7 +267,7 @@ instance Show1 LookupType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable LookupType
-- | ShorthandPropertyIdentifier used in object patterns such as var baz = { foo } to mean var baz = { foo: foo }
newtype ShorthandPropertyIdentifier a = ShorthandPropertyIdentifier ByteString
newtype ShorthandPropertyIdentifier a = ShorthandPropertyIdentifier T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 ShorthandPropertyIdentifier where liftEq = genericLiftEq
@ -406,7 +405,7 @@ instance Ord1 ParenthesizedType where liftCompare = genericLiftCompare
instance Show1 ParenthesizedType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ParenthesizedType
newtype PredefinedType a = PredefinedType { _predefinedType :: ByteString }
newtype PredefinedType a = PredefinedType { _predefinedType :: T.Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 PredefinedType where liftEq = genericLiftEq
@ -414,7 +413,7 @@ instance Ord1 PredefinedType where liftCompare = genericLiftCompare
instance Show1 PredefinedType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PredefinedType
newtype TypeIdentifier a = TypeIdentifier ByteString
newtype TypeIdentifier a = TypeIdentifier T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 TypeIdentifier where liftEq = genericLiftEq
@ -539,7 +538,7 @@ instance Ord1 TypeArguments where liftCompare = genericLiftCompare
instance Show1 TypeArguments where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeArguments
newtype ThisType a = ThisType ByteString
newtype ThisType a = ThisType T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 ThisType where liftEq = genericLiftEq
@ -547,7 +546,7 @@ instance Ord1 ThisType where liftCompare = genericLiftCompare
instance Show1 ThisType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ThisType
newtype ExistentialType a = ExistentialType ByteString
newtype ExistentialType a = ExistentialType T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 ExistentialType where liftEq = genericLiftEq
@ -736,7 +735,7 @@ instance Ord1 JsxElement where liftCompare = genericLiftCompare
instance Show1 JsxElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxElement
newtype JsxText a = JsxText ByteString
newtype JsxText a = JsxText T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
instance Eq1 JsxText where liftEq = genericLiftEq

View File

@ -18,7 +18,6 @@ module Semantic.Graph
import Analysis.Abstract.Evaluating
import Analysis.Abstract.Graph
import Control.Monad.Effect.Trace
import Control.Abstract
import qualified Control.Exception as Exc
import Control.Monad.Effect (reinterpret)
@ -26,12 +25,12 @@ import Data.Abstract.Address
import Data.Abstract.Evaluatable
import Data.Abstract.Module
import Data.Abstract.Package as Package
import Data.Abstract.Value (Value, ValueError(..), runValueErrorWith)
import Data.ByteString.Char8 (pack)
import Data.Abstract.Value (Value, ValueError (..), runValueErrorWith)
import Data.Graph
import Data.Project
import Data.Record
import Data.Term
import Data.Text (pack)
import Parsing.Parser
import Prologue hiding (MonadError (..))
import Semantic.IO (Files)

View File

@ -44,7 +44,7 @@ import qualified Data.ByteString as B
import qualified Data.ByteString.Builder as B
import qualified Data.ByteString.Lazy as BL
import Data.Language
import Data.Source (fromBytes, fromText)
import Data.Source (fromUTF8, fromText)
import Prelude hiding (readFile)
import Prologue hiding (MonadError (..), fail)
import System.Directory (doesDirectoryExist)
@ -61,7 +61,7 @@ readFile :: forall m. MonadIO m => File -> m (Maybe Blob.Blob)
readFile (File "/dev/null" _) = pure Nothing
readFile (File path language) = do
raw <- liftIO (Just <$> B.readFile path)
pure $ Blob.sourceBlob path language . fromBytes <$> raw
pure $ Blob.sourceBlob path language . fromUTF8 <$> raw
readFilePair :: forall m. MonadIO m => File -> File -> m Blob.BlobPair
readFilePair a b = Join <$> join (maybeThese <$> readFile a <*> readFile b)

View File

@ -4,17 +4,18 @@ module Assigning.Assignment.Spec (spec) where
import Assigning.Assignment
import Data.AST
import Data.Bifunctor (first)
import Data.ByteString.Char8 as B (ByteString, length, words)
import Data.Ix
import Data.Range
import Data.Semigroup ((<>))
import Data.Source
import Data.Span
import Data.Term
import Data.Text as T (Text, length, words)
import Data.Text.Encoding (encodeUtf8)
import GHC.Stack (getCallStack)
import Prelude hiding (words)
import Test.Hspec
import TreeSitter.Language (Symbol(..), SymbolType(..))
import TreeSitter.Language (Symbol (..), SymbolType (..))
spec :: Spec
spec = do
@ -33,8 +34,8 @@ spec = do
it "matches repetitions" $
let s = "colourless green ideas sleep furiously"
w = words s
(_, nodes) = foldl (\ (i, prev) word -> (i + B.length word + 1, prev <> [node Red i (i + B.length word) []])) (0, []) w in
fst <$> runAssignment (fromBytes s) (many red) (makeState nodes)
(_, nodes) = foldl (\ (i, prev) word -> (i + T.length word + 1, prev <> [node Red i (i + T.length word) []])) (0, []) w in
fst <$> runAssignment (fromUTF8 (encodeUtf8 s)) (many red) (makeState nodes)
`shouldBe`
Right (Out <$> w)
@ -259,9 +260,9 @@ data Grammar = Palette | Red | Green | Blue | Magenta
instance Symbol Grammar where
symbolType Magenta = Anonymous
symbolType _ = Regular
symbolType _ = Regular
data Out = Out B.ByteString | OutError B.ByteString
data Out = Out T.Text | OutError T.Text
deriving (Eq, Show)
red :: HasCallStack => Assignment [] Grammar Out

View File

@ -299,7 +299,7 @@ instance Listable Span where
instance Listable Source where
tiers = fromBytes `mapT` tiers
tiers = fromUTF8 `mapT` tiers
instance Listable ByteString where
tiers = (T.encodeUtf8 . T.pack) `mapT` strings

View File

@ -22,7 +22,7 @@ spec = parallel $ do
describe "spanToRange" $ do
prop "computes single-line ranges" $
\ s -> let source = fromBytes s
\ s -> let source = fromUTF8 s
spans = zipWith (\ i Range {..} -> Span (Pos i 1) (Pos i (succ (end - start)))) [1..] ranges
ranges = sourceLineRanges source in
spanToRange source <$> spans `shouldBe` ranges

View File

@ -3,6 +3,7 @@ module Diffing.Interpreter.Spec where
import Data.Diff
import Data.Functor.Listable
import Data.Maybe
import Data.Record
import Data.Sum
import Data.Term
@ -12,6 +13,7 @@ import qualified Data.Syntax as Syntax
import Test.Hspec (Spec, describe, it, parallel)
import Test.Hspec.Expectations.Pretty
import Test.Hspec.LeanCheck
import Test.LeanCheck.Core
spec :: Spec
spec = parallel $ do
@ -34,8 +36,11 @@ spec = parallel $ do
wrap = termIn Nil . inject in
diffTerms (wrap [ term "b" ]) (wrap [ term "a", term "b" ]) `shouldBe` merge (Nil, Nil) (inject [ inserting (term "a"), merging (term "b") ])
prop "compares nodes against context" $
\ a b -> diffTerms a (termIn Nil (inject (Syntax.Context (pure b) a))) `shouldBe` insertF (In Nil (inject (Syntax.Context (pure (inserting b)) (merging (a :: Term ListableSyntax (Record '[]))))))
let noContext :: Term ListableSyntax a -> Bool
noContext = isNothing . project @Syntax.Context . termOut
prop "compares nodes against context" . forAll (filterT (noContext . fst) tiers) $
\ (a, b) -> diffTerms a (termIn Nil (inject (Syntax.Context (pure b) a))) `shouldBe` insertF (In Nil (inject (Syntax.Context (pure (inserting b)) (merging (a :: Term ListableSyntax (Record '[]))))))
prop "diffs forward permutations as changes" $
\ a -> let wrap = termIn Nil . inject

View File

@ -9,10 +9,11 @@ import Data.Sum
import qualified Data.Syntax.Declaration as Decl
import qualified Data.Syntax.Literal as Lit
import qualified Data.Syntax.Statement as Stmt
import Data.Text (Text)
import SpecHelpers
-- This gets the ByteString contents of all integers
integerMatcher :: (Lit.Integer :< fs) => Matcher (Term (Sum fs) ann) ByteString
-- This gets the Text contents of all integers
integerMatcher :: (Lit.Integer :< fs) => Matcher (Term (Sum fs) ann) Text
integerMatcher = match Lit.integerContent target
-- This matches all for-loops with its index variable new variable bound to 0,

View File

@ -200,7 +200,7 @@ programOf diff = merge (programInfo, programInfo) (inject [ diff ])
functionOf :: Text -> Term' -> Term'
functionOf n body = termIn (Just (FunctionDeclaration n mempty Nothing) :. emptyInfo) (inject (Declaration.Function [] name' [] (termIn (Nothing :. emptyInfo) (inject [body]))))
where
name' = termIn (Nothing :. emptyInfo) (inject (Syntax.Identifier (name (encodeUtf8 n))))
name' = termIn (Nothing :. emptyInfo) (inject (Syntax.Identifier (name n)))
programInfo :: Record '[Maybe Declaration, Range, Span]
programInfo = Nothing :. emptyInfo

View File

@ -17,39 +17,27 @@
->(Integer) })
{ (Identifier)
->(Identifier) })))
{+(Statements
{+(Type
{+(Identifier)+}
{+(Array
{+(Integer)+}
{+(Array
{+(Integer)+}
{+(Identifier)+})+})+})+})+}
{+(Statements
{+(Type
{+(Identifier)+}
{+(Array
{+(Integer)+}
{+(Array
{+(Integer)+}
{+(Array
{+(Integer)+}
{+(Identifier)+})+})+})+})+})+}
{-(Statements
{-(Type
{-(Identifier)-}
{-(Array
{-(Integer)-}
{-(Array
{-(Integer)-}
{-(Identifier)-})-})-})-})-}
{-(Statements
{-(Type
{-(Identifier)-}
{-(Array
{-(Integer)-}
{-(Array
{-(Integer)-}
{-(Array
{-(Integer)-}
{-(Identifier)-})-})-})-})-})-})))
(Statements
(Type
{ (Identifier)
->(Identifier) }
(Array
{ (Integer)
->(Integer) }
(Array
{ (Integer)
->(Integer) }
(Identifier)))))
(Statements
(Type
{ (Identifier)
->(Identifier) }
(Array
{ (Integer)
->(Integer) }
(Array
(Integer)
(Array
{ (Integer)
->(Integer) }
(Identifier)))))))))

View File

@ -17,39 +17,27 @@
->(Integer) })
{ (Identifier)
->(Identifier) })))
{+(Statements
{+(Type
{+(Identifier)+}
{+(Array
{+(Integer)+}
{+(Array
{+(Integer)+}
{+(Identifier)+})+})+})+})+}
{+(Statements
{+(Type
{+(Identifier)+}
{+(Array
{+(Integer)+}
{+(Array
{+(Integer)+}
{+(Array
{+(Integer)+}
{+(Identifier)+})+})+})+})+})+}
{-(Statements
{-(Type
{-(Identifier)-}
{-(Array
{-(Integer)-}
{-(Array
{-(Integer)-}
{-(Identifier)-})-})-})-})-}
{-(Statements
{-(Type
{-(Identifier)-}
{-(Array
{-(Integer)-}
{-(Array
{-(Integer)-}
{-(Array
{-(Integer)-}
{-(Identifier)-})-})-})-})-})-})))
(Statements
(Type
{ (Identifier)
->(Identifier) }
(Array
{ (Integer)
->(Integer) }
(Array
{ (Integer)
->(Integer) }
(Identifier)))))
(Statements
(Type
{ (Identifier)
->(Identifier) }
(Array
{ (Integer)
->(Integer) }
(Array
(Integer)
(Array
{ (Integer)
->(Integer) }
(Identifier)))))))))

View File

@ -11,9 +11,9 @@
(Array
(Identifier))
(Statements
{+(Integer)+}
{+(Integer)+}
{ (Integer)
->(Integer) }
{-(Integer)-}
{-(Integer)-})))))
{ (Integer)
->(Integer) }
{ (Integer)
->(Integer) })))))

View File

@ -11,9 +11,9 @@
(Array
(Identifier))
(Statements
{+(Integer)+}
{ (Integer)
->(Integer) }
{ (Integer)
->(Integer) }
{-(Integer)-})))))
{ (Integer)
->(Integer) })))))

View File

@ -35,25 +35,25 @@
{+(Plus
{+(Identifier)+}
{+(Integer)+})+})+}
{+(Assignment
{+(Identifier)+}
{+(LShift
{+(Identifier)+}
{+(Integer)+})+})+}
{+(Assignment
{+(Identifier)+}
{+(RShift
{+(Identifier)+}
{+(Integer)+})+})+}
(Assignment
{ (Identifier)
->(Identifier) }
{ (Times
{-(Identifier)-}
{-(Integer)-})
->(LShift
->(DividedBy
{+(Identifier)+}
{+(Integer)+}) })
{+(Assignment
{+(Identifier)+}
{+(RShift
{+(Identifier)+}
{+(Integer)+})+})+}
{+(Assignment
{+(Identifier)+}
{+(DividedBy
{+(Identifier)+}
{+(Integer)+})+})+}
{+(Assignment
{+(Identifier)+}
{+(BXOr

View File

@ -30,11 +30,15 @@
{+(Times
{+(Identifier)+}
{+(Integer)+})+})+}
{+(Assignment
{+(Identifier)+}
{+(Plus
(Assignment
{ (Identifier)
->(Identifier) }
{ (Times
{-(Identifier)-}
{-(Integer)-})
->(Plus
{+(Identifier)+}
{+(Integer)+})+})+}
{+(Integer)+}) })
{+(Assignment
{+(Identifier)+}
{+(LShift
@ -60,12 +64,16 @@
{+(Modulo
{+(Identifier)+}
{+(Integer)+})+})+}
{+(Assignment
{+(Identifier)+}
{+(Not
(Assignment
{ (Identifier)
->(Identifier) }
{ (Plus
{-(Identifier)-}
{-(Integer)-})
->(Not
{+(BAnd
{+(Identifier)+}
{+(Integer)+})+})+})+}
{+(Integer)+})+}) })
{+(Assignment
{+(Identifier)+}
{+(Statements
@ -78,16 +86,6 @@
{+(KeyValue
{+(Identifier)+}
{+(Integer)+})+})+})+})+})+})+}
{-(Assignment
{-(Identifier)-}
{-(Times
{-(Identifier)-}
{-(Integer)-})-})-}
{-(Assignment
{-(Identifier)-}
{-(Plus
{-(Identifier)-}
{-(Integer)-})-})-}
{-(Assignment
{-(Identifier)-}
{-(LShift

View File

@ -92,31 +92,28 @@
{+(Identifier)+}
{+(Identifier)+})+}
{+(Empty)+})+})+}
{+(For
{+(Empty)+}
{+(LessThan
(For
(Empty)
{ (Empty)
->(LessThan
{+(Integer)+}
{+(Integer)+})+}
{+(Empty)+}
{+(Call
{+(Identifier)+}
{+(Statements)+}
{+(Empty)+})+})+}
{+(ForEach
{+(Empty)+}
{+(Identifier)+}
{+(Statements)+})+}
{-(For
{-(Empty)-}
{-(Empty)-}
{-(Empty)-}
{-(Statements
{+(Integer)+}) }
(Empty)
{ (Statements
{-(Call
{-(Identifier)-}
{-(Statements)-}
{-(Empty)-})-}
{-(Continue
{-(Identifier)-})-})-})-}
{-(Identifier)-})-})
->(Call
{+(Identifier)+}
{+(Statements)+}
{+(Empty)+}) })
{+(ForEach
{+(Empty)+}
{+(Identifier)+}
{+(Statements)+})+}
{-(For
{-(LessThan
{-(Identifier)-}

View File

@ -2,18 +2,18 @@
(Package
(Identifier))
(Statements
{ (QualifiedImport
{-(Identifier)-})
->(QualifiedImport
{+(Identifier)+}) }
{ (Import
{-(TextElement)-})
->(Import
{+(TextElement)+}) }
{ (QualifiedImport
{-(Identifier)-})
->(QualifiedImport
{+(Identifier)+}) })
{+(QualifiedImport
{+(Identifier)+})+}
{+(Import
{+(TextElement)+})+}
{+(QualifiedImport
{+(Identifier)+})+}
{-(QualifiedImport
{-(Identifier)-})-}
{-(Import
{-(TextElement)-})-}
{-(QualifiedImport
{-(Identifier)-})-})
(Function
(Empty)
(Identifier)

View File

@ -2,18 +2,18 @@
(Package
(Identifier))
(Statements
{+(QualifiedImport
{+(Identifier)+})+}
{+(Import
{+(TextElement)+})+}
{ (QualifiedImport
{-(Identifier)-})
->(QualifiedImport
{+(Identifier)+}) }
{ (Import
{-(TextElement)-})
->(Import
{+(TextElement)+}) }
{ (QualifiedImport
{-(Identifier)-})
->(QualifiedImport
{+(Identifier)+}) })
{-(Import
{-(TextElement)-})-}
{-(QualifiedImport
{-(Identifier)-})-})
(Function
(Empty)
(Identifier)

View File

@ -23,18 +23,17 @@
{+(Empty)+}
{+(Empty)+}
{+(Empty)+})+}
{+(Slice
{+(Identifier)+}
{+(Integer)+}
{+(Integer)+}
{+(Integer)+})+}
(Slice
{ (Identifier)
->(Identifier) }
(Integer)
(Integer)
{ (Empty)
->(Integer) })
{+(Slice
{+(Identifier)+}
{+(Integer)+}
{+(Integer)+}
{+(Empty)+})+}
(Empty))
{-(Slice
{-(Identifier)-}
{-(Integer)-}

View File

@ -1,7 +1,10 @@
(Statements
{+(Import)+}
{+(QualifiedAliasedImport
{+(Identifier)+})+}
{ (Import)
->(Import) }
{ (QualifiedAliasedImport
{-(Identifier)-})
->(QualifiedAliasedImport
{+(Identifier)+}) }
{ (Import)
->(Import) }
{+(Import)+}
@ -14,9 +17,6 @@
{+(QualifiedAliasedImport
{+(Identifier)+})+})+}
{+(SideEffectImport)+}
{-(QualifiedAliasedImport
{-(Identifier)-})-}
{-(Import)-}
{-(Import)-}
{-(Import)-}
{-(Statements

View File

@ -1,8 +1,12 @@
(Statements
{+(Import)+}
{+(QualifiedAliasedImport
{+(Identifier)+})+}
{+(Import)+}
{ (Import)
->(Import) }
{ (QualifiedAliasedImport
{-(Identifier)-})
->(QualifiedAliasedImport
{+(Identifier)+}) }
{ (Import)
->(Import) }
{+(Import)+}
{+(Import)+}
{+(Statements
@ -14,10 +18,6 @@
{+(Identifier)+})+})+}
{+(SideEffectImport)+}
{-(Import)-}
{-(QualifiedAliasedImport
{-(Identifier)-})-}
{-(Import)-}
{-(Import)-}
{-(Import)-}
{-(Statements
{-(Import)-}

View File

@ -10,18 +10,14 @@
{ (Identifier)
->(Identifier) }
(Integer))
{+(Assignment
{+(Identifier)+}
{+(Statements
{+(Integer)+}
{+(Integer)+})+})+}
{-(Assignment
{-(Statements
(Assignment
{ (Statements
{-(Identifier)-}
{-(Identifier)-})-}
{-(Statements
{-(Integer)-}
{-(Integer)-})-})-}
{-(Identifier)-})
->(Identifier) }
(Statements
(Integer)
(Integer)))
{-(Assignment
{-(Identifier)-}
{-(Statements

View File

@ -7,21 +7,21 @@
->(RShift
{+(Identifier)+}
{+(Integer)+}) })
{+(Assignment
{+(Identifier)+}
{+(DividedBy
{+(Identifier)+}
{+(Integer)+})+})+}
(Assignment
(Identifier)
{ (Identifier)
->(Identifier) }
{ (RShift
{-(Identifier)-}
{-(Integer)-})
->(DividedBy
{+(Identifier)+}
{+(Integer)+}) })
(Assignment
{ (Identifier)
->(Identifier) }
{ (DividedBy
{-(Identifier)-}
{-(Integer)-})
->(Plus
{+(Identifier)+}
{+(Integer)+}) })
{-(Assignment
{-(Identifier)-}
{-(DividedBy
{-(Identifier)-}
{-(Integer)-})-})-})
{+(Integer)+}) }))

View File

@ -7,23 +7,21 @@
->(Plus
{+(Identifier)+}
{+(Integer)+}) })
{+(Assignment
{+(Identifier)+}
{+(RShift
{+(Identifier)+}
{+(Integer)+})+})+}
{+(Assignment
{+(Identifier)+}
{+(DividedBy
{+(Identifier)+}
{+(Integer)+})+})+}
{-(Assignment
{-(Identifier)-}
{-(DividedBy
(Assignment
{ (Identifier)
->(Identifier) }
{ (DividedBy
{-(Identifier)-}
{-(Integer)-})-})-}
{-(Assignment
{-(Identifier)-}
{-(Plus
{-(Integer)-})
->(RShift
{+(Identifier)+}
{+(Integer)+}) })
(Assignment
{ (Identifier)
->(Identifier) }
{ (Plus
{-(Identifier)-}
{-(Integer)-})-})-})
{-(Integer)-})
->(DividedBy
{+(Identifier)+}
{+(Integer)+}) }))

View File

@ -17,12 +17,9 @@
{+(Equal
{+(Identifier)+}
{+(Identifier)+})+})+}
{ (LessThan
{-(Identifier)-}
{-(Identifier)-})
->(GreaterThan
{+(GreaterThan
{+(Identifier)+}
{+(Identifier)+}) }
{+(Identifier)+})+}
{+(GreaterThanEqual
{+(Identifier)+}
{+(Identifier)+})+}
@ -30,14 +27,17 @@
{+(Equal
{+(Identifier)+}
{+(Identifier)+})+})+}
(LessThanEqual
{+(LessThanEqual
{+(Identifier)+}
{+(Identifier)+})+}
(LessThan
{ (Identifier)
->(Identifier) }
{ (Identifier)
->(Identifier) })
{+(LessThan
{+(Identifier)+}
{+(Identifier)+})+}
{-(LessThanEqual
{-(Identifier)-}
{-(Identifier)-})-}
{-(Not
{-(Equal
{-(Identifier)-}

View File

@ -5,34 +5,35 @@
{+(LessThanEqual
{+(Identifier)+}
{+(Identifier)+})+}
{+(Not
{+(Equal
{+(Identifier)+}
{+(Identifier)+})+})+}
{+(GreaterThanEqual
{+(Identifier)+}
{+(Identifier)+})+}
{+(GreaterThan
{+(Identifier)+}
{+(Identifier)+})+}
(Not
(Equal
{ (Identifier)
->(Identifier) }
{ (Identifier)
->(Identifier) }))
{+(GreaterThanEqual
{+(Identifier)+}
{+(Identifier)+})+}
{+(GreaterThan
{+(Identifier)+}
{+(Identifier)+})+}
(Not
{ (Member
{-(Identifier)-}
{-(Identifier)-})
->(Equal
{+(Identifier)+}
{+(Identifier)+}) })
{+(Member
{+(Identifier)+}
{+(Identifier)+})+}
{+(Equal
{+(Identifier)+}
{+(Identifier)+})+}
(Not
(Member
{ (Identifier)
->(Identifier) }
{ (Identifier)
->(Identifier) }))
{+(Not
{+(Member
{+(Identifier)+}
{+(Identifier)+})+})+}
{+(Not
{+(Equal
{+(Identifier)+}

View File

@ -1,28 +1,21 @@
(Statements
{+(Call
{+(Identifier)+}
{+(TextElement)+}
{+(Identifier)+}
{+(Empty)+})+}
{+(Call
{+(Identifier)+}
{+(TextElement)+}
{+(Identifier)+}
{+(Identifier)+}
{+(Empty)+})+}
(Call
(Identifier)
{ (TextElement)
->(TextElement) }
{+(Identifier)+}
(Empty))
{-(Call
{-(Identifier)-}
{-(TextElement)-}
(Call
(Identifier)
(TextElement)
{+(Identifier)+}
{+(Identifier)+}
{-(Null)-}
{-(Empty)-})-}
{-(Call
{-(Identifier)-}
{-(TextElement)-}
(Empty))
(Call
(Identifier)
{ (TextElement)
->(TextElement) }
{-(Identifier)-}
{-(Identifier)-}
{-(Empty)-})-})
(Empty)))

View File

@ -1,22 +1,21 @@
(Statements
{+(Call
{+(Identifier)+}
{+(TextElement)+}
{+(Empty)+})+}
(Call
(Identifier)
{ (TextElement)
->(TextElement) }
{-(Identifier)-}
(Empty))
(Call
(Identifier)
(TextElement)
{+(Null)+}
{-(Identifier)-}
{-(Identifier)-}
(Empty))
(Call
(Identifier)
(TextElement)
{ (TextElement)
->(TextElement) }
{+(Identifier)+}
(Identifier)
{-(Identifier)-}
(Empty))
{-(Call
{-(Identifier)-}
{-(TextElement)-}
{-(Empty)-})-})
{+(Identifier)+}
(Empty)))

View File

@ -6,13 +6,13 @@
->(Float) }
{+(Float)+}
{+(Float)+}
{ (Float)
->(Float) }
{+(Float)+}
{+(Float)+}
{+(Float)+}
{+(Float)+}
{+(Float)+}
{+(Float)+}
{-(Float)-}
{-(Float)-}
{-(Float)-}
{-(Float)-}

View File

@ -7,12 +7,12 @@
{+(Float)+}
{+(Float)+}
{+(Float)+}
{ (Float)
->(Float) }
{+(Float)+}
{+(Float)+}
{+(Float)+}
{+(Float)+}
{+(Float)+}
{-(Float)-}
{-(Float)-}
{-(Float)-}
{-(Float)-}

View File

@ -1,11 +1,11 @@
(Statements
{+(Import)+}
{+(Import)+}
{+(Import)+}
{+(Import)+}
{ (Import)
->(Import) }
{+(Import)+}
{+(Import)+}
{+(Import)+}
{+(Import)+}
{+(Import)+}
{-(Import)-}
{-(Import)-}
{-(Import)-}

View File

@ -1,10 +1,10 @@
(Statements
{ (Import)
->(Import) }
{+(Import)+}
{+(Import)+}
{+(Import)+}
{+(Import)+}
{+(Import)+}
{-(Import)-}
{-(Import)-}
{-(Import)-}
{-(Import)-}

View File

@ -9,15 +9,15 @@
{+(Negate
{+(Integer)+})+}
{+(Integer)+}
{ (Integer)
->(Integer) }
{+(Integer)+}
{+(Integer)+}
{+(Integer)+}
{+(Integer)+}
{ (Integer)
->(Integer) }
{+(Integer)+}
{+(Integer)+}
{+(Integer)+}
{-(Integer)-}
{-(Integer)-}
{-(Negate
{-(Integer)-})-}
{-(Integer)-}

View File

@ -5,19 +5,19 @@
{ (Integer)
->(Integer) }
{+(Integer)+}
{ (Integer)
->(Integer) }
{+(Integer)+}
{+(Negate
{+(Integer)+})+}
{ (Integer)
->(Integer) }
{+(Integer)+}
{+(Integer)+}
{+(Integer)+}
{ (Integer)
->(Integer) }
{+(Integer)+}
{+(Integer)+}
{+(Integer)+}
{+(Integer)+}
{+(Integer)+}
{-(Integer)-}
{-(Negate
{-(Integer)-})-}
{-(Integer)-}

View File

@ -1,13 +1,13 @@
(Statements
{+(TextElement)+}
(TextElement)
{+(TextElement)+}
{ (TextElement)
->(TextElement) }
{ (TextElement)
->(TextElement) }
{+(TextElement)+}
{+(TextElement)+}
{+(TextElement)+}
{+(TextElement)+}
{-(TextElement)-}
{-(TextElement)-}
{-(TextElement)-}
{-(TextElement)-}

View File

@ -1,7 +1,6 @@
(Statements
{-(TextElement)-}
(TextElement)
{+(TextElement)+}
{ (TextElement)
->(TextElement) }
{+(TextElement)+}
@ -9,7 +8,8 @@
{ (TextElement)
->(TextElement) }
{+(TextElement)+}
{-(TextElement)-}
{ (TextElement)
->(TextElement) }
{-(TextElement)-}
{-(TextElement)-}
(TextElement)

View File

@ -2,9 +2,10 @@
{+(Negate
{+(Identifier)+})+}
{+(Identifier)+}
(Complement
{ (Identifier)
->(Identifier) })
{+(Complement
{+(Identifier)+})+}
{-(Complement
{-(Identifier)-})-}
{-(Negate
{-(Identifier)-})-}
{-(Identifier)-})

View File

@ -1,12 +1,12 @@
(Statements
{+(TextElement)+}
{+(TextElement)+}
{ (TextElement)
->(TextElement) }
{ (TextElement)
->(TextElement) }
{+(TextElement)+}
{+(TextElement)+}
{+(TextElement)+}
{+(TextElement)+}
{-(TextElement)-}
{-(TextElement)-}
{-(TextElement)-}
{-(TextElement)-}
{-(TextElement)-}

View File

@ -1,11 +1,11 @@
(Statements
{+(TextElement)+}
{+(TextElement)+}
{+(TextElement)+}
{+(TextElement)+}
{+(TextElement)+}
{ (TextElement)
->(TextElement) }
{+(TextElement)+}
{+(TextElement)+}
{+(TextElement)+}
{-(TextElement)-}
{-(TextElement)-}
{-(TextElement)-}

View File

@ -3,17 +3,17 @@
{+(KeyValue
{+(Symbol)+}
{+(TextElement)+})+}
{+(KeyValue
{+(Symbol)+}
{+(Integer)+})+}
{+(KeyValue
{+(TextElement)+}
{+(Boolean)+})+}
(KeyValue
{ (Symbol)
->(Symbol) }
{ (TextElement)
->(Integer) })
{+(KeyValue
{+(TextElement)+}
{+(Boolean)+})+}
{+(KeyValue
{+(Symbol)+}
{+(Integer)+})+}
{-(KeyValue
{-(Symbol)-}
{-(Integer)-})-}

View File

@ -1,15 +1,15 @@
(Statements
{+(Integer)+}
{ (Integer)
->(Integer) }
{+(Integer)+}
{+(Integer)+}
{+(Integer)+}
{ (Integer)
->(Integer) }
{+(Integer)+}
{+(Integer)+}
{+(Float)+}
{-(Integer)-}
{-(Integer)-}
{-(Integer)-}
{-(Integer)-}
{-(Integer)-}
{-(Integer)-}
{-(Float)-})

View File

@ -1,15 +1,15 @@
(Statements
{+(Integer)+}
{ (Integer)
->(Integer) }
{+(Integer)+}
{+(Integer)+}
{+(Integer)+}
{+(Integer)+}
{+(Integer)+}
{ (Integer)
->(Integer) }
{+(Float)+}
{-(Integer)-}
{-(Integer)-}
{-(Integer)-}
{-(Integer)-}
{-(Integer)-}
{-(Integer)-}
{-(Float)-})

View File

@ -1,7 +1,10 @@
(Statements
{+(Import)+}
{+(QualifiedAliasedImport
{+(Identifier)+})+}
{ (Import)
->(Import) }
{ (QualifiedAliasedImport
{-(Identifier)-})
->(QualifiedAliasedImport
{+(Identifier)+}) }
{ (Import)
->(Import) }
{+(Import)+}
@ -14,9 +17,6 @@
{+(QualifiedAliasedImport
{+(Identifier)+})+})+}
{+(SideEffectImport)+}
{-(QualifiedAliasedImport
{-(Identifier)-})-}
{-(Import)-}
{-(Import)-}
{-(Import)-}
{-(Statements

View File

@ -1,8 +1,12 @@
(Statements
{+(Import)+}
{+(QualifiedAliasedImport
{+(Identifier)+})+}
{+(Import)+}
{ (Import)
->(Import) }
{ (QualifiedAliasedImport
{-(Identifier)-})
->(QualifiedAliasedImport
{+(Identifier)+}) }
{ (Import)
->(Import) }
{+(Import)+}
{+(Import)+}
{+(Statements
@ -16,10 +20,6 @@
{+(QualifiedAliasedImport
{+(Identifier)+})+}
{-(Import)-}
{-(QualifiedAliasedImport
{-(Identifier)-})-}
{-(Import)-}
{-(Import)-}
{-(Import)-}
{-(Statements
{-(Import)-}

View File

@ -51,57 +51,36 @@
(TypeIdentifier))
(Identifier)
(Float))
{+(PublicFieldDefinition
(PublicFieldDefinition
{+(Identifier)+}
{+(Empty)+}
{+(Annotation
{+(TypeIdentifier)+})+}
{+(Identifier)+}
{+(Float)+})+}
{+(PublicFieldDefinition
{+(Identifier)+}
{+(Readonly)+}
{+(Annotation
{+(TypeIdentifier)+})+}
{+(Identifier)+}
{+(TextElement)+})+}
{+(PublicFieldDefinition
{+(Empty)+}
{+(Empty)+}
{+(Annotation
{+(TypeIdentifier)+})+}
{+(Identifier)+}
{+(Float)+})+}
{+(PublicFieldDefinition
{+(Empty)+}
{+(Empty)+}
{+(Empty)+}
{+(Identifier)+}
{+(Float)+})+}
{-(PublicFieldDefinition
{-(Empty)-}
(Empty)
{-(Readonly)-}
{-(Annotation
{-(TypeIdentifier)-})-}
{-(Identifier)-}
{-(Float)-})-}
{-(PublicFieldDefinition
(Annotation
(TypeIdentifier))
(Identifier)
(Float))
(PublicFieldDefinition
{+(Identifier)+}
{-(Empty)-}
{-(Readonly)-}
{-(Annotation
{-(TypeIdentifier)-})-}
{-(Identifier)-}
{-(Float)-})-}
{-(PublicFieldDefinition
{-(Empty)-}
{-(Empty)-}
{-(Annotation
{-(TypeIdentifier)-})-}
{-(Identifier)-}
{-(Float)-})-}
{-(PublicFieldDefinition
{-(Empty)-}
{-(Empty)-}
{-(Empty)-}
{-(Identifier)-}
{-(Float)-})-})))
(Readonly)
(Annotation
{ (TypeIdentifier)
->(TypeIdentifier) })
(Identifier)
{ (Float)
->(TextElement) })
(PublicFieldDefinition
(Empty)
(Empty)
(Annotation
(TypeIdentifier))
{ (Identifier)
->(Identifier) }
(Float))
(PublicFieldDefinition
(Empty)
(Empty)
(Empty)
(Identifier)
{ (Float)
->(Float) }))))

View File

@ -51,52 +51,36 @@
(TypeIdentifier))
(Identifier)
(Float))
{+(PublicFieldDefinition
{+(Empty)+}
{+(Readonly)+}
{+(Annotation
{+(TypeIdentifier)+})+}
{+(Identifier)+}
{+(Float)+})+}
{+(PublicFieldDefinition
{+(Empty)+}
{+(Readonly)+}
{+(Annotation
{+(TypeIdentifier)+})+}
{+(Identifier)+}
{+(Float)+})+}
(PublicFieldDefinition
{-(Identifier)-}
(Empty)
{+(Readonly)+}
(Annotation
(TypeIdentifier))
(Identifier)
(Float))
(PublicFieldDefinition
{+(Empty)+}
{-(Identifier)-}
(Readonly)
(Annotation
{ (TypeIdentifier)
->(TypeIdentifier) })
(Identifier)
{ (TextElement)
->(Float) })
(PublicFieldDefinition
(Empty)
(Empty)
(Annotation
(TypeIdentifier))
{ (Identifier)
->(Identifier) }
(Float))
{+(PublicFieldDefinition
{+(Empty)+}
{+(Empty)+}
{+(Empty)+}
{+(Identifier)+}
{+(Float)+})+}
{-(PublicFieldDefinition
{-(Identifier)-}
{-(Readonly)-}
{-(Annotation
{-(TypeIdentifier)-})-}
{-(Identifier)-}
{-(TextElement)-})-}
{-(PublicFieldDefinition
{-(Empty)-}
{-(Empty)-}
{-(Annotation
{-(TypeIdentifier)-})-}
{-(Identifier)-}
{-(Float)-})-}
{-(PublicFieldDefinition
{-(Empty)-}
{-(Empty)-}
{-(Empty)-}
{-(Identifier)-}
{-(Float)-})-})))
(PublicFieldDefinition
(Empty)
(Empty)
(Empty)
(Identifier)
{ (Float)
->(Float) }))))