Re: [Haskell-cafe] Small question

2007-08-09 Thread Stefan O'Rear
On Fri, Aug 10, 2007 at 02:28:09PM +0800, Hugh Perkins wrote: > On 8/10/07, Stefan O'Rear <[EMAIL PROTECTED]> wrote: > > > > Haskell's purpose: To be a generally cool language > > Haskell's competition: C++, SML, ... hundreds of thousands more and I make > > no assertion of a representative sample

Re: [Haskell-cafe] Small question

2007-08-09 Thread Donald Bruce Stewart
hughperkins: > You'll find by the way that the imperative >GC'd, stack/heap protected languages run *significantly* >faster for many (not all I guess?) algorithms and >applications. Wow. Big claims. It must be silly hat day on the Haskell lists. We're trying hard

Re: [Haskell-cafe] Small question

2007-08-09 Thread Thomas Conway
On 8/10/07, Hugh Perkins <[EMAIL PROTECTED]> wrote: > On 8/10/07, Stefan O'Rear <[EMAIL PROTECTED]> wrote: > > Haskell's purpose: To be a generally cool language > > Haskell's competition: C++, SML, ... hundreds of thousands more and I make > no assertion of a representative sample ... > > > > Well

Re: [Haskell-cafe] Small question

2007-08-09 Thread Hugh Perkins
On 8/10/07, Stefan O'Rear <[EMAIL PROTECTED]> wrote: > > Haskell's purpose: To be a generally cool language > Haskell's competition: C++, SML, ... hundreds of thousands more and I make > no assertion of a representative sample ... > Well, C++ is not really competitive with Haskell, because C++ doe

Re: [Haskell-cafe] Small question

2007-08-09 Thread Andrew Coppin
Stefan O'Rear wrote: I like pretty pictures. ...and have lots of spare time, apparently. ;-) [I actually meant to write (Bool,Bool), but anyway...] Whereas my Quad object is going to be a pointer to one of 4 values... so it looks like Quads save space. (And they're more strict.) OTOH, I'

Re: [Haskell-cafe] Small question

2007-08-09 Thread Stefan O'Rear
On Fri, Aug 10, 2007 at 02:08:42PM +0800, Hugh Perkins wrote: > On 8/10/07, Stefan O'Rear <[EMAIL PROTECTED]> wrote: > > > > Good idea! Maybe it could be fit into the GHC Performance Resource > > somehow? (http://www.haskell.org/haskellwiki/Performance/GHC) > > > > >From the wiki: "Since GHC

Re: [Haskell-cafe] Small question

2007-08-09 Thread Hugh Perkins
On 8/10/07, Stefan O'Rear <[EMAIL PROTECTED]> wrote: > > Good idea! Maybe it could be fit into the GHC Performance Resource > somehow? (http://www.haskell.org/haskellwiki/Performance/GHC) > >From the wiki: "Since GHC doesn't have any credible competition

Re: [Haskell-cafe] Small question

2007-08-09 Thread Stefan O'Rear
On Thu, Aug 09, 2007 at 11:09:36PM -0400, [EMAIL PROTECTED] wrote: > Quoting Stefan O'Rear <[EMAIL PROTECTED]>: > > In general, GHC doesn't do "unboxing". Instead it has a simpler and > > more general approach, [...] > > I'm not convinced that the phrase "more general" is appropriate here. :-) No

Re[2]: [Haskell-cafe] Small question

2007-08-09 Thread Bulat Ziganshin
Hello John, Friday, August 10, 2007, 5:15:56 AM, you wrote: > data Quad = BL | BR | TL | TR > under jhc (and probably ghc at some point in the future) there is another > very strong advantage to the second one, since it is an enumerated type, > internally it can be represented by a simple unboxe

[Haskell-cafe] Typeclasses and implicit parameters

2007-08-09 Thread ajb
{-# OPTIONS -fglasgow-exts #-} -- G'day everyone. -- This is okay. f1 :: (?foo :: String) => String f1 = ?foo -- So is this. f2 :: (Show a, ?foo :: a) => a -> String f2 _ = show ?foo -- Hugs allows this. GHC rejects it on the grounds that "a" is unused -- on the right-hand side of the (=>). I

Re: Re[4]: [Haskell-cafe] In-place modification

2007-08-09 Thread Hugh Perkins
On 7/15/07, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote: > > Oh, and I forgot you count up by two now. Here's the Haskell > transliteration (again). > > > {-# OPTIONS -O2 -optc-O -fbang-patterns #-} > > import Control.Monad.ST > import Data.Array.ST > import Data.Array.Base >

Re: [Haskell-cafe] Dynamic thread management?

2007-08-09 Thread Hugh Perkins
On 8/10/07, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote: > > Perhaps have a look at this new paper: > > "Feedback directed implicit parallelism in Haskell" > http://research.microsoft.com/~tharris/papers/2007-fdip.pdf > > -- Don > Ok interesting. So: it's a viable strategy, it's sortof

Re: [Haskell-cafe] Dynamic thread management?

2007-08-09 Thread Donald Bruce Stewart
hughperkins: > >Haskell/FP seems to have solved the hardest bit of >threading, which is making it obvious which bits of a >program are parallelizable, and which are not. >Remains to actually parallelize out the programs. Am I >being naive or is this trivial? >Is there som

[Haskell-cafe] Dynamic thread management?

2007-08-09 Thread Hugh Perkins
Haskell/FP seems to have solved the hardest bit of threading, which is making it obvious which bits of a program are parallelizable, and which are not. Remains to actually parallelize out the programs. Am I being naive or is this trivial? There has been a lot of talk about parallelizing out a pr

Re: [Haskell-cafe] Pure functional GUI

2007-08-09 Thread Hugh Perkins
Another way to get glade on Windows is to download mono, which contains both gtk and glade. One advantage of getting it this way is you then have mono at your disposal for benchmarking ghc ;-) (Not that you'd benchmark a gui app, but it seems there are many people who still think that comparing ha

Re: [Haskell-cafe] where to put handy functions?

2007-08-09 Thread Donald Bruce Stewart
rk: > On 8/9/07, Chad Scherrer <[EMAIL PROTECTED]> wrote: > > Is there process for submitting functions for consideration for > > inclusion into future versions of the standard libraries? For example, > > I'd like to see this in Data.List: > > I imagine including it in std lib takes a while. Would

Re: [Haskell-cafe] where to put handy functions?

2007-08-09 Thread Rahul Kapoor
On 8/9/07, Chad Scherrer <[EMAIL PROTECTED]> wrote: > Is there process for submitting functions for consideration for > inclusion into future versions of the standard libraries? For example, > I'd like to see this in Data.List: I imagine including it in std lib takes a while. Would it be a good id

Re: [Haskell-cafe] Small question

2007-08-09 Thread ajb
G'day all. Quoting Stefan O'Rear <[EMAIL PROTECTED]>: > In general, GHC doesn't do "unboxing". Instead it has a simpler and > more general approach, [...] I'm not convinced that the phrase "more general" is appropriate here. :-) > As far as actual heap usage goes, GHC creates single static val

Re: [Haskell-cafe] where to put handy functions?

2007-08-09 Thread ok
On 10 Aug 2007, at 9:37 am, Stefan O'Rear wrote: http://www.haskell.org/haskellwiki/Library_submissions I'd like to ask if it's possible to add expm1 and log1p to the Floating class: class ... Floating a where ... exp, log, sqrt :: a -> a expm1, lop1p:: a -> a-

Re: [Haskell-cafe] Re: Re: a regressive view of support for imperative programming in Haskell

2007-08-09 Thread David Menendez
On 8/9/07, Benjamin Franksen <[EMAIL PROTECTED]> wrote: > David Menendez wrote: > > There is also RHaskell, which implements an O'Haskell-like system as a > > Haskell library. > > > > > > Thanks for the pointer, I didn't know about this. Will t

Re: [Haskell-cafe] a regressive view of support for imperative programming in Haskell

2007-08-09 Thread ok
On 10 Aug 2007, at 6:42 am, David Roundy wrote: do x1 <- e1 if x1 then do x2 <- e2 xx <- if x2 then e3 else do x4 <- e4 x5 <- e5 e6 x4 x5 e7 xx x1 e

Re: [Haskell-cafe] Small question

2007-08-09 Thread John Meacham
On Thu, Aug 09, 2007 at 06:37:32PM +0100, Andrew Coppin wrote: > Which of these is likely to go faster? > type Quad = (Bool,Bool) ... > data Quad = BL | BR | TL | TR ... > I'm hoping that the latter one will more more strict / use less space. > But I don't truely know... The second one will be

Re: [Haskell-cafe] Matters of precision

2007-08-09 Thread ajb
G'day. Quoting Andrew Coppin <[EMAIL PROTECTED]>: > First of all, currently I'm just using Double to represent coordinates. > Can anybody tell me what the smallest value you can represent with one > is? (Not including denormals.) Remember that floating point numbers are stored in three parts. T

Re: [Haskell-cafe] a regressive view of support for imperative programming in Haskell

2007-08-09 Thread Brandon Michael Moore
On Thu, Aug 09, 2007 at 11:52:17AM -0700, David Roundy wrote: > On Thu, Aug 09, 2007 at 02:08:20PM +0100, Jules Bean wrote: *snip* > > A third example is with nested dos: > > > > do x <- bar y > >baz > >something $ do foo x > > > > is not the same as > > > > do baz > >something $

Re: [Haskell-cafe] can't build haxml under ghc 6.7, says HughesPJ is hidden... but ghc-pkg doesn't say it's hidden...

2007-08-09 Thread Stefan O'Rear
On Thu, Aug 09, 2007 at 06:40:47PM -0400, Thomas Hartman wrote: > Can I get some help building HaXml (from hackage) under ghc 6.7? > > I'm hoping to get HAppS running under 6.7, and use the new debugger to > better understand what's going on under the hood. Eg, when I'm in the h > function, I c

[Haskell-cafe] can't build haxml under ghc 6.7, says HughesPJ is hidden... but ghc-pkg doesn't say it's hidden...

2007-08-09 Thread Thomas Hartman
Can I get some help building HaXml (from hackage) under ghc 6.7? I'm hoping to get HAppS running under 6.7, and use the new debugger to better understand what's going on under the hood. Eg, when I'm in the h function, I can take a look at the args and just see what types they are. (I am findin

Re: [Haskell-cafe] Small question

2007-08-09 Thread Stefan O'Rear
On Thu, Aug 09, 2007 at 10:19:59PM +0100, Andrew Coppin wrote: > Right. So a Bool is a 32 or 64 bit quantity. (Rather like Smalltalk...) > > That presumably means that a (Double,Double) is going to be a thunk that > evaluates to a (,) pointing to two thunks that evaluate to pointers... IOW, > som

RE: [Haskell-cafe] Re: Re: a regressive view of support for imperative programming in Haskell

2007-08-09 Thread Simon Peyton-Jones
There's been lots of interesting stuff on this thread. Does anyone feel up to summarizing it on a Wiki page, for others to polish? At least part of that page should comprise a compact specification of what the (<- ) proposal is; but there have been lots of other suggestions. Otherwise it'll a

Re: [Haskell-cafe] where to put handy functions?

2007-08-09 Thread Brent Yorgey
On 8/9/07, Chad Scherrer <[EMAIL PROTECTED]> wrote: > > > extract :: [Int] -> [a] -> [a] > extract = f 0 > where > f _ _ [] = [] > f _ [] _ = [] > f k nss@(n:ns) (x:xs) = if n == k then x:f (k+1) ns xs > else f (k+1) nss xs > > This behaves roughly as > e

Re: [Haskell-cafe] where to put handy functions?

2007-08-09 Thread Stefan O'Rear
On Thu, Aug 09, 2007 at 02:29:50PM -0700, Chad Scherrer wrote: > Is there process for submitting functions for consideration for > inclusion into future versions of the standard libraries? For example, > I'd like to see this in Data.List: > > extract :: [Int] -> [a] -> [a] > extract = f 0 > wh

RE: [Haskell-cafe] Problem with question 3 about knights and knaves onw ikipedia

2007-08-09 Thread Peter Verswyvelen
Indeed, I missed that. This rules out the first answer is "no" But I still keep the 3 other solutions then :( >("John is a knight","Bill is a knight","Yes","No ") >("John is a knave ","Bill is a knight","Yes","Yes") >("John is a knave ","Bill is a knave ","Yes","No ") Any more help (or just the

Re: [Haskell-cafe] Pure functional GUI

2007-08-09 Thread Radosław Grzanka
2007/8/9, Peter Verswyvelen <[EMAIL PROTECTED]>: > Yeah I tried that one, but only the runtime, because I assumed that glade > would be part of it, but I could not find it. I guess I should install the > development version. Windows users look differently at these things, they > expect all tools

[Haskell-cafe] where to put handy functions?

2007-08-09 Thread Chad Scherrer
Is there process for submitting functions for consideration for inclusion into future versions of the standard libraries? For example, I'd like to see this in Data.List: extract :: [Int] -> [a] -> [a] extract = f 0 where f _ _ [] = [] f _ [] _ = [] f k nss@(n:ns) (x:xs) = if n == k

Re: [Haskell-cafe] Problem with question 3 about knights and knaves onw ikipedia

2007-08-09 Thread Steve Schafer
On Thu, 9 Aug 2007 23:06:04 +0200, you wrote: >Is still don't get it completely... Could you give me an extra hint? I'm >getting crazy here, especially because I was really good at this stuff 20 >years ago! :) > >Here's the reasoning > >The first answer could not be "no" because from that I can in

Re: [Haskell-cafe] Pure functional GUI

2007-08-09 Thread Andrew Coppin
Radosław Grzanka wrote: The google knows?? http://gladewin32.sourceforge.net/modules/news/ Ah - most optimal... Now finally I can try Glade. :-D ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskel

Re: [Haskell-cafe] Small question

2007-08-09 Thread Andrew Coppin
Stefan O'Rear wrote: On Thu, Aug 09, 2007 at 09:27:23PM +0100, Andrew Coppin wrote: OOC, in what way is Bool not "primitive enough"? You mean because it's an algebraic data type, rather than a bunch of bits in the machine? For that matter, just how much space does such a type typically use?

RE: [Haskell-cafe] Pure functional GUI

2007-08-09 Thread Peter Verswyvelen
Yeah I tried that one, but only the runtime, because I assumed that glade would be part of it, but I could not find it. I guess I should install the development version. Windows users look differently at these things, they expect all tools to be precompiled ;) I'll try again and dig deeper. --

Re: [Haskell-cafe] Small question

2007-08-09 Thread Stefan O'Rear
On Thu, Aug 09, 2007 at 09:27:23PM +0100, Andrew Coppin wrote: > OOC, in what way is Bool not "primitive enough"? You mean because it's an > algebraic data type, rather than a bunch of bits in the machine? For that > matter, just how much space does such a type typically use? Yes. data Bool = F

[Haskell-cafe] Re: Re: a regressive view of support for imperative programming in Haskell

2007-08-09 Thread Benjamin Franksen
David Roundy wrote: > On Thu, Aug 09, 2007 at 08:45:14PM +0200, Benjamin Franksen wrote: >> David Roundy wrote: >> > Several times since reading the beginning of this discussion I've wished I >> > had the new syntax so I could write something like: >> > >> > do if predicateOnFileContents (<- rea

Re: [Haskell-cafe] Small question

2007-08-09 Thread Andrew Coppin
Stefan O'Rear wrote: On Thu, Aug 09, 2007 at 07:12:12PM +0100, Sebastian Sylvan wrote: {-#OPTIONS -funbox-strict-fields #-} data Quad = Quad !Bool !Bool foo True True = ... foo True False = ... etc... The GHC option just causese GHC to unbox primitive types when they're strict in the

Re: [Haskell-cafe] Pure functional GUI

2007-08-09 Thread Radosław Grzanka
2007/8/9, Peter Verswyvelen <[EMAIL PROTECTED]>: > > Indeed - the *hard* part seems to be figuring out how to run Glade on > Windoze... > > I did not dare to ask this question because I could not believe this was > hard... So anybody know how to do this? Run Glade on Window$? The google knows?? ht

[Haskell-cafe] Explaining monads

2007-08-09 Thread Brian Brunswick
(Better view the below in a fixed-width font!) With all the recent monad discussions, I embarked on trying to clarify my own thoughts about them, and started to think about things in terms of just /where/ extra structure is 'understood'. I think I can explain why 'a->IO b' is better than 'IO a->b

[Haskell-cafe] Haskell DB tutorial link is broken.

2007-08-09 Thread Edward Ing
Hi, The following link is broken. http://www.haskell.org/hawiki/HaskellDbTutorial Edward Ing ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Re: a regressive view of support for imperative programming in Haskell

2007-08-09 Thread Benjamin Franksen
David Menendez wrote: > On 8/9/07, Benjamin Franksen <[EMAIL PROTECTED]> wrote: >> Donn Cave wrote: >> > (I have a soft spot for O'Haskell, but >> > alas I must be nearly alone on that.) >> >> You are /not/ alone :-) I always found it very sad that O'Haskell and also >> its sucessor Timber (with al

Re: [Haskell-cafe] how can I get template haskell macro-expanded code from inferStartState? (repeated post, now with subject)

2007-08-09 Thread Thomas Hartman
I would say both. The stuff under Examples in the repo should all run with 8.8. (I think currently it doesn't.) The stuff in the wiki should say what is 8.8, what is 8.4, and obviously also give examples that work. The advantage of the wiki is you can make a change that propogates to the comm

Re: [Haskell-cafe] Derivation of Eq given Ord

2007-08-09 Thread Andreas Marth
I have to admit that I didn't test it before my first response. But now I did and can verify that it in deed "it does relay an error from deriving module to using [module/ghci]". So if I don't do any comparisons on Ego everything succeeds. If there is any comparision then ghc (6.6 in my case) retur

Re: [Haskell-cafe] New Eq instance

2007-08-09 Thread Miguel Mitrofanov
rb> data Step = Step Id Scenario Action State Response rb> instance Eq Step where rb> Step id1 scenario1 action1 state1 response1 == Step id2 rb> scenario2 action2 state2 response2 = id == id rb> _ == _ = False "id == id" must be replaced with "id1 == id2". Error message you've got might be

Re: [Haskell-cafe] Slow IO or bad code?

2007-08-09 Thread Vimal
On 8/9/07, Marc Weber <[EMAIL PROTECTED]> wrote: > > I wrote a code, but seems to give "Time limit exceeded"! > ?? > Your code writes > 15 to stdout which is correct (with the example given on the page).. > You have to explain what you mean by >>seems to give "Time limit exceeded"<< > > > loop t fu

Re: [Haskell-cafe] Slow IO or bad code?

2007-08-09 Thread Vimal
On 8/9/07, Brent Yorgey <[EMAIL PROTECTED]> wrote: > On 8/9/07, Chaddaï Fouché <[EMAIL PROTECTED]> wrote: > > I get "Wrong answer" with the following code for the same problem... > > Is there something strange in this code : > > This problem description is not worded very well. You have to figure

Re: [Haskell-cafe] Re: a regressive view of support for imperative programming in Haskell

2007-08-09 Thread David Roundy
On Thu, Aug 09, 2007 at 08:45:14PM +0200, Benjamin Franksen wrote: > David Roundy wrote: > > Several times since reading the beginning of this discussion I've wished I > > had the new syntax so I could write something like: > > > > do if predicateOnFileContents (<- readFile "foo") then ... > >

Re: [Haskell-cafe] Re: a regressive view of support for imperative programming in Haskell

2007-08-09 Thread David Menendez
On 8/9/07, Benjamin Franksen <[EMAIL PROTECTED]> wrote: > Donn Cave wrote: > > (I have a soft spot for O'Haskell, but > > alas I must be nearly alone on that.) > > You are /not/ alone :-) I always found it very sad that O'Haskell and also > its sucessor Timber (with all the good real-time stuff add

Re: [Haskell-cafe] a regressive view of support for imperative programming in Haskell

2007-08-09 Thread David Roundy
On Thu, Aug 09, 2007 at 02:08:20PM +0100, Jules Bean wrote: > David Roundy wrote: > >On Wed, Aug 08, 2007 at 02:20:39PM -0400, Paul Hudak wrote: > >As long as the sugar has a pretty obvious desugaring (which I seem to > >recall it did), I don't see how it's likely to make things worse. And > > So

[Haskell-cafe] Re: a regressive view of support for imperative programming in Haskell

2007-08-09 Thread Benjamin Franksen
David Roundy wrote: > Several times since reading the beginning of this discussion I've wished I > had the new syntax so I could write something like: > > do if predicateOnFileContents (<- readFile "foo") then ... > > instead of either > > do contents <- readFile "foo" > if predicateOnF

Re: [Haskell-cafe] a regressive view of support for imperative programming in Haskell

2007-08-09 Thread David Roundy
On Thu, Aug 09, 2007 at 04:02:05PM +1200, ok wrote: > On 9 Aug 2007, at 8:41 am, David Roundy wrote: > >I may be stating the obvious here, but I strongly prefer the do syntax. > >It's nice to know the other also, but the combination of do +indenting > >makes complicated code much clearer than the n

Re: [Haskell-cafe] Operator overloading

2007-08-09 Thread Brent Yorgey
On 8/9/07, rodrigo.bonifacio <[EMAIL PROTECTED]> wrote: > > Hi all. > > I want to overload the operator "^" for working instead of the following > "+++" operator: > > (+++) :: String -> [[String]] -> [[String]] > x +++ y = [ x:e | e<-y ] > > How can I overload the "^" operator? import Prelude hid

RE: [Haskell-cafe] Pure functional GUI

2007-08-09 Thread Peter Verswyvelen
> Indeed - the *hard* part seems to be figuring out how to run Glade on Windoze... I did not dare to ask this question because I could not believe this was hard... So anybody know how to do this? Run Glade on Window$? -Original Message- From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On

Re: [Haskell-cafe] Small question

2007-08-09 Thread Sebastian Sylvan
On 09/08/07, Stefan O'Rear <[EMAIL PROTECTED]> wrote: > On Thu, Aug 09, 2007 at 07:12:12PM +0100, Sebastian Sylvan wrote: > > {-#OPTIONS -funbox-strict-fields #-} > > > > data Quad = Quad !Bool !Bool > > > > foo True True = ... > > foo True False = > > ... etc... > > > > > > The GHC option jus

Re: [Haskell-cafe] Problem with question 3 about knights and knaves onw ikipedia

2007-08-09 Thread Steve Schafer
On Thu, 9 Aug 2007 20:07:02 +0200, you wrote: >("John is a knight","Bill is a knight","Yes","No ") >("John is a knight","Bill is a knave ","No ","No ") >("John is a knave ","Bill is a knight","Yes","Yes") >("John is a knave ","Bill is a knave ","Yes","No ") > >Anyone has an idea what I missed here

Re: [Haskell-cafe] (no subject)

2007-08-09 Thread Bulat Ziganshin
Hello Thomas, Thursday, August 9, 2007, 8:12:27 PM, you wrote: > In the following code which uses template haskell, how can I get > back the macro-expanded code generated from citating http://www.haskell.org/bz/thdoc.htm : In order to make debugging Template Haskell programs easier, compiler su

[Haskell-cafe] Operator overloading

2007-08-09 Thread rodrigo.bonifacio
Hi all. I want to overload the operator "^" for working instead of the following "+++" operator: (+++) :: String -> [[String]] -> [[String]] x +++ y = [ x:e | e<-y ] How can I overload the "^" operator? Thanks a lot. Rodrigo. ___ Haskell-Cafe maili

[Haskell-cafe] Re: a regressive view of support for imperative programming in Haskell

2007-08-09 Thread Benjamin Franksen
Donn Cave wrote: > (I have a soft spot for O'Haskell, but > alas I must be nearly alone on that.) You are /not/ alone :-) I always found it very sad that O'Haskell and also its sucessor Timber (with all the good real-time stuff added) died the 'quick death' of most research languages. Cheers B

Re: [Haskell-cafe] Slow IO or bad code?

2007-08-09 Thread Brent Yorgey
On 8/9/07, Chaddaï Fouché <[EMAIL PROTECTED]> wrote: > > I get "Wrong answer" with the following code for the same problem... > Is there something strange in this code : This problem description is not worded very well. You have to figure out the matching that maximizes the sum of hotnesses; you

Re: [Haskell-cafe] Derivation of Eq given Ord

2007-08-09 Thread Isaac Dupree
Andreas Marth wrote: I would say that qualifies as a bug because it relays an error from compile time to run time. It doesn't relay anything to run time - ghci has to _compile_ the expressions you give it too. If you _compile something_ successfully, you will know that _it_ will not fail in t

Re: [Haskell-cafe] Small question

2007-08-09 Thread Stefan O'Rear
On Thu, Aug 09, 2007 at 07:12:12PM +0100, Sebastian Sylvan wrote: > {-#OPTIONS -funbox-strict-fields #-} > > data Quad = Quad !Bool !Bool > > foo True True = ... > foo True False = > ... etc... > > > The GHC option just causese GHC to unbox primitive types when they're > strict in the data

Re: [Haskell-cafe] Small question

2007-08-09 Thread Sebastian Sylvan
On 09/08/07, Andrew Coppin <[EMAIL PROTECTED]> wrote: > Which of these is likely to go faster? > > type Quad = (Bool,Bool) > > foo (r,t) = > let > x = if r ... > y = if t ... > in ... > > > > data Quad = BL | BR | TL | TR > > foo q = > let > x = if q == TL | q

[Haskell-cafe] Problem with question 3 about knights and knaves on wikipedia

2007-08-09 Thread Peter Verswyvelen
I was writing some haskell code for fun to solve some "knights and knaves" problems, and I have troubles with http://en.wikipedia.org/wiki/Knights_and_knaves#Question_3 So knights always tell the truth and knaves always lie. John and Bill are two persons, but you don't know what they are, and you

[Haskell-cafe] Matters of precision

2007-08-09 Thread Andrew Coppin
Hi folks. I'm trying to write a Mandelbrot generator, and I've having a few problems with precision. First of all, currently I'm just using Double to represent coordinates. Can anybody tell me what the smallest value you can represent with one is? (Not including denormals.) (I've built a f

[Haskell-cafe] Small question

2007-08-09 Thread Andrew Coppin
Which of these is likely to go faster? type Quad = (Bool,Bool) foo (r,t) = let x = if r ... y = if t ... in ... data Quad = BL | BR | TL | TR foo q = let x = if q == TL | q == TR ... y = if q == BR | q == TR ... in ... (Unless somebody has a better idea

Re: [Haskell-cafe] Pure functional GUI

2007-08-09 Thread Andrew Coppin
Duncan Coutts wrote: On Thu, 2007-08-09 at 08:59 +0800, Hugh Perkins wrote: uestion on using gtk from haskell: how easy is it to integrate with glade? ie, can we directly bind glade form elements to haskell variables? How easy is it to bind events to glade form elements from within Haskell?

Re: [Haskell-cafe] how can I get template haskell macro-expanded code from inferStartState? (repeated post, now with subject)

2007-08-09 Thread Brian Brunswick
On 09/08/07, Thomas Hartman <[EMAIL PROTECTED]> wrote: > > (sorry, forgot the subject on my first post) > > In the following code which uses template haskell, how can I get back the > macro-expanded code generated from > > $(inferStartState ''MyState) > I just recently used ghc -ddump-splices to

Re: [Haskell-cafe] Derivation of Eq given Ord

2007-08-09 Thread Malte Milatz
I wrote: > instance Eq Ego => Eq Ord where ... This should have been instance Eq (Ego a) => Ord (Ego a) Malte ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Slow IO or bad code?

2007-08-09 Thread Chaddaï Fouché
Note that this code isn't more successful, clearly I have misunderstood one requirement : import qualified Data.ByteString.Char8 as B import Data.List (unfoldr) main = B.interact $ hot hot = B.unlines . map (B.pack . show) . processList . tail . unfoldr readInt1 readInt1 cs = do (n, cs') <- B

Re: [Haskell-cafe] Derivation of Eq given Ord

2007-08-09 Thread Andreas Marth
I would say that qualifies as a bug because it relays an error from compile time to run time. Andreas - Original Message - From: "Dougal Stanton" <[EMAIL PROTECTED]> To: "haskell-cafe" Sent: Thursday, August 09, 2007 5:57 PM Subject: [Haskell-cafe] Derivation of Eq given Ord > Is ther

[Haskell-cafe] how can I get template haskell macro-expanded code from inferStartState? (repeated post, now with subject)

2007-08-09 Thread Thomas Hartman
(sorry, forgot the subject on my first post) In the following code which uses template haskell, how can I get back the macro-expanded code generated from $(inferStartState ''MyState) I *can* recover the macro-expanded code for $(cnst 1 "x") using a debugging technique bulat describes on h

Re: [Haskell-cafe] Derivation of Eq given Ord

2007-08-09 Thread Malte Milatz
Dougal Stanton, Thu, 9 Aug 2007 16:57:26 +0100: > Is there a reason why automatic derivation of Ord without Eq doesn't > do "the sensible thing" and just derive Eq anyway? > > > newtype Id a = Id { a :: String } > >deriving (Read, Show, Eq, Ord) > > newtype Ego a = Ego { b :: S

[Haskell-cafe] (no subject)

2007-08-09 Thread Thomas Hartman
In the following code which uses template haskell, how can I get back the macro-expanded code generated from $(inferStartState ''MyState) I *can* recover the macro-expanded code for $(cnst 1 "x") using a debugging technique bulat describes on his tutorial at http://www.haskell.org/bz/th3.h

Re: [Haskell-cafe] Slow IO or bad code?

2007-08-09 Thread Chaddaï Fouché
I get "Wrong answer" with the following code for the same problem... Is there something strange in this code : module Main where import qualified Data.ByteString.Char8 as B main = B.getLine >>= sequence_ . flip replicate hot . maybe 0 fst . B.readInt hot = do B.getLine men <- B.

[Haskell-cafe] Derivation of Eq given Ord

2007-08-09 Thread Dougal Stanton
Is there a reason why automatic derivation of Ord without Eq doesn't do "the sensible thing" and just derive Eq anyway? > newtype Id a = Id { a :: String } >deriving (Read, Show, Eq, Ord) > newtype Ego a = Ego { b :: String } >deriving (Read, Show, Ord) Bot

Re: [Haskell-cafe] Slow IO or bad code?

2007-08-09 Thread Brent Yorgey
On 8/9/07, Marc Weber <[EMAIL PROTECTED]> wrote: > > > I wrote a code, but seems to give "Time limit exceeded"! > ?? > Your code writes > 15 to stdout which is correct (with the example given on the page).. > You have to explain what you mean by >>seems to give "Time limit > exceeded"<< > I think

Re: [Haskell-cafe] New Eq instance

2007-08-09 Thread Jules Bean
rodrigo.bonifacio wrote: instance Eq Step where Step id1 scenario1 action1 state1 response1 == Step id2 scenario2 action2 state2 response2 = id == id _ == _ = False Almost. You just used 'id' and 'id' when you meant 'id1' and 'id2'. > instance Eq Step where > Step id1 scenario1 action

Re: [Haskell-cafe] Slow IO or bad code?

2007-08-09 Thread Marc Weber
> I wrote a code, but seems to give "Time limit exceeded"! ?? Your code writes 15 to stdout which is correct (with the example given on the page).. You have to explain what you mean by >>seems to give "Time limit exceeded"<< > loop t function Does already exist. sequence $ replicate 10 function is

RE: [Haskell-cafe] New Eq instance

2007-08-09 Thread Bayley, Alistair
> From: [EMAIL PROTECTED] > [mailto:[EMAIL PROTECTED] On Behalf Of > rodrigo.bonifacio > > data Step = Step Id Scenario Action State Response > > How can I define Step as an "Eq Instance", in such way that > two steps are equals if they have the same Id (Id is defined > as a synonimous for th

Re: [Haskell-cafe] Slow IO or bad code?

2007-08-09 Thread Vimal
@Donald: Thanks for the link. > prod = sum . zipWith (*) > > This is the slow part. Prelude.read ist really slow. > > Futhermore use the recusion pattern again: > to_int = map read > > What is n used for? @Lutz: Those are some nice tricks... Thanks! Now, the 'n' is for getting the number of number

[Haskell-cafe] New Eq instance

2007-08-09 Thread rodrigo.bonifacio
Hello, I had defined the follwing data type: data Step = Step Id Scenario Action State Response How can I define Step as an "Eq Instance", in such way that two steps are equals if they have the same Id (Id is defined as a synonimous for the String type). I tried the following code, but someth

Re: [Haskell-cafe] a regressive view of support for imperative programming in Haskell

2007-08-09 Thread David Pollak
For what it's worth from a Haskell newbie (and from someone who's been doing FP since November, mainly in Scala.) I really like Haskell's purity and having the clear separation between zero side effects and monads is most excellent. It was quite a brain change to program functionally. It took a

Re: [Haskell-cafe] a regressive view of support for imperative programming in Haskell

2007-08-09 Thread Jules Bean
David Roundy wrote: On Wed, Aug 08, 2007 at 02:20:39PM -0400, Paul Hudak wrote: As long as the sugar has a pretty obvious desugaring (which I seem to recall it did), I don't see how it's likely to make things worse. And Some people are arguing that the desugaring isn't obvious. Although I lik

Re: [Haskell-cafe] Slow IO or bad code?

2007-08-09 Thread Lutz Donnerhacke
* Vimal wrote: >>> Beginning of CODE > loop t function > | t == 1 = do function > | otherwise = do { function; loop (t - 1) function } > > prod [] [] = 0 > prod (a:as) (b:bs) = a*b + prod as bs prod = sum . zipWith (*) > to_int :: [String] -> [Integer] > to_int [] = [] > to_int (x:xs) = (read x

Re: [Haskell-cafe] Slow IO or bad code?

2007-08-09 Thread Donald Bruce Stewart
j.vimal: > Hi > I am practicing writing code in haskell, by solving problems at this > site. http://spoj.pl. > The problem http://spoj.pl/problems/FASHION , is pretty simple. > > 1. Given two lists A,B , of N numbers, sort them and take sum of products. > i.e. Sum ai * bi > > I wrote a code,

[Haskell-cafe] Slow IO or bad code?

2007-08-09 Thread Vimal
Hi I am practicing writing code in haskell, by solving problems at this site. http://spoj.pl. The problem http://spoj.pl/problems/FASHION , is pretty simple. 1. Given two lists A,B , of N numbers, sort them and take sum of products. i.e. Sum ai * bi I wrote a code, but seems to give "Time lim

Re: [Haskell-cafe] Pure functional GUI (was

2007-08-09 Thread Duncan Coutts
On Thu, 2007-08-09 at 08:59 +0800, Hugh Perkins wrote: > To be fair, GTK is pretty standard. This is so even for "big name" > gc'd imperative languages such as C#. Sure, you can use Windows.Forms > in C#, but you often wouldnt, because of the patent burden. > Also, gtk in partnership with glade r

Re[2]: [Haskell-cafe] Pure functional GUI (was "a regressive view of support for imperativeprogramming in Haskell")

2007-08-09 Thread 'Peter Verswyvelen'
LOL. Yeah you are correct I guess. Oh well ;-) -Original Message- From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] Sent: Thursday, August 09, 2007 7:30 AM To: Peter Verswyvelen Cc: Donn Cave; haskell-cafe@haskell.org Subject: Re[2]: [Haskell-cafe] Pure functional GUI (was "a regressive vie

RE: [Haskell-cafe] How odd...

2007-08-09 Thread Simon Peyton-Jones
Indeed! Getting the library numerics to do the Right Thing is something that can only be done by people who know about numerics. People who build compilers aren't, alas. It's quite a specialised subject, and very easy to screw up. And there's performance to worry about too in the common case

Re: [Haskell-cafe] Language support for imperative code. Was: Re: monad subexpressions

2007-08-09 Thread Jules Bean
Brian Hulley wrote: Haskell is designed so that any attempt at abstracting mutable local state will infect the entire program (modulo use of a highly dangerous function whose semantics is entirely unclear, depending on the vagaries of evaluation strategy of the particular compiler) (Your em