[Haskell-cafe] specialization in type classes

Cetin Sert cetin.sert at gmail.com
Fri Jun 5 08:09:25 EDT 2009


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?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090605/70192386/attachment.html


More information about the Haskell-Cafe mailing list