Stupid question, re: overloaded type classes

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

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, Jan 18, 2009 at 12:43 PM, sam lee
The following code compiles fine on my ghci
This seems like a bug, you didn't enable overlapping instances and these two instances clearly overlap:
instance Sexpable String where instance Sexpable a => Sexpable [ a ] where
since String is a synonym for [Char]. Although maybe overlapping doesn't get checked until you use the instance? Try adding this line:
test = toSexp "hello"
-- ryan -- ryan

On Sun, Jan 18, 2009 at 11:23 AM, Brian Hurt
instance Sexpable String where
instance Sexpable a => Sexpable [ a ] where
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].
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?
1) Incoherent instances end up being used in code like this: blah :: Sexpable a => a -> Sexp blah x = toSexp [x] In this case, assuming an instance for Sexpable Char, this code may or may not use the "wrong" instance, depending on what happens with inlining: blah 'x' which passes the dictionary for Sexpable Char and then probably uses the instance Sexpable a => Sexpable [a] (with a = Char), instead of Sexpable String. As long as there are no instances for Sexpable Char anywhere, incoherent instances won't cause an error in this case. That said, you can't guarantee that someone won't go and add an instance for Char. 2) A third choice is to do what Show does, which is kind of a hack but solves this specific problem: class Sexpable a where toSexp :: a -> Sexp fromSexp :: Sexp -> Maybe a toSexpList :: [a] -> Sexp fromSexpList :: Sexp -> Maybe [a] toSexpList = List . map toSexp fromSexpList (List lst) = mapM fromSexp lst fromSexpList _ = Nothing instance Sexpable a => Sexpable [a] where toSexp = toSexpList -- from Sexpable a, not [a] fromSexp = fromSexpList This requires Sexpable Char, though, to give you the right place to put the instance. But it seems easy enough to include those; is there a reason you explicitly don't want an instance for Char? instance Sexpable Char where toSexp c = toSexpList [c] fromSexp l = do [c] <- fromSexp l return c toSexpList s = Atom s fromSexpList (Atom s) = Just s fromSexpList _ = Nothing I think that a design for typeclasses that eliminates the need for the "showList" hack would be quite welcome. -- ryan

Maybe [a] . The default implementation of this method is as in your instance for lists. For chars, you simply override this method to handle lists of chars differently. See the show and showList methods of the Show typeclass for an example of how this is done in
The simple and H98 solution here is to give your typeclass a toSexpList method and a fromSexpList method of [a] -> Sexp and Sexp - the standard libraries. --S On Jan 18, 2009, at 2:23 PM, Brian Hurt 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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Brian Hurt
-
Ryan Ingram
-
sam lee
-
Sterling Clover