2015-11-18 00:29:55 +03:00
|
|
|
module Syntax where
|
|
|
|
|
2016-07-22 22:30:35 +03:00
|
|
|
import Data.Sequenceable
|
2016-07-11 19:18:20 +03:00
|
|
|
import GHC.Generics
|
2016-07-22 22:30:35 +03:00
|
|
|
import Prologue
|
2016-06-30 21:10:44 +03:00
|
|
|
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.
|
|
|
|
data Syntax
|
|
|
|
a -- ^ The type of leaves in the syntax tree, typically String, but possibly some datatype representing different leaves more precisely.
|
|
|
|
f -- ^ The type representing another level of the tree, e.g. the children of branches. Often Cofree or Fix or similar.
|
|
|
|
=
|
|
|
|
-- | A terminal syntax node, e.g. an identifier, or atomic literal.
|
2015-11-18 03:17:42 +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-07-11 19:18:20 +03:00
|
|
|
deriving (Eq, Foldable, Functor, Generic, Generic1, Ord, Show, Traversable)
|
2016-06-30 21:10:44 +03:00
|
|
|
|
|
|
|
|
|
|
|
-- Instances
|
|
|
|
|
|
|
|
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
|
|
|
|
|
|
|
|
instance (Arbitrary leaf, Arbitrary f) => Arbitrary (Syntax leaf f) where
|
|
|
|
arbitrary = sized (syntaxOfSize (`resize` arbitrary) )
|
|
|
|
|
|
|
|
shrink = genericShrink
|
2016-07-22 22:30:35 +03:00
|
|
|
|
|
|
|
instance Sequenceable (Syntax leaf) where
|
|
|
|
sequenceAlt syntax = case syntax of
|
|
|
|
Leaf a -> pure (Leaf a)
|
|
|
|
Indexed i -> Indexed <$> sequenceAlt i
|
|
|
|
Fixed i -> Fixed <$> sequenceAlt i
|