2016-07-11 20:59:27 +03:00
{- # LANGUAGE RankNTypes, TypeFamilies # -}
2016-06-30 19:59:26 +03:00
{- # OPTIONS_GHC - fno - warn - orphans # -}
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-07-11 22:13:16 +03:00
import Data.Align.Generic
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-07-08 20:44:29 +03:00
import Data.These
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
2015-11-18 22:28:16 +03:00
type Term a annotation = Cofree ( Syntax a ) annotation
2015-11-18 22:39:08 +03:00
2016-05-04 21:37:24 +03:00
type instance Base ( Cofree f a ) = CofreeF f a
instance Functor f => Foldable . Foldable ( Cofree f a ) where project = runCofree
2016-05-04 22:15:25 +03:00
instance Functor f => Foldable . Unfoldable ( 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-07-11 22:13:16 +03:00
zipTerms t1 t2 = iter go ( alignCofreeWith galign ( const Nothing ) both ( These t1 t2 ) )
where go ( a :< s ) = cofree . ( a :< ) <$> sequenceA s
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
2016-07-08 20:44:29 +03:00
2016-07-11 21:33:51 +03:00
-- | Aligns (zips, retaining non-overlapping portions of the structure) a pair of terms.
2016-07-11 21:41:59 +03:00
alignCofreeWith :: Functor f
=> ( forall a b . f a -> f b -> Maybe ( f ( These a b ) ) ) -- ^ A function comparing a pair of structures, returning `Just` the combined structure if they are comparable (e.g. if they have the same constructor), and `Nothing` otherwise. The 'Data.Align.Generic.galign' function is usually what you want here.
-> ( These ( Cofree f a ) ( Cofree f b ) -> contrasted ) -- ^ A function mapping a 'These' of incomparable terms into 'Pure' values in the resulting tree.
-> ( a -> b -> combined ) -- ^ A function mapping the input terms’ annotations into annotations in the 'Free' values in the resulting tree.
-> These ( Cofree f a ) ( Cofree f b ) -- ^ The input terms.
-> Free ( CofreeF f combined ) contrasted
2016-07-11 21:33:05 +03:00
alignCofreeWith compare contrast combine = go
where go terms = fromMaybe ( pure ( contrast terms ) ) $ case terms of
2016-07-11 21:27:38 +03:00
These t1 t2 -> wrap . ( combine ( extract t1 ) ( extract t2 ) :< ) . fmap go <$> compare ( unwrap t1 ) ( unwrap t2 )
2016-07-11 21:03:05 +03:00
_ -> Nothing