
This is indeed a functor, but it’s a functor from type constructors
and index-preserving functions to types and functions. You can’t
represent these with the standard Functor class, and I’m not aware of
a specific package that provides these.
There have been a few attempts to make more general Functor classes
that could include these functors, such as Kmett’s “hask”, but I
suspect they’re a bit more powerful than you need. You are probably
better off defining your class, if you find it useful.
For reference, the Functor class represents objects in Hask -> Hask.
McBride’s indexed functors are (|k| -> Hask) -> (|k| -> Hask), where k
may be Hask or a data kind. (The bars indicate a category with no
arrows between objects.) Your functors are (|k| -> Hask) -> Hask.
On Fri, Jul 7, 2017 at 12:48 AM, Clinton Mead
Consider the illustrative code below:
{-# LANGUAGE GADTs #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE UndecidableInstances #-}
data Param = Param1 | Param2
data T (p :: Param) where TInt :: Int -> T Param1 TInteger :: Integer -> T Param1 TBool :: Bool -> T Param2
data U (p :: Param) where UDouble :: Double -> U Param1 UString :: String -> U Param2
data F (t :: Param -> *) where F :: t Param1 -> t Param2 -> F t
f :: T a -> U a f (TInt x) = UDouble (fromIntegral x) f (TInteger x) = UDouble (fromIntegral x) f (TBool x) = UString (show x)
class MyFunctor f where myFmap :: (forall a. t a -> u a) -> f t -> f u
instance MyFunctor F where myFmap 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.
--
Dave Menendez