2016-07-22 23:15:04 +03:00
|
|
|
{-# LANGUAGE DeriveAnyClass #-}
|
2015-11-18 00:29:55 +03:00
|
|
|
module Syntax where
|
|
|
|
|
2017-01-09 22:59:04 +03:00
|
|
|
import Data.Aeson
|
2017-02-22 00:26:11 +03:00
|
|
|
import Data.Functor.Classes
|
|
|
|
import Data.Functor.Classes.Eq.Generic
|
2017-01-05 23:22:29 +03:00
|
|
|
import Data.Functor.Listable
|
2016-07-23 00:38:10 +03:00
|
|
|
import Data.Mergeable
|
2016-07-11 19:18:20 +03:00
|
|
|
import GHC.Generics
|
2017-01-09 22:59:04 +03:00
|
|
|
import Prologue
|
2015-11-18 00:29:55 +03:00
|
|
|
|
2015-11-27 17:41:43 +03:00
|
|
|
-- | A node in an abstract syntax tree.
|
2016-08-04 19:26:07 +03:00
|
|
|
--
|
|
|
|
-- 'a' is the type of leaves in the syntax tree, typically 'Text', but possibly some datatype representing different leaves more precisely.
|
|
|
|
-- 'f' is the type representing another level of the tree, e.g. the children of branches. Often 'Cofree', 'Free' or similar.
|
|
|
|
data Syntax a f
|
2015-11-27 17:41:43 +03:00
|
|
|
-- | A terminal syntax node, e.g. an identifier, or atomic literal.
|
2016-08-04 19:25:56 +03:00
|
|
|
= Leaf a
|
2015-11-27 17:41:43 +03:00
|
|
|
-- | An ordered branch of child nodes, expected to be variadic in the grammar, e.g. a list of statements or uncurried function parameters.
|
2015-11-18 03:17:42 +03:00
|
|
|
| Indexed [f]
|
2015-11-27 17:41:43 +03:00
|
|
|
-- | An ordered branch of child nodes, expected to be of fixed length in the grammar, e.g. a binary operator & its operands.
|
2015-11-18 03:17:42 +03:00
|
|
|
| Fixed [f]
|
2016-06-09 00:18:54 +03:00
|
|
|
-- | A function call has an identifier where f is a (Leaf a) and a list of arguments.
|
|
|
|
| FunctionCall f [f]
|
2016-06-17 23:32:07 +03:00
|
|
|
-- | A ternary has a condition, a true case and a false case
|
|
|
|
| Ternary { ternaryCondition :: f, ternaryCases :: [f] }
|
2016-08-23 02:55:54 +03:00
|
|
|
-- | An anonymous function has a list of expressions and params.
|
2016-10-27 19:24:28 +03:00
|
|
|
| AnonymousFunction { params :: [f], expressions :: [f] }
|
2016-06-10 20:11:32 +03:00
|
|
|
-- | A function has a list of expressions.
|
2017-03-27 23:28:37 +03:00
|
|
|
| Function { id :: f, params :: [f], ty :: Maybe f, expressions :: [f] }
|
2016-06-14 01:32:41 +03:00
|
|
|
-- | An assignment has an identifier where f can be a member access, and the value is another syntax element (function call, leaf, etc.)
|
2016-06-14 00:32:08 +03:00
|
|
|
| Assignment { assignmentId :: f, value :: f }
|
2016-12-06 23:36:56 +03:00
|
|
|
-- | An operator assignment represents expressions with operators like math (e.g x += 1) or conditional (e.g. x ||= 1) assignment.
|
|
|
|
| OperatorAssignment f f
|
2016-06-14 01:32:23 +03:00
|
|
|
-- | A member access contains a syntax, and another syntax that identifies a property or value in the first syntax.
|
|
|
|
-- | e.g. in Javascript x.y represents a member access syntax.
|
|
|
|
| MemberAccess { memberId :: f, property :: f }
|
2016-06-13 00:26:20 +03:00
|
|
|
-- | A method call consisting of its target, the method name, and the parameters passed to the method.
|
|
|
|
-- | e.g. in Javascript console.log('hello') represents a method call.
|
2016-08-17 17:42:05 +03:00
|
|
|
| MethodCall { targetId :: f, methodId :: f, methodParams :: [f] }
|
2016-06-18 01:03:09 +03:00
|
|
|
-- | An operator can be applied to a list of syntaxes.
|
|
|
|
| Operator [f]
|
2016-06-16 00:58:48 +03:00
|
|
|
-- | A variable declaration. e.g. var foo;
|
2017-03-27 23:28:37 +03:00
|
|
|
| VarDecl [f]
|
2016-06-16 00:58:48 +03:00
|
|
|
-- | A variable assignment in a variable declaration. var foo = bar;
|
2017-03-27 23:28:37 +03:00
|
|
|
| VarAssignment { varId :: [f], varValue :: f }
|
2016-06-17 22:39:18 +03:00
|
|
|
-- | A subscript access contains a syntax, and another syntax that indefies a property or value in the first syntax.
|
|
|
|
-- | e.g. in Javascript x["y"] represents a subscript access syntax.
|
|
|
|
| SubscriptAccess { subscriptId :: f, subscriptElement :: f }
|
2017-01-23 23:02:52 +03:00
|
|
|
| Switch { switchExpr :: [f], cases :: [f] }
|
2016-11-05 01:35:09 +03:00
|
|
|
| Case { caseExpr :: f, caseStatements :: [f] }
|
2017-01-11 00:05:55 +03:00
|
|
|
-- | A default case in a switch statement.
|
2017-01-18 22:06:45 +03:00
|
|
|
| DefaultCase [f]
|
2016-11-15 01:47:04 +03:00
|
|
|
| Select { cases :: [f] }
|
2016-12-07 00:09:04 +03:00
|
|
|
| Object { objectTy :: Maybe f, keyValues :: [f] }
|
2016-07-28 18:24:19 +03:00
|
|
|
-- | A pair in an Object. e.g. foo: bar or foo => bar
|
2016-07-08 20:16:03 +03:00
|
|
|
| Pair f f
|
2016-07-28 18:24:19 +03:00
|
|
|
-- | A comment.
|
2016-07-08 18:17:46 +03:00
|
|
|
| Comment a
|
2016-07-28 18:24:19 +03:00
|
|
|
-- | A term preceded or followed by any number of comments.
|
2016-07-08 18:48:20 +03:00
|
|
|
| Commented [f] (Maybe f)
|
2017-01-25 11:09:53 +03:00
|
|
|
| ParseError [f]
|
2016-10-27 20:07:24 +03:00
|
|
|
-- | A for statement has a list of expressions to setup the iteration and then a list of expressions in the body.
|
|
|
|
| For [f] [f]
|
2016-07-28 21:26:42 +03:00
|
|
|
| DoWhile { doWhileBody :: f, doWhileExpr :: f }
|
2016-10-31 23:14:32 +03:00
|
|
|
| While { whileExpr :: f, whileBody :: [f] }
|
2016-12-06 02:54:59 +03:00
|
|
|
| Return [f]
|
2016-07-29 22:31:11 +03:00
|
|
|
| Throw f
|
2016-07-30 21:27:11 +03:00
|
|
|
| Constructor f
|
2016-11-07 21:26:59 +03:00
|
|
|
-- | TODO: Is it a problem that in Ruby, this pattern can work for method def too?
|
|
|
|
| Try { tryBegin :: [f], catchRescue :: [f], beginElse :: Maybe f, finallyEnsure :: Maybe f }
|
2016-08-01 20:30:37 +03:00
|
|
|
-- | An array literal with list of children.
|
2016-12-07 00:09:04 +03:00
|
|
|
| Array (Maybe f) [f]
|
2016-07-30 01:31:39 +03:00
|
|
|
-- | A class with an identifier, superclass, and a list of definitions.
|
2017-03-29 01:16:04 +03:00
|
|
|
| Class f [f] [f]
|
2017-02-08 01:53:15 +03:00
|
|
|
-- | A method definition with an identifier, optional receiver, optional return type, params, and a list of expressions.
|
|
|
|
| Method f (Maybe f) (Maybe f) [f] [f]
|
2016-10-27 00:32:08 +03:00
|
|
|
-- | An if statement with an expression and maybe more expression clauses.
|
|
|
|
| If f [f]
|
2016-10-04 01:17:03 +03:00
|
|
|
-- | A module with an identifier, and a list of syntaxes.
|
|
|
|
| Module { moduleId:: f, moduleBody :: [f] }
|
2017-03-28 22:54:31 +03:00
|
|
|
-- | An interface with an identifier, a list of clauses, and a list of declarations..
|
|
|
|
| Interface f [f] [f]
|
2017-03-28 22:40:10 +03:00
|
|
|
| Namespace { namespaceId:: f, namespaceBody :: [f] }
|
2016-10-06 23:47:29 +03:00
|
|
|
| Import f [f]
|
2016-10-07 00:03:06 +03:00
|
|
|
| Export (Maybe f) [f]
|
2016-12-06 02:56:18 +03:00
|
|
|
| Yield [f]
|
2016-11-08 00:33:41 +03:00
|
|
|
-- | A negation of a single expression.
|
2016-11-08 00:12:53 +03:00
|
|
|
| Negate f
|
2016-11-04 22:29:02 +03:00
|
|
|
-- | A rescue block has a list of arguments to rescue and a list of expressions.
|
|
|
|
| Rescue [f] [f]
|
2016-11-15 03:05:02 +03:00
|
|
|
| Go f
|
|
|
|
| Defer f
|
2016-11-21 23:27:06 +03:00
|
|
|
| TypeAssertion f f
|
2016-11-21 23:44:31 +03:00
|
|
|
| TypeConversion f f
|
2017-01-10 23:09:09 +03:00
|
|
|
-- | A struct with an optional type.
|
2016-12-07 00:09:04 +03:00
|
|
|
| Struct (Maybe f) [f]
|
2017-01-18 01:20:50 +03:00
|
|
|
| Break (Maybe f)
|
|
|
|
| Continue (Maybe f)
|
2016-12-13 02:26:26 +03:00
|
|
|
-- | A block statement has an ordered branch of child nodes, e.g. BEGIN {...} or END {...} in Ruby/Perl.
|
|
|
|
| BlockStatement [f]
|
2017-01-10 23:09:09 +03:00
|
|
|
-- | A parameter declaration with an optional type.
|
|
|
|
| ParameterDecl (Maybe f) f
|
2017-01-13 01:56:41 +03:00
|
|
|
-- | A type declaration has an identifier and a type.
|
2017-01-11 02:04:34 +03:00
|
|
|
| TypeDecl f f
|
2017-01-17 19:53:44 +03:00
|
|
|
-- | A field declaration with an optional type, and an optional tag.
|
2017-03-28 20:00:15 +03:00
|
|
|
| FieldDecl [f]
|
2017-01-13 01:56:41 +03:00
|
|
|
-- | A type.
|
2017-01-23 22:39:12 +03:00
|
|
|
| Ty [f]
|
2017-01-13 02:39:09 +03:00
|
|
|
-- | A send statement has a channel and an expression in Go.
|
|
|
|
| Send f f
|
2017-03-14 02:23:33 +03:00
|
|
|
deriving (Eq, Foldable, Functor, Generic, Generic1, Mergeable, Ord, Show, Traversable, ToJSON, NFData)
|
2016-06-30 21:10:44 +03:00
|
|
|
|
2016-07-22 20:52:48 +03:00
|
|
|
|
2016-06-30 21:10:44 +03:00
|
|
|
-- Instances
|
|
|
|
|
2017-01-05 23:22:29 +03:00
|
|
|
instance Listable2 Syntax where
|
|
|
|
liftTiers2 leaf recur
|
|
|
|
= liftCons1 leaf Leaf
|
|
|
|
\/ liftCons1 (liftTiers recur) Indexed
|
|
|
|
\/ liftCons1 (liftTiers recur) Fixed
|
|
|
|
\/ liftCons2 recur (liftTiers recur) FunctionCall
|
|
|
|
\/ liftCons2 recur (liftTiers recur) Ternary
|
|
|
|
\/ liftCons2 (liftTiers recur) (liftTiers recur) AnonymousFunction
|
2017-01-25 19:41:09 +03:00
|
|
|
\/ liftCons4 recur (liftTiers recur) (liftTiers recur) (liftTiers recur) Function
|
2017-01-05 23:22:29 +03:00
|
|
|
\/ liftCons2 recur recur Assignment
|
|
|
|
\/ liftCons2 recur recur OperatorAssignment
|
|
|
|
\/ liftCons2 recur recur MemberAccess
|
|
|
|
\/ liftCons3 recur recur (liftTiers recur) MethodCall
|
|
|
|
\/ liftCons1 (liftTiers recur) Operator
|
2017-03-27 23:28:37 +03:00
|
|
|
\/ liftCons1 (liftTiers recur) VarDecl
|
|
|
|
\/ liftCons2 (liftTiers recur) recur VarAssignment
|
2017-01-05 23:22:29 +03:00
|
|
|
\/ liftCons2 recur recur SubscriptAccess
|
2017-01-18 19:14:03 +03:00
|
|
|
\/ liftCons2 (liftTiers recur) (liftTiers recur) Switch
|
2017-01-05 23:22:29 +03:00
|
|
|
\/ liftCons2 recur (liftTiers recur) Case
|
|
|
|
\/ liftCons1 (liftTiers recur) Select
|
2017-01-18 19:14:03 +03:00
|
|
|
\/ liftCons2 (liftTiers recur) (liftTiers recur) Syntax.Object
|
2017-01-05 23:22:29 +03:00
|
|
|
\/ liftCons2 recur recur Pair
|
|
|
|
\/ liftCons1 leaf Comment
|
|
|
|
\/ liftCons2 (liftTiers recur) (liftTiers recur) Commented
|
2017-01-25 11:09:53 +03:00
|
|
|
\/ liftCons1 (liftTiers recur) Syntax.ParseError
|
2017-01-05 23:22:29 +03:00
|
|
|
\/ liftCons2 (liftTiers recur) (liftTiers recur) For
|
|
|
|
\/ liftCons2 recur recur DoWhile
|
|
|
|
\/ liftCons2 recur (liftTiers recur) While
|
|
|
|
\/ liftCons1 (liftTiers recur) Return
|
|
|
|
\/ liftCons1 recur Throw
|
|
|
|
\/ liftCons1 recur Constructor
|
|
|
|
\/ liftCons4 (liftTiers recur) (liftTiers recur) (liftTiers recur) (liftTiers recur) Try
|
2017-01-18 19:14:03 +03:00
|
|
|
\/ liftCons2 (liftTiers recur) (liftTiers recur) Syntax.Array
|
2017-01-05 23:22:29 +03:00
|
|
|
\/ liftCons3 recur (liftTiers recur) (liftTiers recur) Class
|
2017-02-08 01:53:15 +03:00
|
|
|
\/ liftCons5 recur (liftTiers recur) (liftTiers recur) (liftTiers recur) (liftTiers recur) Method
|
2017-01-05 23:22:29 +03:00
|
|
|
\/ liftCons2 recur (liftTiers recur) If
|
|
|
|
\/ liftCons2 recur (liftTiers recur) Module
|
2017-03-28 22:40:10 +03:00
|
|
|
\/ liftCons2 recur (liftTiers recur) Namespace
|
2017-01-05 23:22:29 +03:00
|
|
|
\/ liftCons2 recur (liftTiers recur) Import
|
|
|
|
\/ liftCons2 (liftTiers recur) (liftTiers recur) Export
|
|
|
|
\/ liftCons1 (liftTiers recur) Yield
|
|
|
|
\/ liftCons1 recur Negate
|
|
|
|
\/ liftCons2 (liftTiers recur) (liftTiers recur) Rescue
|
|
|
|
\/ liftCons1 recur Go
|
|
|
|
\/ liftCons1 recur Defer
|
|
|
|
\/ liftCons2 recur recur TypeAssertion
|
|
|
|
\/ liftCons2 recur recur TypeConversion
|
2017-01-18 19:14:03 +03:00
|
|
|
\/ liftCons1 (liftTiers recur) Break
|
|
|
|
\/ liftCons1 (liftTiers recur) Continue
|
2017-01-05 23:22:29 +03:00
|
|
|
\/ liftCons1 (liftTiers recur) BlockStatement
|
2017-01-18 19:14:03 +03:00
|
|
|
\/ liftCons2 (liftTiers recur) recur ParameterDecl
|
|
|
|
\/ liftCons2 recur recur TypeDecl
|
2017-03-28 20:00:15 +03:00
|
|
|
\/ liftCons1 (liftTiers recur) FieldDecl
|
2017-01-23 22:39:12 +03:00
|
|
|
\/ liftCons1 (liftTiers recur) Ty
|
2017-01-18 19:14:03 +03:00
|
|
|
\/ liftCons2 recur recur Send
|
2017-01-18 22:06:45 +03:00
|
|
|
\/ liftCons1 (liftTiers recur) DefaultCase
|
2016-07-30 01:33:09 +03:00
|
|
|
|
2017-01-05 23:22:49 +03:00
|
|
|
instance Listable leaf => Listable1 (Syntax leaf) where
|
|
|
|
liftTiers = liftTiers2 tiers
|
2016-07-30 01:33:09 +03:00
|
|
|
|
2017-01-05 23:22:56 +03:00
|
|
|
instance (Listable leaf, Listable recur) => Listable (Syntax leaf recur) where
|
|
|
|
tiers = tiers1
|
2017-02-22 00:26:11 +03:00
|
|
|
|
|
|
|
instance Eq leaf => Eq1 (Syntax leaf) where
|
|
|
|
liftEq = genericLiftEq
|