2016-11-10 02:39:07 +03:00
|
|
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
2016-10-13 00:28:27 +03:00
|
|
|
{-# OPTIONS_GHC -funbox-strict-fields #-}
|
2016-02-04 21:59:33 +03:00
|
|
|
module Category where
|
2015-11-18 22:23:35 +03:00
|
|
|
|
2016-05-26 19:58:04 +03:00
|
|
|
import Prologue
|
2016-07-28 20:48:44 +03:00
|
|
|
import Test.QuickCheck hiding (Args)
|
2016-11-10 02:39:07 +03:00
|
|
|
import Data.Text (pack)
|
2016-07-06 23:22:25 +03:00
|
|
|
import Data.Text.Arbitrary()
|
2015-11-18 22:23:35 +03:00
|
|
|
|
2016-02-05 00:35:42 +03:00
|
|
|
-- | A standardized category of AST node. Used to determine the semantics for
|
|
|
|
-- | semantic diffing and define comparability of nodes.
|
2016-06-04 01:32:21 +03:00
|
|
|
data Category
|
2016-06-04 01:34:42 +03:00
|
|
|
-- | The top-level branch node.
|
|
|
|
= Program
|
2016-06-04 01:37:40 +03:00
|
|
|
-- | A node indicating syntax errors.
|
|
|
|
| Error
|
2016-06-16 17:54:05 +03:00
|
|
|
-- | A boolean expression.
|
|
|
|
| Boolean
|
2016-08-17 18:59:24 +03:00
|
|
|
-- | A bitwise operator.
|
|
|
|
| BitwiseOperator
|
2016-09-17 01:20:36 +03:00
|
|
|
-- | A boolean operator (e.g. ||, &&).
|
|
|
|
| BooleanOperator
|
2016-02-05 00:35:42 +03:00
|
|
|
-- | A literal key-value data structure.
|
2016-02-06 00:59:38 +03:00
|
|
|
| DictionaryLiteral
|
2016-02-14 05:01:52 +03:00
|
|
|
-- | A pair, e.g. of a key & value
|
|
|
|
| Pair
|
2016-02-06 00:54:08 +03:00
|
|
|
-- | A call to a function.
|
|
|
|
| FunctionCall
|
2016-06-10 22:19:29 +03:00
|
|
|
-- | A function declaration.
|
2016-06-10 20:11:32 +03:00
|
|
|
| Function
|
2016-06-10 22:19:29 +03:00
|
|
|
-- | An identifier.
|
|
|
|
| Identifier
|
2016-06-12 21:29:48 +03:00
|
|
|
-- | A function's parameters.
|
2016-06-10 22:10:50 +03:00
|
|
|
| Params
|
2016-06-12 21:29:48 +03:00
|
|
|
-- | A function's expression statements.
|
2016-06-10 22:10:50 +03:00
|
|
|
| ExpressionStatements
|
2016-06-13 00:26:20 +03:00
|
|
|
-- | A method call on an object.
|
|
|
|
| MethodCall
|
2016-06-14 19:53:35 +03:00
|
|
|
-- | A method's arguments.
|
|
|
|
| Args
|
2016-02-24 23:47:53 +03:00
|
|
|
-- | A string literal.
|
|
|
|
| StringLiteral
|
|
|
|
-- | An integer literal.
|
|
|
|
| IntegerLiteral
|
2016-06-15 19:09:52 +03:00
|
|
|
-- | A regex literal.
|
|
|
|
| Regex
|
2016-08-12 20:42:22 +03:00
|
|
|
-- | A return statement.
|
|
|
|
| Return
|
2016-02-24 23:47:53 +03:00
|
|
|
-- | A symbol literal.
|
|
|
|
| SymbolLiteral
|
2016-06-15 18:38:16 +03:00
|
|
|
-- | A template string literal.
|
|
|
|
| TemplateString
|
2016-03-03 07:01:46 +03:00
|
|
|
-- | An array literal.
|
|
|
|
| ArrayLiteral
|
2016-06-14 01:31:45 +03:00
|
|
|
-- | An assignment expression.
|
2016-06-14 00:31:32 +03:00
|
|
|
| Assignment
|
2016-06-17 22:57:51 +03:00
|
|
|
-- | A math assignment expression.
|
|
|
|
| MathAssignment
|
2016-06-14 01:31:45 +03:00
|
|
|
-- | A member access expression.
|
|
|
|
| MemberAccess
|
2016-06-17 22:38:12 +03:00
|
|
|
-- | A subscript access expression.
|
|
|
|
| SubscriptAccess
|
2016-06-15 03:43:26 +03:00
|
|
|
-- | A variable assignment within a variable declaration.
|
|
|
|
| VarAssignment
|
|
|
|
-- | A variable declaration.
|
|
|
|
| VarDecl
|
2016-06-17 23:31:50 +03:00
|
|
|
-- | A switch expression.
|
2016-06-16 01:48:27 +03:00
|
|
|
| Switch
|
2016-08-12 00:39:44 +03:00
|
|
|
-- | A if/else expression.
|
|
|
|
| If
|
2016-07-28 20:48:44 +03:00
|
|
|
-- | A for expression.
|
|
|
|
| For
|
2016-07-28 21:00:28 +03:00
|
|
|
-- | A while expression.
|
|
|
|
| While
|
|
|
|
-- | A do/while expression.
|
|
|
|
| DoWhile
|
2016-06-17 23:31:40 +03:00
|
|
|
-- | A ternary expression.
|
|
|
|
| Ternary
|
2016-06-17 23:31:50 +03:00
|
|
|
-- | A case expression.
|
2016-06-16 01:48:27 +03:00
|
|
|
| Case
|
2016-06-18 01:02:54 +03:00
|
|
|
-- | An expression with an operator.
|
|
|
|
| Operator
|
2016-08-16 22:44:02 +03:00
|
|
|
-- | An comma operator expression
|
|
|
|
| CommaOperator
|
2016-06-24 00:39:27 +03:00
|
|
|
-- | An object/dictionary/hash literal.
|
|
|
|
| Object
|
2016-07-29 22:32:54 +03:00
|
|
|
-- | A throw statement.
|
|
|
|
| Throw
|
2016-07-30 21:25:52 +03:00
|
|
|
-- | A constructor statement, e.g. new Foo;
|
|
|
|
| Constructor
|
2016-07-29 22:58:49 +03:00
|
|
|
-- | A try statement.
|
|
|
|
| Try
|
|
|
|
-- | A catch statement.
|
|
|
|
| Catch
|
|
|
|
-- | A finally statement.
|
|
|
|
| Finally
|
2016-07-29 23:28:27 +03:00
|
|
|
-- | A class declaration.
|
|
|
|
| Class
|
2016-07-30 06:41:21 +03:00
|
|
|
-- | A class method declaration.
|
|
|
|
| Method
|
2016-08-16 21:08:23 +03:00
|
|
|
-- | A comment.
|
|
|
|
| Comment
|
2016-02-05 00:35:42 +03:00
|
|
|
-- | A non-standard category, which can be used for comparability.
|
2016-06-06 22:45:44 +03:00
|
|
|
| Other Text
|
2016-08-18 00:12:40 +03:00
|
|
|
-- | A relational operator (e.g. < or >=)
|
|
|
|
| RelationalOperator
|
2016-08-19 22:53:04 +03:00
|
|
|
-- | An empty statement. (e.g. ; in JavaScript)
|
|
|
|
| Empty
|
2016-09-13 07:06:53 +03:00
|
|
|
-- | A number literal.
|
|
|
|
| NumberLiteral
|
2016-09-17 01:20:55 +03:00
|
|
|
-- | A mathematical operator (e.g. +, -, *, /).
|
|
|
|
| MathOperator
|
2016-10-04 01:18:09 +03:00
|
|
|
-- | A module
|
|
|
|
| Module
|
2016-10-06 23:18:09 +03:00
|
|
|
-- | An import
|
|
|
|
| Import
|
|
|
|
-- | An export
|
|
|
|
| Export
|
2016-11-02 22:25:50 +03:00
|
|
|
-- | An anonymous function.
|
2016-11-01 21:36:23 +03:00
|
|
|
| AnonymousFunction
|
2016-10-24 20:43:31 +03:00
|
|
|
-- | An interpolation (e.g. "#{bar}" in Ruby)
|
2016-10-21 23:55:00 +03:00
|
|
|
| Interpolation
|
2016-10-24 20:43:31 +03:00
|
|
|
-- | A subshell command (e.g. `ls -la` in Ruby)
|
|
|
|
| Subshell
|
2016-12-06 22:42:41 +03:00
|
|
|
-- | Operator assignment, e.g. a ||= b, a += 1 in Ruby.
|
|
|
|
| OperatorAssignment
|
2016-10-26 20:27:38 +03:00
|
|
|
-- | A yield statement.
|
|
|
|
| Yield
|
2016-10-26 22:54:21 +03:00
|
|
|
-- | An until expression.
|
|
|
|
| Until
|
2016-10-27 00:49:51 +03:00
|
|
|
-- | A unless/else expression.
|
|
|
|
| Unless
|
2016-11-02 20:52:40 +03:00
|
|
|
| Begin
|
2016-11-02 21:10:01 +03:00
|
|
|
| Else
|
2016-11-02 22:32:46 +03:00
|
|
|
| Elsif
|
2016-11-02 22:55:48 +03:00
|
|
|
| Ensure
|
2016-11-02 23:05:30 +03:00
|
|
|
| Rescue
|
2016-11-03 19:23:35 +03:00
|
|
|
| RescueModifier
|
2016-11-07 19:00:06 +03:00
|
|
|
| RescuedException
|
2016-11-09 21:48:22 +03:00
|
|
|
| RescueArgs
|
|
|
|
| When
|
2016-11-08 01:23:17 +03:00
|
|
|
| Negate
|
2016-11-15 01:47:04 +03:00
|
|
|
-- | A select expression in Go.
|
|
|
|
| Select
|
2016-11-15 03:05:02 +03:00
|
|
|
| Defer
|
|
|
|
| Go
|
2016-11-21 21:01:38 +03:00
|
|
|
| Slice
|
2016-11-21 23:27:06 +03:00
|
|
|
| TypeAssertion
|
2016-11-21 23:44:31 +03:00
|
|
|
| TypeConversion
|
2016-11-10 23:59:48 +03:00
|
|
|
-- | An argument pair, e.g. foo(run: true) or foo(:run => true) in Ruby.
|
2016-11-09 21:48:50 +03:00
|
|
|
| ArgumentPair
|
2016-11-10 23:59:48 +03:00
|
|
|
-- | A keyword parameter, e.g. def foo(name:) or def foo(name:false) in Ruby.
|
2016-11-10 23:55:06 +03:00
|
|
|
| KeywordParameter
|
2016-11-10 23:59:48 +03:00
|
|
|
-- | An optional/default parameter, e.g. def foo(name = nil) in Ruby.
|
2016-11-10 20:56:36 +03:00
|
|
|
| OptionalParameter
|
2016-11-10 23:59:48 +03:00
|
|
|
-- | A splat parameter, e.g. def foo(*array) in Ruby.
|
2016-11-10 20:56:36 +03:00
|
|
|
| SplatParameter
|
2016-11-10 23:59:48 +03:00
|
|
|
-- | A hash splat parameter, e.g. def foo(**option) in Ruby.
|
2016-11-10 20:56:36 +03:00
|
|
|
| HashSplatParameter
|
2016-11-10 23:59:48 +03:00
|
|
|
-- | A block parameter, e.g. def foo(&block) in Ruby.
|
2016-11-10 20:56:36 +03:00
|
|
|
| BlockParameter
|
2016-12-01 23:33:37 +03:00
|
|
|
-- | A float literal.
|
|
|
|
| FloatLiteral
|
2016-12-07 00:09:04 +03:00
|
|
|
| ArrayTy
|
|
|
|
| DictionaryTy
|
|
|
|
| StructTy
|
|
|
|
| Struct
|
2016-12-01 00:30:11 +03:00
|
|
|
-- | A break statement, e.g. break; in JavaScript.
|
|
|
|
| Break
|
2016-12-01 00:40:06 +03:00
|
|
|
-- | A continue statement, e.g. continue; in JavaScript.
|
|
|
|
| Continue
|
2016-12-06 22:23:10 +03:00
|
|
|
-- | A binary statement, e.g. a | b in Ruby.
|
|
|
|
| Binary
|
|
|
|
-- | A unary statement, e.g. !a in Ruby.
|
|
|
|
| Unary
|
2016-12-07 21:45:55 +03:00
|
|
|
-- | A constant, e.g `Foo::Bar` in Ruby.
|
|
|
|
| Constant
|
|
|
|
-- | A superclass, e.g `< Foo` in Ruby.
|
|
|
|
| Superclass
|
2016-12-11 19:36:26 +03:00
|
|
|
-- | A singleton class declaration, e.g. `class << self;end` in Ruby
|
2016-12-10 03:12:07 +03:00
|
|
|
| SingletonClass
|
2016-12-11 19:36:26 +03:00
|
|
|
-- | A range expression, e.g. `1..10` in Ruby.
|
|
|
|
| RangeExpression
|
2016-12-12 19:30:43 +03:00
|
|
|
-- | A scope resolution operator, e.g. `Foo::bar` in Ruby.
|
|
|
|
| ScopeOperator
|
2016-12-13 00:41:55 +03:00
|
|
|
-- | A BEGIN {} block of statements.
|
|
|
|
| BeginBlock
|
|
|
|
-- | An END {} block of statements.
|
|
|
|
| EndBlock
|
2017-01-10 23:09:09 +03:00
|
|
|
| ParameterDecl
|
2017-01-11 00:05:55 +03:00
|
|
|
-- | A default case in a switch statement.
|
|
|
|
| Default
|
2017-01-11 02:04:34 +03:00
|
|
|
-- | A type declaration.
|
|
|
|
| TypeDecl
|
2016-06-23 16:55:43 +03:00
|
|
|
deriving (Eq, Generic, Ord, Show)
|
2016-06-23 16:55:48 +03:00
|
|
|
|
2016-06-23 23:25:49 +03:00
|
|
|
-- Instances
|
|
|
|
|
2016-06-23 16:55:48 +03:00
|
|
|
instance Hashable Category
|
2016-06-23 23:29:19 +03:00
|
|
|
|
2016-11-10 02:39:07 +03:00
|
|
|
instance (StringConv Category Text) where
|
|
|
|
strConv _ = pack . show
|
|
|
|
|
2016-06-23 23:29:19 +03:00
|
|
|
instance Arbitrary Category where
|
2016-07-13 21:32:53 +03:00
|
|
|
arbitrary = oneof [
|
2016-07-17 18:18:31 +03:00
|
|
|
pure Program
|
2016-06-23 23:29:19 +03:00
|
|
|
, pure Error
|
2016-07-13 21:32:53 +03:00
|
|
|
, pure Boolean
|
2016-09-17 01:20:36 +03:00
|
|
|
, pure BooleanOperator
|
2016-09-17 01:20:55 +03:00
|
|
|
, pure MathOperator
|
2016-06-23 23:29:19 +03:00
|
|
|
, pure DictionaryLiteral
|
|
|
|
, pure Pair
|
|
|
|
, pure FunctionCall
|
2016-07-13 21:32:53 +03:00
|
|
|
, pure Function
|
|
|
|
, pure Identifier
|
|
|
|
, pure Params
|
|
|
|
, pure ExpressionStatements
|
|
|
|
, pure MethodCall
|
|
|
|
, pure Args
|
2016-06-23 23:29:19 +03:00
|
|
|
, pure StringLiteral
|
|
|
|
, pure IntegerLiteral
|
2016-09-13 07:06:53 +03:00
|
|
|
, pure NumberLiteral
|
2016-12-01 23:33:37 +03:00
|
|
|
, pure FloatLiteral
|
2016-07-13 21:32:53 +03:00
|
|
|
, pure Regex
|
2016-08-12 20:42:22 +03:00
|
|
|
, pure Return
|
2016-06-23 23:29:19 +03:00
|
|
|
, pure SymbolLiteral
|
2016-07-13 21:32:53 +03:00
|
|
|
, pure TemplateString
|
2016-06-23 23:29:19 +03:00
|
|
|
, pure ArrayLiteral
|
2016-07-13 21:32:53 +03:00
|
|
|
, pure Assignment
|
|
|
|
, pure MathAssignment
|
|
|
|
, pure MemberAccess
|
|
|
|
, pure SubscriptAccess
|
|
|
|
, pure VarAssignment
|
|
|
|
, pure VarDecl
|
2016-07-28 21:00:28 +03:00
|
|
|
, pure For
|
|
|
|
, pure DoWhile
|
|
|
|
, pure While
|
2016-07-13 21:32:53 +03:00
|
|
|
, pure Switch
|
|
|
|
, pure Ternary
|
|
|
|
, pure Case
|
|
|
|
, pure Operator
|
|
|
|
, pure Object
|
2016-08-12 20:42:22 +03:00
|
|
|
, pure Throw
|
|
|
|
, pure Constructor
|
|
|
|
, pure Try
|
|
|
|
, pure Catch
|
|
|
|
, pure Finally
|
|
|
|
, pure Class
|
|
|
|
, pure Method
|
2016-10-04 01:18:09 +03:00
|
|
|
, pure Module
|
2016-10-06 23:18:09 +03:00
|
|
|
, pure Import
|
|
|
|
, pure Export
|
2016-10-21 23:55:00 +03:00
|
|
|
, pure Interpolation
|
2016-10-24 20:43:31 +03:00
|
|
|
, pure Subshell
|
2016-12-06 22:42:41 +03:00
|
|
|
, pure OperatorAssignment
|
2016-10-26 20:27:38 +03:00
|
|
|
, pure Yield
|
2016-10-26 22:54:21 +03:00
|
|
|
, pure Until
|
2016-10-27 00:49:51 +03:00
|
|
|
, pure Unless
|
2016-11-02 20:52:40 +03:00
|
|
|
, pure Begin
|
2016-11-02 21:10:01 +03:00
|
|
|
, pure Else
|
2016-11-02 22:32:46 +03:00
|
|
|
, pure Elsif
|
2016-11-02 22:55:48 +03:00
|
|
|
, pure Ensure
|
2016-11-02 23:05:30 +03:00
|
|
|
, pure Rescue
|
2016-11-03 19:23:35 +03:00
|
|
|
, pure RescueModifier
|
2016-11-07 19:00:06 +03:00
|
|
|
, pure RescuedException
|
2016-11-09 21:48:22 +03:00
|
|
|
, pure RescueArgs
|
|
|
|
, pure When
|
2016-11-08 01:23:17 +03:00
|
|
|
, pure Negate
|
2016-11-15 03:05:02 +03:00
|
|
|
, pure Select
|
|
|
|
, pure Defer
|
|
|
|
, pure Go
|
2016-11-21 21:01:38 +03:00
|
|
|
, pure Slice
|
2016-11-21 23:27:06 +03:00
|
|
|
, pure TypeAssertion
|
2016-11-21 23:44:31 +03:00
|
|
|
, pure TypeConversion
|
2016-11-09 21:48:50 +03:00
|
|
|
, pure ArgumentPair
|
2016-11-10 23:55:06 +03:00
|
|
|
, pure KeywordParameter
|
2016-11-10 20:56:36 +03:00
|
|
|
, pure OptionalParameter
|
|
|
|
, pure SplatParameter
|
|
|
|
, pure HashSplatParameter
|
|
|
|
, pure BlockParameter
|
2016-12-07 00:09:04 +03:00
|
|
|
, pure ArrayTy
|
|
|
|
, pure DictionaryTy
|
2016-12-01 00:30:11 +03:00
|
|
|
, pure Break
|
2016-12-01 00:40:06 +03:00
|
|
|
, pure Continue
|
2016-12-06 22:23:10 +03:00
|
|
|
, pure Binary
|
|
|
|
, pure Unary
|
2016-12-07 21:45:55 +03:00
|
|
|
, pure Constant
|
|
|
|
, pure Superclass
|
2016-12-10 03:12:07 +03:00
|
|
|
, pure SingletonClass
|
2017-01-10 23:09:09 +03:00
|
|
|
, pure ParameterDecl
|
2016-06-23 23:29:19 +03:00
|
|
|
, Other <$> arbitrary
|
|
|
|
]
|
|
|
|
|
|
|
|
shrink (Other s) = Other <$> shrink s
|
|
|
|
shrink _ = []
|