Re: Writing a counter function

2002-06-29 Thread Jon Cast


Mark Carroll <[EMAIL PROTECTED]> wrote:
> On Sat, 29 Jun 2002, Samuel E. Moelius III wrote:
> (snip)
> > Here's another not-exactly-what-you-wanted solution.  :)
> (snip)

> Do any of the experimental extensions to Haskell allow a
> what-he-wanted solution? I couldn't arrange one in H98 without
> something having an infinitely-recursive type signature.

That's because the problem requires an infinitely-recursive type.

> I'm sure it would have been easy in Lisp, and he already gave a Perl
> equivalent,

That's because both Lisp and Perl are weakly typed.  Haskell is
strongly typed.  Consider Lisp:

(defun self-apply (f)
"Apply F to itself."
   (f f))

No problem (and I'm sure you can pull the same trick off in Perl).
Consider Haskell:

self-apply f = f f

The *typing algorithm* (the thing that didn't complain in Lisp)
proceeds roughly as follows:

f is applied to at least one argument, so f must have type a -> b.
Therefore, f's argument (f) must have type a.  So, we conclude:

f :: a -> b
f :: a

But f can only have one type, so we set its types equal:

a = a -> b

This is clearly recursive, right?

> so I'm wondering if it could be at all sane for Haskell to allow
> such stuff

Sure.  All it has to do is:

1. Create its own newtype in response to such things as
`self-apply' above.

2. Ensure that

self-apply f = f f

and

self-apply' g = g g

have the same type.  I would *love* to hear ideas on how to do that,
but it's difficult.

> and if Haskell is somehow keeping us on the straight and narrow by
> disallowing the exact counter that was originally requested.

Well, it's a more general problem than the `exact counter'.  And, yes,
Haskell is erring on the side of safety here; there's a reason it's
called a ``statically typed language''.

> The beauty of his request was that it was so simple and seemed to
> make sense; I went ahead and tried to fulfill it before realising I
> couldn't do it either.

Well, it makes sense, yes.  But I think learning to manually `unify'
these things (add a newtype) is not hard, and probably useful ---
Haskell is not the only statically-typed language out there.
Learn how to solve this problem, and you understand the problem, the
solution, typing, and life in general :)

> -- Mark

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



Re: Writing a counter function

2002-06-29 Thread that jefu guy

On Sat, 2002-06-29 at 15:26, Mark Carroll wrote:
> On Sat, 29 Jun 2002, Samuel E. Moelius III wrote:
> (snip)
> > Here's another not-exactly-what-you-wanted solution.  :)
> (snip)
> 
> Do any of the experimental extensions to Haskell allow a what-he-wanted
> solution? I couldn't arrange one in H98 without something having an
> infinitely-recursive type signature. I'm sure it would have been easy in
> Lisp, and he already gave a Perl equivalent, so I'm wondering if it could
> be at all sane for Haskell to allow such stuff and if Haskell is somehow
> keeping us on the straight and narrow by disallowing the exact counter
> that was originally requested.
> 
> The beauty of his request was that it was so simple and seemed to make
> sense; I went ahead and tried to fulfill it before realising I couldn't
> do it either.

I could not manage to do this with a simple always-increment-by-one
function, but the problem of adding a number n each time was a quite
a bit easier - though it still took me a while to escape the infinite
recursive type , it seems that you need to indirect through another 
datatype (here FP).  

you can't print z or z', but the show defined will allow you to print
out a FooPair

-

data FooPair =  FP Integer (Integer -> FooPair) 

instance Show FooPair  where
   show (FP i f) = "FooPair " ++ (show i) ++ "...fun..."

incg :: Integer -> Integer -> FooPair 
incg n = \i ->  let j = n+i in  (FP j  (incg j))

val (FP i _) = i 
fun (FP _ f) = f 

x  = incg 7  -- the original function 
y  = x 3 -- increment the current value by 3 and return the FP pair
zf = fun y   -- get the new function
zv = val y   -- and the value in the pair 
z' = z 99-- now get the next value function pair 

-

--
jeff putnam -- [EMAIL PROTECTED] -- http://home1.get.net/res0tm0p

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



Re: Writing a counter function

2002-06-29 Thread Mark Carroll

On Sat, 29 Jun 2002, Samuel E. Moelius III wrote:
(snip)
> Here's another not-exactly-what-you-wanted solution.  :)
(snip)

Do any of the experimental extensions to Haskell allow a what-he-wanted
solution? I couldn't arrange one in H98 without something having an
infinitely-recursive type signature. I'm sure it would have been easy in
Lisp, and he already gave a Perl equivalent, so I'm wondering if it could
be at all sane for Haskell to allow such stuff and if Haskell is somehow
keeping us on the straight and narrow by disallowing the exact counter
that was originally requested.

The beauty of his request was that it was so simple and seemed to make
sense; I went ahead and tried to fulfill it before realising I couldn't
do it either.

-- Mark

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



Re: Writing a counter function

2002-06-29 Thread Samuel E. Moelius III

> No. But I want to generate an irregular series, which I determine the
> intervals between two consecutive numbers myself. E.g:
>
> let (num1, next1) = (counter 5)
> (num2, next2) = (next1 100)
> (num3, next3) = (next2 50) in
> [num1,num2,num3]
>
> Will have the numbers [5, 105, 155].

Here's another not-exactly-what-you-wanted solution.  :)

If you don't mind changing your example to

let (num1, next1) = out (counter 5)
(num2, next2) = out (next1 100)
(num3, next3) = out (next2 50) in
[num1,num2,num3]

then, you can do this:

newtype Counter = MkCounter Int

counter :: Int -> Counter
counter n = MkCounter n

out :: Counter -> (Int,Int -> Counter)
out (MkCounter n) = (n,MkCounter . (n +))

Sam Moelius

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



Re: Writing a counter function

2002-06-29 Thread Samuel E. Moelius III

> No. But I want to generate an irregular series, which I determine the
> intervals between two consecutive numbers myself. E.g:
>
> let (num1, next1) = (counter 5)
> (num2, next2) = (next1 100)
> (num3, next3) = (next2 50) in
> [num1,num2,num3]
>
> Will have the numbers [5, 105, 155].

Here's another not-exactly-what-you-wanted solution.  :)

If you don't mind changing your example to

let (num1, next1) = out (counter 5)
(num2, next2) = out (next1 100)
(num3, next3) = out (next2 50) in
[num1,num2,num3]

then, you can do this:

newtype Counter = MkCounter Int

counter :: Int -> Counter
counter n = MkCounter n

out :: Counter -> (Int,Int -> Counter)
out (MkCounter n) = (n,MkCounter . (n +))

Sam Moelius

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



Re: Writing a counter function

2002-06-29 Thread John Hughes

On Sat, 29 Jun 2002, Shlomi Fish wrote:
>
> No. But I want to generate an irregular series, which I determine the
> intervals between two consecutive numbers myself. E.g:
>
> let (num1, next1) = (counter 5)
> (num2, next2) = (next1 100)
> (num3, next3) = (next2 50) in
> [num1,num2,num3]
>
> Will have the numbers [5, 105, 155].
>

The other answers you've received really question whether this is a good
way to use Haskell at all --- usually, if you want to generate a sequence
of values, it's a good idea just to represent them explicitly as a (lazy)
list. For example, you can compute more-or-less the same result as you
want just using standard list processing functions:

Main> scanl (+) 0 [5,100,50]
[0,5,105,155]

However, you can also do almost exactly what you suggest. Not quite
exactly, because the function you describe would have a recursive type

type Counter = Int -> (Int, Counter)

and Haskell requires that type recursion involve a data or newtype. So,
here's a solution:

newtype Counter = Counter (Int -> (Int, Counter))

count :: Counter -> Int -> (Int, Counter)
count (Counter c) = c

counter n = (n, Counter next)
  where next k = counter (n+k)

xs = let (num1, next1) = (counter 5)
 (num2, next2) = (next1 `count` 100)
 (num3, next3) = (next2 `count` 50) in
   [num1,num2,num3]

Main> xs
[5,105,155]

The only difference from your idea is that a counter is not a function; we
have to use the function count to invoke it. And that's forced on us by
the need to avoid type recursion.

John Hughes


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



Re: Writing a counter function

2002-06-29 Thread Shlomi Fish


Just for the record, here is a Perl function that does this:

###
sub counter
{
my $a = shift;

my $next = sub {
my $to_add = shift ;
return counter($to_add+$a);
};

return ($a, $next);
}

my ($result,$next) = counter(5);
my ($result2, $next2) = $next->(100);
my ($result3, $next3) = $next2->(50);
my ($result4, $next4) = $next->(30);

print "\$result=$result\n\$result2=$result2\n\$result3=$result3\n\$result4=$result4\n";


Regards,

Shlomi Fish



--
Shlomi Fish[EMAIL PROTECTED]
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

He who re-invents the wheel, understands much better how a wheel works.

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



Re: Writing a counter function

2002-06-29 Thread Shlomi Fish

On Sat, 29 Jun 2002, Jon Fairbairn wrote:

> Shlomi Fish wrote:
> > No. But I want to generate an irregular series, which I determine the
> > intervals between two consecutive numbers myself. E.g:
> >
> > let (num1, next1) = (counter 5)
> > (num2, next2) = (next1 100)
> > (num3, next3) = (next2 50) in
> > [num1,num2,num3]
> >
> > Will have the numbers [5, 105, 155].
>
> What do you mean by "determine"?
>

_I_ want to determine which step to go to next. I'd like to pass a
parameter the counter each time, and each time get the next number as well
as a new counter.

Regards,

Shlomi Fish


> You can write
>
> sequence = iterate step_counter 0
>
> if the interval between successive numbers is determined by
> the current number, or
>
> sequence = map f [1..]
>
> if it's determined by the index in the sequence.
>
> or
>
> sequence =  map snd $ iterate step_counter (0,-7)
> step_counter (a,b) = (a+1, f a b)
>
> if it depends on both.
>
>
>   Jón
>



--
Shlomi Fish[EMAIL PROTECTED]
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

He who re-invents the wheel, understands much better how a wheel works.

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



Re: Writing a counter function

2002-06-29 Thread Jon Fairbairn

Shlomi Fish wrote:
> No. But I want to generate an irregular series, which I determine the
> intervals between two consecutive numbers myself. E.g:
> 
> let (num1, next1) = (counter 5)
> (num2, next2) = (next1 100)
> (num3, next3) = (next2 50) in
> [num1,num2,num3]
> 
> Will have the numbers [5, 105, 155].

What do you mean by "determine"?

You can write 

sequence = iterate step_counter 0

if the interval between successive numbers is determined by
the current number, or

sequence = map f [1..]

if it's determined by the index in the sequence.

or 

sequence =  map snd $ iterate step_counter (0,-7)
step_counter (a,b) = (a+1, f a b) 

if it depends on both.


  Jón
-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


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



Re: Writing a counter function

2002-06-29 Thread Shlomi Fish

On Sat, 29 Jun 2002, Hannah Schroeter wrote:

> Hello!
>
> On Sat, Jun 29, 2002 at 06:23:27PM +0300, Shlomi Fish wrote:
> > [...]
>
> > Actually, I'd like a more generalized counter. Something that would return
> > both the number and a handler to add another number, which in turn would
> > return the new sum and a new handler, etc.
>
> That's just what lazy lists are for. The "handler" thing is done
> automatically thanks to lazy evaluation.
>
> I.e. countFrom n = n : countFrom (n + 1)
> or just countFrom n = [n..]
>

No. But I want to generate an irregular series, which I determine the
intervals between two consecutive numbers myself. E.g:

let (num1, next1) = (counter 5)
(num2, next2) = (next1 100)
(num3, next3) = (next2 50) in
[num1,num2,num3]

Will have the numbers [5, 105, 155].

Regards,

Shlomi Fish

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



--
Shlomi Fish[EMAIL PROTECTED]
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

He who re-invents the wheel, understands much better how a wheel works.

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



Re: Writing a counter function

2002-06-29 Thread Hannah Schroeter

Hello!

On Sat, Jun 29, 2002 at 06:23:27PM +0300, Shlomi Fish wrote:
> [...]

> Actually, I'd like a more generalized counter. Something that would return
> both the number and a handler to add another number, which in turn would
> return the new sum and a new handler, etc.

That's just what lazy lists are for. The "handler" thing is done
automatically thanks to lazy evaluation.

I.e. countFrom n = n : countFrom (n + 1)
or just countFrom n = [n..]

Kind regards,

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



Re: Writing a counter function

2002-06-29 Thread Shlomi Fish

On Sat, 29 Jun 2002, Mark Carroll wrote:

> On Sat, 29 Jun 2002, Shlomi Fish wrote:
> (snip)
> > counter n = (n,(counter (n+1)))
> (snip)
>
> This doesn't work because you seem to be defining an infinitely deep tuple
> (1,(2,(3,(4,() which is naughty.
>
> I'm not really sure what alternative to suggest beyond [n .. ] without
> knowing more about what you are trying to do.
>

Actually, I'd like a more generalized counter. Something that would return
both the number and a handler to add another number, which in turn would
return the new sum and a new handler, etc.

Regards,

Shlomi Fish

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



--
Shlomi Fish[EMAIL PROTECTED]
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

He who re-invents the wheel, understands much better how a wheel works.

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



Re: Writing a counter function

2002-06-29 Thread Mark Carroll

On Sat, 29 Jun 2002, Shlomi Fish wrote:
(snip)
> counter n = (n,(counter (n+1)))
(snip)

This doesn't work because you seem to be defining an infinitely deep tuple
(1,(2,(3,(4,() which is naughty.

I'm not really sure what alternative to suggest beyond [n .. ] without
knowing more about what you are trying to do.

-- Mark

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



Writing a counter function

2002-06-29 Thread Shlomi Fish


I'm trying to write a counter function that would return a tuple whose
first element is the current value and whose second element is a new
counter. The following line:

counter n = (n,(counter (n+1)))

Generates the following error on Hugs and a similar one with ghci:

ERROR "counter.hs":6 - Type error in function binding
*** Term   : counter
*** Type   : a -> (a,b)
*** Does not match : a -> b
*** Because: unification would give infinite type

Is there any way to do it? I tried using data, type and newtype and none
of them worked.

Regards,

Shlomi Fish

--
Shlomi Fish[EMAIL PROTECTED]
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

He who re-invents the wheel, understands much better how a wheel works.

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