[Hugs-users] Typing the plus operator

Daniel Fischer daniel.is.fischer at web.de
Sat Aug 5 20:04:43 EDT 2006


Am Samstag, 5. August 2006 19:58 schrieb aldirithms at gmx.net:
> Hello Hugs Users,
>
> do you know why
>
> Hugs> :t 1
> 1 :: Num a => a
>
>
> and therefore
>
>
> Hugs> 1 :: Num a => a
> 1
>
>
> is possible under Hugs, whereas
>
> Hugs> :t (+)
> (+) :: Num a => a -> a -> a
>
> and (not?) therefore
>
> Hugs> (+) :: Num a => a -> a -> a
> ERROR - Cannot find "show" function for:
> *** Expression : (+)
> *** Of type    : Integer -> Integer -> Integer
>
>
> yields the error message shown?
>
> Thank you very much,
>
> Christian,
>
> Haskell beginner

Ugh, what do you know about type classes yet? 
If you know a little Java, the statement that type classes are much like a 
Java interface should give you an approximate idea.
If you let hugs evaluate an expression, it prints out a String representation 
of (the result of evaluating) the expression _if it can construct one_.
How canit construct one? That's what the Show class is for, types that are 
instances of Show provide a method to construct String representations of 
values of such a type (this method is, surprise, surprise, called show -- 
there's more to the Show class, but you needn't care about that yet).
Now if you type 
:i Num
to the hugs prompt, it will print out
...
class (Eq a, Show a) => Num a where
... ,
meaning that all types which instantiate Num must necessarily also instantiate 
Show, so that such values can be displayed and that's what happens if you 
type
Hugs> 1 :: Num a => a
to the prompt, the expression is evaluated and the appropriate "show" method 
is invoked to get the String representation that is printed out -- however, 
here's also something else going on: defaulting. Since 1 is polymorphic, if 
hugs is to print a representation of 1, it must select a show function to 
convert it to a String and, unless something else is specified by a 
default-declaration, it selects the Integer instance of Show to print out the 
value (cf. section 4.3.4 of the Haskell report, as a deviant example:
BoolNum> 1
True
BoolNum> 1.0
1 % 1
BoolNum> :t 1
1 :: Num a => a
BoolNum> :t 1.0
1.0 :: Fractional a => a

where I used 

module BoolNum where

default (Bool, Rational)

instance Num Bool where
    (+) = (/=)
    (-) = (/=)
    (*) = (&&)
    negate x = x
    abs x = x
    signum x = x
    fromInteger = odd

)

but (+) is a function, of type Num a => a -> a -> a, and function types aren't 
instances of Show (well, there's a module Text.Show.Functions that makes them 
instances of Show, but:
Text.Show.Functions> (+)
<function>
Text.Show.Functions> sin
<function>,
so that's not really helpful) and that's what hugs complains about:
BoolNum> (+)
ERROR - Cannot find "show" function for:
*** Expression : (+)
*** Of type    : Bool -> Bool -> Bool

it can't find an appropriate "show" function -- note that here, with my 
default declaration, it looks for a show-function of type 
(Bool -> Bool -> Bool) -> String, whereas with the default default, it looked 
for a show-function of type
(Integer -> Integer -> Integer) -> String,
that's defaulting in action.
However, if I also provide

instance Show a => Show (Bool -> a) where
    showsPrec p f = showParen (p > 0)
                    (showString ('\n':replicate (4*p) ' ') .
                     showString "True  -> " . showsPrec (p+1) (f True) .
                     showString ('\n':replicate (4*p) ' ') .
                     showString "False -> " . showsPrec (p+1) (f False))

(that requires the -98 flag for hugs),
 I get
BoolNum> (+)

True  -> (
    True  -> False
    False -> True)
False -> (
    True  -> True
    False -> False)
BoolNum> (+) :: Integer -> Integer -> Integer
ERROR - Cannot find "show" function for:
*** Expression : (+)
*** Of type    : Integer -> Integer -> Integer

Now you might ask "why aren't functions showable?"
a) well, how could you show them? 
The above method could be generalised to functions with other small domains 
(in principle also with large domains, as long as they are finite) and 
showable results, but imagine thus showing a function of type
Bool -> Bool -> ... -> Bool 
where the ellipsis stands for, say, 1000 further occurences of Bool.
Printing that out would take a while (had you started at Big Bang with a 
really fast computer, by now you wouldn't have printed a significant portion 
of the function) and the output would be completely unhelpful. And if you 
consider theoretically infinite types like Integer and Rational (in practice 
these too are finite because your computer is), showing a function table is 
obviously not an option.

b) there's a deeper reason, too. I don't remember the details, but a few 
months ago there was a discussion on haskell cafe where it was mentioned that 
showing functions (in a non-constant way, what Text.Show.Functions provides 
is harmless) breaks referential transparency (deep waters for a beginner, 
keep out for a while).

HTH,
Daniel

-- 

"In My Egotistical Opinion, most people's C programs should be
indented six feet downward and covered with dirt."
	-- Blair P. Houghton



More information about the Hugs-Users mailing list