
Now there's also a stackoverflow question for this:
http://stackoverflow.com/questions/955711/specialization-in-type-classes-usi...
Any help highly appreciated!
2009/6/5 Cetin Sert
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@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?