1
1
mirror of https://github.com/github/semantic.git synced 2024-12-21 22:01:46 +03:00
semantic/src/Syntax.hs

108 lines
4.9 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DeriveAnyClass #-}
2015-11-18 00:29:55 +03:00
module Syntax where
2016-09-16 17:13:28 +03:00
import Prologue
2016-07-23 00:38:10 +03:00
import Data.Mergeable
2016-07-11 19:18:20 +03:00
import GHC.Generics
import Test.QuickCheck hiding (Fixed)
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.
= 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] }
-- | An anonymous function has a list of expressions and params.
2016-10-07 01:20:05 +03:00
| AnonymousFunction { params :: [f], expressions :: f }
2016-06-10 20:11:32 +03:00
-- | A function has a list of expressions.
2016-10-07 01:20:05 +03:00
| Function { id :: f, params :: [f], expressions :: f }
-- | 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 }
-- | A math assignment represents expressions whose operator classifies as mathy (e.g. += or *=).
| MathAssignment { mathAssignmentId :: f, value :: 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 }
-- | 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.
| MethodCall { targetId :: f, methodId :: f, methodParams :: [f] }
2016-06-15 00:37:02 +03:00
-- | The list of arguments to a method call.
-- | TODO: It might be worth removing this and using Fixed instead.
2016-06-14 19:53:35 +03:00
| Args [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;
2016-06-15 03:44:10 +03:00
| VarDecl f
2016-06-16 00:58:48 +03:00
-- | A variable assignment in a variable declaration. var foo = bar;
2016-06-15 03:44:10 +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 }
2016-06-16 01:20:58 +03:00
| Switch { switchExpr :: f, cases :: [f] }
| Case { caseExpr :: f, caseStatements :: f }
2016-07-08 18:17:46 +03:00
| Object { 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)
2016-10-06 00:27:45 +03:00
| Error [f]
| For [f] f
2016-07-28 21:26:42 +03:00
| DoWhile { doWhileBody :: f, doWhileExpr :: f }
| While { whileExpr :: f, whileBody :: Maybe f }
2016-07-28 21:34:53 +03:00
| Return (Maybe f)
2016-07-29 22:31:11 +03:00
| Throw f
2016-07-30 21:27:11 +03:00
| Constructor f
2016-07-29 22:45:25 +03:00
| Try f (Maybe f) (Maybe f)
-- | An array literal with list of children.
2016-07-29 23:42:38 +03:00
| Array [f]
2016-07-30 01:31:39 +03:00
-- | A class with an identifier, superclass, and a list of definitions.
2016-07-29 23:22:41 +03:00
| Class f (Maybe f) [f]
2016-07-30 01:33:01 +03:00
-- | A method definition with an identifier, params, and a list of expressions.
2016-07-30 06:41:21 +03:00
| Method 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] }
| Import f [f]
2016-10-07 00:03:06 +03:00
| Export (Maybe f) [f]
2016-10-24 20:43:31 +03:00
-- | A conditional assignment represents expressions whose operator classifies as conditional (e.g. ||= or &&=).
| ConditionalAssignment { conditionalAssignmentId :: f, value :: f }
2016-10-26 20:27:38 +03:00
| Yield (Maybe f)
| Until { untilExpr :: f, untilBody :: Maybe f }
-- | An unless statement with an expression and maybe more expression clauses.
| Unless f [f]
deriving (Eq, Foldable, Functor, Generic, Generic1, Mergeable, Ord, Show, Traversable)
2016-07-22 20:52:48 +03:00
-- Instances
2016-07-30 01:33:09 +03:00
instance (Arbitrary leaf, Arbitrary f) => Arbitrary (Syntax leaf f) where
arbitrary = sized (syntaxOfSize (`resize` arbitrary) )
shrink = genericShrink
syntaxOfSize :: Arbitrary leaf => (Int -> Gen f) -> Int -> Gen (Syntax leaf f)
syntaxOfSize recur n | n <= 1 = oneof $ (Leaf <$> arbitrary) : branchGeneratorsOfSize n
| otherwise = oneof $ branchGeneratorsOfSize n
where branchGeneratorsOfSize n =
[ Indexed <$> childrenOfSize (pred n)
, Fixed <$> childrenOfSize (pred n)
]
childrenOfSize n | n <= 0 = pure []
childrenOfSize n = do
m <- choose (1, n)
first <- recur m
rest <- childrenOfSize (n - m)
pure $! first : rest