Re: [Haskell-cafe] Re: [Haskell] MR details (was: Implicit type of numeric constants)

2006-09-25 Thread Christian Sievers
Bernie Pope answered:

> > 1. Why do the rules of the monomorphism restriction explicitly mention
> >*simple* pattern bindings?
> >Where is the difference, especially as there is a translation to
> >simple pattern bindings?
> >Why should
> >
> >p | "a"=="b"  = 2
> >  | otherwise = 3
> >
> >be treated different than
> >
> >p = if "a"=="b" then 2 else 3
> 
> 
> They are the same (both are simple pattern bindings). The report says  
> in section 4.4.3.2 that the first can be translated into the second.

Indeed, I meant to allude to this translation.

> A simple pattern binding is one where the lhs is a variable only.

That's consistent with the second reason for rule one of the MR.

However, the mentioned section 4.4.3.2 defines it differently:

   A simple pattern binding has form p = e.

And if there is any doubt about what p stands for, it goes on:

   The pattern p ...

Contrasting to that:

   The general form of a pattern binding is p match, where a match is the same
   structure as for function bindings above; in other words, a pattern binding
   is: 
 
   p| g1= e1
| g2= e2
...
| gm= em
where { decls }


So according to this definition, a pattern binding is simple iff
there are no guards (unless they are in the expression).
Also the translation to a "simple pattern binding" only gets rid of guards.

So there seems to be an error in the report, which can be fixed by either
redefining "simple pattern binding", or using a differnet description in the
MR.


Bye
Christian Sievers
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphism/monomorphism (and the restriction)

2006-09-23 Thread Christian Sievers
Aaron McDaid wrote:

> This code experiments with "Int", "Float" and "(Num a) => a", and I 
> tried to print x*2 and x/2 for each. (4::Int)/2 isn't allowed because / 
> isn't defined for Ints.

More exactly: (/) is a member function of the Fractional class, and Int is not
an instance of this class.

> You can see that
>  kN :: (Num a) => a
> took two different types depending on what method ( / or * ) was applied 
> to it.
>  kN / 2 = 2.0
>  kN * 2 = 8
> kN/2 is a Float (it can't use Int as / isn't defined for Int, so it uses 
> Float, for which / is defined).

kN/2 has type  Fractional a => a  (try ":t kN/2" in ghci)
and when you apply it to show, a specific type will be chosen
by defaulting (Haskell report section 4.3.4).
Without an explicit default declaration, Haskell will try first Integer, then
Double.  Integer is not an instance of Fractional, so Double will be used.

You will get the types you claim to get when you add the line
"default (Int,Float)" at the top of your file.

> kN*2 is an Int.

By itself, it's  Num a => a,  then it will default to Integer.

> The above outputs demonstrates polymorphism, doesn't it? i.e. Not only 

Polymorphism (or rather: overloading) and defaulting.

> has the compiler got a variety of types to choose from, but a variety of 
> types can be used at runtime?

It only chooses (i.e. tries in order) the types given in the (posibly implicit)
default declaration.  At runtime it doesn't care about types, but of course
the same polymorphic or overloaded function can be used with different types.

> The interesting thing is that k behaves as a Float in both cases. This 
> is monomorphism isn't it? i.e. the compiler may have a variety of types 
> to choose from, but it picks one and sticks to it for every usage. In 
> summary, k didn't give the same outputs as kN.

Since (/) is used with k, it must be Fractional, so as in kN/2,
defaulting makes it Double.

> I'm fairly new to these lists, so apologies if I'm covering old ground 
> again. My first aim is to understand exactly what polymorphism and 
> monomorphism is and demonstrate corresponding results, before thinking 
> about the restriction.

The type of   map :: (a -> b) -> [a] -> [b]
is polymorphic.
Here we are talking about overloading, also known as
ad-hoc polymorphism.  In Haskell overloaded functions
are recognizable by the context in their type, e.g.:
   abs :: Num a => a -> a

I think I also mixed this up in one of my earlier mails.
Seems we need a glossary.


Bye
Christian Sievers
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trying to write a TCP proxy

2006-09-23 Thread Christian Sievers
John Ky wrote:

> I finally realised that hGetLine strips out the "\n" newline character
> so when I forward the line to the server, I need to append it again.

Or use hPutStrLn instead of hPutStr ?
(I may be missing something...)


Bye
Christian Sievers
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] puzzle: prove this floorSqrt correct

2004-08-12 Thread Christian Sievers
[EMAIL PROTECTED] wrote:

> -- Here's the discrete version of Newton's method for finding
> -- the square root.  Does it always work?  Any literature?

I recently used, without range check,

sqrtInt n = help n where
help x = let y = ((x + (n `div` x)) `div` 2)
 in if yhttp://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] zip comprehensions and local decls

2004-03-25 Thread Christian Sievers
Hello!

This is about a misconception I had about zip comprehensions and a possible
extension to get the desired result.  As zip compr. are implemented in hugs
and in ghc (though I only tried hugs), I thought that haskell-cafe might be a
good place for it.

In hugs mode, I expected something like the following to work:

  [ (a,a*x) | x <- [1..5] | y <- [10..], let a=x+y ]

but hugs says: ERROR - Undefined variable "x"

I think I can see why: 
The expression is rewritten to
  [ (a,a*x) | (x,y) <- zip [ x | x<-[1..5] ]
   [ y | y <- [10..], let a=x+y ] ]

This scheme is useful if one has   ...|y<-list, let a=..., sometest a
which drops some elements from the list before zipping.

But it would be nice to have a way to drop already zipped tuples and to allow
such usages of local declarations.  Maybe a final '|' branch without
generator, so to get what was intended with the expression above one might
write

  [ (a,a*x) | x <- [1..5] | y <- [10..] | let a=x+y ]

or, as another example, one could have

  [ (x,y) | x <- [1..5] | y <- [10..] | even x ]

giving [(2,11),(4,13)].

So the idea is to rewrite
  [ e | oldstyle parallel list comprehension | declsandpreds ]
to
  [ e | zipN   , declsandpreds ]

Is this clear enough?
Does it sound useful?  Can you think of a nicer syntax?


All the best
Christian Sievers

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Library for concurrent threads running

2002-12-16 Thread Christian Sievers
Dusan Kolar asked:

>My question/wish is maybe naive, but anyway:
> Is there a library (not a language extension, like
> Concurrent Haskell, Glasgow Parallel Haskell, ...) enabling
> to run two functions in parallel, possibly in cascade?

I think the best you can get without language extensions is what is described
in Koen Claessen's Functional Pearl "A Poor Man's Concurrency Monad".  It's
really nice, but not exactly what you seem to want.  You can get that article
from http://www.cs.chalmers.se/~koen/publications.html


All the best
Christian Sievers
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Question about use of | in a class declaration

2002-08-21 Thread Christian Sievers

Simon Guest asked:

> Please could someone explain the meaning of | in this class declaration (from 
>Andrew's example):
> 
>   class (Ord k) => Map m k v | m -> k v where
> lookupM :: m -> k -> Maybe v
> 
> I couldn't find reference to this in any of my standard Haskell tutorials, nor the 
>Haskell 98 report.  Any references?

It might not have become clear from the previous answers:
this construction is not Haskell 98, but an extension.
That's why it's not in the report.

BTW: Already multi parameter type classes 
(such as  "class (Ord k) => Map m k v where ...")
^ ^ ^ only one type variable allowed here
aren't Haskell 98.


All the best
Christian Sievers
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: newbie:: getting random Ints

2002-03-28 Thread Christian Sievers

Peter Rooney wrote:

> over my head), but have been unable to get any combination of
> getStdRandom randomR, etc. to work. even the example in the 98 report,
> 
> import Random
>  
> rollDice :: IO Int
> rollDice = getStdRandom (randomR (1,6))
> 
> gets me:
> 
> 
> Main> rollDice
>  
> Main>
> 
> after loading the file, which makes me think i'm missing something!


This looks like you are using Hugs.  Given an IO action, it will perform it.
That is different from giving it a non-IO expression, which it will evaluate
and print.
In this case, it will simply generate a random number - and throw it away!

You can try

  do dice <- rollDice; print dice

or

  rollDice >>= print

(which is essentially the same) instead, which is an IO action that, when
performed, will generate a random number and print it.

If your problem was not knowing what Hugs does when given an IO action, that's
it. But if you don't yet know who to handle IO, you have still some way to go.


HTH
Christian Sievers



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: zips and maps

2001-03-09 Thread Christian Sievers

Mieszko Lis (and others) wrote:

> zipMap = zipWith ($)

which is even in the report (end of section 6.2).
Interestingly, there is also a shorter, though rather unreadable
definition:

zipMap = zipWith id


Christian Sievers

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe