]> git.saurik.com Git - cycript.git/blobdiff - Parser.hpp
Update copyright for 2014 and relicense to AGPLv3.
[cycript.git] / Parser.hpp
index 7197428bfe112e27d83b4b26ef43205005670f63..697fbeac73fbdf013e62032e896b8f23f6002d0e 100644 (file)
@@ -1,21 +1,21 @@
 /* Cycript - Optimizing JavaScript Compiler/Runtime
- * Copyright (C) 2009-2012  Jay Freeman (saurik)
+ * Copyright (C) 2009-2014  Jay Freeman (saurik)
 */
 
-/* GNU Lesser General Public License, Version 3 {{{ */
+/* GNU Affero General Public License, Version 3 {{{ */
 /*
- * Cycript is free software: you can redistribute it and/or modify it under
- * the terms of the GNU Lesser General Public License as published by the
- * Free Software Foundation, either version 3 of the License, or (at your
- * option) any later version.
- *
- * Cycript is distributed in the hope that it will be useful, but WITHOUT
- * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
- * FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser General Public
- * License for more details.
- *
- * You should have received a copy of the GNU Lesser General Public License
- * along with Cycript.  If not, see <http://www.gnu.org/licenses/>.
+ * This program is free software: you can redistribute it and/or modify
+ * it under the terms of the GNU Affero General Public License as published by
+ * the Free Software Foundation, either version 3 of the License, or
+ * (at your option) any later version.
+
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU Affero General Public License for more details.
+
+ * You should have received a copy of the GNU Affero General Public License
+ * along with this program.  If not, see <http://www.gnu.org/licenses/>.
 **/
 /* }}} */
 
@@ -24,7 +24,6 @@
 
 #include <iostream>
 
-#include <stack>
 #include <string>
 #include <vector>
 #include <map>
 #include <cstdio>
 #include <cstdlib>
 
-#include "location.hh"
-
 #include "List.hpp"
 #include "Pooling.hpp"
 #include "Options.hpp"
 
-class CYContext;
+struct CYContext;
 
 struct CYThing {
     virtual ~CYThing() {
@@ -350,11 +347,14 @@ struct CYProgram :
 };
 
 struct CYNonLocal;
+struct CYThisScope;
 
 struct CYContext {
     CYOptions &options_;
 
     CYScope *scope_;
+    CYThisScope *this_;
+
     CYIdentifierUsageVector rename_;
 
     CYNonLocal *nonlocal_;
@@ -364,6 +364,7 @@ struct CYContext {
     CYContext(CYOptions &options) :
         options_(options),
         scope_(NULL),
+        this_(NULL),
         nonlocal_(NULL),
         nextlocal_(NULL),
         unique_(0)
@@ -414,6 +415,25 @@ struct CYNonLocal {
     }
 };
 
+struct CYThisScope :
+    CYNext<CYThisScope>
+{
+    CYIdentifier *identifier_;
+
+    CYThisScope() :
+        identifier_(NULL)
+    {
+    }
+
+    CYIdentifier *Identifier(CYContext &context) {
+        if (next_ != NULL)
+            return next_->Identifier(context);
+        if (identifier_ == NULL)
+            identifier_ = context.Unique();
+        return identifier_;
+    }
+};
+
 struct CYBlock :
     CYStatement,
     CYThing
@@ -430,7 +450,7 @@ struct CYBlock :
     }
 
     void AddPrev(CYStatement *statement) {
-        CYSetLast(statement, statements_);
+        CYSetLast(statement) = statements_;
         statements_ = statement;
     }
 
@@ -440,89 +460,6 @@ struct CYBlock :
     virtual void Output(CYOutput &out, CYFlags flags) const;
 };
 
-enum CYState {
-    CYClear,
-    CYRestricted,
-    CYNewLine
-};
-
-class CYDriver {
-  public:
-    void *scanner_;
-
-    CYState state_;
-    bool nobrace_;
-    std::stack<bool> in_;
-
-    const char *data_;
-    size_t size_;
-    FILE *file_;
-
-    bool strict_;
-
-    enum Condition {
-        RegExpCondition,
-        XMLContentCondition,
-        XMLTagCondition,
-    };
-
-    std::string filename_;
-
-    struct Error {
-        bool warning_;
-        cy::location location_;
-        std::string message_;
-    };
-
-    typedef std::vector<Error> Errors;
-
-    CYProgram *program_;
-    Errors errors_;
-
-    bool auto_;
-
-    struct Context {
-        CYExpression *context_;
-
-        Context(CYExpression *context) :
-            context_(context)
-        {
-        }
-
-        typedef std::vector<CYWord *> Words;
-        Words words_;
-    };
-
-    typedef std::vector<Context> Contexts;
-    Contexts contexts_;
-
-    CYExpression *context_;
-
-    enum Mode {
-        AutoNone,
-        AutoPrimary,
-        AutoDirect,
-        AutoIndirect,
-        AutoMessage
-    } mode_;
-
-  private:
-    void ScannerInit();
-    void ScannerDestroy();
-
-  public:
-    CYDriver(const std::string &filename = "");
-    ~CYDriver();
-
-    Condition GetCondition();
-    void SetCondition(Condition condition);
-
-    void PushCondition(Condition condition);
-    void PopCondition();
-
-    void Warning(const cy::location &location, const char *message);
-};
-
 struct CYForInitialiser {
     virtual ~CYForInitialiser() {
     }
@@ -548,13 +485,12 @@ struct CYNumber;
 struct CYString;
 
 struct CYExpression :
-    CYNext<CYExpression>,
     CYForInitialiser,
     CYForInInitialiser,
     CYClassName,
     CYThing
 {
-    virtual unsigned Precedence() const = 0;
+    virtual int Precedence() const = 0;
 
     virtual bool RightHand() const {
         return true;
@@ -567,7 +503,7 @@ struct CYExpression :
 
     virtual void Output(CYOutput &out) const;
     virtual void Output(CYOutput &out, CYFlags flags) const = 0;
-    void Output(CYOutput &out, unsigned precedence, CYFlags flags) const;
+    void Output(CYOutput &out, int precedence, CYFlags flags) const;
 
     virtual CYExpression *ClassName(CYContext &context, bool object);
     virtual void ClassName(CYOutput &out, bool object) const;
@@ -576,7 +512,7 @@ struct CYExpression :
     virtual CYAssignment *Assignment(CYContext &context);
 
     virtual CYExpression *Primitive(CYContext &context) {
-        return this;
+        return NULL;
     }
 
     virtual CYNumber *Number(CYContext &context) {
@@ -598,8 +534,8 @@ struct CYExpression :
     }
 
 #define CYPrecedence(value) \
-    static const unsigned Precedence_ = value; \
-    virtual unsigned Precedence() const { \
+    static const int Precedence_ = value; \
+    virtual int Precedence() const { \
         return Precedence_; \
     }
 
@@ -611,16 +547,16 @@ struct CYExpression :
 struct CYCompound :
     CYExpression
 {
-    CYExpression *expressions_;
+    CYExpression *expression_;
+    CYExpression *next_;
 
-    CYCompound(CYExpression *expressions = NULL) :
-        expressions_(expressions)
+    CYCompound(CYExpression *expression, CYExpression *next = NULL) :
+        expression_(expression),
+        next_(next)
     {
-    }
-
-    void AddPrev(CYExpression *expression) {
-        CYSetLast(expression, expressions_);
-        expressions_ = expression;
+        if (expression_ == NULL)
+            throw;
+        _assert(expression_ != NULL);
     }
 
     CYPrecedence(17)
@@ -653,6 +589,16 @@ struct CYComprehension :
     CYNext<CYComprehension>,
     CYThing
 {
+    CYComprehension(CYComprehension *next = NULL) :
+        CYNext<CYComprehension>(next)
+    {
+    }
+
+    CYComprehension *Modify(CYComprehension *next) {
+        next_ = next;
+        return this;
+    }
+
     virtual const char *Name() const = 0;
 
     virtual CYFunctionParameter *Parameter(CYContext &context) const = 0;
@@ -667,7 +613,8 @@ struct CYForInComprehension :
     CYIdentifier *name_;
     CYExpression *set_;
 
-    CYForInComprehension(CYIdentifier *name, CYExpression *set) :
+    CYForInComprehension(CYIdentifier *name, CYExpression *set, CYComprehension *next = NULL) :
+        CYComprehension(next),
         name_(name),
         set_(set)
     {
@@ -688,7 +635,8 @@ struct CYForOfComprehension :
     CYIdentifier *name_;
     CYExpression *set_;
 
-    CYForOfComprehension(CYIdentifier *name, CYExpression *set) :
+    CYForOfComprehension(CYIdentifier *name, CYExpression *set, CYComprehension *next = NULL) :
+        CYComprehension(next),
         name_(name),
         set_(set)
     {
@@ -708,7 +656,8 @@ struct CYIfComprehension :
 {
     CYExpression *test_;
 
-    CYIfComprehension(CYExpression *test) :
+    CYIfComprehension(CYExpression *test, CYComprehension *next = NULL) :
+        CYComprehension(next),
         test_(test)
     {
     }
@@ -745,6 +694,10 @@ struct CYLiteral :
 {
     CYPrecedence(0)
     CYRightHand(false)
+
+    virtual CYExpression *Primitive(CYContext &context) {
+        return this;
+    }
 };
 
 struct CYTrivial :
@@ -1364,7 +1317,7 @@ struct New :
     {
     }
 
-    virtual unsigned Precedence() const {
+    virtual int Precedence() const {
         return arguments_ == NULL ? 2 : 1;
     }
 
@@ -1475,7 +1428,9 @@ struct CYFunction {
     CYIdentifier *name_;
     CYFunctionParameter *parameters_;
     CYBlock code_;
+
     CYNonLocal *nonlocal_;
+    CYThisScope this_;
 
     CYFunction(CYIdentifier *name, CYFunctionParameter *parameters, CYStatement *statements) :
         name_(name),
@@ -1510,6 +1465,23 @@ struct CYFunctionExpression :
     virtual void Output(CYOutput &out, CYFlags flags) const;
 };
 
+// XXX: this should derive from CYAnonymousFunction
+struct CYFatArrow :
+    CYFunction,
+    CYExpression
+{
+    CYFatArrow(CYFunctionParameter *parameters, CYStatement *statements) :
+        CYFunction(NULL, parameters, statements)
+    {
+    }
+
+    CYPrecedence(0)
+    CYRightHand(false)
+
+    virtual CYExpression *Replace(CYContext &context);
+    virtual void Output(CYOutput &out, CYFlags flags) const;
+};
+
 // XXX: this should derive from CYAnonymousFunctionExpression
 struct CYRubyProc :
     CYFunctionExpression
@@ -1545,7 +1517,7 @@ struct CYExpress :
     CYExpress(CYExpression *expression) :
         expression_(expression)
     {
-        if (expression == NULL)
+        if (expression_ == NULL)
             throw;
     }
 
@@ -1616,6 +1588,347 @@ struct CYFinally :
     virtual void Output(CYOutput &out) const;
 };
 
+struct CYTypeSpecifier :
+    CYThing
+{
+    virtual CYExpression *Replace(CYContext &context) = 0;
+};
+
+struct CYTypeError :
+    CYTypeSpecifier
+{
+    CYTypeError() {
+    }
+
+    virtual CYExpression *Replace(CYContext &context);
+    virtual void Output(CYOutput &out) const;
+};
+
+struct CYTypeVoid :
+    CYTypeSpecifier
+{
+    CYTypeVoid() {
+    }
+
+    virtual CYExpression *Replace(CYContext &context);
+    virtual void Output(CYOutput &out) const;
+};
+
+struct CYTypeVariable :
+    CYTypeSpecifier
+{
+    CYIdentifier *name_;
+
+    CYTypeVariable(CYIdentifier *name) :
+        name_(name)
+    {
+    }
+
+    CYTypeVariable(const char *name) :
+        name_(new($pool) CYIdentifier(name))
+    {
+    }
+
+    virtual CYExpression *Replace(CYContext &context);
+    virtual void Output(CYOutput &out) const;
+};
+
+struct CYTypeUnsigned :
+    CYTypeSpecifier
+{
+    CYTypeSpecifier *specifier_;
+
+    CYTypeUnsigned(CYTypeSpecifier *specifier) :
+        specifier_(specifier)
+    {
+    }
+
+    virtual CYExpression *Replace(CYContext &context);
+    virtual void Output(CYOutput &out) const;
+};
+
+struct CYTypeSigned :
+    CYTypeSpecifier
+{
+    CYTypeSpecifier *specifier_;
+
+    CYTypeSigned(CYTypeSpecifier *specifier) :
+        specifier_(specifier)
+    {
+    }
+
+    virtual CYExpression *Replace(CYContext &context);
+    virtual void Output(CYOutput &out) const;
+};
+
+struct CYTypeLong :
+    CYTypeSpecifier
+{
+    CYTypeSpecifier *specifier_;
+
+    CYTypeLong(CYTypeSpecifier *specifier) :
+        specifier_(specifier)
+    {
+    }
+
+    virtual CYExpression *Replace(CYContext &context);
+    virtual void Output(CYOutput &out) const;
+};
+
+struct CYTypeShort :
+    CYTypeSpecifier
+{
+    CYTypeSpecifier *specifier_;
+
+    CYTypeShort(CYTypeSpecifier *specifier) :
+        specifier_(specifier)
+    {
+    }
+
+    virtual CYExpression *Replace(CYContext &context);
+    virtual void Output(CYOutput &out) const;
+};
+
+struct CYTypeModifier :
+    CYNext<CYTypeModifier>
+{
+    CYTypeModifier(CYTypeModifier *next) :
+        CYNext<CYTypeModifier>(next)
+    {
+    }
+
+    virtual int Precedence() const = 0;
+
+    virtual CYExpression *Replace_(CYContext &context, CYExpression *type) = 0;
+    CYExpression *Replace(CYContext &context, CYExpression *type);
+
+    virtual void Output(CYOutput &out, CYIdentifier *identifier) const = 0;
+    void Output(CYOutput &out, int precedence, CYIdentifier *identifier) const;
+};
+
+struct CYTypeArrayOf :
+    CYTypeModifier
+{
+    CYExpression *size_;
+
+    CYTypeArrayOf(CYExpression *size, CYTypeModifier *next = NULL) :
+        CYTypeModifier(next),
+        size_(size)
+    {
+    }
+
+    CYPrecedence(1)
+
+    virtual CYExpression *Replace_(CYContext &context, CYExpression *type);
+    virtual void Output(CYOutput &out, CYIdentifier *identifier) const;
+};
+
+struct CYTypeConstant :
+    CYTypeModifier
+{
+    CYTypeConstant(CYTypeModifier *next = NULL) :
+        CYTypeModifier(next)
+    {
+    }
+
+    CYPrecedence(0)
+
+    virtual CYExpression *Replace_(CYContext &context, CYExpression *type);
+    virtual void Output(CYOutput &out, CYIdentifier *identifier) const;
+};
+
+struct CYTypePointerTo :
+    CYTypeModifier
+{
+    CYTypePointerTo(CYTypeModifier *next = NULL) :
+        CYTypeModifier(next)
+    {
+    }
+
+    CYPrecedence(0)
+
+    virtual CYExpression *Replace_(CYContext &context, CYExpression *type);
+    virtual void Output(CYOutput &out, CYIdentifier *identifier) const;
+};
+
+struct CYTypeVolatile :
+    CYTypeModifier
+{
+    CYTypeVolatile(CYTypeModifier *next = NULL) :
+        CYTypeModifier(next)
+    {
+    }
+
+    CYPrecedence(0)
+
+    virtual CYExpression *Replace_(CYContext &context, CYExpression *type);
+    virtual void Output(CYOutput &out, CYIdentifier *identifier) const;
+};
+
+struct CYTypedIdentifier :
+    CYNext<CYTypedIdentifier>,
+    CYThing
+{
+    CYIdentifier *identifier_;
+    CYTypeSpecifier *specifier_;
+    CYTypeModifier *modifier_;
+
+    CYTypedIdentifier(CYIdentifier *identifier = NULL) :
+        identifier_(identifier),
+        specifier_(NULL),
+        modifier_(NULL)
+    {
+    }
+
+    CYTypedIdentifier(CYTypeSpecifier *specifier, CYTypeModifier *modifier = NULL) :
+        identifier_(NULL),
+        specifier_(specifier),
+        modifier_(modifier)
+    {
+    }
+
+    inline CYTypedIdentifier *Modify(CYTypeModifier *modifier) {
+        CYSetLast(modifier_) = modifier;
+        return this;
+    }
+
+    virtual CYExpression *Replace(CYContext &context);
+    virtual void Output(CYOutput &out) const;
+};
+
+struct CYEncodedType :
+    CYExpression
+{
+    CYTypedIdentifier *typed_;
+
+    CYEncodedType(CYTypedIdentifier *typed) :
+        typed_(typed)
+    {
+    }
+
+    CYPrecedence(1)
+
+    virtual CYExpression *Replace(CYContext &context);
+    virtual void Output(CYOutput &out, CYFlags flags) const;
+};
+
+struct CYTypedParameter :
+    CYNext<CYTypedParameter>,
+    CYThing
+{
+    CYTypedIdentifier *typed_;
+
+    CYTypedParameter(CYTypedIdentifier *typed, CYTypedParameter *next) :
+        CYNext<CYTypedParameter>(next),
+        typed_(typed)
+    {
+    }
+
+    CYArgument *Argument(CYContext &context);
+    CYFunctionParameter *Parameters(CYContext &context);
+    CYExpression *TypeSignature(CYContext &context, CYExpression *prefix);
+
+    virtual void Output(CYOutput &out) const;
+};
+
+struct CYLambda :
+    CYExpression
+{
+    CYTypedIdentifier *typed_;
+    CYTypedParameter *parameters_;
+    CYStatement *statements_;
+
+    CYLambda(CYTypedIdentifier *typed, CYTypedParameter *parameters, CYStatement *statements) :
+        typed_(typed),
+        parameters_(parameters),
+        statements_(statements)
+    {
+    }
+
+    CYPrecedence(1)
+
+    virtual CYExpression *Replace(CYContext &context);
+    virtual void Output(CYOutput &out, CYFlags flags) const;
+};
+
+struct CYModule :
+    CYNext<CYModule>,
+    CYThing
+{
+    CYWord *part_;
+
+    CYModule(CYWord *part, CYModule *next = NULL) :
+        CYNext<CYModule>(next),
+        part_(part)
+    {
+    }
+
+    CYString *Replace(CYContext &context, const char *separator) const;
+    void Output(CYOutput &out) const;
+};
+
+struct CYImport :
+    CYStatement
+{
+    CYModule *module_;
+
+    CYImport(CYModule *module) :
+        module_(module)
+    {
+    }
+
+    virtual CYStatement *Replace(CYContext &context);
+    virtual void Output(CYOutput &out, CYFlags flags) const;
+};
+
+struct CYTypeDefinition :
+    CYStatement
+{
+    CYTypedIdentifier *typed_;
+
+    CYTypeDefinition(CYTypedIdentifier *typed) :
+        typed_(typed)
+    {
+    }
+
+    virtual CYStatement *Replace(CYContext &context);
+    virtual void Output(CYOutput &out, CYFlags flags) const;
+};
+
+struct CYTypeBlockWith :
+    CYTypeModifier
+{
+    CYTypedParameter *parameters_;
+
+    CYTypeBlockWith(CYTypedParameter *parameters, CYTypeModifier *next = NULL) :
+        CYTypeModifier(next),
+        parameters_(parameters)
+    {
+    }
+
+    CYPrecedence(0)
+
+    virtual CYExpression *Replace_(CYContext &context, CYExpression *type);
+    virtual void Output(CYOutput &out, CYIdentifier *identifier) const;
+};
+
+struct CYTypeFunctionWith :
+    CYTypeModifier
+{
+    CYTypedParameter *parameters_;
+
+    CYTypeFunctionWith(CYTypedParameter *parameters, CYTypeModifier *next = NULL) :
+        CYTypeModifier(next),
+        parameters_(parameters)
+    {
+    }
+
+    CYPrecedence(1)
+
+    virtual CYExpression *Replace_(CYContext &context, CYExpression *type);
+    virtual void Output(CYOutput &out, CYIdentifier *identifier) const;
+};
+
 namespace cy {
 namespace Syntax {
 
@@ -1843,7 +2156,7 @@ CYPrefix_(false, "-", Negate)
 CYPrefix_(false, "~", BitwiseNot)
 CYPrefix_(false, "!", LogicalNot)
 
-CYInfix_(false, 5, "*", Multiply)
+CYInfix_(false, 5, "*", Multiply, CYReplace)
 CYInfix_(false, 5, "/", Divide)
 CYInfix_(false, 5, "%", Modulus)
 CYInfix_(false, 6, "+", Add, CYReplace)