1
1
mirror of https://github.com/github/semantic.git synced 2024-12-26 00:12:29 +03:00
semantic/src/Term.hs

27 lines
1.1 KiB
Haskell
Raw Normal View History

2015-11-18 22:27:09 +03:00
module Term where
2015-11-19 04:33:09 +03:00
import Data.Map
2015-11-19 04:11:13 +03:00
import Data.Maybe
import Control.Comonad.Cofree
import Syntax
import Categorizable
type Term a annotation = Cofree (Syntax a) annotation
instance Categorizable annotation => Categorizable (Term a annotation) where
categories (annotation :< _) = categories annotation
2015-11-19 03:58:37 +03:00
zipTerms :: Term a annotation -> Term a annotation -> Maybe (Cofree (Syntax a) (annotation, annotation))
2015-11-19 04:33:09 +03:00
zipTerms (annotation1 :< a) (annotation2 :< b) = annotate $ zipUnwrap a b
2015-11-19 03:58:37 +03:00
where
2015-11-19 04:33:09 +03:00
annotate = fmap ((annotation1, annotation2) :<)
zipUnwrap (Leaf a) (Leaf b) = Just $ Leaf b
2015-11-19 04:38:48 +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-19 05:00:10 +03:00
zipUnwrap (Keyed a) (Keyed b) | keys a == keys b = Just . Keyed . fromList . catMaybes $ zipUnwrapMaps a b <$> keys a
2015-11-19 03:58:37 +03:00
zipUnwrap a b = Nothing
2015-11-19 05:00:10 +03:00
zipUnwrapMaps a b key = (,) key <$> zipTerms (a ! key) (b ! key)
2015-11-20 04:17:17 +03:00
cata :: (annotation -> Syntax a b -> b) -> Term a annotation -> b
cata f (annotation :< syntax) = f annotation $ cata f <$> syntax