{-# LANGUAGE CPP, Rank2Types #-} -- it seems that older GHCs do not like multiple LANGUAGE pragmas? -- {- LANGUAGE CPP -} -- ifdef __GLASGOW_HASKELL__ -- {- LANGUAGE Rank2Types -} -- endif -- | Changing the structure of a tree. module Data.Generics.Fixplate.Structure ( NatTrafo , restructure , liftAnn ) where -------------------------------------------------------------------------------- import Data.Generics.Fixplate.Base -------------------------------------------------------------------------------- -- #ifdef __GLASGOW_HASKELL__ -- | The type of natural transformations. type NatTrafo f g = forall a. (f a -> g a) -- | Changing the structure of a tree. restructure :: Functor f => NatTrafo f g -> Mu f -> Mu g restructure trafo = go where go = Fix . trafo . fmap go . unFix -- #else {- data NatTrafo f g = NatTrafo (f Int) (g Int) -- fake and opaque data type -- | Unfortunately, this function requires Rank2Types, -- thus we only provide it for GHC. restructure :: Functor f => NatTrafo f g -> Mu f -> Mu g restructure = error "restructure: this operation requires Rank2Types" -} -- #endif -------------------------------------------------------------------------------- -- | Lifting natural transformations to annotations. liftAnn :: (f e -> g e) -> Ann f a e -> Ann g a e liftAnn trafo (Ann a x) = Ann a (trafo x) --------------------------------------------------------------------------------