[Haskell-cafe] Type families again

Robert Greayer robgreayer at gmail.com
Thu Dec 2 23:23:47 CET 2010


On Thu, Dec 2, 2010 at 4:39 PM, Antoine Latter <aslatter at gmail.com> wrote:
> On Thu, Dec 2, 2010 at 3:29 PM, Andrew Coppin
> <andrewcoppin at btinternet.com> wrote:
>> Yes, it's me. And yes, I come with yet more questions.
>>
>> With Haskell 98 (or, indeed, Haskell 2010) it is impossible to define a
>> polymorphic version of "head" that works for [], Set and ByteString. You can
>> use a higher-kinded type class for [], but that fails for Set (because you
>> can't specify the Ord constraint) and fails spectacularly for ByteString
>> (because it has the wrong kind). The basic problem is that the function's
>> type needs to refer to the type of the container and the type of elements it
>> contains, but the relationship between these types can be arbitrary.
>>
>> Type families allow you to neatly and cleanly fix the problem:
>>
>>  class Head c where
>>    type Element c :: *
>>    head :: c -> Element c
>>
>> It's simple, comprehensible, and it /actually works/.
>>
>> Following this success, we can define functions such as tail, join, and so
>> forth.
>>
>> What we /can't/ do is define a polymorphic map function. One might try to do
>> something like
>>
>>  class Functor f where
>>    type Element f :: *
>>    fmap :: (Element f2 ~ y) => (x -> y) -> f -> f2
>>
>>  instance Functor [x] where
>>    type Element [x] = x
>>    fmap = map
>>
>> However, this fails. Put simply, the type for fmap fails to specify that f
>> and f2 must be /the same type of thing/, just with different element types.
>>
>> The trouble is, after spending quite a bit of brainpower, I literally cannot
>> think of a way of writing such a constraint. Does anybody have any
>> suggestions?
>>
>
> Does this do what you need?
>
> http://hackage.haskell.org/packages/archive/rmonad/0.6/doc/html/Control-RMonad.html#t:RFunctor
>
> Antoine
>

I think this doesn't handle the ByteString case (wrong kind).  Here's
another mostly unsatisfactory (injectivity issues) solution that may
possibly not even work though it does compile:

import qualified Data.ByteString as B
import Data.Word

type family P c z

class Mappable1 c1 c2 where
    type E1 c1 c2
    type E2 c1 c2
    map1 :: (P c1 a ~ P c2 a) => (E1 c1 c2 -> E2 c1 c2) -> c1 -> c2

instance Mappable1 [a] [b] where
    type E1 [a] [b] = a
    type E2 [a] [b] = b
    map1 = map

type instance P [a] b = [b]

instance Mappable1 B.ByteString B.ByteString where
    type E1 B.ByteString B.ByteString = Word8
    type E2 B.ByteString B.ByteString = Word8
    map1 = B.map

type instance P B.ByteString b = B.ByteString



More information about the Haskell-Cafe mailing list