Re: [Haskell-cafe] Simple matrix

2006-06-22 Thread Bjorn Lisper
I wrote:
Here is one way to do it. First, you have to interpret operations on
matrices as being elementwise applied. E.g, (*) is interpreted as zipWith
(zipWith (*)) rather than matrix multiply, and similar for (+) etc. You then
obtain a lazy semantics for the operations, where the extent of the
resulting matrix is the intersection of the extents of the argument
matrices. Second, you lift constants into infinite matrices containing the
constant, that is: fromInteger n = repeat (repeat n). Now your examples will
work as intended.

Ah, should of course be fromInteger n = repeat (repeat (fromInteger n)).

Björn Lisper
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Re: Functional programming for processing of largeraster images

2006-06-22 Thread Bulat Ziganshin
Hello Ralf,

Thursday, June 22, 2006, 12:02:43 AM, you wrote:

 limited to function types. Users of parser combinators heavily rely
 on this feature. Just try to define/use parsing combinators
 ins a strict language.

C++ Boost contains one parsing combinators library. part of it is, of
course, a lazy eveluation sub-library :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


RE: [Haskell-cafe] Re: Functional programming for processing oflargeraster images

2006-06-22 Thread Simon Peyton-Jones
| Everything else about Haskell is so great and well thought out (eg
type
| classes, no side effects, higher rank polymorphism, existentials) it
seems a
| pity to throw all this away just because of one unfortunate feature

I thought it might be worth mentioning that GHC (well, the HEAD, which
will become 6.6) supports bang patterns.  See
http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/BangPatter
ns

Bang patterns make it much more convenient to write a strict function.
E.g
f (x, !y) = ...
is strict both in the pair (of course) but also in the second component
of the pair, y.

You can also use them in lets
let !x = rhs in body
which will evaluate rhs before body.

It's an experimental feature, and I'm interested to know how useful, or
otherwise, it turns out to be.

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


Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-22 Thread Jerzy Karczmarczuk

Brian Hulley wrote:

[EMAIL PROTECTED] wrote:



you may transform a recurrential equation yielding Y out of X:
Y[n+1] = a*X[n+1] + b*Y[n]
usually (imperatively) implemented as a loop, into a stream
definition:

...

Can you explain how this transformation was accomplished?
I don't see how
yq = a * xq + b * y
relates to
   Y[n+1] = a*X[n+1] + b*Y[n]  -- (assuming the X[N+1] was a typo)

since y is a longer list than yq but Y[n] is an earlier element than 
Y[n+1], so it seems that the function is multiplying b by a later factor 
than it should.


Sure, y[n] is earlier, so defining the tail by the stream itself refers
an element to its predecessor. No problemo Baby, as used to say
Terminator 2, whose relevance to our problem is obvious, since he
also couldn't terminate him(it)self...

Let's write the stream construction once more. Starting with x=(x0:xq)
and parameters a and b, assuming that for n0 you take zero:

y  = (a*x0:yq)   -- Here I was in error, a missing
yq = a*xq + b*y

with, of course, a*xq meaning map(a*) xq; x+y meaning zipWith(*) x y ...


y0 = a*x0
Look yourself:  y1 = a*x1 + b*y0
y2 = a*x2 + b*y1, etc. So, first, this is correct,
  element by element.

Don't tell me you have never seen the assembly of all non-negative
integers as an infinite list thereof:

integs = 0 : (integs + ones)   where ones = 1:ones

it is quite similar (conceptually).

y IS NOT a longer list than yq, since co-recursive equations without
limiting cases, apply only to *infinite* streams. Obviously, the
consumer of such a stream will generate a finite segment only, but it
is his/her/its problem, not that of the producer.



So:
1) Someone reading the code needs to do a lot of work to try to recover 
the original equation
2) Wouldn't an imperative loop, using the original equation directly, 
have made everything much simpler?

3) Therefore laziness has lead to obfuscated code.


1. Such codes are not meant to be thrown at an unprepared audience. Either
   the reader knows something about stream processing, or some introduction
   is necessary.

2. Are we speaking about assembly-style, imperative programming, or about
   functional style? Please write your loop in Haskell or any other fun.
   language, and share with us its elegance.
   Please note that for stream-oriented applications, as the sound processing
   I mentioned, this n index has no meaning whatsoever, it just denotes
   a position within the stream. Index-less style is more compact, with less
   redundant entities.

3. Full disagreement. There is NOTHING obfuscated here, on the contrary, the
   full semantics is in front of your eyes, it requires only some reasoning
   in terms of infinite lists. See point (1).

Thanks.

Jerzy Karczmarczuk
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Functional programming for processing oflargeraster images

2006-06-22 Thread Matthias Fischmann

On Thu, Jun 22, 2006 at 09:22:34AM +0100, Simon Peyton-Jones wrote:
 To: Brian Hulley [EMAIL PROTECTED], Joel Reymont [EMAIL PROTECTED]
 Cc: haskell-cafe@haskell.org
 From: Simon Peyton-Jones [EMAIL PROTECTED]
 Date: Thu, 22 Jun 2006 09:22:34 +0100
 Subject: RE: [Haskell-cafe] Re: Functional programming for processing
   oflargeraster images
 
 http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/BangPatterns
 
 Bang patterns make it much more convenient to write a strict function.
 E.g
   f (x, !y) = ...
 is strict both in the pair (of course) but also in the second component
 of the pair, y.

i am ecstatic to hear that :).

if it really means that 'y' will be fully evaluated (not top level
normal form, but whatsthenameforthis, in the way ocaml evaluates
expressions), it's something i have been missing so much that i was
thinking of switching back to a strict language again.

will upgrade as soon as i can, thanks!


m.


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-22 Thread minh thu

hi !

2006/6/22, Brian Hulley [EMAIL PROTECTED]:
[snip]

So:
1) Someone reading the code needs to do a lot of work to try to recover the
original equation
2) Wouldn't an imperative loop, using the original equation directly, have
made everything much simpler?
3) Therefore laziness has lead to obfuscated code.


the way i see :
1/ but why do you call it 'original equation' ? the original thing is
expressed informaly in your head, then into a formula or an algorithm.
Here i find the first one-liner really readable. (although i think it
misses Y[0] = X[0]). But the loop is really readable too for
imperative enabled mind.
2/ for me, list or loop is quite the same thing (in this case)
(although loop is mor general since you can use the base index in
weird ways).
3/ see 1/ and 2/

Jerzy :
can you know a mean to express such computation but with elements
depending of time (in about the same way as languages as esterel)
(i.e. depending of IO)?
Paul Hudak uses a Channel in his book Haskell SOE .. but is there another way ?

thanks,
vo minh thu
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Functional programming for processing oflargeraster images

2006-06-22 Thread minh thu

hi,

2006/6/22, Simon Peyton-Jones [EMAIL PROTECTED]:
[real big snip :)]

I think you're one of the best person to advocate pros and cons of
laziness/strictness.
So i'm a bit surprised to see this :


It's an experimental feature, and I'm interested to know how useful, or
otherwise, it turns out to be.


Coudn't you predict it (both in terms of the programmers and compiler writers) ?

thanks,
vo minh thu
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Principal type in Haskell

2006-06-22 Thread william kim

Hi All,

I am confused by the notion of principal type in Haskell with type classes. 
Consider a simple example:


f x y = [x] == [y]

GHCi yields type f :: (Eq [a]) = a - a - Bool.

But according to the paper Type classes: an exploration of the design 
space, predicate Eq [a] should be reduced to Eq a. Is this reduction 
performed here? What should be the principal type of f?


Thanks.

william

_
Get an advanced look at the new version of MSN Messenger. 
http://messenger.msn.com.sg/Beta/Default.aspx


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


Re: [Haskell-cafe] Principal type in Haskell

2006-06-22 Thread Gerrit van den Geest

According to Haskell 98 the principal type of f should be:

f :: (Eq a) = a - a - Bool.

GHC does only perform context-reduction using instance-declarations if 
there are no type-variables in the type. Because the type in this 
function is [a], ghc doesn't perform context-reduction. Ghc chooses this 
strategy because of extensions like overlapping instances, there remains 
more information in the type of a function to select an instance.


For some reason GHC also applies this strategy if one turns of the 
extensions.




Grt




william kim wrote:


Hi All,

I am confused by the notion of principal type in Haskell with type 
classes. Consider a simple example:


f x y = [x] == [y]

GHCi yields type f :: (Eq [a]) = a - a - Bool.

But according to the paper Type classes: an exploration of the design 
space, predicate Eq [a] should be reduced to Eq a. Is this reduction 
performed here? What should be the principal type of f?


Thanks.

william

_
Get an advanced look at the new version of MSN Messenger. 
http://messenger.msn.com.sg/Beta/Default.aspx


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



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


Re: [Haskell-cafe] Simple matrix

2006-06-22 Thread Udo Stenzel
Bjorn Lisper wrote:
 Here is one way to do it. First, you have to interpret operations on
 matrices as being elementwise applied. E.g, (*) is interpreted as zipWith
 (zipWith (*)) rather than matrix multiply

What's this, the principle of greatest surprise at work?  Nonono, (*)
should be matrix multiplication, fromInteger x should be (x * I) and I
should be the identity matrix.  Now all we need is an infinitely large
I, and that gives:

instance Num a = Num [[a]] where
(+) = zipWith (zipWith (+))
(-) = zipWith (zipWith (-))
negate = map (map negate)
fromInteger x = fix (((x : repeat 0) :) . map (0:))
m * n = [ [ sum $ zipWith (*) v w | w - transpose n ] | v - m ] 


Udo.


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Principal type in Haskell

2006-06-22 Thread Jerzy Karczmarczuk

william kim wrote:

I am confused by the notion of principal type in Haskell with type 
classes. Consider a simple example:


f x y = [x] == [y]

GHCi yields type f :: (Eq [a]) = a - a - Bool.

But according to the paper Type classes: an exploration of the design 
space, predicate Eq [a] should be reduced to Eq a.


Does it mean that nobody is entitled to override the standard instance, and,
say, declare:


instance Eq [a] where
  x==y  =  length x == length y

?

Jerzy Karczmarczuk
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-22 Thread Udo Stenzel
[EMAIL PROTECTED] wrote:
 apparently - Clean has better handling of strictness
 issues [saying at the same time that he/she doesn't use Clean...]

Uhm... well... and does it?  From what I've heard, Clean has the same
mechanism as Haskell, which is the 'seq' primitive.  Clean just adds
some syntactic sugar to make functions strict in some arguments.  If
that's the only difference, I'm quite happy with the False-guard idiom
(and may be even more happy with !-patterns).

 And here apparently I am one of rare people  - I am not proud of it,
 rather quite sad, who defends laziness as an *algorithmisation tool*,
 which makes it easy and elegant to construct co-recursive codes. Circular
 programs, run-away infinite streams, hidden backtracking etc. 

And don't forget the Most Unreliable Method to Compute Pi!  That would
be plain impossible without lazy evaluation.  (Nice blend of humor and
insight in that paper, by the way.)

 
 In this context, I found Clean more helpful than Haskell, for ONE reason.
 Clean has a primitive datatype: unboxed, spine-lazy but head-strict lists.

If I understand correctly, you'd get the same in GHC by defining

* data IntList = Nil | Cons I# IntList

though it is monomorphic, and you'd get the same semantics from

* data List a = Nil | Cons !a (List a)

Now it is polymorphic and it may even get unpacked.


Udo.
-- 
If your life was a horse, you'd have to shoot it.


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Template haskell and scoping

2006-06-22 Thread Simon Peyton-Jones
A genuine bug, thank you.  I've just fixed it.  We'll put the fix in
6.4.3.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of C
| Rodrigues
| Sent: 21 June 2006 21:55
| To: haskell-cafe@haskell.org
| Subject: [Haskell-cafe] Template haskell and scoping
| 
| The (..) in the splice is out of scope according to GHC.  If I use
[||]
| then it works, but for my purposes it's easier to use the
constructors.  How
| should I refer to that variable?
| 
| import Data.Bits
| import Language.Haskell.TH
| 
| main = print $ $(return $ VarE $ mkName ..) 7 (14 :: Int)
| 
| 
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] user type declarations in Haskell

2006-06-22 Thread Vladimir Portnykh

I am trying to define the following types

data MyStringType a = String deriving (Eq, Ord, Show)
data QADouble a = Double deriving (Eq, Ord, Show)
data HType a = QADouble a| DDTraceType a deriving (Eq, Ord, Show)

So HType can represent strings or doubles.
later I want to do something like the following:
let a1 =QADouble 1
let a2 =QADouble 2
let a3 = a1 + a2

First, it is not working because Haskell complains about a3. it does not 
know how to calculate it.
Is it a way to give him a hint? QADouble is Double...am I doing something 
absolutely wrong and silly?


many thanks, vladimir

_
Are you using the latest version of MSN Messenger? Download MSN Messenger 
7.5 today! http://join.msn.com/messenger/overview


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


Re: [Haskell-cafe] Simple matrix

2006-06-22 Thread Ross Paterson
On Thu, Jun 22, 2006 at 11:57:37AM +0200, Udo Stenzel wrote:
 instance Num a = Num [[a]] where
   (+) = zipWith (zipWith (+))
   (-) = zipWith (zipWith (-))
   negate = map (map negate)
   fromInteger x = fix (((x : repeat 0) :) . map (0:))
   m * n = [ [ sum $ zipWith (*) v w | w - transpose n ] | v - m ] 

or perhaps

fromInteger x = iterate (0:) (x : repeat 0)

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


Re: [Haskell-cafe] user type declarations in Haskell

2006-06-22 Thread minh thu

2006/6/22, Vladimir Portnykh [EMAIL PROTECTED]:

I am trying to define the following types

data MyStringType a = String deriving (Eq, Ord, Show)
data QADouble a = Double deriving (Eq, Ord, Show)
data HType a = QADouble a| DDTraceType a deriving (Eq, Ord, Show)

So HType can represent strings or doubles.
later I want to do something like the following:
let a1 =QADouble 1
let a2 =QADouble 2
let a3 = a1 + a2


a1 and a2 have type HType (not QADouble, nor Double).
GHC doesn't know how to use (+) on HType because (+) is meaningful
only for Num instances :
try to type ':t (+)' in ghci : it will give you the type of (+).
try to type also ':t a1'.

hope it helps,
vo minh thu
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-22 Thread Jerzy Karczmarczuk

minh thu wrote:

/about the stream algorithms, lazy style/


can you know a mean to express such computation but with elements
depending of time (in about the same way as languages as esterel)
(i.e. depending of IO)?
Paul Hudak uses a Channel in his book Haskell SOE .. but is there 
another way ?


Frankly, I don't see it well. The co-recursive, lazy constructions are
based on the fact that it is the consumer who unrolls the list and
forces the reduction. So, the unevaluated closures should contain
somehow the latent data, or rather refer to them. Synchronous processing
is another story, here the producer is really active.

Esterel until the version 4 demanded that all 'circuits' which handled
the data flows be *acyclic*; now it is more flexible, so you can do a lot
of own-tail-eating snakes with it, but differently.

I believe that ways of producing intricate streams by such languages or
Lustre are somehow based on continuation mechanisms. The paper on Esterel,
etc. :   ftp://ftp-sop.inria.fr/esterel/pub/papers/foundations.pdf

gives you an example in Lustre
X[n+1] = U[n+1]*sin(X[n] + S[n+1]-S[n])
S[n+1] = cos(S[n]+U[n+1]

in a form remarkably analogous as I did:

node Control(U:float) returns X:float
  var S:float
  let
X = 0.0 - (U*sin(pre(X)+S-pre(S));
S = 1.0 - cos(pre(S)+U);
  tel

So, I would say that this is obviously a live domain. The language Signal
can oversample, and produce output faster than the input, but I have
never followed the details.

Perhaps some YamPa-ladins who read this list could shed some light on the
reactive stream processing?
They use Arrows, a generalization (and twist, not compatible) of Monads, so
there is obviously *some* relation to continuations here... But I am a
Perfect Non-Specialist.


Jerzy Karczmarczuk


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


Re: [Haskell-cafe] Principal type in Haskell

2006-06-22 Thread Bulat Ziganshin
Hello william,

Thursday, June 22, 2006, 1:22:32 PM, you wrote:


 GHCi yields type f :: (Eq [a]) = a - a - Bool.

 But according to the paper Type classes: an exploration of the design
 space, predicate Eq [a] should be reduced to Eq a. Is this reduction 
 performed here? What should be the principal type of f?

Ghc, unlike H98, supports instances like this:

instance Eq [MyType] where
  a==b = True

so this extension to type inference allows to use such instance even
if MyType is not in Eq class


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: Functional programming for processing oflargeraster images

2006-06-22 Thread voigt . 16734551
--- Matthias Fischmann [EMAIL PROTECTED] wrote:

 On Thu, Jun 22,
2006 at 09:22:34AM +0100, Simon Peyton-Jones wrote:
  To: Brian Hulley
[EMAIL PROTECTED], Joel Reymont [EMAIL PROTECTED]
  Cc: haskell-cafe@haskell.org

  From: Simon Peyton-Jones [EMAIL PROTECTED]
  Date: Thu, 22 Jun
2006 09:22:34 +0100
  Subject: RE: [Haskell-cafe] Re: Functional programming
for processing
  oflargeraster images
  
  http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/BangPatterns

  
  Bang patterns make it much more convenient to write a strict function.

  E.g
  f (x, !y) = ...
  is strict both in the pair (of course)
but also in the second component
  of the pair, y.
 
 i am ecstatic
to hear that :).

Well, you shouldn't be too enthusiastic, but rather follow
the above link ...
 
 if it really means that 'y' will be fully evaluated
(not top level
 normal form, but whatsthenameforthis, in the way ocaml evaluates

 expressions), it's something i have been missing so much that i was

thinking of switching back to a strict language again.

... to find out
that that's exactly not what bang patterns will do for you. They are compiled
into uses of seq, which means evaluation to weak head normal form.

Ciao,
Janis.

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


RE: [Haskell-cafe] ghc-pkg on Windows XP

2006-06-22 Thread Simon Peyton-Jones








Has anyone else encountered this? Its ok for us, and for at least
some other people. Perhaps uninstall and reinstall? You cant overlook anything
when installing, assuming you use the pre-packaged installer.

Simon









From:
[EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On
Behalf Of Jeff Polakow
Sent: 21 June 2006 15:22
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] ghc-pkg on Windows XP








Hello, 

 I have
installed ghc-6.4.2 on a windows XP machine. However, the machine refuses to
execute ghc-pkg (thus preventing me from using Cabal) and complains that
C:\ghc\ghc-6.4.2\bin\ghc-pkg.exe is not a valid Win32 application.
Is there something obvious I might have overlooked while installing? 

Also, I am new
to using ghc on windows and was wondering what are the trade-offs of using
cygwin or minsys versus just living in a emacs shell? 

thanks, 
 Jeff


--
This
e-mail may contain confidential and/or privileged information. If you are not
the intended recipient (or have received this e-mail in error) please notify
the sender immediately and destroy this e-mail. Any unauthorized copying,
disclosure or distribution of the material in this e-mail is strictly
forbidden. 








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


Re: [Haskell-cafe] user type declarations in Haskell

2006-06-22 Thread Udo Stenzel
Vladimir Portnykh wrote:
 I am trying to define the following types
 
 data MyStringType a = String deriving (Eq, Ord, Show)
 data QADouble a = Double deriving (Eq, Ord, Show)

These are not what you think they are.  MyStringType has a phantom type
parameter and only one value, which is the constant String (but not of
type String).  What you actually meant can only be guessed, and I'm not
even trying.

 
 So HType can represent strings or doubles.
 later I want to do something like the following:
 let a1 =QADouble 1
 let a2 =QADouble 2
 let a3 = a1 + a2

data HType = QADouble Double | QAString Double

 First, it is not working because Haskell complains about a3. it does not 
 know how to calculate it.

What did you expect?  What's the sum of a Double and a String if not an
error?  You have to define (+), which is already defined.  Use some
other name and give a definition:

QADouble x `plus` QADouble y = ...
QADouble x `plus` QAString y = ...
QAString x `plus` QAString y = ...
QAString x `plus` QADouble y = ...


Udo.
-- 
Lieber vom Fels zertrümmert als bei einer Frau verkümmert.
-- aus einem Gipfelbuch


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-22 Thread Ross Paterson
On Thu, Jun 22, 2006 at 01:24:32PM +0200, Jerzy Karczmarczuk wrote:
 I believe that ways of producing intricate streams by such languages or
 Lustre are somehow based on continuation mechanisms. The paper on Esterel,
 etc. :   ftp://ftp-sop.inria.fr/esterel/pub/papers/foundations.pdf
 
 gives you an example in Lustre
 X[n+1] = U[n+1]*sin(X[n] + S[n+1]-S[n])
 S[n+1] = cos(S[n]+U[n+1]
 
 in a form remarkably analogous as I did:
 
 node Control(U:float) returns X:float
   var S:float
   let
 X = 0.0 - (U*sin(pre(X)+S-pre(S));
 S = 1.0 - cos(pre(S)+U);
   tel

For comparison, here's a version using arrows (except that the U stream
is shifted forward, so its first value is used):

class ArrowLoop a = ArrowCircuit a where
delay :: b - a b b

control :: ArrowCircuit a = a Float Float
control = proc u - do
rec let x' = u * sin (x + s' - s)
s' = cos (s * u)
x - delay 0 - x'
s - delay 1 - s'
returnA - x

One can plug in various implementations of ArrowCircuit.  For stream
processors, delay is just cons, and the computation is equivalent to
the infinite list version.  Another implementation uses continuations.

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


Re: [Haskell-cafe] Simple matrix

2006-06-22 Thread Bjorn Lisper
Udo Stenzel:
Bjorn Lisper wrote:
 Here is one way to do it. First, you have to interpret operations on
 matrices as being elementwise applied. E.g, (*) is interpreted as zipWith
 (zipWith (*)) rather than matrix multiply

What's this, the principle of greatest surprise at work?  Nonono, (*)
should be matrix multiplication, fromInteger x should be (x * I) and I
should be the identity matrix.  Now all we need is an infinitely large
I, and that gives:

instance Num a = Num [[a]] where
   (+) = zipWith (zipWith (+))
   (-) = zipWith (zipWith (-))
   negate = map (map negate)
   fromInteger x = fix (((x : repeat 0) :) . map (0:))
   m * n = [ [ sum $ zipWith (*) v w | w - transpose n ] | v - m ] 

There are pros and cons, of course. Using (*) for matrix multiply is
well-established in linear algebra. But:

- it breaks the symmetry. This particular operator is then overloaded in a
  different way than all the others, and

- your definition of fromInteger will behave strangely with the elementwise
  extended operations, like (+). 1 + [[1,2],[3,4]] will become
  [[2,2],[3,5]] rather than [[2,3],[4,5]]. Array languages supporting this
  kind of overloading invariably have the second form of semantics.

Björn Lisper
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Brian Hulley

Jerzy Karczmarczuk wrote:

Brian Hulley wrote:

[EMAIL PROTECTED] wrote:



you may transform a recurrential equation yielding Y out of X:
Y[n+1] = a*X[n+1] + b*Y[n]
usually (imperatively) implemented as a loop, into a stream
definition:

...

Can you explain how this transformation was accomplished?



y  = (a*x0:yq)   -- Here I was in error, a missing
yq = a*xq + b*y

with, of course, a*xq meaning map(a*) xq; x+y meaning zipWith(*) x y

y0 = a*x0
Look yourself:  y1 = a*x1 + b*y0
y2 = a*x2 + b*y1, etc. So, first, this is correct,
  element by element.

Don't tell me you have never seen the assembly of all non-negative
integers as an infinite list thereof:

integs = 0 : (integs + ones)   where ones = 1:ones

it is quite similar (conceptually).


Thanks for the explanation.



y IS NOT a longer list than yq, since co-recursive equations without
limiting cases, apply only to *infinite* streams. Obviously, the
consumer of such a stream will generate a finite segment only, but it
is his/her/its problem, not that of the producer.


I still don't understand this point, since y = (a*x0 : yq) so surely by 
induction on the length of yq, y has 1 more element?




2. Are we speaking about assembly-style, imperative programming, or
   about functional style? Please write your loop in Haskell or any
   other fun. language, and share with us its elegance.


Starting with: Y[n+1] = a*X[n+1] + b*Y[n]

 filtr a b (x0:xs) = y0 : filtr' xs y0
where
y0 = a * x0
filtr' (x_n1 : xs) y_n = y_n1 : filtr' xs y_n1
where
   y_n1 = a * x_n1 + b * y_n

In a sense I'm still using a lazy stream, but the difference is that I'm not 
making any use of the evaluate once then store for next time aspect of 
lazyness, so the above code could be translated directly to use the 
force/delay streams I mentioned before. Also, the original formula now 
appears directly in the definition of filtr' so it can be understood without 
an initiation into stream processing.


(Piotr - I see my original wording imperative loop was misleading - in the 
context of functional programming I tend to just use this to mean a simple 
recursive function)




3. Full disagreement. There is NOTHING obfuscated here, on the
   contrary, the full semantics is in front of your eyes, it requires
   only some reasoning in terms of infinite lists. See point (1).


The same could be said for all obfuscated code: it's always fully visible 
but just requires reasoning to understand it! :-) Still I suppose perhaps 
the word obfuscated was a bit strong and certainly with your explanation, 
which you mentioned as a prerequisite in answer to my point 1), I now 
understand your original code also, but not without making some effort.


Best regards,
Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread minh thu

2006/6/22, Brian Hulley [EMAIL PROTECTED]:

Jerzy Karczmarczuk wrote:
 Brian Hulley wrote:

[snip]

 y IS NOT a longer list than yq, since co-recursive equations without
 limiting cases, apply only to *infinite* streams. Obviously, the
 consumer of such a stream will generate a finite segment only, but it
 is his/her/its problem, not that of the producer.

I still don't understand this point, since y = (a*x0 : yq) so surely by
induction on the length of yq, y has 1 more element?


y and yq are infinite...

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


Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Brian Hulley

minh thu wrote:

2006/6/22, Brian Hulley [EMAIL PROTECTED]:

Jerzy Karczmarczuk wrote:

Brian Hulley wrote:

[snip]

y IS NOT a longer list than yq, since co-recursive equations without
limiting cases, apply only to *infinite* streams. Obviously, the
consumer of such a stream will generate a finite segment only, but
it is his/her/its problem, not that of the producer.


I still don't understand this point, since y = (a*x0 : yq) so surely
by induction on the length of yq, y has 1 more element?


y and yq are infinite...


But how does this change the fact that y still has 1 more element than yq?
yq is after all, not a circular list.
I don't see why induction can't just be applied infinitely to prove this.

Regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Jon Fairbairn
On 2006-06-22 at 15:16BST Brian Hulley wrote:
 minh thu wrote:
  y and yq are infinite...
 
 But how does this change the fact that y still has 1 more element than yq?
 yq is after all, not a circular list.

infinity+1 = infinity

 I don't see why induction can't just be applied infinitely
 to prove this.

because (ordinary) induction won't go that far.

-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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


Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Bill Wood
On Thu, 2006-06-22 at 15:16 +0100, Brian Hulley wrote:
   . . .
 But how does this change the fact that y still has 1 more element than yq?
 yq is after all, not a circular list.
 I don't see why induction can't just be applied infinitely to prove this.

The set of all non-negative integers has one more element than the set
of all positive integers, however they have the same cardinality,
aleph-null.  This phenomenon is the hallmark of infinite sets.

 -- Bill Wood


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


Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread minh thu

2006/6/22, Brian Hulley [EMAIL PROTECTED]:

minh thu wrote:
 2006/6/22, Brian Hulley [EMAIL PROTECTED]:
 Jerzy Karczmarczuk wrote:
 Brian Hulley wrote:
 [snip]
 y IS NOT a longer list than yq, since co-recursive equations without
 limiting cases, apply only to *infinite* streams. Obviously, the
 consumer of such a stream will generate a finite segment only, but
 it is his/her/its problem, not that of the producer.

 I still don't understand this point, since y = (a*x0 : yq) so surely
 by induction on the length of yq, y has 1 more element?

 y and yq are infinite...

But how does this change the fact that y still has 1 more element than yq?
yq is after all, not a circular list.
I don't see why induction can't just be applied infinitely to prove this.


maybe i wrong, anyway :
induction can be used to prove a property.
we claim that the property is true for any finite i.
so what's the property that you want to prove by induction ?
you say 'by induction on the lenght of yq'.. but yq is just y (modulo
the a*xq + b*).

it's exactly the same in
ones = 1:ones

does the left ones longer than the right one ?

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


Re: [Haskell-cafe] Simple matrix

2006-06-22 Thread Udo Stenzel
Bjorn Lisper wrote:
 - your definition of fromInteger will behave strangely with the elementwise
   extended operations, like (+). 1 + [[1,2],[3,4]] will become
   [[2,2],[3,5]] rather than [[2,3],[4,5]]. Array languages supporting this
   kind of overloading invariably have the second form of semantics.

Don't call an array a matrix.  If is named matrix, it should have
matrix multiplication, addition, and they should obey the expected laws.  


Udo.
-- 
Jeder Idiot kann seine Fehler verteidigen, was die meisten Idioten ja
auch tun.  -- Dale Carnegie


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Brian Hulley

Jon Fairbairn wrote:

On 2006-06-22 at 15:16BST Brian Hulley wrote:

minh thu wrote:

y and yq are infinite...


But how does this change the fact that y still has 1 more element
than yq? yq is after all, not a circular list.


infinity+1 = infinity


Surely this is just a mathematical convention, not reality! :-)




I don't see why induction can't just be applied infinitely
to prove this.


because (ordinary) induction won't go that far.


I wonder why?
For any finite list yq, |y| == |yq| + 1
So considering any member yq (and corresponding y) of the set of all finite 
lists, |y| == |yq| + 1


Couldn't an infinite list just be regarded as the maximum element of the 
(infinite) set of all finite lists?


Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Jon Fairbairn
On 2006-06-22 at 15:45BST Brian Hulley wrote:
 Jon Fairbairn wrote:
  infinity+1 = infinity
 
 Surely this is just a mathematical convention, not reality! :-)

I'm not sure how to answer that. The only equality worth
talking about on numbers (and lists) is the mathematical
one, and it's a mathematical truth, not a convention.

  I don't see why induction can't just be applied infinitely
  to prove this.
 
  because (ordinary) induction won't go that far.
 
 I wonder why?
 For any finite list yq, |y| == |yq| + 1
 So considering any member yq (and corresponding y) of the set of all finite 
 lists, |y| == |yq| + 1

But the infinite lists /aren't/ members of that set. For
infinite lists the arithmetic is different. |y| == |yq| +1 == |yq|

If you don't use the appropriate arithmetic, your logic will
eventually blow up.

 Couldn't an infinite list just be regarded as the maximum element of the 
 (infinite) set of all finite lists?

It can be, but that doesn't get it into the set.


-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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


Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Robert Dockins


On Jun 22, 2006, at 10:16 AM, Brian Hulley wrote:


minh thu wrote:

2006/6/22, Brian Hulley [EMAIL PROTECTED]:

Jerzy Karczmarczuk wrote:

Brian Hulley wrote:

[snip]
y IS NOT a longer list than yq, since co-recursive equations  
without

limiting cases, apply only to *infinite* streams. Obviously, the
consumer of such a stream will generate a finite segment only, but
it is his/her/its problem, not that of the producer.

I still don't understand this point, since y = (a*x0 : yq) so surely
by induction on the length of yq, y has 1 more element?

y and yq are infinite...


But how does this change the fact that y still has 1 more element  
than yq?

yq is after all, not a circular list.
I don't see why induction can't just be applied infinitely to prove  
this.


Induction doesn't apply to co-inductive objects, such as infinite  
lists AKA streams.


I particular, the length of an infinite list is undefined, much as  
the size of an infinite set is undefined.  The only think you can  
discuss, a la Cantor, is cardinality.  In both cases, as mentioned by  
another poster, it is aleph-null.


aside
Every few months a discussion arises about induction and Haskell  
datatypes, and I feel compelled to trot out this oft-misunderstood  
fact about Haskell: 'data' declarations in Haskell introduce co- 
inductive definitions, NOT inductive ones.  Induction, in general,  
does not apply to ADTs defined in Haskell; this is in contrast to  
similar-looking definitions in, eg, ML.  This is a common source of  
confusion, especially for mathematically-inclined persons new to  
Haskell.  Does anyone know of a good reference which clearly explains  
the difference and its ramifications?  I've never been able to find a  
paper on the topic that doesn't dive head-first into complicated  
category theory (which I usually can't follow) ...

/aside


Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG

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


Re: [Haskell-cafe] Eager Parser Combinators [was: Functional programming for processing of largeraster images]

2006-06-22 Thread Greg Buchholz
Ralf Hinze wrote:
 Also, in a non-strict language recursive definitions are not
 limited to function types. Users of parser combinators heavily rely
 on this feature. Just try to define/use parsing combinators
 ins a strict language.

Anyone care to comment on what goes wrong with parser combinators in
an eager language?  Is it mainly a space usage problem (where the lazy
version might essentially perform a depth-first-search, while the eager
version is breadth-first)?  Or is there something else I'm missing?  

As a reference, back when I was trying to understand monads, I
ported the parser combinators from the Hutton and Meijer paper to
perl...

http://sleepingsquirrel.org/monads/parser/monad_parser.txt


Thanks,

Greg Buchholz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Ross Paterson
On Thu, Jun 22, 2006 at 11:06:38AM -0400, Robert Dockins wrote:
 aside
 Every few months a discussion arises about induction and Haskell  
 datatypes, and I feel compelled to trot out this oft-misunderstood  
 fact about Haskell: 'data' declarations in Haskell introduce co- 
 inductive definitions, NOT inductive ones.  Induction, in general,  
 does not apply to ADTs defined in Haskell; this is in contrast to  
 similar-looking definitions in, eg, ML.  This is a common source of  
 confusion, especially for mathematically-inclined persons new to  
 Haskell.  Does anyone know of a good reference which clearly explains  
 the difference and its ramifications?  I've never been able to find a  
 paper on the topic that doesn't dive head-first into complicated  
 category theory (which I usually can't follow) ...
 /aside

I think that's untrue, from a certain point of view.

A convenient semantics for Haskell data types includes values for
non-termination (_|_, or bottom), partial values (containing _|_) and
infinite values, with a termination ordering -- a complete partial order
(cpo for short).  The infinite values are needed for the complete
part: they arise as the limits of ascending chains of partial values.
(The semantics of ML types has extra values too, but in a different
place: the partial functions in the - type.)

You can do induction over Haskell data types, as long as your predicate
is well-behaved on limits (which conjunctions of equations are), and
also satisfied by _|_.  There's a good introduction to this sort of
reasoning in Introduction to Functional Programming using Haskell
by Bird (or the first edition by Bird and Wadler).

It works because Haskell 'data' definitions yield both an initial fixed
point (with respect to strict functions) and a terminal fixed point (with
respect to arbitrary functions), and moreover these are usually the same.
The former is inductive, the latter co-inductive.  They differ only when
the definition is strict in the recursive type, as in

data Nat = Zero | Succ !Nat

The initial fixed point is the natural numbers plus _|_.
The terminal fixed point has those elements plus an infinity.
The former corresponds to what Haskell provides.

So actually Haskell data types are always inductive, and usually also
co-inductive.

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


Re: [Haskell-cafe] Principal type in Haskell

2006-06-22 Thread william kim


Thanks. Do I therefore able to conclude that none of the reductions using 
instance declarations are not performed because of potential overlapping 
instances?


william


From: Bulat Ziganshin [EMAIL PROTECTED]
Reply-To: Bulat Ziganshin [EMAIL PROTECTED]
To: william kim [EMAIL PROTECTED]
CC: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Principal type in Haskell
Date: Thu, 22 Jun 2006 14:28:14 +0400

Hello william,

Thursday, June 22, 2006, 1:22:32 PM, you wrote:


 GHCi yields type f :: (Eq [a]) = a - a - Bool.

 But according to the paper Type classes: an exploration of the design
 space, predicate Eq [a] should be reduced to Eq a. Is this reduction
 performed here? What should be the principal type of f?

Ghc, unlike H98, supports instances like this:

instance Eq [MyType] where
  a==b = True

so this extension to type inference allows to use such instance even
if MyType is not in Eq class


--
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



_
Find love on MSN Personals http://personals.msn.com.sg/

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


Re: [Haskell-cafe] Eager Parser Combinators [was: Functional programming for processing of largeraster images]

2006-06-22 Thread Jared Updike

On 6/22/06, Greg Buchholz [EMAIL PROTECTED] wrote:

Ralf Hinze wrote:
 Also, in a non-strict language recursive definitions are not
 limited to function types. Users of parser combinators heavily rely
 on this feature. Just try to define/use parsing combinators
 ins a strict language.

Anyone care to comment on what goes wrong with parser combinators in
an eager language?  Is it mainly a space usage problem (where the lazy
version might essentially perform a depth-first-search, while the eager
version is breadth-first)?  Or is there something else I'm missing?


Slide 22 (Combinator Libraries) of
 http://research.microsoft.com/~simonpj/papers/haskell-retrospective/
shows that in an eager language, you have to make the argument
explicit, which destroys the Parser abstraction. Indeed I rolled my
own sort of monads and made my own parser combinators in C# and they
were a lot like your Perl combinators: very imperative and verbose
(~10x more code than Haskell for the same parser), instead of clean
and declarative like BNF or Haskell parser combinators.

 Jared.


As a reference, back when I was trying to understand monads, I
ported the parser combinators from the Hutton and Meijer paper to
perl...

http://sleepingsquirrel.org/monads/parser/monad_parser.txt


Thanks,

Greg Buchholz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




--
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Polymorphic type

2006-06-22 Thread Sara Kenedy

Hello all,

Now I am trying with the function of polymorphic type: This function
returns the Nth element of list with type a. I try it as below.

getNthElem :: Int - [a] - Maybe a
getNthElemt _ []= Nothing
getNthElem 0 _  = Nothing
getNthElem n s  
| n  length s   = Nothing
| otherwise = Just ((drop (n-1) (take n s))!!0)


getNthElem 2 [a,b,c]

Just b

However, I do not satisfy with this function because I want to return
the Nth element of type a, not (Maybe a). For example, I want this
function:
getNthElem :: Int - [a] -  a

But, I do not know how to define the empty element of type a.

getNthElemt _ []= 
getNthElem 0 _  =  

If you have some ideas about this, please give me some clues. Thanks a lot.

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


Re: [Haskell-cafe] Functional progr., images, laziness and alltherest

2006-06-22 Thread Jared Updike

 Therefore the list of non-negative integers is longer than the list of
 positive integers. I agree they have the same cardinality but this doesn't
 mean they have the same length.

Are you saying that some of the (0,1,2,3,4,5,...), (1,2,3,4,5,...) and
(1-1,2-1,3-1,4-1,5-1,...) lists have different lengths?


Q: Which list is longer, [0..] or [1..] ?
A: MU! (see http://en.wikipedia.org/wiki/Mu_%28negative%29 ) I am
un-asking the question. They don't have length. Length only makes
sense for lists with [] in them and infinite lists do not use [].

 Jared.

P.S. If you still don't believe me, this code should put this mystery to rest:

length2 x y = f 0 0 x y where
  f a b [] []  = (a, b)
  f a b [] (y:ys)  = f a (b+1) [] ys
  f a b (x:xs) []  = f (a+1) b xs []
  f a b (x:xs) (y:ys)  = f (a+1) (b+1) xs ys

length2 [0..] [1..]

Feel free to get back to us with the results!
--
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic type

2006-06-22 Thread Jared Updike

On 6/22/06, Sara Kenedy [EMAIL PROTECTED] wrote:

Hello all,

Now I am trying with the function of polymorphic type: This function
returns the Nth element of list with type a. I try it as below.

getNthElem :: Int - [a] - Maybe a
getNthElemt _ []= Nothing
getNthElem 0 _  = Nothing
getNthElem n s
| n  length s  = Nothing
| otherwise = Just ((drop (n-1) (take n s))!!0)

getNthElem 2 [a,b,c]
Just b

However, I do not satisfy with this function because I want to return
the Nth element of type a, not (Maybe a). For example, I want this
function:
getNthElem :: Int - [a] -  a

But, I do not know how to define the empty element of type a.


Not all types (especially numbers) have an empty element (what does
that even mean?). Suppose you have a list
 [0, 1, -2, -1, 2]
and you try getNthElemt 4 and your program assumes that the empty
element for integers is 0. How can you tell that 0 from the 0 at the
beginning of the list [0, 1, 2]? Think really hard about what you are
asking and you will see why Maybe a takes the type a and extends it,
in a way, with an empty element, Nothing. To convert it from Maybe a
to a, try, e.g.
 fromJust (Just 4)    4
(it will give exceptions when Nothing shows up).


getNthElemt _ []= 
getNthElem 0 _  =  


One possiblity is to make a class called empty with a single member:


class Empty a where
  empty :: a
instance Empty [a] where   -- this also makes= empty   for String
  empty = []
instance Empty Maybe a where   -- is this desirable?
  empty = Nothing
instance Integer where -- or this?
  empty = 0
...


and then add the constraint to your function:


getNthElem :: Empty a = Int - [a] - a
getNthElem :: Int - [a] - Maybe a
getNthElemt _ []= empty
getNthElem 0 _  = empty
getNthElem n s
| n  length s  = empty
| otherwise = ((drop (n-1) (take n s))!!0)



but you need overlapping instances to instantiate [a].  Or you could
use MonadPlus and mzero instead of Empty and empty, but that would
only work for List, Maybe and other monads and not for Integer, etc.

Note that in a dynamic language the same thing happens. In python
  4 + None
raises an exception. I don't think it's possible to get away from this
whole failure concept (except silently ignore it---in perl   4+null
yields 4 but is that always the right behavior in all situations? It
makes bugs really hard to find.)

 Jared.
--
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic type

2006-06-22 Thread minh thu

2006/6/22, Sara Kenedy [EMAIL PROTECTED]:

Hello all,

Now I am trying with the function of polymorphic type: This function
returns the Nth element of list with type a. I try it as below.

getNthElem :: Int - [a] - Maybe a
getNthElemt _ []= Nothing
getNthElem 0 _  = Nothing
getNthElem n s
   | n  length s  = Nothing
   | otherwise = Just ((drop (n-1) (take n s))!!0)

getNthElem 2 [a,b,c]
Just b

However, I do not satisfy with this function because I want to return
the Nth element of type a, not (Maybe a). For example, I want this
function:
getNthElem :: Int - [a] -  a

But, I do not know how to define the empty element of type a.

getNthElemt _ []= 
getNthElem 0 _  =  

 If you have some ideas about this, please give me some clues. Thanks a lot.



hi,
precisely, you want to return an a only when there is one
accordingly to your above code. the only way to handle this without
resorting to [] or Nothing to say there is no such value is to use
error or default value.

infact, ask yourself, what do you want ?

getNthElem 5 [a,b,c]

or

getNthElem 0 [a,b,c]

or

getNthElem (-1) [a,b,c]

do you want

a
[]
Nothing
wrong

or raise an exception (i.e. you use the error function) ?

once you know what you want, you can code it.

note, i think your 'take is unnecessary here

   | otherwise = Just ((drop (n-1) (take n s))!!0)

also
you can use

   | otherwise = Just (n!!some_value) -- :)

this is where you see that the function you're trying to write is
really close of

(!!)


cheers,
mt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Brian Hulley

minh thu wrote:

maybe i wrong, anyway :
induction can be used to prove a property.
we claim that the property is true for any finite i.
so what's the property that you want to prove by induction ?
you say 'by induction on the lenght of yq'.. but yq is just y (modulo
the a*xq + b*).

it's exactly the same in
ones = 1:ones

does the left ones longer than the right one ?


Thanks for pointing this out - I'd somehow missed the fact that yq was also 
defined in terms of y, so of course the idea of length becomes meaningless 
in this context (at least as far as trying to compare the length of yq with 
that of y)


Best regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Functional progr., images, laziness and alltherest

2006-06-22 Thread Brian Hulley

Stepan Golosunov wrote:

On Thu, Jun 22, 2006 at 03:32:25PM +0100, Brian Hulley wrote:

Bill Wood wrote:

On Thu, 2006-06-22 at 15:16 +0100, Brian Hulley wrote:
 . . .

But how does this change the fact that y still has 1 more element
than yq? yq is after all, not a circular list.
I don't see why induction can't just be applied infinitely to prove
this.


The set of all non-negative integers has one more element than the
set of all positive integers, however they have the same
cardinality, aleph-null.  This phenomenon is the hallmark of
infinite sets.


Therefore the list of non-negative integers is longer than the list
of positive integers. I agree they have the same cardinality but
this doesn't mean they have the same length.


Are you saying that some of the (0,1,2,3,4,5,...), (1,2,3,4,5,...) and
(1-1,2-1,3-1,4-1,5-1,...) lists have different lengths?


I'd say that the list [0,1,2,3,4,5,..] is longer than [1,2,3,4,5,..] and 
that [1-1,2-1,3-1,4-1,5-1,..] ie [0,1,2,3,4,..] is the same length as 
[1,2,3,4,5,..], assuming that they all grow at the same rate. I think of 
them as physically growing objects, which at any moment have a finite 
length, not as some kind of fixed infinite structure.


I don't believe in the abstract mathematical notion of infinity. I just see 
it as a kind of hack that makes conventional mathematics workable to some 
extent, although as everyone knows there are plenty of contradictions in it. 
This doesn't mean that these contradictions reflect reality - just that 
maths hasn't yet reached a true understanding of reality imho.


For example, why do people accept that infinity == infinity + 1 ? Surely 
this expression is just ill-typed. infinity can't be a number. Maths was 
developed before programming languages so perhaps the concept of well typed 
expressions was not known when infinity was invented.


Still, as others have pointed out in offlist emails, I can't really take 
this line of reasoning further without providing an alternative system, and 
to be honest, I don't have one (yet :-) ).


If I was going to try to re-write the foundations of mathematics, I'd start 
by re-reading the book On the origin of objects by Brian Cantwell Smith, 
which blows apart many of the things that logical systems of thought often 
seem to take for granted about the nature of reality. For example he talks 
about particularity and individuality, and the idea that something can be a 
particular entity without being an individual, so (this is just my thought 
now) perhaps one of the problems with (infinity + 1) is that it is an 
attempt to add a particular number which is not an individual number, namely 
infinity, with an individual number, so there is no individual component 
of infinity to add the 1 onto...


In any case, if I just use the subset of Haskell equivalent to strict 
evaluation with force/delay lists (as in my alternative definition of the 
filter function),  I can reason about my programs without entering the areas 
of maths that I don't believe in, which is one more reason for my desire to 
have a totally strict version of Haskell ;-)


Best regards (also thanks to everyone else who replied),
Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Polymorphic type

2006-06-22 Thread Brian Hulley

Sara Kenedy wrote:

Hello all,

Now I am trying with the function of polymorphic type: This function
returns the Nth element of list with type a. I try it as below.

getNthElem :: Int - [a] - Maybe a
getNthElemt _ [] = Nothing
getNthElem 0 _ = Nothing
getNthElem n s

n  length s = Nothing
otherwise = Just ((drop (n-1) (take n s))!!0)



getNthElem 2 [a,b,c]

Just b

However, I do not satisfy with this function because I want to return
the Nth element of type a, not (Maybe a). For example, I want this
function:
getNthElem :: Int - [a] -  a

But, I do not know how to define the empty element of type a.

getNthElemt _ [] = 
getNthElem 0 _ =  

If you have some ideas about this, please give me some clues. Thanks
a lot.


You might find it's always a lot easier to start counting from zero rather 
than 1, so that a is the 0th element, b is the 1st element etc. Just 
like a building with 2 floors has a ground floor and a first floor, and if 
you want to find what day of the week it is in 46 days from today you just 
use (today + 46) `mod` 7 instead of (((today - 1) + 46) `mod` 7) + 1


That aside, why not just throw an error when the function is called with an 
index that's out of range?


   getNthElemt _ [] = error getNthElemt

Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Functional progr., images, laziness and alltherest

2006-06-22 Thread Bill Wood
On Thu, 2006-06-22 at 20:13 +0100, Brian Hulley wrote:
   . . .
 filter function),  I can reason about my programs without entering the areas 
 of maths that I don't believe in, which is one more reason for my desire to 
 have a totally strict version of Haskell ;-)

This may also explain why those who *do* believe in some of those maths
resist the move to totally strict Haskell :-).

 -- Bill Wood


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


Re: [Haskell-cafe] Functional progr., images, laziness and alltherest

2006-06-22 Thread Piotr Kalinowski

On 22/06/06, Brian Hulley [EMAIL PROTECTED] wrote:
...

This doesn't mean that these contradictions reflect reality - just that
maths hasn't yet reached a true understanding of reality imho.


Well, I for instance believe that contradiction IS the true nature of
reality... ;)



For example, why do people accept that infinity == infinity + 1 ? Surely
this expression is just ill-typed. infinity can't be a number.


This equation is just a shortcut, so I can't see how can it be
ill-typed. It means something like: if you add one element to an
infinite list, will it be longer? I found the explanation in terms of
defining bijection between both lists very appealing (along with a
metaphor of taking one element at a time from both lists and never
being left with one of the lists empty, which was demonstrated here as
well).

Seems I don't understand your problem with infinity after all :)

Regards,
Piotr Kalinowski
--
Intelligence is like a river: the deeper it is, the less noise it makes
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functional progr., images, laziness and alltherest

2006-06-22 Thread Brian Hulley

Piotr Kalinowski wrote:

On 22/06/06, Brian Hulley [EMAIL PROTECTED] wrote:
...

This doesn't mean that these contradictions reflect reality - just
that maths hasn't yet reached a true understanding of reality imho.


Well, I for instance believe that contradiction IS the true nature of
reality... ;)


Perhaps I should have said: are the *particular* contradictions found in 
maths relevant to reality? (Obviously they are in the sense that maths as an 
artifact of human endeavour is just as much part of reality as anything else 
and reflects aspects of the current and past human condition in the way it's 
formulated, and in turn possibly influences how we perceive reality...)






For example, why do people accept that infinity == infinity + 1 ?
Surely this expression is just ill-typed. infinity can't be a number.


This equation is just a shortcut, so I can't see how can it be
ill-typed. It means something like: if you add one element to an
infinite list, will it be longer?


What does your intuition say about this?


I found the explanation in terms of
defining bijection between both lists very appealing (along with a
metaphor of taking one element at a time from both lists and never
being left with one of the lists empty, which was demonstrated here as
well).


But this explanation might just be vapid sophistry. Do you *really* want to 
trust it? Especially when the explanation makes use of the physical notion 
of taking one element at a time from both lists. Can we really rely on 
intuitions about taking an element from an infinite list when we are trying 
to prove something counter-intuitive about adding an element to an infinite 
list?




Seems I don't understand your problem with infinity after all :)


Just that there is a conflict with intuition no matter which option you 
choose: if I think that the list would be longer, I have to reject any proof 
to the contrary, but then my intuitions about valid proof are confounded, 
whereas if I accept the proof, my intuition about physical objects is 
confounded: if the list doesn't get longer, then where *is* the thing I 
added to it? Did it just disappear?

So for these reasons I find that infinity is a troublesome concept.

Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Functional progr., images, laziness and alltherest

2006-06-22 Thread Piotr Kalinowski

On 23/06/06, Brian Hulley [EMAIL PROTECTED] wrote:

 This equation is just a shortcut, so I can't see how can it be
 ill-typed. It means something like: if you add one element to an
 infinite list, will it be longer?

What does your intuition say about this?


It won't be longer. How can it be? It's already infinite ;) It's like
throwing things into bottomless hole and expecting it to get more
full.


But this explanation might just be vapid sophistry. Do you *really* want to
trust it?


I perceive it as a way to explain to beginner students where bijection
idea comes from. It's all it means to me. I suppose the whole idea is
to start at something intuitive and then extend it to completely
counter-intuitive notion of being infinite.


Just that there is a conflict with intuition no matter which option you
choose: if I think that the list would be longer, I have to reject any proof
to the contrary, but then my intuitions about valid proof are confounded,
whereas if I accept the proof, my intuition about physical objects is
confounded: if the list doesn't get longer, then where *is* the thing I
added to it? Did it just disappear?
So for these reasons I find that infinity is a troublesome concept.


I suppose infinity can't be totally intuitive in the end. We are not
used to handle infinite objects and intuition as such was not
developed to handle them.

Regards,
Piotr Kalinowski

--
Intelligence is like a river: the deeper it is, the less noise it makes
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Functional progr., infinity, and the Universe

2006-06-22 Thread jerzy . karczmarczuk
Brian Hulley wrote: 



Couldn't an infinite list just be regarded as the maximum element of the 
(infinite) set of all finite lists?



Brian, I will say something you might find acrimonious and impolite, but
it is serious, you might find this in some philosophical works. 

If you are right, then YOU JUST PROVED THE EXISTENCE OF GOD. 

= 


More seriously...
Perhaps you (and possibly Piotr Kalinowski) would look up some materials
on intuitionism in mathematics, on the constructive theory of sets, etc. 





Jerzy Karczmarczuk 



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


[Haskell-cafe] neural network code

2006-06-22 Thread John Meacham
I was curious if there was any code floating around out there for
dealing with neural networks in haskell?

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic type

2006-06-22 Thread Sara Kenedy

Thanks all. I think for my function, I only need to throw an error
message for the out of range index. But through this, I know more some
ways to deal with the polymorphic type.


On 6/22/06, Brian Hulley [EMAIL PROTECTED] wrote:

Sara Kenedy wrote:
 Hello all,

 Now I am trying with the function of polymorphic type: This function
 returns the Nth element of list with type a. I try it as below.

 getNthElem :: Int - [a] - Maybe a
 getNthElemt _ [] = Nothing
 getNthElem 0 _ = Nothing
 getNthElem n s
 n  length s = Nothing
 otherwise = Just ((drop (n-1) (take n s))!!0)

 getNthElem 2 [a,b,c]
 Just b

 However, I do not satisfy with this function because I want to return
 the Nth element of type a, not (Maybe a). For example, I want this
 function:
 getNthElem :: Int - [a] -  a

 But, I do not know how to define the empty element of type a.

 getNthElemt _ [] = 
 getNthElem 0 _ =  

 If you have some ideas about this, please give me some clues. Thanks
 a lot.

You might find it's always a lot easier to start counting from zero rather
than 1, so that a is the 0th element, b is the 1st element etc. Just
like a building with 2 floors has a ground floor and a first floor, and if
you want to find what day of the week it is in 46 days from today you just
use (today + 46) `mod` 7 instead of (((today - 1) + 46) `mod` 7) + 1

That aside, why not just throw an error when the function is called with an
index that's out of range?

getNthElemt _ [] = error getNthElemt

Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com



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


Re: [Haskell-cafe] Functional progr., infinity, and the Universe

2006-06-22 Thread Paul Hudak
Actually Brian's intuition is right on target.  One way to define an 
infinite list is as the limit of an infinite chain of partial lists 
(which, in domain theory, is essentially how all elements are defined). 
 A chain is a sequence a1 = a2 = ... = an, where = is the domain 
ordering.  A partial list is any list ending in _|_ (i.e. bottom).


So, for example, the infinite list of ones can be defined as the limit 
of the following chain:

_|_
= 1 : _|_
= 1 : 1 : _|_
= 1 : 1 : 1 : _|_
...
To verify that this is a chain, remember that (:) is right associative, 
and _|_ = x for all x.


Or, another way to look at this, is that the infinite list is the LUB 
(least upper bound) of the infinite set of all of these partial (but 
finite) lists.  That explanation corresponds most closely with Brian's 
intuition.


If anyone thinks that this explanation is baroque, I should also point 
out that in a pragmatic sense this idea forms the basis for doing 
inductive proofs on programs generating infinite lists (as described in 
my book, as well as in many other sources).


  -Paul


[EMAIL PROTECTED] wrote:

Brian Hulley wrote:

Couldn't an infinite list just be regarded as the maximum element of 
the (infinite) set of all finite lists?


Brian, I will say something you might find acrimonious and impolite, but
it is serious, you might find this in some philosophical works.
If you are right, then YOU JUST PROVED THE EXISTENCE OF GOD.
=
More seriously...
Perhaps you (and possibly Piotr Kalinowski) would look up some materials
on intuitionism in mathematics, on the constructive theory of sets, etc.

Jerzy Karczmarczuk

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


Re: [Haskell-cafe] Functional programming for processing of large raster images

2006-06-22 Thread ajb
G'day all.

Quoting [EMAIL PROTECTED]:

 Recently Vo Minh Thu wondered if Haskell (or, I generalize, functional
 programming) can be of much use for computer graphics programming.

As others have pointed out, it's Haskell (and its laziness) that he
perceived to be the problem.

However, I'd like to take the discussion up one more level.

I hope that Thu doesn't mind me saying this, but off-list, I got a
better idea of the program that he was trying to write.  He's not
interested writing an image processing system.  In that sense, raster
images are actually not a central data structure.

The scenario is quite typical:

- A decent, ambitious idea about a program or suite of programs
  that someone would like to write.

- A good idea about how to write something simple to start with,
  at least as a proof of concept, possibly to be refactored into
  something more sophisticated later.

- Some thinking, exploratory code or back-of-the-envelope playing
  around reveals some data structure to be extremely important to
  get right for the simple system, even though it's likely to
  play a small, non-central role in the real system.  There's no
  obvious, clean, efficient way to implement this data structure in
  Haskell.

I think that a lot of people here have been in precisely this position.
Often there's a good substitute (e.g. I'll wager that a lot of GHC had
already been written before FastPackedString became necessary; String
turns out to be fine to start things off), but sometimes there isn't.

I have a suspicion that this is related to an old complaint, namely
that programmers are trained to think about algorithms and data
structures and not so much about APIs.

An efficient algorithm or data structure is indeed a fine thing.  But
for 99.9% of cases, for overall program efficiency, nothing beats a
well-designed API.  If your program has an efficiency problem, you
simply remove the offending code and put in new code which conforms to
the same API.  As if by magic, everything works much as it did, only
more efficiently.

This advice is triply important for a data structure or algorithm which
may not play a central role in the final program.

Now I don't know if there are any decent references on API design.
This gives the general idea, though:

http://lcsd05.cs.tamu.edu/slides/keynote.pdf

With my agile programming hat on, however, I'd argue that if you're
writing an application (as opposed to an ISO standard), the most
important thing is to write something, anything, that WORKS and put
it behind a very thin API layer to start with, even if it's a quick
and dirty choice of implementation.  Both the implementation and the
API can be changted as it needs to, and simply having the API there
(even if it's bad) will encourage you to modify said API instead of
digging into the innards of what you're trying to protect.

Eventually, you'll find the true set of operations that you need.

(If you are writing an ISO standard, of course, then you need to take
more care.  The rule of threes states that a) you need to examine at
least three systems to find out what you need in the API, and b) you
need to use the API at least three times to ensure that it's reusable.
Nobody claimed this stuff was easy.)

 In this project, functional programming does what it is probably best
 suited: to develop a `compiler' -- a compiler from a filter
 specification to quite efficient code.

Or, in even more generality:

http://c2.com/cgi/wiki?AlternateHardAndSoftLayers

Functional programming is great for implementing the soft layers where
the smart and flexible bits lie.  It may not be as great for implementing
the hard layers where the dirty bit hackery and tight loops lie (though
it might be okay for prototyping that part).  Over time, anything in the
soft layer which turns out to have efficiency issues can migrate to the
hard layer as required.

As Henry James famously pointed out, all writing is rewriting.  That's
especially true of software.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Principal type in Haskell

2006-06-22 Thread Bulat Ziganshin
Hello william,

Thursday, June 22, 2006, 9:12:44 PM, you wrote:

sorry, i don't even understood your question

 Thanks. Do I therefore able to conclude that none of the reductions using
 instance declarations are not performed because of potential overlapping
 instances?

Ghc, unlike H98, supports instances like this:

instance Eq [MyType] where
   a==b = True

so this extension to type inference allows to use such instance even
if MyType is not in Eq class


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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