module Generics.MultiRec.Compos where
import Control.Monad (liftM)
import Control.Applicative (Applicative(..), liftA)
import Generics.MultiRec.Base
import Generics.MultiRec.HFunctor
compos :: (Fam phi, HFunctor phi (PF phi)) =>
          (forall ix. phi ix -> ix -> ix) -> phi ix -> ix -> ix
compos f p = to p . hmap (\ p -> I0 . f p . unI0) p . from p
composM :: (Fam phi, HFunctor phi (PF phi), Monad m) =>
           (forall ix. phi ix -> ix -> m ix) -> phi ix -> ix -> m ix
composM f p = liftM (to p) . hmapM (\ p -> liftM I0 . f p . unI0) p . from p
composA :: (Fam phi, HFunctor phi (PF phi), Applicative a) =>
           (forall ix. phi ix -> ix -> a ix) -> phi ix -> ix -> a ix
composA f p = liftA (to p) . hmapA (\ p -> liftA I0 . f p . unI0) p . from p