[Haskell-cafe] Higher order functor package?
Clinton Mead
clintonmead at gmail.com
Fri Jul 7 04:48:44 UTC 2017
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?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170707/7870496e/attachment-0001.html>
More information about the Haskell-Cafe
mailing list