[Haskell-cafe] Stupid question, re: overloaded type classes

sam lee skynare at gmail.com
Sun Jan 18 15:43:23 EST 2009


The following code compiles fine on my ghci

ghci> :l sexpr.hs
[1 of 1] Compiling Sexpr            ( sexpr.hs, interpreted )
Ok, modules loaded: Sexpr.

$ ghci --version
The Glorious Glasgow Haskell Compilation System, version 6.8.2

-- code
    {-# LANGUAGE TypeSynonymInstances #-}
    module Sexpr where

    data Sexp = List [Sexp]
        | Atom String
        deriving (Eq, Ord, Show)

    class Sexpable a where
        toSexp :: a -> Sexp
        fromSexp :: Sexp -> Maybe a

    instance Sexpable String where
        toSexp s = Atom s
        fromSexp (Atom s) = Just s
        fromSexp _ = Nothing

    instance Sexpable a => Sexpable [ a ] where
        toSexp lst = List $ map toSexp lst
        fromSexp (List lst) = mapM fromSexp lst
        fromSexp _ = Nothing

On Sun, Jan 18, 2009 at 2:23 PM, Brian Hurt <bhurt at spnz.org> wrote:
>
> So, I'm working with this simplistic S-expression library of my own design (yes, I know, reinventing the wheel).  Basically, I have the type:
>
> data Sexp =
>        List of [ Sexp ]
>        | Atom of String
>
> with the associated parsers and printers which really aren't relevent to the question at hand.  Then, I want to define the type class of types I can convert to and from s-expressions, like:
>
> class Sexpable a where
>        toSexp :: a -> Sexp
>        fromSexp :: Sexp -> Maybe a
>
> here, fromSexp can return Nothing is the s-expression isn't the right form to be parsed into a whatever.
>
> Now, here's the problem.  I want to define a bunch of default instances, and two in particular I want to define are:
>
> instance Sexpable String where
>        toSexp s = Atom s
>        fromSexp (Atom s) = Just s
>        fromSexp _ = Nothing
>
> instance Sexpable a => Sexpable [ a ] where
>        toSexp lst = List $ map toSexp lst
>        fromSexp (List lst) = mapM fromSexp lst
>        fromSexp _ = Nothing
>
> Note that I am not implementing Sexpable Char anywhere, so the only valid transform for [Char] should be the String one.  But this still causes a compiler error due to the overloaded instances on [Char].
>
> There are two solutions to this that I already know of.  One is to play games with newtype, which I don't like because it simply adds complexity in my case and doesn't help anything else.  The second possibility is to compile with -fallow-incoherent-instances, which I'm slightly afraid of because I'm not sure what (if any) possible errors adding this option might allow.
>
> So my question is twofold: 1) what errors might be allowed if I add -fallow-incoherent-instances, and 2) is there some third choice that avoids both solutions I already know about?
>
> Thanks.
>
> Brian
>
> _______________________________________________
> 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