[Haskell-cafe] Removing polymorphism from type classes (viz. Functor)

Edward Kmett ekmett at gmail.com
Thu Jul 9 09:36:51 EDT 2009


Well, you're going to wind up with a lot of cases where you really want a
quantified context, even with just your Functor definition, but in that same
spirit you can build an 'Applicative-like' instance as well.

> type family Arg f :: *
> type instance Arg [a -> b] = [a]

> type family Result f :: *
> type instance Result [a -> b] = [b]

> class Pointed f => Applicative f where
>     (<*>) :: f -> Arg f -> Result f

> instance Applicative [a -> b] where
>     fs <*> xs = do f <- fs; map f

The thing is these definitions are very hard to actually use. I have a
similar construction for Foldable/Traversable-like containers in the
'monoids' package as Data.Generator that you might want to look at for
ideas.

-Edward Kmett

On Tue, Jul 7, 2009 at 7:03 PM, George Pollard <porges at porg.es> wrote:

> Ok, so I have a small idea I'm trying to work on; call it a
> Prelude-rewrite if you want. For this I want to be able to have the
> hierarchy Functor → Applicative → Monad.
>
> For Functor, I would like to be able to implement it for a wider
> variety of types, as there are types which have aren't polymorphic
> which would also benefit from having an instance.
> My running example for this set of types is ByteString; the module
> contains the method:
>
>    map ∷ (Word8 → Word8) → ByteString → ByteString
>
> However, we cannot use this for Functor because ByteString isn't
> polymorphic. To get around this, I devised the following:
>
> Introduce a type family which represents ‘points’ inside the type:
>
>    type family Point f ∷ ★
>
> For ByteString we have:
>
>    type instance Point ByteString = Word8
>
> For a polymorphic example (lists) we have:
>
>    type instance Point [a] = a
>
> Now Functor becomes:
>
>    class SimpleFunctor f where
>        fmap ∷ (Point f → Point f) → (f → f)
>
> However, this doesn't allow for the existence of functions with the
> type (a → b). I need to introduce another type into the class:
>
>    class Functor f g where
>        fmap ∷ (Point f → Point g) → (f → g)
>
> But having two types isn't very nice (for one thing we can't introduce
> a fundep because for lists as it fails one of the coverage
> conditions), so introduce another type family to represent types which
> can be produced by giving a free variable:
>
>    type Subst f a ∷ ★
>    type Subst [a] b = [b]
>    type Subst ByteString b = ByteString
>
>    class Functor f where
>        fmap ∷ (Point f → Point (Subst f a)) → (f → Subst f a)
>
> I'm not sure how much of a hack this is, or if there is a better way.
> It seems to be OK...
>
> Now I want to implement Applicative. It would make sense to have
> ‘return’ be split out into a separate class, because this can be
> restricted in a similar way to Functor:
>
>    class Pointed f where
>        return ∷ Point f → f
>
>    instance Pointed [a] where
>        return x = [x]
>
>    instance Pointed ByteString where
>        return = BS.singleton
>
> Now, I want to be able to restrict Applicative to things which have
> [Pointed f, and forall a b. Point f ~ (a → b)]. At the moment I can't
> figure this out because I believe it would require something like the
> ‘quantified contexts’ proposal:
>
>    class (Pointed f, ∀ a b. Point f ~ (a → b)) ⇒ Applicative f where
>        ...
>
> I could have something like:
>
>    class (Pointed f, Point f ~ (a → b)) ⇒ Applicative f a b where
>        apply ∷ f → Subst f a → Subst f b
>
> This is still not very nice, because it requires two more type
> variables in the class, and the non-type-families version is far more
> straightforward... in fact, it makes sense for the Applicative class
> to have a polymorphic type because it must be able to have ‘return’
> applied to arbitrary functions (remember [fmap f xs ≡ return f `apply`
> xs]). So back to:
>
>    class Applicative f where
>        apply ∷ f (a → b) → f a → f b
>
> But then ‘return’ cannot be added via a superclass restriction to
> Pointed! I seem to have painted myself into a corner. Does anyone see
> a better way to go about this?
>
> Thanks,
> - George
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090709/b25d80a8/attachment.html


More information about the Haskell-Cafe mailing list