Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Why is type "Integer -> Integer" and not     "(Num a) => a
      -> a"? (Chadda? Fouch?)
   2. Re:  Why is type "Integer -> Integer" and not     "(Num a) => a
      -> a"? (Shawn Willden)
   3. Re:  Why is type "Integer -> Integer" and not     "(Num a) => a
      -> a"? (Felipe Lessa)
   4. Re:  Why is type "Integer -> Integer" and not     "(Num a) => a
      -> a"? (Nathan M. Holden)
   5. Re:  Why is type "Integer -> Integer" and not     "(Num a) => a
      -> a"? (Chadda? Fouch?)
   6. Re:  maybe this could be improved? (Patrick LeBoutillier)
   7. Re:  maybe this could be improved? (Michael Mossey)
   8. Re:  maybe this could be improved? (Patrick LeBoutillier)


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

Message: 1
Date: Thu, 12 Nov 2009 10:04:53 +0100
From: Chadda? Fouch? <chaddai.fou...@gmail.com>
Subject: Re: [Haskell-beginners] Why is type "Integer -> Integer" and
        not     "(Num a) => a -> a"?
To: Dag Hovland <dag.hovl...@uib.no>
Cc: beginners@haskell.org
Message-ID:
        <e9350eaf0911120104w47a61b3fiafa66ed762f13...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Thu, Nov 12, 2009 at 9:37 AM, Dag Hovland <dag.hovl...@uib.no> wrote:
> Hi!
>
> I have a problem with understanding some types given by ghc and hugs.
> The file loaded is:
>
> f1 = \x -> x * 2
> f2 x = x * 2
>
> After they are loaded I get the following from ghci
>
> *Main> :t f1
> f1 :: Integer -> Integer
> *Main> :t f2
> f2 :: (Num a) => a -> a
> *Main> :t \x -> x * 2
> \x -> x * 2 :: (Num a) => a -> a

This is called the monomorphism restriction, it's a rule that state a
binding _without_parameters_ shall be inferred of a monomorphic type
unless an explicit signature is given. There are several reasons for
it, some of efficiency (polymorphism has a cost) and some of a more
technical nature, refer to the Haskell Report for a more detailed
explanation.

Some Haskellers think this restriction is no longer required, that GHC
is now often intelligent enough to alleviate the cost of polymorphism,
that the technical reasons are not really all that pertinent and that
the default should be to infer the more general type in all case
rather than confuse beginners and oblige experts to put explicit
signatures. It is already possible to deactivate the restriction by
using the -XNoMonomorphismRestriction argument (or putting the
equivalent language pragma in the code itself or in the cabal
description file) and making this the default is discussed for
Haskell' (the future standard for Haskell).

In the meantime, it is a good idea to put ":set
-XNoMonomorphismRestriction" in your .ghci file since most usage of
GHCi would only hit the disadvantages of this rule and reap no
benefits from it.

-- 
Jedaï


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

Message: 2
Date: Thu, 12 Nov 2009 02:06:00 -0700
From: Shawn Willden <shawn-hask...@willden.org>
Subject: Re: [Haskell-beginners] Why is type "Integer -> Integer" and
        not     "(Num a) => a -> a"?
To: beginners@haskell.org
Message-ID: <200911120206.00364.shawn-hask...@willden.org>
Content-Type: text/plain;  charset="iso-8859-1"

On Thursday 12 November 2009 01:45:08 am Joe Fredette wrote:
> My guess is that, defining in GHCi
>
>  > let f x = x * 2
>  > let g = \x -> x * 2
>
> the former doesn't default to anything (it just does inference) since
> it's a function definition, and the latter defaults the '2' to an
> Integer because it's a value -- or some suitable analog of that
> situation.

Hmm.  Would that also explain this?

Prelude> let f1 x = x * 2
Prelude> :type f1
f1 :: (Num a) => a -> a
Prelude> let f2 = \x -> f1 x
Prelude> :type f2
f2 :: Integer -> Integer

        Shawn.


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

Message: 3
Date: Thu, 12 Nov 2009 08:40:49 -0200
From: Felipe Lessa <felipe.le...@gmail.com>
Subject: Re: [Haskell-beginners] Why is type "Integer -> Integer" and
        not     "(Num a) => a -> a"?
To: Shawn Willden <shawn-hask...@willden.org>
Cc: beginners@haskell.org
Message-ID:
        <c2701f5c0911120240le8bcb7ao85e7ade64e0d6...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Thu, Nov 12, 2009 at 7:06 AM, Shawn Willden
<shawn-hask...@willden.org> wrote:
> Hmm.  Would that also explain this?
>
> Prelude> let f1 x = x * 2
> Prelude> :type f1
> f1 :: (Num a) => a -> a
> Prelude> let f2 = \x -> f1 x
> Prelude> :type f2
> f2 :: Integer -> Integer

Yes, that's the same monomorphism restriction.  Also, note that you
are defaulting to Integer here:

Prelude> :s -Wall
Prelude> let f1 x = x * 2
Prelude> :t f1
f1 :: (Num a) => a -> a
Prelude> let f2 = \x -> f1 x

<interactive>:1:15:
    Warning: Defaulting the following constraint(s) to type `Integer'
             `Num a' arising from a use of `f1' at <interactive>:1:15-18
    In the expression: f1 x
    In the expression: \ x -> f1 x
    In the definition of `f2': f2 = \ x -> f1 x
Prelude> let f3 :: Int -> Int; f3 = \x -> f1 x
Prelude> let f4 :: Num a => a -> a; f4 = \x -> f1 x

I find -Wall very useful. Relatively few times it gets annoying.

HTH,

-- 
Felipe.


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

Message: 4
Date: Thu, 12 Nov 2009 11:40:35 -0500
From: "Nathan M. Holden" <nathanmhol...@gmail.com>
Subject: Re: [Haskell-beginners] Why is type "Integer -> Integer" and
        not     "(Num a) => a -> a"?
To: dag.hovl...@uib.no
Cc: beginners@haskell.org
Message-ID: <200911121140.35748.nathanmhol...@gmail.com>
Content-Type: Text/Plain;  charset="us-ascii"

This is just a theory, but in my (limited) experience, GHCi is willing to 
guess at the type of values, where at functions (explicitly or implicitly 
typed) it can't guess.

In your original function, it multiplied a number (Num a) => a by an Int, 
therefor it must be Int -> Int (because you can't multiply a Double by an Int, 
don't be crazy.

In the new function, though, it can infer the type of the 2, and therefor it 
can infer it to whatever numerical type you send it.

I've run into this problem a few times, but for whatever reason I can't get 
myself to fall into any of the usual ways I walk blindly into these sorts of 
problems this time.


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

Message: 5
Date: Thu, 12 Nov 2009 18:44:59 +0100
From: Chadda? Fouch? <chaddai.fou...@gmail.com>
Subject: Re: [Haskell-beginners] Why is type "Integer -> Integer" and
        not     "(Num a) => a -> a"?
To: "Nathan M. Holden" <nathanmhol...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <e9350eaf0911120944g44c1720cge94f735fa110b...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Thu, Nov 12, 2009 at 5:40 PM, Nathan M. Holden
<nathanmhol...@gmail.com> wrote:
> This is just a theory, but in my (limited) experience, GHCi is willing to
> guess at the type of values, where at functions (explicitly or implicitly
> typed) it can't guess.
>
> In your original function, it multiplied a number (Num a) => a by an Int,
> therefor it must be Int -> Int (because you can't multiply a Double by an Int,
> don't be crazy.

That is not the problem : as the rest of your message acknowledge 2 is
not an Int, it is of type (Num a) => a. The issue rest squarely with
the fact that the binding f1 don't have parameter expressed on the
left side of the "=", thus the monomorphism restriction kicks in (as
alluded, probably, by your first paragraph) and GHC has to use the
defaulting rules to find a monomorphic type for f1.

-- 
Jedaï


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

Message: 6
Date: Thu, 12 Nov 2009 14:05:58 -0500
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Subject: Re: [Haskell-beginners] maybe this could be improved?
To: Michael P Mossey <m...@alumni.caltech.edu>
Cc: beginners@haskell.org
Message-ID:
        <b217a64f0911121105p3429c6b7g5e08f928ffa7a...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Michael,

Here's my stab at it, not sure if it's really better though:


findClosestPitch :: SampleMap -> Pitch -> ErrorT String Identity Pitch
findClosestPitch samples inPitch = do
  when (M.null samples) $ throwError "Was given empty sample table."
  case M.splitLookup inPitch samples of
    (_, Just _, _) -> return inPitch
    (ml, _, mh)    -> return $ approxPitch ml mh
    where
      approxPitch ml mh | M.null ml = fst . M.findMin $ mh
      approxPitch ml mh | M.null mh = fst . M.findMax $ ml
      approxPitch ml mh             = closest (fst . M.findMax $ ml)
(fst . M.findMin $ mh)
        where closest a b = min (inPitch - a) (b - inPitch)


I tried to separate the approximation part from the rest of the code,
and used a bit of deduction to eliminate (hopefully correctly...) some
of the testing conditions.
Anyways, I had fun doing working on this, and I learned a bit about
computerized music as well!


Thanks,

Patrick




On Wed, Nov 11, 2009 at 9:15 PM, Michael P Mossey
<m...@alumni.caltech.edu> wrote:
> Patrick LeBoutillier wrote:
>>
>> Michael,
>>
>> Your code is interesting and I'd like to run it, but I'm not to
>> familiar with Maps and Monad transformers.
>> Could you provide a function to create a SampleMap and a way to test
>> it from ghci?
>>
>
> Sure,
>
>
> import Control.Monad.Identity
> import Control.Monad.Error
> import Control.Monad
> import qualified Data.Map as M
>
> type Pitch = Int
> type Sample = String
> type SampleMap = M.Map Pitch Sample
>
>
> -- Given a SampleMap and a Pitch, find the Pitch in the SampleMap
> -- which is closest to the supplied Pitch and return that. Also
> -- handle case of null map by throwing an error.
> findClosestPitch :: SampleMap -> Pitch -> ErrorT String Identity Pitch
> findClosestPitch samples inPitch = do
>  when (M.null samples) $ throwError "Was given empty sample table."
>  case M.splitLookup inPitch samples of
>   (_,Just _,_ ) -> return inPitch
>   (m1,_        ,m2) | (M.null m1) && not (M.null m2) -> case1
>                     | not (M.null m1) && (M.null m2) -> case2
>                     | otherwise                      -> case3
>     where case1 = return . fst . M.findMin $ m2
>           case2 = return . fst . M.findMax $ m1
>           case3 = return $ closest (fst . M.findMax $ m1)
>                                    (fst . M.findMin $ m2)
>           closest a b = if abs (a - inPitch) < abs (b - inPitch)
>                          then a
>                          else b
>
>
> testMap1 = M.fromList [ (1,"sample1")
>                      , (5,"sample2")
>                      , (9,"sample3") ]
>
> -- testMap2 ==> Right 1
> testMap2 = runIdentity $ runErrorT $ findClosestPitch testMap1 2
>
>
> -- testMap3 ==> Right 5
> testMap3 = runIdentity $ runErrorT $ findClosestPitch testMap1 5
>
> -- testMap4 ==> Left "Was given empty sample table."
> testMap4 = runIdentity $ runErrorT $ findClosestPitch M.empty 5
>
>
>
>
>



-- 
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada


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

Message: 7
Date: Thu, 12 Nov 2009 14:31:29 -0800
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: Re: [Haskell-beginners] maybe this could be improved?
To: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <4afc8cc1.1040...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hi, Thanks for your help and it looks like you identified some conditions 
that could be removed. There is one change necessary, I think.

closest a b = if (inPitch - a) < (b - inPitch) then a else b

Patrick LeBoutillier wrote:
> Michael,
> 
> Here's my stab at it, not sure if it's really better though:
> 
> 
> findClosestPitch :: SampleMap -> Pitch -> ErrorT String Identity Pitch
> findClosestPitch samples inPitch = do
>   when (M.null samples) $ throwError "Was given empty sample table."
>   case M.splitLookup inPitch samples of
>     (_, Just _, _) -> return inPitch
>     (ml, _, mh)    -> return $ approxPitch ml mh
>     where
>       approxPitch ml mh | M.null ml = fst . M.findMin $ mh
>       approxPitch ml mh | M.null mh = fst . M.findMax $ ml
>       approxPitch ml mh             = closest (fst . M.findMax $ ml)
> (fst . M.findMin $ mh)
>         where closest a b = min (inPitch - a) (b - inPitch)
> 
> 
> I tried to separate the approximation part from the rest of the code,
> and used a bit of deduction to eliminate (hopefully correctly...) some
> of the testing conditions.
> Anyways, I had fun doing working on this, and I learned a bit about
> computerized music as well!
> 
> 
> Thanks,
> 
> Patrick
> 
> 
> 


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

Message: 8
Date: Thu, 12 Nov 2009 19:06:23 -0500
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Subject: Re: [Haskell-beginners] maybe this could be improved?
To: Michael Mossey <m...@alumni.caltech.edu>
Cc: beginners@haskell.org
Message-ID:
        <b217a64f0911121606m7004f769of03fa1f82fd44...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Thu, Nov 12, 2009 at 5:31 PM, Michael Mossey <m...@alumni.caltech.edu> wrote:
> Hi, Thanks for your help and it looks like you identified some conditions
> that could be removed. There is one change necessary, I think.
>
> closest a b = if (inPitch - a) < (b - inPitch) then a else b

Yes, of course. I just happens that in the test code (testMap2) it
gives the same answer...

Patrick



>
> Patrick LeBoutillier wrote:
>>
>> Michael,
>>
>> Here's my stab at it, not sure if it's really better though:
>>
>>
>> findClosestPitch :: SampleMap -> Pitch -> ErrorT String Identity Pitch
>> findClosestPitch samples inPitch = do
>>  when (M.null samples) $ throwError "Was given empty sample table."
>>  case M.splitLookup inPitch samples of
>>    (_, Just _, _) -> return inPitch
>>    (ml, _, mh)    -> return $ approxPitch ml mh
>>    where
>>      approxPitch ml mh | M.null ml = fst . M.findMin $ mh
>>      approxPitch ml mh | M.null mh = fst . M.findMax $ ml
>>      approxPitch ml mh             = closest (fst . M.findMax $ ml)
>> (fst . M.findMin $ mh)
>>        where closest a b = min (inPitch - a) (b - inPitch)
>>
>>
>> I tried to separate the approximation part from the rest of the code,
>> and used a bit of deduction to eliminate (hopefully correctly...) some
>> of the testing conditions.
>> Anyways, I had fun doing working on this, and I learned a bit about
>> computerized music as well!
>>
>>
>> Thanks,
>>
>> Patrick
>>
>>
>>
>



-- 
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada


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

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 17, Issue 15
*****************************************

Reply via email to