[Haskell-cafe] Re: specialization in type classes

Ryan Ingram ryani.spam at gmail.com
Fri Jun 5 13:35:28 EDT 2009


The SPECIALIZE pragma doesn't do what you think; those implementations
are already as specialized as they get.

You can enable OverlappingInstances, but the big problem is that it
doesn't really work; consider this function:

> foo :: Show a => a -> String
> foo x = out x

> question = foo "hello"

What should "question" return?  "hello", or "\"hello\""?

With the "dictionary-passing-style" that GHC uses for typeclasses,
"foo" will always call the Show a => Out a instance of out.  But
that's incorrect; question passes a String which has a specific
implementation of "out", and that implementation doesn't get called.

The right answer is to do this:

> newtype UseShow a = UseShow a
> instance Show a => Out (UseShow a) where
>    out (UseShow a) = show a

Now you can write

> test1 = out (UseShow 1) -- "1"
> test2 = out (UseShow "hello") -- "\"hello\""
> test3 = out "hello" -- "hello"

Feel free to use a shorter name for UseShow, of course :)

I believe there is a proposal to allow you to declare ad-hoc
superclasses of typeclasses; this would let you write

-- notice reversed => to <=
class Show a <= Out a where
   out :: a -> String
   out = show

This means that every instance of Show is required to be an instance
of Out; the default implementation of "out" for types that don't have
an explicit instance is given.  (In the dictionary-passing world, this
means that every "Show" dictionary will contain an "Out" dictionary,
instead of having to construct the "out" implementation as in your
instance, it could contain a different "out" function that the
default)

But this isn't in the language currently.

  -- ryan

2009/6/5 Cetin Sert <cetin.sert at gmail.com>:
> Now there's also a stackoverflow question for this:
> http://stackoverflow.com/questions/955711/specialization-in-type-classes-using-ghc
> Any help highly appreciated!
>
> 2009/6/5 Cetin Sert <cetin.sert at gmail.com>
>>
>> module IOStream where
>>
>> import System.IO
>> import System.IO.Unsafe
>>
>> class Out a where
>>   out :: a → String
>>
>> instance Show a => Out a where
>>   out = show
>>
>> instance Out String where
>>   {-# SPECIALISE out :: String → String #-}
>>   out = id
>>
>> instance Out Char where
>>   {-# SPECIALISE out :: Char → String #-}
>>   out = \x → [x]
>>
>> infixl 0 <<, ≪
>> (≪), (<<) :: Out a => IO Handle → a → IO Handle
>> (<<)= (≪)
>> h ≪ a = do
>>   s ← h
>>   hPutStr s $ out a
>>   return s
>>
>> cout, cin, cerr :: IO Handle
>> cout = return stdout
>> cin  = return stdin
>> cerr = return stderr
>>
>> endl :: String
>> endl = "\n"
>>
>> ---
>>
>> cetin at unique:~/lab/c/linking/demo$ ghci -fglasgow-exts iostream.hs
>> GHCi, version 6.10.2: http://www.haskell.org/ghc/  :? for help
>> Loading package ghc-prim ... linking ... done.
>> Loading package integer ... linking ... done.
>> Loading package base ... linking ... done.
>> Ok, modules loaded: IOStream.
>> Prelude IOStream> cout << 22 << False
>> 22False{handle: <stdout>}
>> Prelude IOStream> cout << 22 << False << endl
>>
>> <interactive>:1:0:
>>     Overlapping instances for Out String
>>       arising from a use of `<<' at <interactive>:1:0-26
>>     Matching instances:
>>       instance (Show a) => Out a -- Defined in IOStream
>>       instance Out String -- Defined in IOStream
>>     In the expression: cout << 22 << False << endl
>>     In the definition of `it': it = cout << 22 << False << endl
>>
>> o________________O
>>
>> how can I specialise a type class function?
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


More information about the Haskell-Cafe mailing list