Recompiling doesn't notice re-exports being removed

2005-07-19 Thread Ian Lynagh
Recompiling doesn't notice re-exports being removed: $ cat A.hs module A where foo :: Int foo = 4 $ cat B.hs module B (foo) where import A (foo) $ cat C.hs module Main (main) where import B (foo) main :: IO () main = print foo $ ghc --make C -o c Chasing modules from: C Compiling A

RE: Problem building GHC

2005-07-19 Thread Simon Marlow
On 18 July 2005 17:29, Dinko Tenev wrote: On 7/18/05, Simon Marlow [EMAIL PROTECTED] wrote: That's the general rule, anyway. It would be an interesting exercise to specify the GHC command-line semantics, or better still, redesign it :) I for one would find it quite helpful to see a

[Haskell] combining IntMaps

2005-07-19 Thread Scherrer, Chad
Title: combining IntMaps I'm using the (IntMap Int) type to implement functions (Int - Int), by treating non-keys as values that map to zero. I'd like to be able to add two of these pointwise, and delete the key from the resulting map when the sum of the values is zero. My specification is

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

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

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

[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 |

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 {|

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

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},

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

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=

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

[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

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

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

[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

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

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

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

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

[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

[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

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

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.

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

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

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

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#