[Haskell-cafe] Typeclass default implementation in subclasses

Roel van Dijk vandijk.roel at gmail.com
Mon Jul 20 08:40:26 EDT 2009


This post is also literate haskell. By enabling these potentially
dangerous extensions you'll get the behaviour you want.

> {-# LANGUAGE TypeSynonymInstances #-}
> {-# LANGUAGE UndecidableInstances #-}
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE OverlappingInstances #-}

> module Thing where

> import Text.PrettyPrint.HughesPJ

> ppQuote :: Show a => a -> Doc
> ppQuote = doubleQuotes . text . show

> x :: Int
> x = 1

> y :: String
> y = "hello"
> z :: Char
> z = 'a'

> class (Show a) => Quotable a where
>   quote :: a -> Doc
>   quote = ppQuote

> instance (Show a) => Quotable a

> instance Quotable String where
>   quote = text . show -- don't need the doubleQuotes call for String

> instance Quotable Char where
>   quote c = quote [c] -- just lift it to String

Example:

*Thing> quote "pi"
"pi"
*Thing> quote 3.14159
"3.14159"


More information about the Haskell-Cafe mailing list