[Haskell-cafe] Function composition questions from a newbie

Daniel Fischer daniel.is.fischer at web.de
Tue Dec 1 10:48:52 EST 2009


Am Dienstag 01 Dezember 2009 10:32:24 schrieb newbie2009:
> leledumbo wrote:
> > None of them are legal, at least in my WinHugs they're not. What tools
> > are you using?
>
> 1) I am using GHCi. I put the following into a file named composition.hs
> and typed ":l composition.hs" in GHCi. I also did a ":browse Main"
> 2) Next, I installed WinHugs, and loaded the same hs file. It failed with
> an error when processing the definition for composition2

That's because composition2 has the context (Num (a -> a), Num a), which isn't allowed by 
Haskell98 [A type class constraint must have the form (T a1 a2 ... an), where T is a type 
constructor of arity n and the ai are *distinct* type variables; so (Num (a -> b)) would 
be legal, but (Num (a -> a)) isn't because it uses the same type variable twice]. If you 
enable extensions (I don't know how to do it in WinHugs, in hugs you'd pass the flag -98 
on the command line: hugs -98 composition.hs) it will work.

ghci has by default a few extensions enabled, so it accepts such a context *if it infers 
it itself* - if you want to give such a context in a type signature, you must enable 
FlexibleContexts ({-# LANGUAGE FlexibleContexts #-} in the source file or 
-XFlexibleContexts on the command line).

> 3) is GHC the standard Haskell implementation or should i be using WinHugs?

Depends on for what you'll be using it. For any serious programmes, you'll need GHC to 
compile. And GHC implements more (seriously useful) extensions. And most code will run 
significantly faster in ghci than in hugs/WinHugs.
But hugs/WinHugs loads the code faster.
If you're working on a large project, it can be bothersome to wait for ghci to load the 
code again after making changes, so testing the changes in hugs/WinHugs is preferred by 
some (I've never worked on a project that took more than a few seconds to load in ghci, 
which is more than compensated by the faster execution, so I don't use hugs much).

While learning Haskell, it's probably good to use hugs/WinHugs at least alongside ghci 
because hugs' error messages are often more newbie-friendly.

>
> -----------8<-----------

What does ghci tell us is the type of things, and why does it tell us that?

>
square :: (Num a) => a -> a
Obvious, isn't it?
> square x = x * x

add :: (Num a) => a -> a -> a                                 
That too.
> add x y = x + y

add3 :: (Num a) => a -> a -> a -> a                           
And that.
> add3 x y z = x + y + z

composition1 :: Integer -> Integer -> Integer                 
This - not.
> composition1 = add . square

Why is the type of composition1 not
composition1 :: (Num a) => a -> a -> a
as one would expect from the types of square, add and (.) ?

Welcome to the wonderful world of "The dreaded Monomorphism Restriction".
(http://haskell.org/onlinereport/decls.html#sect4.5.5 , 
http://www.haskell.org/haskellwiki/Monomorphism_restriction )
Indeed, (Num a) => a -> a -> a *is* the type determined by type inference.
But since it is defined with neither type signature nor argument, the monomorphism 
restriction says the type variable a must be resolved to a plain type. By the defaulting 
rules, the type variable a is replaced by Integer.

To give composition1 the more general type,
a) give a type signature
b) define it with an argument: composition1 x = (add . square) x
c) pass -XNoMonomorphismRestriction to ghci on the command line 
(or put ":set -XNoMonomorphismRestriction" in your .ghci file).

a) is good practice anyway
b) is a good way if you define functions at the interactive prompt
c) is especially good if you don't want to write type signatures

> -- composition1 5 6 == 31
>
> -- composition2 = square . add -- wont work
>
composition2 :: (Num (a -> a), Num a) => a -> a -> a          
Okay, (square . add) x = square (add x) = (add x) * (add x); If x has type a (belonging to 
the Num class), add x has type (a -> a), since we want to apply square to that, its type 
also must belong to the Num class, hence the inferred type
> composition2 x = (square . add) x	-- to make it work, make composition2
> take an argument

Without the argument, we'd enter MR-land again, but now the constraint (Num (a -> a)) 
prevents the assignment of a monomorphic type (its form violates the demands of the 
defaulting rules, http://haskell.org/onlinereport/decls.html#sect4.3.4), so it doesn't 
work.
Again, it would work with a type signature or with the monomorphism restriction turned 
off. 
The same (with minor modifications) applys to the "square . add3" variants.

> -- composition2 5 9 == 196
>
> composition3 x y = square . (add3 x y)	-- composition3 1 2 3 == 36
> composition4 x y = square . add3 x y	-- composition4 1 2 3 == 36

composition4 is exactly the same as composition3, function application has higher 
precedence than composition, so both are parsed as

square . ((add3 x) y)

> composition5 x y = (square . add3) x y	-- TODO: what does this mean?? how
> do we invoke composition5

To invoke it, we need an 
instance Num (a -> a -> a)
for some type a belonging to Num (or for all a belonging to Num).
It's possible to declare such instances, but you really shouldn't.

> composition6 x = (square . add3) x 		-- TODO: what does this mean?? how do
> we invoke composition5
> composition7 x = (square . add3) x 8
> composition8 x = (square . add3) 1 2 x
> composition9 x = (square . add3) x
> composition10 x = (square . add3) 1 2 3
>
> -----------8<-----------


I suspect that what you want are functions

sqadd x y = square (x+y)
sqadd3 x y z = square (x + y + z)

, first apply add/add3 to the appropriate number of arguments and then square it.

If that is correct, the following may help:

sqadd x y = square (add x y)
    = square ((add x) y)
    = (square . (add x)) y

hence

sqadd x = square . add x
    = (.) square (add x)
    = ((.) square) (add x)
    = (((.) square) . add) x

hence 

sqadd = ((.) square) . add

or, nicer IMO,

sqadd = (square .) . add

Similarly,

sqadd3 = ((square .) .) . add3

For each argument you want the right hand function to consume, you need one composition 
(.).



More information about the Haskell-Cafe mailing list