[Haskell-cafe] Higher order functor package?

Clinton Mead clintonmead at gmail.com
Fri Jul 7 18:44:14 UTC 2017


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-Index.html#t::-45--62->
b)
-> f a :->
<http://hackage.haskell.org/package/index-core-1.0.4/docs/Control-Category-Index.html#t::-45--62->
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 <hesselink at gmail.com> 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.html
>
> On 7 July 2017 at 06:48, Clinton Mead <clintonmead at gmail.com> 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.
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170708/3b747e32/attachment.html>


More information about the Haskell-Cafe mailing list