2016-05-03 19:17:38 +03:00
|
|
|
{-# LANGUAGE TypeFamilies, TypeSynonymInstances, FlexibleInstances #-}
|
2015-11-18 22:27:09 +03:00
|
|
|
module Term where
|
2015-11-18 22:28:16 +03:00
|
|
|
|
2016-05-26 19:58:04 +03:00
|
|
|
import Prologue
|
2016-05-03 19:17:38 +03:00
|
|
|
import Data.Functor.Foldable as Foldable
|
2016-02-29 18:12:34 +03:00
|
|
|
import Data.Functor.Both
|
2016-02-29 18:07:44 +03:00
|
|
|
import Data.OrderedMap hiding (size)
|
2015-11-18 22:28:16 +03:00
|
|
|
import Syntax
|
|
|
|
|
2016-01-13 23:35:40 +03:00
|
|
|
-- | An annotated node (Syntax) in an abstract syntax tree.
|
2016-05-03 19:17:38 +03:00
|
|
|
type TermF a annotation = CofreeF (Syntax a) annotation
|
2016-05-04 21:37:24 +03:00
|
|
|
type Term a annotation = Cofree (Syntax a) annotation
|
|
|
|
|
|
|
|
type instance Base (Cofree f a) = CofreeF f a
|
2016-05-27 20:10:04 +03:00
|
|
|
instance Functor f => Recursive (Cofree f a) where project = runCofree
|
|
|
|
instance Functor f => Corecursive (Cofree f a) where embed = cofree
|
2015-11-18 22:39:08 +03:00
|
|
|
|
2016-01-13 23:35:40 +03:00
|
|
|
-- | Zip two terms by combining their annotations into a pair of annotations.
|
|
|
|
-- | If the structure of the two terms don't match, then Nothing will be returned.
|
2016-02-29 18:12:34 +03:00
|
|
|
zipTerms :: Term a annotation -> Term a annotation -> Maybe (Term a (Both annotation))
|
2016-05-04 21:37:24 +03:00
|
|
|
zipTerms t1 t2 = annotate (zipUnwrap a b)
|
2015-11-19 03:58:37 +03:00
|
|
|
where
|
2016-05-04 21:37:24 +03:00
|
|
|
(annotation1 :< a, annotation2 :< b) = (runCofree t1, runCofree t2)
|
|
|
|
annotate = fmap (cofree . (Both (annotation1, annotation2) :<))
|
2015-11-27 20:02:28 +03:00
|
|
|
zipUnwrap (Leaf _) (Leaf b') = Just $ Leaf b'
|
2016-03-11 22:21:42 +03:00
|
|
|
zipUnwrap (Indexed a') (Indexed b') = Just . Indexed . catMaybes $ zipWith zipTerms a' b'
|
|
|
|
zipUnwrap (Fixed a') (Fixed b') = Just . Fixed . catMaybes $ zipWith zipTerms a' b'
|
2015-11-27 20:02:28 +03:00
|
|
|
zipUnwrap (Keyed a') (Keyed b') | keys a' == keys b' = Just . Keyed . fromList . catMaybes $ zipUnwrapMaps a' b' <$> keys a'
|
|
|
|
zipUnwrap _ _ = Nothing
|
|
|
|
zipUnwrapMaps a' b' key = (,) key <$> zipTerms (a' ! key) (b' ! key)
|
2015-11-20 04:17:17 +03:00
|
|
|
|
2016-04-11 22:06:53 +03:00
|
|
|
-- | Return the node count of a term.
|
2015-12-01 03:13:20 +03:00
|
|
|
termSize :: Term a annotation -> Integer
|
2016-01-13 23:32:03 +03:00
|
|
|
termSize = cata size where
|
2016-05-03 19:17:38 +03:00
|
|
|
size (_ :< syntax) = 1 + sum syntax
|