Consider the illustrative code below:{-# LANGUAGE GADTs #-}{-# LANGUAGE DataKinds #-}{-# LANGUAGE KindSignatures #-}{-# LANGUAGE RankNTypes #-}{-# LANGUAGE PolyKinds #-}{-# LANGUAGE StandaloneDeriving #-}{-# LANGUAGE UndecidableInstances #-}data Param = Param1 | Param2data T (p :: Param) whereTInt :: Int -> T Param1TInteger :: Integer -> T Param1TBool :: Bool -> T Param2data U (p :: Param) whereUDouble :: Double -> U Param1UString :: String -> U Param2data F (t :: Param -> *) whereF :: t Param1 -> t Param2 -> F tf :: T a -> U af (TInt x) = UDouble (fromIntegral x)f (TInteger x) = UDouble (fromIntegral x)f (TBool x) = UString (show x)class MyFunctor f wheremyFmap :: (forall a. t a -> u a) -> f t -> f uinstance MyFunctor F wheremyFmap f (F x1 x2) = F (f x1) (f x2)deriving instance Show (U a)deriving instance (Show (t Param1), Show (t Param2)) => Show (F t)main = print $ myFmap f (F (TInt 42) (TBool False))Basically this is a sort of "higher order" functor, but I can't seem to fit it into an ordinary functor.But it seems like I'm reinventing the wheel, as my code is suspiciously like `Functor` but only slightly different.Has this sort of class already been created and if so what package is it in?
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell- cafe
Only members subscribed via the mailman list are allowed to post.