Re[2]: [Haskell-cafe] How to variables

2005-07-19 Thread Bulat Ziganshin
Hello robert,

Monday, July 18, 2005, 10:14:43 PM, you wrote:


rd main = loop 0 0 0 -- initial values
rd   where loop loop_num xpos ypos =
rd  do e - pollEvent
rd let xpos' = calculate new xpos
rd ypos' = calculate new ypos
rd someActionInvolvingPosition xpos' ypos'
rd when breakCondition (return ())
rd loop (loop_num+1) xpos' ypos'

the last two lines should be

if breakCondition
  then return ()
  else loop (loop_num+1) xpos' ypos'

`when` can only conditionally execute some code, it can't be used to
return from center of `do` body!



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell-cafe] How to variables

2005-07-19 Thread Bulat Ziganshin
Hello yin,

Tuesday, July 19, 2005, 12:39:24 AM, you wrote:

y I saw it. The problem is, I need an amount of 100*X of mutable variables
y to implement the system (camera position, rotation, aceleration, ...,
y position and deformetion infomations for every object, ..., renderer
y situations [like temprary fading and other efects], ... and more)

you can use global variables, records, impicit parameters. careful
deisigning in terms which procedure needs which variables and which
variables must be joined in records because them used together will
help you. some data can belong just to modules where used, some data
are better to convert into functions (for example, i convert regular
expressions into functions checking match with that regular
expressions)

i recommend you to see examples of imperative programs written in
Haskell, including my own (freearc.narod.ru), Yi editor
(ftp://ftp.cse.unsw.edu.au/pub/users/dons/yi/yi-0.1.0.tar.gz), web server 
written by authors of GHC, PostMaster mail server
(http://postmaster.cryp.to/postmaster-2005-02-14.tar.gz)

my own program are extensively commented in Russian, plus
contains examples of calling C routines which then calls back to
Haskell using given code thunks (see Compress.hs)

writing imperative program in Haskell is not as convenient as in C
because all I/O and reading/writing variables must be coded as
separate actions. but on the other side, you will get all the benefits
of power data manipulations and also can invent your own control
structures. you can find in my Utils.hs a number of such small helpers


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: Re[2]: [Haskell-cafe] How to variables

2005-07-19 Thread Bernard Pope
On Tue, 2005-07-19 at 09:48 +0400, Bulat Ziganshin wrote:
 Hello robert,
 
 Monday, July 18, 2005, 10:14:43 PM, you wrote:
 
 
 rd main = loop 0 0 0 -- initial values
 rd   where loop loop_num xpos ypos =
 rd  do e - pollEvent
 rd let xpos' = calculate new xpos
 rd ypos' = calculate new ypos
 rd someActionInvolvingPosition xpos' ypos'
 rd when breakCondition (return ())
 rd loop (loop_num+1) xpos' ypos'
 
 the last two lines should be
 
 if breakCondition
   then return ()
   else loop (loop_num+1) xpos' ypos'

Or even better:

   unless breakCondition $ loop (loop_num+1) xpos' ypos'

Bernie.

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


[Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Ben Lippmeier


Hello,

I often find it useful to determine whether two objects are using the 
same constructor, without worrying about the constructors' arguments.


An example, using some arbitrary data type Thingo:

 class ShallowEq a where
  shallowEq  :: a - a - Bool

 data Thingo a b
= TOne   a
| TTwo   a b Int Char Float
| TThree Int Char b b

 (TOne 23) `shallowEq` TOne{}
True

 (TThree 5 'c' True False)  `shallowEq` TTwo{}
False

--
Having some sort of generic shallowEq operator reduces the need for a 
host of predicates such as: (this one from Data.Maybe)


 isJust x
  = case x of
Just {} - True
_   - False

.. which is an approach that is obviously going to be tedious when the 
size of the data type becomes large.


--
There is way to hack together a partial implementation of the ShallowEq 
class within GHC, but it leaves much to be desired:


 instance Show a = ShallowEq a where
  ([EMAIL PROTECTED]) a b
= (head $ words $ show a) == (head $ words $ show b)

Notice that in the example the term TTwo{} is a partially constructed 
record. The implementation relies on laziniess to avoid trying to show 
the missing fields (which would fail).


--
Questions:
 1) Does anyone know a better/existing way to implement ShallowEq that 
doesn't involve enumerating all the constructors in the data type?


 2) If not, can anyone think of reasons why it wouldn't be a good idea 
for GHC to derive ShallowEq (by expanding said enumeration)?



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


Re: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Stefan Holdermans

Ben,

I often find it useful to determine whether two objects are using the 
same constructor, without worrying about the constructors' arguments.


In Generic Haskell, you can define shallowEq, well ;), generically:

  shallowEq {| a :: * |} :: (shallowEq {| a |}) = a - a - Bool

  shallowEq {| Unit |} Unit Unit   = True
  shallowEq {| Sum a b |} (Inl _) (Inl _)  = True
  shallowEq {| Sum a b |} (Inr _) (Inr _)  = True
  shallowEq {| Sum a b |} _ _  = False
  shallowEq {| Prod a b |} (_ :*: _) (_ :*: _) = True
  shallowEq {| Int |} n1 n2= n1 == n2
  shallowEq {| Char |} c1 c2   = c1 == c2

There are some more lightweight variations of this style of programming 
that can be embedded in Haskell, but they require some additional 
effort per data type.


I'm not sure how this can be done with the Scrap Your Boilerplate 
approach, i.e., I have not give it too much thought yet, but I'm sure 
something can be done there too.


Regards,

Stefan

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


Re: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Bernard Pope
On Tue, 2005-07-19 at 17:01 +1000, Ben Lippmeier wrote:
 Hello,
 
 I often find it useful to determine whether two objects are using the 
 same constructor, without worrying about the constructors' arguments.

[snip]

 Having some sort of generic shallowEq operator reduces the need for a 
 host of predicates such as: (this one from Data.Maybe)
 
   isJust x
= case x of
  Just {} - True
  _   - False
 
 .. which is an approach that is obviously going to be tedious when the 
 size of the data type becomes large.
 
 --
 There is way to hack together a partial implementation of the ShallowEq 
 class within GHC, but it leaves much to be desired:
 
   instance Show a = ShallowEq a where
([EMAIL PROTECTED]) a b
  = (head $ words $ show a) == (head $ words $ show b)

Ouch!

 Questions:
   1) Does anyone know a better/existing way to implement ShallowEq that 
 doesn't involve enumerating all the constructors in the data type?
 
   2) If not, can anyone think of reasons why it wouldn't be a good idea 
 for GHC to derive ShallowEq (by expanding said enumeration)?

DriFT comes to mind:

   http://repetae.net/john/computer/haskell/DrIFT/

it already supplies some query operators that might make shallowEq
redundant. 

Cheers,
Bernie.

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


RE: [Haskell-cafe] Strict and non-strict vs eager and lazy, was C onfused about Cyclic struture

2005-07-19 Thread Bayley, Alistair
 From: Bernard Pope [mailto:[EMAIL PROTECTED] 
 
 I should have mentioned this paper:
 
 @article{Tremblay01,
   author=   {G. Tremblay},
   title={Lenient evaluation is neither strict nor lazy},
   journal=  {Computer Languages},
   volume=   {26},
   number=   {1},
   pages={43--66},
   year= {2001},
 }
 
 (however I think he says that Haskell is lazy!)


Thanks. Do you have a link to a free (beer) version? I don't have an ACM
subscription.

I found this related paper, which was useful:
How Much Non-strictness do Lenient Programs Require?
http://www.cs.ucsb.edu/~schauser/papers/95-fpca.ps


(unrelated) BTW, I found this, which sounds similar to the STM in GHC 6.4.
Again, does anyone have a link to a free version?

P. Tinker and M. Katz. Parallel execution of sequential Scheme with
ParaTran.
http://portal.acm.org/citation.cfm?doid=62678.62682


Alistair.

-
*
Confidentiality Note: The information contained in this   message, and any
attachments, may contain confidential   and/or privileged material. It is
intended solely for the   person(s) or entity to which it is addressed. Any
review,   retransmission, dissemination, or taking of any action in
reliance upon this information by persons or entities other   than the
intended recipient(s) is prohibited. If you received  this in error, please
contact the sender and delete the   material from any computer.
*

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


Re: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Henning Thielemann

On Tue, 19 Jul 2005, Ben Lippmeier wrote:

 An example, using some arbitrary data type Thingo:

   class ShallowEq a where
shallowEq  :: a - a - Bool

   data Thingo a b
  = TOne   a
  | TTwo   a b Int Char Float
  | TThree Int Char b b

 Questions:
   1) Does anyone know a better/existing way to implement ShallowEq that
 doesn't involve enumerating all the constructors in the data type?

A more general approach are projection functions like

getTOne :: Thingo a b - Maybe a
getTOne (TOne x) = Just x
getTOne _= Nothing

Then you can map the values to be compared into a Maybe and you need only
a shallowEq for Maybe.

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


RE: [Haskell-cafe] Strict and non-strict vs eager and lazy, was C onfused about Cyclic struture

2005-07-19 Thread Bernard Pope
On Tue, 2005-07-19 at 09:03 +0100, Bayley, Alistair wrote:
  From: Bernard Pope [mailto:[EMAIL PROTECTED] 
  
  I should have mentioned this paper:
  
  @article{Tremblay01,
author=   {G. Tremblay},
title={Lenient evaluation is neither strict nor lazy},
journal=  {Computer Languages},
volume=   {26},
number=   {1},
pages={43--66},
year= {2001},
  }
  
  (however I think he says that Haskell is lazy!)

 Thanks. Do you have a link to a free (beer) version? I don't have an ACM
 subscription.

No. I only have a paper copy lying around somewhere.

 I found this related paper, which was useful:
 How Much Non-strictness do Lenient Programs Require?
 http://www.cs.ucsb.edu/~schauser/papers/95-fpca.ps

I haven't read that. Thanks for the pointer. 

There was a discussion related to this topic on the types list a while
back.

Here is a link to the conclusion:

http://lists.seas.upenn.edu/pipermail/types-list/2004/000352.html

Bernie.

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


Re: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Bulat Ziganshin
Hello Ben,

Tuesday, July 19, 2005, 11:01:32 AM, you wrote:
BL I often find it useful to determine whether two objects are using the
BL same constructor, without worrying about the constructors' arguments.

BL There is way to hack together a partial implementation of the ShallowEq
BL class within GHC, but it leaves much to be desired:

BL   instance Show a = ShallowEq a where
BL([EMAIL PROTECTED]) a b
BL= (head $ words $ show a) == (head $ words $ show b)

reading GHC sources is always very interesting :)

that is from GHC/Base.hs :

%*
%*  *
[EMAIL PROTECTED]@}
%*  *
%*

Returns the 'tag' of a constructor application; this function is used
by the deriving code for Eq, Ord and Enum.

The primitive dataToTag# requires an evaluated constructor application
as its argument, so we provide getTag as a wrapper that performs the
evaluation before calling dataToTag#.  We could have dataToTag#
evaluate its argument, but we prefer to do it this way because (a)
dataToTag# can be an inline primop if it doesn't need to do any
evaluation, and (b) we want to expose the evaluation to the
simplifier, because it might be possible to eliminate the evaluation
in the case when the argument is already known to be evaluated.

\begin{code}
{-# INLINE getTag #-}
getTag :: a - Int#
getTag x = x `seq` dataToTag# x
\end{code}




-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


[Haskell-cafe] lazy Graphics, was - How to variables

2005-07-19 Thread Jake Luck



I need to write functions fast and efective. Math, heuristic, metadata
and expert systems are better in haskell. If I could use haskel from C,
I would do it. The problem are optimalizations, which are a critical
change in algorithm. Other (and me too) won't understand my concepts.
The speed and usability of Haskell is a good argument to use and learn it.


I can buy that. Well, one can actually call into Haskell from C.  It is less 
commonly done, but very possible.  Skim through the FFI addendum; you can 
export static functions (foreign export) or arbitrary thunks (with the 
confusingly named foreign import wrapper).  If you are real adventurous, 
you can tie directly into the GHC API from the C side as well (although I'm 
not sure I can seriously recommend this method).


Having said that, if you feel that Haskell has sufficient advantages to 
warrant its use, I don't think you lose much by writing your main loops etc. 
in Haskell as well, and I would recommend you go with the labeled record 
technique to contain your program state.


I too am working on a Haskell 3d renderer. However, my motivation is mostly 
inspired by Conal Elliott's Tbag and Vertigo projects. In my opinion, geometry, 
expressions and most 3d technologies fit naturally with the functional 
approach, like you said (math, heuristic, metadata and expert systems). 
Haskell's lazy execution is where I see opportunity for parallel optimization. 
Think about all the computed pixels and polygons that we throw away in our 
culling and clipping. Now if we can structure the system inside out  (do 
you see what I am getting at?) Having written several keyframe system, I feel 
that Fran's frameless timing approach is ingenious (Hudak's School of 
Expression book has an excellent section describing its motivation).


Though I am not without reservation in all of this, paying close attention to 
the graphics world, where things are progressively moving towards programmable 
hardware. IMO, Vertigo is a good example of a practical application using 
Haskell. I think that the division between where does functional stops and 
where imperative starts will be a key deciding factor in the performance 
feasability as well as adaptability for haskell software in the real graphics 
world. In other words, 1 million IORefs make me feel quite unsettled.


Anyone care to comment on the feasability of those hypothesis?

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


Re: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Remi Turk
On Tue, Jul 19, 2005 at 08:16:35PM +1000, Ben Lippmeier wrote:
 Bulat Ziganshin wrote:
 
 reading GHC sources is always very interesting :)
 that is from GHC/Base.hs :
 
 getTag :: a - Int#
 getTag x = x `seq` dataToTag# x
 
 ! This is just what I was looking for, thankyou.
 
 My shallowEq function is now simply:
 
 shallowEq :: a - a - Bool
 shallowEq a b = getTag a ==# getTag b
 
 My project is already totally reliant on GHC, and this will save me the 
 heartache of hacking DrIFT (which I was in the process of setting up 
 when I saw this mail) into my makefile.
 
 Portability be damned!
 
 Ben.

You might increase portability a bit by using

import Data.Generics

shallowEq :: Data a = a - a - Bool
shallowEq x y = toConstr x == toConstr y

it does introduce a dependency on Data though

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.


pgpyTyB9kylSx.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] matrix computations based on the GSL

2005-07-19 Thread Alberto Ruiz
Hello Bulat, thanks a lot for your message, the RULES pragma is just what we 
need!

However, in some initial experiments I have observed some strange behavior. 
For instance, in the following program:
 
-- 
{-# OPTIONS_GHC -fglasgow-exts #-}

apply :: (Int - Int) - Int - Int
apply f n = f n

sqr :: Int - Int
sqr n = n * n

optimized_sqr :: Int - Int 
optimized_sqr n = n*n+1 -- to check that the rule works :-)

{-# RULES
apply/sqrapply sqr = optimized_sqr
 #-}

main = do
--print $ apply sqr 3 
print $ apply sqr 5
-

The rule is not applied.

1 RuleFired
1 *#

if we uncomment the first line in the main function

main = do
print $ apply sqr 3 
print $ apply sqr 5 

then the rule is correctly applied:

6 RuleFired
2 *#
2 +#
2 apply/sqr

Solution: include at the beginning of the file

module Main
where

and then the rule works in both cases.

I have a similar problem in the LinearAlgebra library but there, curiously, 
the rule only works if it is applied once:

module Main 
where
import (...)
(...)
main = do 
 (...)
print $ Vector.map cos v
 --print $ Vector.map cos v

 Grand total simplifier statistics 
Total ticks: 2584

461 PreInlineUnconditionally
230 PostInlineUnconditionally
387 UnfoldingDone
91 RuleFired
2 *#
16 *##
5 +##
8 ++
5 -##
2 SPEC $fLinearArray1
2 SPEC $fLinearArray2
1 SPEC $fNumComplex
1 SPEC $fShowComplex
1 Vector.map/cos  --- OK
20 int2Double#
4 map
4 mapList
2 plusDouble 0.0 x
4 plusDouble x 0.0
2 timesDouble x 0.0
2 timesDouble x 1.0
3 unpack
3 unpack-list
2 zipWith
2 zipWithList
47 LetFloatFromLet
9 EtaReduction
1136 BetaReduction
6 CaseOfCase
217 KnownBranch
14 SimplifierDone

But:

(...)
main = do 
 (...)
print $ Vector.map cos v
 print $ Vector.map cos v

 Grand total simplifier statistics 
Total ticks: 2664

470 PreInlineUnconditionally
240 PostInlineUnconditionally
402 UnfoldingDone
90 RuleFired
2 *#
16 *##
5 +##
8 ++
5 -##
2 SPEC $fLinearArray1
2 SPEC $fLinearArray2
1 SPEC $fNumComplex
1 SPEC $fShowComplex
20 int2Double#
4 map
4 mapList
2 plusDouble 0.0 x
4 plusDouble x 0.0
2 timesDouble x 0.0
2 timesDouble x 1.0
3 unpack
3 unpack-list
2 zipWith
2 zipWithList
49 LetFloatFromLet
9 EtaReduction
1181 BetaReduction
5 CaseOfCase
218 KnownBranch
17 SimplifierDone

I have tried several ideas, without any luck. 

Alberto

On Monday 18 July 2005 10:14, Bulat Ziganshin wrote:
 Hello Alberto,

 Wednesday, July 13, 2005, 8:13:48 PM, you wrote:
 If there are no efficiency concerns, I would drop element-wise operations
 and prefer a matrix-map and a matrix-zipWith. If these operations shall
 remain I would somehow point to their element-wise operation in the name.

 AR There is about 5x speed gain if we map in the C side. The optimized
 floating AR map functions could be moved to a separate module.

 GHC also have a RULES pragma which can be used to automatically
 convert, for example, mmap (*) to multipleElementWise. below is
 examples of using this pragma in the standard GHC modules:

 {-# RULES
 foldr/idfoldr (:) []  = \x-x
 foldr/single  forall k z x. foldr k z [x] = k x z
 foldr/nil forall k z.   foldr k z []  = z
  #-}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Error with Float

2005-07-19 Thread Dinh Tien Tuan Anh


This is my function to convert a fraction (0x1) to binary :

  f x
 ¦t1= 0::f t
 ¦otherwise = 1::f (t-1)
 where t = 2*x


I guess there's nothing wrong with that, but when traced, it has something 
like 0.6*2 - 1 = 0.61
This error got accumulated and made my f function wrong (will eventually 
evaluate an infinite 0, no matter what value of x)


Please tell me there's some ways to deal with that.

Thanks a lot

_
Want to block unwanted pop-ups? Download the free MSN Toolbar now!  
http://toolbar.msn.co.uk/


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


RE: [Haskell-cafe] Error with Float

2005-07-19 Thread Dinh Tien Tuan Anh

Opps, its 0:f t
not 0:: f t
and the same for 1:f (t-1)




From: Dinh Tien Tuan Anh [EMAIL PROTECTED]
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Error with Float
Date: Tue, 19 Jul 2005 14:48:55 +


This is my function to convert a fraction (0x1) to binary :

  f x
 ¦t1= 0::f t
 ¦otherwise = 1::f (t-1)
 where t = 2*x


I guess there's nothing wrong with that, but when traced, it has something 
like 0.6*2 - 1 = 0.61
This error got accumulated and made my f function wrong (will eventually 
evaluate an infinite 0, no matter what value of x)


Please tell me there's some ways to deal with that.

Thanks a lot

_
Want to block unwanted pop-ups? Download the free MSN Toolbar now!  
http://toolbar.msn.co.uk/


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


_
Want to block unwanted pop-ups? Download the free MSN Toolbar now!  
http://toolbar.msn.co.uk/


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


Re: [Haskell-cafe] Error with Float

2005-07-19 Thread Cale Gibbard
Perhaps you mean:
f x
| x  1 = 0 : f (2*x)
| otherwise = 1 : f (2*(x-1))

Note that in the second case, the 1 is subtracted before multiplication by 2.

If you were referring to the problem that this eventually gives
constantly 0 for values like 0.6, try importing the Ratio module and
applying it to 6%10, which is the exact rational value rather than a
floating point representation.

 - Cale

On 19/07/05, Dinh Tien Tuan Anh [EMAIL PROTECTED] wrote:
 
 This is my function to convert a fraction (0x1) to binary :
 
f x
   ¦t1= 0::f t
   ¦otherwise = 1::f (t-1)
   where t = 2*x
 
 
 I guess there's nothing wrong with that, but when traced, it has something
 like 0.6*2 - 1 = 0.61
 This error got accumulated and made my f function wrong (will eventually
 evaluate an infinite 0, no matter what value of x)
 
 Please tell me there's some ways to deal with that.
 
 Thanks a lot
 
 _
 Want to block unwanted pop-ups? Download the free MSN Toolbar now!
 http://toolbar.msn.co.uk/
 
 ___
 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] Error with Float

2005-07-19 Thread Dinh Tien Tuan Anh

Here's what i got



writeln x = putStr (x++ \n)


f:: Double - IO Double
f x = do
   let t = 2*x
   if (t1)
then return t
else return (t-1)


gen :: Double - IO()
gen x = do c-f x
   writeln (Value  is:  ++ show c)
   if (c /= 0.0)
then  gen c
else  return ()






Main gen 0.1
Value  is: 0.2
Value  is: 0.4
Value  is: 0.8
Value  is: 0.6
Value  is: 0.2
Value  is: 0.4
Value  is: 0.801
Value  is: 0.601
Value  is: 0.203
Value  is: 0.406
Value  is: 0.811
Value  is: 0.623
Value  is: 0.245
Value  is: 0.491
Value  is: 0.8000182
Value  is: 0.6000364
Value  is: 0.2000728
Value  is: 0.4001455
Value  is: 0.800291
Value  is: 0.6005821
Value  is: 0.2011642
Value  is: 0.4023283
Value  is: 0.8046566
Value  is: 0.6093132
Value  is: 0.2186265
Value  is: 0.4372529
Value  is: 0.8745058
Value  is: 0.60001490116
Value  is: 0.20002980232
Value  is: 0.40005960464
Value  is: 0.80011920929
Value  is: 0.60023841858
Value  is: 0.20047683716
Value  is: 0.40095367432
Value  is: 0.80190734863
Value  is: 0.60381469727
Value  is: 0.20762939453
Value  is: 0.41525878906
Value  is: 0.83051757813
Value  is: 0.66103515625
Value  is: 0.20001220703125
Value  is: 0.4000244140625
Value  is: 0.800048828125
Value  is: 0.60009765625
Value  is: 0.2001953125
Value  is: 0.400390625
Value  is: 0.80078125
Value  is: 0.6015625
Value  is: 0.203125
Value  is: 0.40625
Value  is: 0.8125
Value  is: 0.625
Value  is: 0.25
Value  is: 0.5
Value  is: 0.0







From: Cale Gibbard [EMAIL PROTECTED]
Reply-To: Cale Gibbard [EMAIL PROTECTED]
To: Dinh Tien Tuan Anh [EMAIL PROTECTED]
CC: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Error with Float
Date: Tue, 19 Jul 2005 11:00:34 -0400

Perhaps you mean:
f x
| x  1 = 0 : f (2*x)
| otherwise = 1 : f (2*(x-1))

Note that in the second case, the 1 is subtracted before multiplication by 
2.


If you were referring to the problem that this eventually gives
constantly 0 for values like 0.6, try importing the Ratio module and
applying it to 6%10, which is the exact rational value rather than a
floating point representation.

 - Cale



_
Winks  nudges are here - download MSN Messenger 7.0 today! 
http://messenger.msn.co.uk


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


Re: [Haskell-cafe] How to variables

2005-07-19 Thread robert dockins

Some people may suggest that you to create top-level IORefs using
unsafePerformIO, but I don't recommend that for this situation.



Well I can't imagine which particular people you have in mind :-)

But, as a vocal advocate of sound support for top level mutable
state, I would just like to go on record as saying I certainly
would not advocate it for this problem.

But then again, I wouldn't advocate the use of explicit entire
program state record passing either :-)


Fair enough.  The main reason I suggested it is a fairly painless way to 
emulate global variables within a main control loop, which was the OPs 
stated goal.  (it's important to implement it in as most imperative 
form as possible...)


I would personally attempt to adopt a more functional way of approaching 
the problem (Arrows and whatnot), but those are still pretty murky waters.


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


[Haskell-cafe] Re: How to variables/O'Haskell

2005-07-19 Thread Donn Cave
On Tue, 19 Jul 2005, robert dockins wrote:
[ ... re explicit entire program state record passing ... ]

 Fair enough.  The main reason I suggested it is a fairly painless way to 
 emulate global variables within a main control loop, which was the OPs 
 stated goal.  (it's important to implement it in as most imperative 
 form as possible...)
 
 I would personally attempt to adopt a more functional way of approaching 
 the problem (Arrows and whatnot), but those are still pretty murky waters.

Bummer.  It's as simple and obvious as it could be in O'Haskell,
which as I understand it basically packages up your record of IORefs,
in its reactive object.  The I/O event driven execution model seems
meant for problems like this, too.  I hope if the links people ever
spawn a new FP language and it's anything like Haskell, they'll take
an approach somewhat like this and leave the Haskell world fumbling
around with its Arrows and whatnot.

But, to try to answer the recent question about O'Haskell, I wouldn't
expect it to serve very well as a bridge to OO languages.  There are
some OO elements, but for example if you read to the bottom of
http://www.cs.chalmers.se/~nordland/ohaskell/survey.html, there are
also some significant omissions.  For example, he doesn't use this
phrase, but I think there's no open recursion.  I can't imagine
using this language's OO features in a C++ toolkit wrapper.  But I
never tried it, and it might be an interesting demonstration project.

Donn Cave, [EMAIL PROTECTED]

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


[Haskell-cafe] Named data type members

2005-07-19 Thread yin
Hello,

I've a data type:

data SomeData =
SomeData {
int1 :: Int,
int2 :: Int
}
   
class SomeClass where
   infix 1 `i_`
   i_ :: SomeData - Int - SomeData
   infix 1 `_i`
   _i :: SomeData - Int - SomeData
   
instance SomeClass SomeData where
   (SomeData int1 int2) `i_` i = SomeData (int1 + i) int2
   (SomeData int1 int2) `_i` i = SomeData int1 (int2 + i)

1.  Possible optimalizations ...?
2.  There are several data type members in 'SomeData' and I wish to
access them in other way then (SomeData m1 m2 m3 m4 m5 ... m100) `a` i
= SomeData (m1 + i) m2 m3 ... m100
3a. The 'SomeData' is something like c structure, which holds all
application data. One instanciated variable is passed in more functions
to each other:

-- SomeData is now very complex
initsomeData :: SomeData
initsomeData = do
var1 - init...
...
SomeData 0 0 0 1 1 True False (-1) var1 var2 ...
   
main = do p - initAplication
   processEvents p
   
-- First Function
processEvents :: SomeData - IO ()
processEvents p = do
   event - pollEvent
   case event of
  Event1 - do
 processEvents (SomeData v1 v2 v3 (v4*2) ... v100)
  Event2 - do
 processEvents (SomeData v1 ... False ... v100)
  Event2' - do
 processEvents (SomeData v1 ... True ... v100)
  EventQuit - do
 return ()
  NoMoreEvents - do computeNext p
  _ - processEvents p
   where (SomeData v1 v2 v3 v4 v5 ... v100) = p
   
-- An time based function
computeNextStep = do
timeDelta - getTimeDelta
let
i1' = compute1 i1 i2 i3 ... i50
i2' = compute2 i1 i2 i3 ... i50
   ...
   if (condition) then
  -- need more computing
  computeNextStep (SomeData u1 u2 ... u50 i1 i2 ... i50)
   else do
  p' - (SomeData u1 u2 ... u50 i1 i2 ... i50)
  draw p'
  processEvents p'
   where (SomeData u1 u2 ... u50 i1 i2 ... i50) = p
-- ux - uninteresting (State variables, like left-key-down
was last left-key related event: move left)
-- ix - interesting for computing
-- where x = 1, 2 ... 50
...
...
3b. every funtion needs only a part of the data... can I build for every
fintion a class with defined operators to manipulate with the data and then:
* pass the variable in func1 known as class A to func2, which is
infering a class B?

Thank you all...

Matej 'Yin' Gagyi

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


Re: [Haskell-cafe] Error with Float

2005-07-19 Thread Dinh Tien Tuan Anh


So there's no way to get exact stream that represents a fraction, such as:
.5 = .1
.2 = .00110011001100110011


???



From: Udo Stenzel [EMAIL PROTECTED]
To: Dinh Tien Tuan Anh [EMAIL PROTECTED]
Subject: Re: [Haskell-cafe] Error with Float
Date: Tue, 19 Jul 2005 20:51:14 +0200

 Value  is: 0.801

What did you expect?  Floating point numbers are inexact by their very
nature.  Since 0.8, like many other numbers, is not representable
exactly in binary, (10 * 0.8 - 8) will certainly not be zero.

Take a course in numerical mathematics some time.  It helps.


Udo.
--
HTML needs a rant tag.  -- Alan Cox
 signature.asc 


_
It's fast, it's easy and it's free. Get MSN Messenger 7.0 today! 
http://messenger.msn.co.uk


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


Re: [Haskell-cafe] IO Monad

2005-07-19 Thread yin
Dinh Tien Tuan Anh wrote:


 Hi,
 Could anyone explain for me why its not possible to return a primitive
 type (such as Integer, String) while doing some IO actions ?

 e.g: foo :: IO() - String

 What does it have to do with lazy evalution paradigm ?

In short, to not break functional aproach. Non-IO functions can't call
IO functions, because IO functions are evaluated every time you call them.

Matej 'Yin' Gagyi

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


Re: [Haskell-cafe] Error with Float

2005-07-19 Thread Cale Gibbard
To get exact fractions, use the Ratio module (import Ratio) and the
Rational type which is defined there.

The code you wrote below has a serious style problem that I thought
I'd point out: you shouldn't use the IO monad for pure functions. You
can define f as follows:

f x = let t = 2 * x 
  in if t  1
  then t
  else t - 1

or with guards:

f x | t  1 = t
| otherwise = t - 1
   where t = 2 * x

Note that there isn't any problem with using pure functions from the
IO monad. You can write gen as follows:

gen :: Double - IO ()
gen x | c == 0.0 = return ()
  | otherwise = do putStrLn $ Value is:  ++ show c; gen c
   where c = f x

(writeln is called putStrLn in the standard prelude)

Or syntactically closer to your original code:

gen :: Double - IO ()
gen x = do let c = f x
   putStrLn (Value  is:  ++ show c)
   if (c /= 0.0)
then gen c
else return ()

You don't use the c - f x notation because (f x) is directly the
value you want, not an IO action which executes to produce that value.

So long as you don't put a type signature on it (causing it to get
inferred), or if you give it the type signature:
f :: (Num a, Ord a) = a - a
it will work with any ordered type of numbers, which allows you to
load up the Ratio module in ghci (:m + Ratio) and try it with things
like 1%3 (which represents one-third exactly).

Hope this is useful,
 - Cale

On 19/07/05, Dinh Tien Tuan Anh [EMAIL PROTECTED] wrote:
 Here's what i got
 
 writeln x = putStr (x++ \n)
 
 f:: Double - IO Double
 f x = do
 let t = 2*x
 if (t1)
 then return t
 else return (t-1)
 
 
 gen :: Double - IO()
 gen x = do c-f x
writeln (Value  is:  ++ show c)
if (c /= 0.0)
 then  gen c
 else  return ()
 
-snip-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error with Float

2005-07-19 Thread Josh Hoyt
On 7/19/05, Cale Gibbard [EMAIL PROTECTED] wrote:
 The code you wrote below has a serious style problem that I thought
 I'd point out: you shouldn't use the IO monad for pure functions. You
 can define f as follows:
 [snip]

I agree on the stylistic front. Another approach is to make the
generator function return the list of values.

gen :: Double - [Double]
gen x = (takeWhile (/= 0.0) $ iterate f x) ++ [0.0]
where f x = let t = 2 * x in if t  1 then t else t-1

showSteps :: [Double] - [String]
showSteps xs = map showStep $ zip [1..] xs
where showStep (n, x) = (show n) ++ . Value is:  ++ (show x)

iogen :: Double - IO ()
iogen x = mapM_ putStrLn $ showSteps $ gen x

I added the ++ [0.0] to gen so that it will generate the same list as
the original version.

To illustrate the generality of the floating-point inexactness
problem, I added the step numbering to compare with another
programming language. In Python:

def gen(x, n=1):
t = x * 2.
if t  1.:
c = t
else:
c = t - 1
print '%d. Value is: %.16f' % (n, c)
if c != 0:
gen(c, n + 1)

Both programs terminate in the same number of steps, since their
floating-point types have the same underlying implementation. Python
has no Rational type to fall back on, however.

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


RE: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Ralf Lammel
As Bulat points out, the GHC primitive dataToTag#
indeed nicely solves the problem. Ben, just for
completeness' sake; with SYB, you get such reflective
information too (and others):

shallowEq :: Data a = a - a - Bool
shallowEq x y = toConstr x == toConstr y

(dataToTag# returns Int, while toConstr comprises other things like the
constructor name.)

Regards,
Ralf

 -Original Message-
 From: [EMAIL PROTECTED] [mailto:haskell-cafe-
 [EMAIL PROTECTED] On Behalf Of Bulat Ziganshin
 Sent: Tuesday, July 19, 2005 1:18 AM
 To: Ben Lippmeier
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Proposal: deriving ShallowEq?
 
 Hello Ben,
 
 Tuesday, July 19, 2005, 11:01:32 AM, you wrote:
 BL I often find it useful to determine whether two objects are using
the
 BL same constructor, without worrying about the constructors'
arguments.
 
 BL There is way to hack together a partial implementation of the
 ShallowEq
 BL class within GHC, but it leaves much to be desired:
 
 BL   instance Show a = ShallowEq a where
 BL([EMAIL PROTECTED]) a b
 BL= (head $ words $ show a) == (head $ words $ show b)
 
 reading GHC sources is always very interesting :)
 
 that is from GHC/Base.hs :
 
 %*
 %*  *
 [EMAIL PROTECTED]@}
 %*  *
 %*
 
 Returns the 'tag' of a constructor application; this function is used
 by the deriving code for Eq, Ord and Enum.
 
 The primitive dataToTag# requires an evaluated constructor application
 as its argument, so we provide getTag as a wrapper that performs the
 evaluation before calling dataToTag#.  We could have dataToTag#
 evaluate its argument, but we prefer to do it this way because (a)
 dataToTag# can be an inline primop if it doesn't need to do any
 evaluation, and (b) we want to expose the evaluation to the
 simplifier, because it might be possible to eliminate the evaluation
 in the case when the argument is already known to be evaluated.
 
 \begin{code}
 {-# INLINE getTag #-}
 getTag :: a - Int#
 getTag x = x `seq` dataToTag# x
 \end{code}
 
 
 
 
 --
 Best regards,
  Bulatmailto:[EMAIL PROTECTED]
 
 
 
 ___
 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] Proposal: deriving ShallowEq?

2005-07-19 Thread Ben Lippmeier

Ralf Lammel wrote:

As Bulat points out, the GHC primitive dataToTag#
indeed nicely solves the problem. Ben, just for
completeness' sake; with SYB, you get such reflective
information too (and others):

shallowEq :: Data a = a - a - Bool
shallowEq x y = toConstr x == toConstr y

(dataToTag# returns Int, while toConstr comprises other things like the
constructor name.)



Ralf,
Yes, I ended up using the propper SYB approach instead, though I have 
noticed that the reflection data types Constr and DataRep make no 
mention of type variables or functions.


For example, this works fine:
 getTag (Just 5)   ==# getTag (Just{})
 getTag (Just (\x - x))   ==# getTag (Just{})

But this does not
 toConstr (Just 5) == toConstr (Just{})
Ambiguous type variables.

 toConstr (Just (\x - x)) == toConstr (Just{})
No instance for Data (t - t)

I appreciate the reasons why this is so, though I think it's interesting 
to see the practical consequences.


A toConstr version of shallowEq works ok so long as you provide a type 
signature to constrain both arguments to be the same type, and one of 
them is always fully constructed - which is fine for me at the moment.


Ben.


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