Re: JVM bridge

2004-01-09 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 Mark T.B. Carroll [EMAIL PROTECTED] wrote:

 I don't suppose anyone can hand-hold me through tracking this problem
 down?

I've been rather neglecting JVM Bridge since I got a paying job back in 
December. But I'll try to have a look at this over the weekend.

Likely areas: GHC 6.2 changed something, or it's a GCC version thing.

-- 
Ashley Yakeley, Seattle WA

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


Re: no continuations

2004-01-09 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 [EMAIL PROTECTED] wrote:

 Similarly, R5RS obligates any Scheme implementation to resort to
 assignments when processing a letrec form.

Not mine! I do use a polyvariadic fixed-point function.

  (define circular (letrec ((c (cons 'x c))) c))

  (list-head circular 10)

=

  (x x x x x x x x x x)

Try it yourself at http://hscheme.sourceforge.net/interpret.php.
I also make the fixed-point function available as call-with-result, 
it's more or less equivalent to this:

  (lambda (f) (letrec ((x (f x))) x))

 An implementation may not
 use a (polyvariadic) Y to implement letrec, unless the implementation
 can prove that the difference is unobservable for the form in
 question.

Do you have an example of use of Y for letrec where a program would 
violate R5RS?

-- 
Ashley Yakeley, Seattle WA

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


Re: pet project - 7 Millennium Prize problemss

2004-01-09 Thread Keith Wansbrough
Christopher Milton [EMAIL PROTECTED] writes:

 I think  Haskell can be used to solve several, if not all, of
 the seven problems.
 
 Now I have to decide which problem to tackle first.

(a joke, I assume...)

http://www.claymath.org/Millennium_Prize_Problems/

1. Birch and Swinnerton-Dyer Conjecture
2. Hodge Conjecture
3. Navier-Stokes Equations
4. P vs NP
5. Poincare Conjecture
6. Riemann Hypothesis
7. Yang-Mills Theory

Any ideas how to solve any of these, with Haskell or otherwise?

--KW 8-)
-- 
Keith Wansbrough [EMAIL PROTECTED]
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: Type checking

2004-01-09 Thread Keith Wansbrough
 Hi,
 
 Can anyone explain to me how hugs manages to derive that
 
 f x y z = y (y z) x
 
 is of type
 
 f :: a - ((a - b) - a - b) - (a - b) - b

This question was posted from an Oxford University computer; it also smells like 
homework.

If it's genuinely not homework, Lee, I apologise!

See http://www.haskell.org/hawiki/HomeworkHelp

--KW 8-)
-- 
Keith Wansbrough [EMAIL PROTECTED]
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: Combining distinct-thread state monads?

2004-01-09 Thread Mark Carroll
Another bit of code that seems to work is:

convertState :: (s1 - s2)
 - (s2 - s1)
 - State s2 a
 - State s1 a

convertState fromState toState computation =
do oldState - get
   let (result, newState) =
   runState computation (fromState oldState)
   put (toState newState)
   return result

Buoyed by this apparent success, I had a go with a Parsec parser:

convertParser :: (s1 - s2)
  - (s2 - s1)
  - GenParser tok s2 a
  - GenParser tok s1 a

convertParser fromState toState parser =
do oldState - getState
   oldInput - getInput
   case runParser (wrapParser parser)
(fromState oldState)  oldInput of
  Left error -
  fail (show error)
  Right (result, newState, newInput) -
  do setState (toState newState)
 setInput newInput
 return result
where
wrapParser parser =
do result - parser
   state - getState
   input - getInput
   return (result, state, input)

However, this has problems, not least of which are that the source
filepath is lost in the handing down, and the ParseError can't be passed
upward easily without some extra housekeeping, so the resulting shown
error has multiple locations. So maybe composed monads are the way to go.

Is there a better way to do this - with lifting or whatever - *while
keeping the type signatures the same*? (If this has already been said in a
way that wasn't obvious to me the first time, just let me know who said it
and I'll hunt in the list archives.)

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


Re: no continuations

2004-01-09 Thread dvanhorn
Ashley Yakeley wrote:
 In article [EMAIL PROTECTED],
  [EMAIL PROTECTED] wrote:
 
Similarly, R5RS obligates any Scheme implementation to resort to
assignments when processing a letrec form.
 
 Not mine! I do use a polyvariadic fixed-point function.

An implementation may not
use a (polyvariadic) Y to implement letrec, unless the implementation
can prove that the difference is unobservable for the form in
question.
 
 Do you have an example of use of Y for letrec where a program would 
 violate R5RS?

http://groups.google.com/groups?selm=976rij%24jd1%241%40news.gte.com

In this post to c.l.scheme, Dorai Sitaram writes:

   letrec with set! is certainly different from letrec with Y,
   and you don't need call/cc to distinguish the two.

   (define *keep-track* '())

   (letrec ((fact (lambda (n) 
(set! *keep-track* (cons fact *keep-track*))
(if (= n 0) 1
(* n (fact (- n 1)))
 (fact 8))

   and then do

   (eq? (car *keep-track*) (cadr *keep-track*))

   If letrec is set!-based (as in Scheme), the
   result is #t.  If it is Y-based, the result is #f.  Why
   this is should be obvious if you mentally (or with
   pencil) trace what Y does.

   Scheme's letrec defines recursive procedures by making
   the lexical variable bound to a recursive procedure
   whose body contains the references to the same lexical
   variable.   In other words, data recursion in the
   underlying environment is used to represent the
   recursive procedure perceived by the user.  The
   fixed-point approach does not (and clearly
   cannot) do that.  

   There is no wrong choice in the sense that
   alternative choices were cut off.  Users have enough
   machinery to define their preferred version of letrec
   using syntactic extension.  But the letrec that
   comes with Scheme is an extremely good and pragmatic
   one, and is more efficient than a Y-based letrec could
   be expected to be. 

   --d

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


Re: pet project - 7 Millennium Prize problemss

2004-01-09 Thread Christopher Milton
--- Keith Wansbrough [EMAIL PROTECTED] wrote:
 Christopher Milton [EMAIL PROTECTED] writes:
  I think  Haskell can be used to solve several, if not all, of
  the seven problems.
  
  Now I have to decide which problem to tackle first.
 
 (a joke, I assume...)
 
 http://www.claymath.org/Millennium_Prize_Problems/
 
 1. Birch and Swinnerton-Dyer Conjecture
 2. Hodge Conjecture
 3. Navier-Stokes Equations
 4. P vs NP
 5. Poincare Conjecture
 6. Riemann Hypothesis
 7. Yang-Mills Theory
 
 Any ideas how to solve any of these, with Haskell or otherwise?

I was thinking of combining one of the algebra libraries with a theorem
prover, and maybe a refactoring tool, then plugging in some of the
equations to see what happens, e.g.:

James J. Leifer: Formal logic via functional programming
http://para.inria.fr/~leifer/research.html
http://para.inria.fr/~leifer/articles/logic/LogicviaFP.300.ps.gz
http://para.inria.fr/~leifer/articles/logic/LogicviaFP.gs

Serge Mechveliani: DoCon the Algebraic Domain Constructor
http://www.haskell.org/docon/

Jeroen Fokker: Explaining algebraic theory with functional programs
http://www.cs.uu.nl/people/jeroen/article/algebra/index.html

Refactoring Functional Programs
http://www.cs.kent.ac.uk/projects/refactor-fp/

Yes, it's crazy and naive, but I need to give my brain some exercise.


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


RE: no continuations

2004-01-09 Thread Kevin S. Millikin
On Friday, January 09, 2004 2:48 AM, Ashley Yakeley 
[SMTP:[EMAIL PROTECTED] wrote:

 Do you have an example of use of Y for letrec where a program would
 violate R5RS?

Sure, take a look at my implementation of Ben Rudiak-Gould's 
implementation of Alan Bawden's implementation of boxes.

In 4.2.2 of R5RS, it says, re letrec:

Semantics: The variables are bound to fresh locations holding 
undefined values, the inits are evaluated in the resulting 
environment (in some unspecified order), each variable is assigned to 
the result of the corresponding init, the body is evaluated in the 
resulting environment, and the value(s) of the last expression in 
body is(are) returned. Each binding of a variable has the entire 
`letrec' expression as its region, making it possible to define 
mutually recursive procedures.

The result of the corresponding init is *assigned to* each variable 
(anyone know why the wording is backward above?), and that is after the 
inits are evaluated, which is after the variables are bound.

There was a discussion on comp.lang.scheme a couple of years ago about 
this.

http://groups.google.com/groups?hl=enlr=ie=UTF-8oe=UTF-8th=fdcf3  
554852a3cadseekm=3AC66F16%40MailAndNews.com#link1
http://groups.google.com/groups?hl=enlr=ie=UTF-8oe=UTF-8th=a47e0  
3e456b2dc2aseekm=200102220358.TAA77339%40adric.cs.nps.navy.mil#link1
http://groups.google.com/groups?hl=enlr=ie=UTF-8oe=UTF-8th=58a68  
6525be78d16rnum=1

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


Re: pet project - 7 Millennium Prize problemss

2004-01-09 Thread Bjorn Lisper
--- Keith Wansbrough [EMAIL PROTECTED] wrote:
 Christopher Milton [EMAIL PROTECTED] writes:
  I think  Haskell can be used to solve several, if not all, of
  the seven problems.
  
  Now I have to decide which problem to tackle first.
 
 (a joke, I assume...)
 
 http://www.claymath.org/Millennium_Prize_Problems/
 
 1. Birch and Swinnerton-Dyer Conjecture
 2. Hodge Conjecture
 3. Navier-Stokes Equations
 4. P vs NP
 5. Poincare Conjecture
 6. Riemann Hypothesis
 7. Yang-Mills Theory
 
 Any ideas how to solve any of these, with Haskell or otherwise?

module P where

import Complexity_class(np)

p = np

:-)

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


Re: no continuations

2004-01-09 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 [EMAIL PROTECTED] wrote:

 In this post to c.l.scheme, Dorai Sitaram writes:
 
letrec with set! is certainly different from letrec with Y,
and you don't need call/cc to distinguish the two.
 
(define *keep-track* '())
 
(letrec ((fact (lambda (n) 
 (set! *keep-track* (cons fact *keep-track*))
 (if (= n 0) 1
 (* n (fact (- n 1)))
  (fact 8))
 
and then do
 
(eq? (car *keep-track*) (cadr *keep-track*))
 
If letrec is set!-based (as in Scheme), the
result is #t.  If it is Y-based, the result is #f.  Why
this is should be obvious if you mentally (or with
pencil) trace what Y does.

Does Haskell mfix count as Y? My implementation is mfix-based, and the 
above code returns 40320 #t. Try it yourself at 
http://hscheme.sourceforge.net/interpret.php
if you don't believe me.

I'd be very interested to know if my implementation of Scheme varies 
from R5RS due to this issue.

-- 
Ashley Yakeley, Seattle WA

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


Re: no continuations

2004-01-09 Thread oleg

Ashley Yakeley wrote:

  Similarly, R5RS obligates any Scheme implementation to resort to
  assignments when processing a letrec form.

 Not mine! I do use a polyvariadic fixed-point function.

I'm sorry but you don't have the choice in the matter -- if you wish
to call your implementation R5RS-compliant. R5RS _requires_ letrec to
use assignments. The latter issue has been extensively discussed, on
comp.lang.scheme, in Amr Sabry's Technical report Recursion as a
computational effect and in many other places.

Here's the exact quote from R5RS, Section 4.2.2

Semantics [of letrec]: The variables are bound to fresh locations
holding undefined values, the inits are evaluated in the resulting
environment (in some unspecified order), each variable is assigned
[sic!] to the result of the corresponding init, the body is evaluated
in the resulting environment, and the value(s) of the last expression
in body is(are) returned.

   (define circular (letrec ((c (cons 'x c))) c))

I'm afraid that is not a R5RS compliant code.

R5RS states (in the same Section 4.2.2)

One restriction on letrec is very important: it must be possible to
evaluate each init without assigning or referring to the value of any
variable . If this restriction is violated, then it is an error.

In the quoted code, the init is (cons 'x c), and it is impossible to
evaluate that expression according to the semantics of Scheme without
referring to the value of variable c.

If it were
(define circular (letrec ((c (cons 'x (delay c c))
then there is no contradiction with R5RS.

 Do you have an example of use of Y for letrec where a program would 
 violate R5RS?

http://google.com/groups?selm=7eb8ac3e.0304131423.4f103d4f%40posting.google.com

The difference between the Y and set! approaches to letrec *is*
observable. I must state that the exact conformance to the R5RS
semantics of letrec is important -- for example, for the code that
uses the non-deterministic choice operator 'amb' or for the code that
uses shift/reset. Otherwise, bizarre behavior can occur -- and has
occurred. I can send you an example privately.

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


Hi, I have a question!

2004-01-09 Thread NamO
Hi.

I am a student, who get interesting in Haskell.
So, nowdays, I study Hakell with Introduction to Functional Programming
using Haskell - second edition
And today, I face an error from bellow code.


module OperationTest where

data Nat = Zero | Succ Nat
deriving (Show)

(+) :: Nat  - Nat - Nat
m + Zero = m
m + Succ n = Succ (m + n)


But above source make an error like bellow

Reading file g:\Haskell\OperationTest.hs:
Dependency analysis
ERROR g:\Haskell\OperationTest.hs:8 - Ambiguous variable occurrence +
*** Could refer to: OperationTest.+ Prelude.+

above source is from the text book - Introduction to Functional Programming
using Haskell - second edition
and I use Hugs to interpret it.

I understand what interpreter say, but I don't know How I can solve this
problem.
Please, Help me!!!


  - 5 -

P.S. Tank you very much to read my broken english letter.



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


Re: no continuations

2004-01-09 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 [EMAIL PROTECTED] wrote:

(define circular (letrec ((c (cons 'x c))) c))
 
 I'm afraid that is not a R5RS compliant code.

Indeed not, it merely demonstrates fixed-point behaviour. Nevertheless, 
allowing this as an extension does not make my implementation 
non-compliant. See section 1.3.2 on this point.

  Do you have an example of use of Y for letrec where a program would 
  violate R5RS?
 
 http://google.com/groups?selm=7eb8ac3e.0304131423.4f103d4f%40posting.google.co
 m
 
 The difference between the Y and set! approaches to letrec *is*
 observable.

I don't believe you. My implementation uses Haskell's mfix, which 
looks like a Y to me. I certainly don't use anything like set!. But my 
implementation passes Dorai Sitaram's test:

  (define *keep-track* '())

  (letrec ((fact (lambda (n) 
 (set! *keep-track* (cons fact *keep-track*))
 (if (= n 0) 1
 (* n (fact (- n 1)))
  (fact 8))
 
  (eq? (car *keep-track*) (cadr *keep-track*))

My implementation returns 

  40320
  #t

...which is apparently correct behaviour for R5RS. Indeed I get exactly 
the same result in mzscheme and guile. Again, I encourage you to try for 
yourself at http://hscheme.sourceforge.net/interpret.php (though it's a bit slow).

-- 
Ashley Yakeley, Seattle WA

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


Re: Hi, I have a question!

2004-01-09 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 NamO [EMAIL PROTECTED] wrote:

 But above source make an error like bellow
 
 Reading file g:\Haskell\OperationTest.hs:
 Dependency analysis
 ERROR g:\Haskell\OperationTest.hs:8 - Ambiguous variable occurrence +
 *** Could refer to: OperationTest.+ Prelude.+

There's already a definition for (+) imported from the Prelude. When you 
write Succ (m + n) the interpreter doesn't know whether you mean the 
one you've just defined (OperationTest.+) or the one imported from the 
Prelude (Prelude.+).

-- 
Ashley Yakeley, Seattle WA

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