{-# OPTIONS_GHC -fglasgow-exts #-} ----------------------------------------------------------------------------- -- | -- Module : Control.Morphism.Meta -- Copyright : (C) 2008 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : experimental -- Portability : non-portable (rank-2 polymorphism) -- -- A very basic Jeremy Gibbons metamorphism, without all -- the productive stream stuff. See: -- -- TODO: Add some support for spigot algorithms over streams/lists. ---------------------------------------------------------------------------- module Control.Morphism.Meta where import Control.Functor.Algebra import Control.Functor.Extras import Control.Functor.Fix import Control.Comonad import Control.Monad.Identity import Control.Morphism.Ana import Control.Morphism.Cata meta :: (Functor f, Functor g) => Coalgebra f b -> (a -> b) -> Algebra g a -> FixF g -> FixF f meta f e g = ana f . e . cata g g_meta :: (Monad m, Functor f, Comonad w, Functor g) => Dist m f -> Dist g w -> GCoalgebra f m b -> (a -> b) -> GAlgebra g w a -> FixF g -> FixF f g_meta m w f e g = g_ana m f . e . g_cata w g