
OK, what about this as a use case then. I want to create a type class 'Term'
with only one function in it. The function returns a 'termTag' which labels
the *"kind"* of a value in a DSL.
class Term a where
termTag :: a -> String
A user of this type-class can happily provide an instance without any other
type class requirement. However, I want those types which are instances of
Data to be an instance of Term automatically. On top of that, I don't want
to stop the user from creating a special instance for their data type.
I want to be able to write the following instance to accomplish that:
instance Data t => Term t where
termTag = show . toConstr
And if the user wants to write a more specific instance, they should be
welcome to do so:
instance Term UserDT where
termTag (...) = ...
I am not very much interested in the technical details about how things
currently are, I am more interested in a discussion about why (if?) this
would be considered a *design flaw*?
Best,
On 1 February 2011 12:18, Stephen Tetley
On 1 February 2011 11:47, Ozgur Akgun
wrote: So, is there a way to declare an AbGroup instance for the types with num instances only?
No - as Henning says its then no more useful than simply a function:
add :: (Num u) => a -> a -> a add = (+)
'Overarching instances' i.e. classes with one implementation are a design flaw, not a virtue [*] so this hypothetical extension isn't welcome...
{-# LANGUAGE OverarchingInstances #-}
[*] Of course, there might be some valid cases for things in Oleg Kiselyov's typecast style, but modelling numericals doesn't look like one of them.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ozgur Akgun