Can anyone help with the following problem. I want to define a class 
called for example 'AType' with a member function called 'typename'  
which will return a string indicating the type of the value applied to 
the function. A default definition of this member function returns the 
string "Default" for types declared as members of the class but which do
not define a string to return. For example, this class listed below 
allows me to do the following (as expected).

> typename 'a'
"Char"

> typename "Hello"
"[Char]"

> typename ('a',"Hello")
"(Char,[Char])"

> typename True
"Default"

My problem though is with members of the 'Num' class, as an overloading
ambiguity problem arises with the following expression. 

> typename 1
"Error ...... etc."

I can circumvent the problem by supplying an explicit type signature

> typename (1::Int)
"Int"

but this is not a satisfactory solution for the class I require. I thought
that the module 'default declaration' keyword might help but I am still 
getting errors. I would (1) preferably like to be able to distinguish 
between all members of the Num class, but (2) would be happy enough if
all members of the Num class were lumped together and a default type
string could be declared eg "Number".

Can anyone suggest how I might solve this problem. (Note there is no 
such problem if I run my script through Gofer!). 

many thanks,

Aiden McCaughey
School of Computing & Mathematics
University of Ulster
EMAIL: [EMAIL PROTECTED]
TEL:   (44) 504 265621 ext 5334

----------------------------------------------------------------------
module AType where

class AType a where
  typename :: a -> String
  typename _ = "Default"

instance AType Int where
  typename _ = "Int"

instance AType Char where
  typename _ = "Char"

instance AType [a] where
  typename (x:xs) = "[" ++ (typename x) ++ "]"

instance (AType a, AType b) => AType (a,b) where
  typename (a,b) = "("++ typename a ++ "," ++ typename b ++ ")"

instance AType Bool

---------------------------------------------------------------------

Reply via email to