[Haskell-cafe] Newbie question: inferred type

Imam Tashdid ul Alam uchchwhash at yahoo.com
Fri Mar 31 04:52:12 EST 2006


most probably yes. I had the exact same question for:

module Factors 
where

import Prelude

divides x y = (mod x y == 0)

factors x = filter (divides x) [1..x]

nonTrivialFactors x = filter (\y -> y /= 1 && y /= x)
[1..x]

isEmpty [] = True
isEmpty _  = False

-- isPrime = isEmpty . nonTrivialFactor 
-- says isPrime :: Integer -> Bool
-- this one say isPrime :: (Integral a) => a -> Bool
isPrime x = isEmpty (nonTrivialFactors x)

frankly this is not desired, but I cannot see why it's
particularly harmful. is it?

note: I was devising this example mostly to show the
usefulness of laziness ;)

--- Neil Mitchell <ndmitchell at gmail.com> wrote:

> I think this is the monomorphism restriction, you
> can see more details
> on the web page:
> 
>
http://www.haskell.org/hawiki/MonomorphismRestriction
> 
> On 3/30/06, David Laffin <dl_y_post at yahoo.co.uk>
> wrote:
> >
> > Hi,
> >
> > Newbie question. Given the inferred type for
> square,
> > the
> > inferred types for quad1, quad2 and quad3 are what
> I
> > would
> > expect. Is there a straightforward explanation
> (i.e.
> > one
> > that a newbie would understand) as to why the
> inferred
> > type
> > for quad4 is less general?
> >
> > Regards,
> > dl
> >
> > -- GHC Interactive, version 6.4, for Haskell 98.
> >
> > Prelude> let square x = x * x
> > Prelude> :t square
> > square :: (Num a) => a -> a
> >
> > Prelude> let quad1 x = square (square x)
> > Prelude> :t quad1
> > quad1 :: (Num a) => a -> a
> >
> > Prelude> let quad2 x = square $ square x
> > Prelude> :t quad2
> > quad2 :: (Num a) => a -> a
> >
> > Prelude> let quad3 x = (square . square) x
> > Prelude> :t quad3
> > quad3 :: (Num a) => a -> a
> >
> > Prelude> let quad4 = square . square
> > Prelude> :t quad4
> > quad4 :: Integer -> Integer
> >
> >
> >
> >
> >
> >
> >
>
___________________________________________________________
> > Yahoo! Photos � NEW, now offering a quality
print
> service from just 8p a photo
> http://uk.photos.yahoo.com
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> >
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 


__________________________________________________
Do You Yahoo!?
Tired of spam?  Yahoo! Mail has the best spam protection around 
http://mail.yahoo.com 


More information about the Haskell-Cafe mailing list