
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?

On 7 July 2017 at 14:48, 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?
The type signature of myFmap looks a bit like that for hoist: http://hackage.haskell.org/package/mmorph-1.1.0/docs/Control-Monad-Morph.htm... -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

I think the keyword you're looking for might be 'indexed', although that
also seems to be used for something different (two indices for pre and post
conditions). Your functor seems to be in 'index-core' [0], and probably
other places (it seems there was something in category-extras but it's
unclear where it went).
Regards,
Erik
[0]
http://hackage.haskell.org/package/index-core-1.0.4/docs/Control-IMonad-Core...
On 7 July 2017 at 06:48, 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.

Hi Erik and All I don't think "indexed-core" is what I'm looking for. "indexed-code" refers to the following type:
(a :-> http://hackage.haskell.org/package/index-core-1.0.4/docs/Control-Category-In... b) -> f a :-> http://hackage.haskell.org/package/index-core-1.0.4/docs/Control-Category-In... f b
Where:
type (:->) a b = forall i. a i -> b i
This effectively makes the result of the functor:
(forall i1. (a i1 -> b i1)) -> (forall i2. (f a i2 -> f b i2))
But what I want is subtly different:
(forall i. (a i -> b i)) -> f a -> f b
Indeed, with my code, "f a i" doesn't make much sense as "f a" itself is of type *. What I'd find useful is something like the following:
class HighFunctor f where hfmap :: (forall a. t a -> u a) -> f t -> f u
class HighFunctor2 f where hfmap2 :: (forall a. t a -> u a -> v a) -> f t -> f u -> f v
class HighFunctorMaybe f where hfmapMaybe :: (forall a. Maybe (t a) -> u a) -> Maybe (f t) -> f u
class HighFunctor2Maybe1 f where hfmap2maybe1 :: (forall a. Maybe (t a) -> u a -> v a) -> Maybe (f t) -> f u -> f v
class HighFunctor2Maybe2 f where hfmap2maybe2 :: (forall a. t a -> Maybe (u a) -> v a) -> f t -> Maybe (f u) -> f v
class HighFunctor2MaybeBoth f where hfmap2maybeBoth :: (forall a. Maybe (t a) -> Maybe (u a) -> v a) -> Maybe (f t) -> Maybe (f u) -> f v
As you can see. I'm basically hacking up with separate classes what can be done easily with applicative, and it's getting a bit messy. I've been trying to clean this up, so I don't need so many different functions for different combinations of maybes, by defining these helper functions:
data Transform outerT innerT a = Transform (outerT (innerT a))
transformIn :: outerT (f innerT) -> f (Transform outerT innerT)
transformOut :: Transform outerT innerT a -> outerT (innerT a) transformOut (Transform x) = x
By applying "transformIn" to an argument on the way in to hfmapN, and "transformOut" on the way out, one can pass through maybes to the standard top to non-maybe "HighFunctor" instances. But note that whilst "transformOut" is always trivial to implement, the way in, "transformIn" doesn't seem trivial. "transformIn" I think has to be implemented for each combination of "outerT" and "f", like so:
class TransformIn outerT f where f :: outerT (f innerT) -> f (Transform outerT innerT)
Anyway, the point of all this is that I'd like to be able to just launch my
base functions (over the "forall i" space) into these higher level
datatypes that wrap the foralls up in a datatype, in a similar way I can do
so with functor and applicative.
I think the code in the first post is the best illustration of what I'm
trying to achieve but with two added things:
1. The ability to deal with multiple arguments in an applicative style <$>
<*> way
2. The ability to promote "wrapped" types, I think kind of in a way
"traversable" does.
Sorry if this all is a bit vague, but hopefully the code in the first post
and this gives the gist of what I'm trying to achieve.
Any help or ideas appreciated.
Thanks,
Clinton
On Fri, Jul 7, 2017 at 4:40 PM, Erik Hesselink
I think the keyword you're looking for might be 'indexed', although that also seems to be used for something different (two indices for pre and post conditions). Your functor seems to be in 'index-core' [0], and probably other places (it seems there was something in category-extras but it's unclear where it went).
Regards,
Erik
[0] http://hackage.haskell.org/package/index-core-1.0.4/docs/ Control-IMonad-Core.html
On 7 July 2017 at 06:48, Clinton Mead
wrote: 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.

I recommend posting this question to StackOverflow and hoping that Conor
McBride notices it.
On Fri, Jul 7, 2017 at 11:46 AM Clinton Mead
Hi Erik and All
I don't think "indexed-core" is what I'm looking for. "indexed-code" refers to the following type:
(a :-> http://hackage.haskell.org/package/index-core-1.0.4/docs/Control-Category-In... b) -> f a :-> http://hackage.haskell.org/package/index-core-1.0.4/docs/Control-Category-In... f b
Where:
type (:->) a b = forall i. a i -> b i
This effectively makes the result of the functor:
(forall i1. (a i1 -> b i1)) -> (forall i2. (f a i2 -> f b i2))
But what I want is subtly different:
(forall i. (a i -> b i)) -> f a -> f b
Indeed, with my code, "f a i" doesn't make much sense as "f a" itself is of type *.
What I'd find useful is something like the following:
class HighFunctor f where hfmap :: (forall a. t a -> u a) -> f t -> f u
class HighFunctor2 f where hfmap2 :: (forall a. t a -> u a -> v a) -> f t -> f u -> f v
class HighFunctorMaybe f where hfmapMaybe :: (forall a. Maybe (t a) -> u a) -> Maybe (f t) -> f u
class HighFunctor2Maybe1 f where hfmap2maybe1 :: (forall a. Maybe (t a) -> u a -> v a) -> Maybe (f t) -> f u -> f v
class HighFunctor2Maybe2 f where hfmap2maybe2 :: (forall a. t a -> Maybe (u a) -> v a) -> f t -> Maybe (f u) -> f v
class HighFunctor2MaybeBoth f where hfmap2maybeBoth :: (forall a. Maybe (t a) -> Maybe (u a) -> v a) -> Maybe (f t) -> Maybe (f u) -> f v
As you can see. I'm basically hacking up with separate classes what can be done easily with applicative, and it's getting a bit messy. I've been trying to clean this up, so I don't need so many different functions for different combinations of maybes, by defining these helper functions:
data Transform outerT innerT a = Transform (outerT (innerT a))
transformIn :: outerT (f innerT) -> f (Transform outerT innerT)
transformOut :: Transform outerT innerT a -> outerT (innerT a) transformOut (Transform x) = x
By applying "transformIn" to an argument on the way in to hfmapN, and "transformOut" on the way out, one can pass through maybes to the standard top to non-maybe "HighFunctor" instances.
But note that whilst "transformOut" is always trivial to implement, the way in, "transformIn" doesn't seem trivial. "transformIn" I think has to be implemented for each combination of "outerT" and "f", like so:
class TransformIn outerT f where f :: outerT (f innerT) -> f (Transform outerT innerT)
Anyway, the point of all this is that I'd like to be able to just launch my base functions (over the "forall i" space) into these higher level datatypes that wrap the foralls up in a datatype, in a similar way I can do so with functor and applicative.
I think the code in the first post is the best illustration of what I'm trying to achieve but with two added things:
1. The ability to deal with multiple arguments in an applicative style <$> <*> way 2. The ability to promote "wrapped" types, I think kind of in a way "traversable" does.
Sorry if this all is a bit vague, but hopefully the code in the first post and this gives the gist of what I'm trying to achieve.
Any help or ideas appreciated.
Thanks,
Clinton
On Fri, Jul 7, 2017 at 4:40 PM, Erik Hesselink
wrote: I think the keyword you're looking for might be 'indexed', although that also seems to be used for something different (two indices for pre and post conditions). Your functor seems to be in 'index-core' [0], and probably other places (it seems there was something in category-extras but it's unclear where it went).
Regards,
Erik
[0] http://hackage.haskell.org/package/index-core-1.0.4/docs/Control-IMonad-Core...
On 7 July 2017 at 06:48, Clinton Mead
wrote: 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.
_______________________________________________ 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.

Hi Clinton, This should be a compilable Literate Haskell program; a copy of your preliminary definitions is at the end.
{-# LANGUAGE MultiParamTypeClasses, PolyKinds, FunctionalDependencies, TypeOperators, GADTs, RankNTypes, DataKinds, StandaloneDeriving, UndecidableInstances, FlexibleContexts, InstanceSigs #-}
import Control.Category import Prelude hiding ((.), id, Functor(..))
What you want certainly looks like a functor[1] in the general sense, only not in the usual category that the Functortype class is specialized for. A more general definition of functors can be found in the categories[2] package. This one also abstracts over the domain and codomain categories r and t. You obtain the standard Functor by restricting to r ~ (->), t ~ (->).
class (Category r, Category t) => Functor f r t | f r -> t, f t -> r where fmap :: r a b -> t (f a) (f b)
The expected result type of myFmap is (f t -> f u), so the codomain category is still (->) (category of types and functions). But t and u here are objects in a different category, which can be defined by the (:->) type below:
-- Objects are types (t, u, ...) of kind (Param -> *), -- morphisms are polymorphic functions of type (forall a. t a -> u a). newtype (:->) t u = HFun (forall a. t a -> u a)
You can indeed implement the type class in Control.Category, and check the category laws...
instance Category (:->) where id = HFun id HFun f . HFun g = HFun (f . g)
And here is a Functor instance:
instance Functor F (:->) (->) where fmap :: (t :-> u) -> F t -> F u fmap (HFun f) (F x1 x2) = F (f x1) (f x2)
Hide away the wrapping of the (:->) newtype:
myFmap :: Functor f (:->) (->) => (forall a. t a -> u a) -> f t -> f u myFmap f = fmap (HFun f)
Voilà.
main = print $ myFmap f (F (TInt 42) (TBool False))
[1] https://en.wikipedia.org/wiki/Category_(mathematics) [2] http://hackage.haskell.org/package/categories Auxiliary definitions
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)
deriving instance Show (U a) deriving instance (Show (t Param1), Show (t Param2)) => Show (F t)

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

On 2017-07-07 12:48 AM, Clinton Mead wrote:
Consider the illustrative code below: ... class MyFunctor f where myFmap :: (forall a. t a -> u a) -> f t -> f u ...
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?
Yes, I have recently created rank2classes package: http://hackage.haskell.org/package/rank2classes Apart from the mirror-universe Functor class, the package exports the Applicative, Foldable, Traversable, Applicative, and Distributive classes, as well as some Template Hashell to derive some of their instances automatically.

Hi All
Thanks for all your help.
I've actually picked up Mario's rank2classes package
http://hackage.haskell.org/package/rank2classes as it seems like I need a
little but more power than Functors, as I want things like `liftA2` for
example.
I've pushed across a very simple pull request to you Mario that simply adds
"PolyKinds" to your list of language extensions. This automatically this
generalises the kinds your Functor and Apply accept (and perhaps others) as
I'm quantifying not over * but over a data kind type. No other changes are
needed.
Clinton
On Sat, Jul 8, 2017 at 5:57 AM, Mario Blažević
On 2017-07-07 12:48 AM, Clinton Mead wrote:
Consider the illustrative code below: ... class MyFunctor f where myFmap :: (forall a. t a -> u a) -> f t -> f u ...
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?
Yes, I have recently created rank2classes package:
http://hackage.haskell.org/package/rank2classes
Apart from the mirror-universe Functor class, the package exports the Applicative, Foldable, Traversable, Applicative, and Distributive classes, as well as some Template Hashell to derive some of their instances automatically.
_______________________________________________ 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.

Hi Clinton,
Sorry for late reply, but just for the sake of completeness the
compdata package defines just the functor you mentioned
http://hackage.haskell.org/package/compdata-0.11/docs/Data-Comp-Multi-HFunct....
Regards,
Sergey
On Tue, Jul 11, 2017 at 9:18 AM, Clinton Mead
Hi All
Thanks for all your help.
I've actually picked up Mario's rank2classes package as it seems like I need a little but more power than Functors, as I want things like `liftA2` for example.
I've pushed across a very simple pull request to you Mario that simply adds "PolyKinds" to your list of language extensions. This automatically this generalises the kinds your Functor and Apply accept (and perhaps others) as I'm quantifying not over * but over a data kind type. No other changes are needed.
Clinton
On Sat, Jul 8, 2017 at 5:57 AM, Mario Blažević
wrote: On 2017-07-07 12:48 AM, Clinton Mead wrote:
Consider the illustrative code below: ... class MyFunctor f where myFmap :: (forall a. t a -> u a) -> f t -> f u ...
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?
Yes, I have recently created rank2classes package:
http://hackage.haskell.org/package/rank2classes
Apart from the mirror-universe Functor class, the package exports the Applicative, Foldable, Traversable, Applicative, and Distributive classes, as well as some Template Hashell to derive some of their instances automatically.
_______________________________________________ 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.
_______________________________________________ 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.

I don't think this is quite the same.
`compdata` seems to define:
(f :->
http://hackage.haskell.org/package/compdata-0.11/docs/Data-Comp-Multi-HFunct...
g)
-> h f :->
http://hackage.haskell.org/package/compdata-0.11/docs/Data-Comp-Multi-HFunct...
h
g
But I want:
(f :->
http://hackage.haskell.org/package/compdata-0.11/docs/Data-Comp-Multi-HFunct...
g)
-> h f ->
http://hackage.haskell.org/package/compdata-0.11/docs/Data-Comp-Multi-HFunct...
h
g
Notice the lack of colon between the last two arguments. It's ordinary
function application there.
On Tue, Jul 11, 2017 at 5:02 PM, Sergey Vinokurov
Hi Clinton,
Sorry for late reply, but just for the sake of completeness the compdata package defines just the functor you mentioned http://hackage.haskell.org/package/compdata-0.11/docs/ Data-Comp-Multi-HFunctor.html#t:HFunctor.
Regards, Sergey
On Tue, Jul 11, 2017 at 9:18 AM, Clinton Mead
wrote: Hi All
Thanks for all your help.
I've actually picked up Mario's rank2classes package as it seems like I need a little but more power than Functors, as I want things like `liftA2` for example.
I've pushed across a very simple pull request to you Mario that simply adds "PolyKinds" to your list of language extensions. This automatically this generalises the kinds your Functor and Apply accept (and perhaps others) as I'm quantifying not over * but over a data kind type. No other changes are needed.
Clinton
On Sat, Jul 8, 2017 at 5:57 AM, Mario Blažević
wrote: On 2017-07-07 12:48 AM, Clinton Mead wrote:
Consider the illustrative code below: ... class MyFunctor f where myFmap :: (forall a. t a -> u a) -> f t -> f u ...
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?
Yes, I have recently created rank2classes package:
http://hackage.haskell.org/package/rank2classes
Apart from the mirror-universe Functor class, the package exports the Applicative, Foldable, Traversable, Applicative, and Distributive classes, as well as some Template Hashell to derive some of their instances automatically.
_______________________________________________ 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.
_______________________________________________ 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.
participants (8)
-
Clinton Mead
-
David Menendez
-
Erik Hesselink
-
Ivan Lazar Miljenovic
-
Li-yao Xia
-
Mario Blažević
-
Rein Henrichs
-
Sergey Vinokurov