Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Miguel Mitrofanov
On 19 May 2009, at 09:06, Ryan Ingram wrote: This is a common problem with trying to use do-notation; there are some cases where you can't make the object an instance of Monad. The same problem holds for Data.Set; you'd can write setBind :: Ord b = Set a - (a - Set b) - Set b setBind m f =

[Haskell-cafe] Expression parsing problem

2009-05-19 Thread leledumbo
I'm writing a paper as a replacement for writing exam and decided to write a simple compiler (got a little experience with it). However, I got trouble in parsing expression. The grammar: expression = get | [ + | - ] term { ( + | - ) term } term = factor { ( * | / ) factor } factor =

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Jason Dusek
2009/05/18 Miguel Mitrofanov miguelim...@yandex.ru: On 19 May 2009, at 09:06, Ryan Ingram wrote: This is a common problem with trying to use do-notation; there are some cases where you can't make the object an instance of Monad.  The same problem holds for Data.Set; you'd can write setBind

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Taral
On Mon, May 18, 2009 at 10:06 PM, Ryan Ingram ryani.s...@gmail.com wrote: On Mon, May 18, 2009 at 3:05 PM, Taral tar...@gmail.com wrote: Will this do? (=) :: (NFData sa, NFData b) = LI sa - (sa - LI b) - LI b No, the problem is that = on monads has no constraints, it must have the type LI

Re: [Haskell-cafe] How to use Data.ByteString ?

2009-05-19 Thread Brandon S. Allbery KF8NH
On May 19, 2009, at 01:42 , Jason Dagit wrote: I've often seen this bit of scary code in VB: Dim i as Integer = 5 If i = 5 Then ' Do something, because 5 = 5 End If Sure, that works in Perl too. But the equivalent case here would be chr$(5), not 5. -- brandon s. allbery

Re: [Haskell-cafe] fast Eucl. dist. - Haskell vs C

2009-05-19 Thread Kenneth Hoste
On May 18, 2009, at 15:28 , Claus Reinke wrote: My current best try uses the uvector package, has two 'vectors' of type (UArr Double) as input, and relies on the sumU and zipWithU functions which use streaming to compute the result: dist_fast :: UArr Double - UArr Double - Double

Re: [Haskell-cafe] fast Eucl. dist. - Haskell vs C

2009-05-19 Thread Kenneth Hoste
On May 18, 2009, at 20:54 , Claus Reinke wrote: As I said, I don't get the fusion if I just add the function above to the original Dist.hs, export it and compile the module with '-c -O2 -ddump-simpl': I can't reproduce this. Interesting. I'm using ghc 6.11.20090320 (windows),

[Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Henning Thielemann
On Mon, 18 May 2009, Nicolas Pouillard wrote: Excerpts from Jason Dusek's message of Sun May 17 15:45:25 +0200 2009: From the documentation: LI could be a strict monad and a strict applicative functor. However it is not a lazy monad nor a lazy applicative functor as required

Re: [Haskell-cafe] Expression parsing problem

2009-05-19 Thread Malcolm Wallace
The grammar: expression = get | [ + | - ] term { ( + | - ) term } term = factor { ( * | / ) factor } factor = IDENTIFIER | VALUE | ( expression ) I can't make term parse, for instance 1 * 2 / 3 Indeed, the grammar does not admit 1*2/3 as a sentence of that language although it

[Haskell-cafe] GUIs, FRP, (Delimited) Continuations and Zippers

2009-05-19 Thread oleg
Could either of those approaches (FRP / Delimited Continuations) be a solution for implementing complex GUI code? I think the answer is generally yes; I have tried writing a user interface which has a form with several controls; a change in one control may affect all other controls on the form

[Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Nicolas Pouillard
Excerpts from Taral's message of Tue May 19 00:05:39 +0200 2009: On Mon, May 18, 2009 at 10:30 AM, Nicolas Pouillard nicolas.pouill...@gmail.com wrote: The type I would need for bind is this one:  (=) :: NFData sa = LI sa - (sa - LI b) - LI b Will this do? (=) :: (NFData sa, NFData

Re: [Haskell-cafe] Expression parsing problem

2009-05-19 Thread leledumbo
Indeed, the grammar does not admit 1*2/3 as a sentence ... Huh? Why not? 1 * 2 / 3 should match factor * factor / factor. Remember that { } is repetition, so it should be able to handle such term. expression ::= term | term + expression term ::= factor | factor * term factor ::= constant |

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Ryan Ingram
To be fair, you can do this with some extensions; I first saw this in a paper on Oleg's site [1]. Here's some sample code: {-# LANGUAGE NoImplicitPrelude, TypeFamilies, MultiParamTypeClasses #-} module SetMonad where import qualified Data.Set as S import qualified Prelude as P (Monad, (=), (),

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Miguel Mitrofanov
I've posted it once or twice. newtype C m r a = C ((a - m r) - m r) It's a monad, regardless of whether m is one or not. If you have something like return and bind, but not exactly the same, you can make casting functions m a - C m r a and backwards. Jason Dusek wrote on 19.05.2009 10:23:

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Nicolas Pouillard
Excerpts from Ryan Ingram's message of Tue May 19 10:23:01 +0200 2009: To be fair, you can do this with some extensions; I first saw this in a paper on Oleg's site [1]. Here's some sample code: This seems like the same trick as the rmonad package:

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Ryan Ingram
Minor addition, optimize (I couldn't help myself!) -- ryan instance Ord b = ConstrainedBind (S.Set a) (S.Set b) where type BindElem (S.Set a) = a m = f = S.unions $ map f $ S.toList m m n = if S.null m then S.empty else n ___

Re: [Haskell-cafe] Expression parsing problem

2009-05-19 Thread Ryan Ingram
Why is Symbol = (String, Token)? A more sensible token type would include values in the Value constructor and string identifiers in the Identifier constructor; the strings in everything else seem redundant. A more pure/monadic parser would have a type like this: data Result a = Error String |

RE: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Sittampalam, Ganesh
Nicolas Pouillard wrote: Excerpts from Ryan Ingram's message of Tue May 19 10:23:01 +0200 2009: To be fair, you can do this with some extensions; I first saw this in a paper on Oleg's site [1]. Here's some sample code: This seems like the same trick as the rmonad package:

Re: [Haskell-cafe] Expression parsing problem

2009-05-19 Thread leledumbo
Why is Symbol = (String, Token)? A more sensible token type would include values in the Value constructor and string identifiers in the Identifier constructor; the strings in everything else seem redundant. Surely you didn't read my original post, do you? I have a very limited knowledge of

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Ryan Ingram
On Tue, May 19, 2009 at 12:54 AM, Miguel Mitrofanov miguelim...@yandex.ru wrote: I've posted it once or twice. newtype C m r a = C ((a - m r) - m r) It's a monad, regardless of whether m is one or not. If you have something like return and bind, but not exactly the same, you can make casting

Re: [Haskell-cafe] GUIs, FRP, (Delimited) Continuations and Zippers

2009-05-19 Thread Wolfgang Jeltsch
Am Samstag, 16. Mai 2009 16:18 schrieb GüŸnther Schmidt: Hi all, In my app, there is one part which has a rather complicated GUI logic, it involves n drop downs with n choices each. Whenever the current selection in one of the drop downs changes by user interaction, the other (n-1) drop

[Haskell-cafe] Re: Haskell-Cafe Digest, Vol 69, Issue 38

2009-05-19 Thread Tom Lokhorst
These QuickCheck properties don't really test your sort function. The `a' type variable will be instantiated to (). So you will test with lists of units, like so: ghci quickCheck (\xs - isSorted (reverse xs)) OK, passed 100 tests. This can be simply solved by added a more specific type

Re: [Haskell-cafe] Expression parsing problem

2009-05-19 Thread Ryan Ingram
Surely you didn't read my original post, do you? I have a very limited knowledge of Monad and I try to find a solution using my current skills because the due date is within two weeks. Therefore, I don't think I can create a Monadic parser for this. I think you're giving up way too easily.

Re: [Haskell-cafe] Expression parsing problem

2009-05-19 Thread leledumbo
I hope you're right. 7 pages... 1-2 nights should be enough. Thanks for all. -- View this message in context: http://www.nabble.com/Expression-parsing-problem-tp23610457p23614011.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Re: [Haskell-cafe] fast Eucl. dist. - Haskell vs C

2009-05-19 Thread Daniel Schüssler
Hello! On Monday 18 May 2009 14:37:51 Kenneth Hoste wrote: I'm mostly interested in the range 10D to 100D is the dimension known at compile-time? Then you could consider Template Haskell. I wrote up some code for generating the vector types and vector subtraction/inner product below, HTH. One

Re: [Haskell-cafe] fast Eucl. dist. - Haskell vs C

2009-05-19 Thread Claus Reinke
I understand from your later post that is was in fact specialized, but how do I make sure it _is_ specialized? -ddump-tc seems to give the generalized type, so it seems you'd need to look at the -ddump-simpl output if you want to know whether a local function is specialized.

Re: [Haskell-cafe] fast Eucl. dist. - Haskell vs C

2009-05-19 Thread Daniel Schüssler
Hi, meh, I just realised that there is no sensible way to actually introduce/eliminate the generated types. I'm attaching a revised version with fromList/toList functions. Maybe the vector type should be polymorphic and be an instance of Functor, Monad and Foldable? But then we really depend

Re: [Haskell-cafe] Expression parsing problem

2009-05-19 Thread Loup Vaillant
Hello, 2009/5/19 leledumbo leledumbo_c...@yahoo.co.id: expression ::= term | term + expression term ::= factor | factor * term factor ::= constant | variable | ( expression ) Oh, left recursion. Well, it should be easy to transform: expression ::= term | moreTerm term ::= factor |

Re: [Haskell-cafe] fast Eucl. dist. - Haskell vs C

2009-05-19 Thread Kenneth Hoste
On May 19, 2009, at 13:24 , Daniel Schüssler wrote: Hello! On Monday 18 May 2009 14:37:51 Kenneth Hoste wrote: I'm mostly interested in the range 10D to 100D is the dimension known at compile-time? Then you could consider Template Haskell. In general, no. :-) It will be known for

Re: [Haskell-cafe] showing a user defined type

2009-05-19 Thread michael rice
Thanks. I had put together something similar to your first suggestion but tried to use PutStrLn(Show...). I'd also thought of your second suggestion about a dummy show for functions. A little further along in The Little MLer the ints function is replaced by other functions like primes and

Re: [Haskell-cafe] showing a user defined type

2009-05-19 Thread michael rice
Cool! Is there *anything* Haskell *can't* do? Michael --- On Mon, 5/18/09, David Menendez d...@zednenem.com wrote: From: David Menendez d...@zednenem.com Subject: Re: [Haskell-cafe] showing a user defined type To: Ryan Ingram ryani.s...@gmail.com Cc: haskell-cafe@haskell.org Date: Monday, May

Re: [Haskell-cafe] How to use Data.ByteString ?

2009-05-19 Thread Chaddaï Fouché
On Tue, May 19, 2009 at 8:46 AM, Brandon S. Allbery KF8NH allb...@ece.cmu.edu wrote: On May 19, 2009, at 01:42 , Jason Dagit wrote: I've often seen this bit of scary code in VB: Dim i as Integer = 5 If i = 5 Then  ' Do something, because 5 = 5 End If Sure, that works in Perl too. That's

RE: [Haskell-cafe] Request for feedback: HaskellDB + HList

2009-05-19 Thread Brian Bloniarz
Hi Justin, I updated my changes to apply against that repo, thanks for the pointer. Cool to see new changes to haskelldb, especially all the new unit tests! You can find my updated repo at: http://patch-tag.com/r/haskelldb-hlist Re-reading your email now, I see you asked for a patch, but

Re: [Haskell-cafe] showing a user defined type

2009-05-19 Thread Miguel Mitrofanov
michael rice wrote on 19.05.2009 18:16: Cool! Is there *anything* Haskell *can't* do? Well, I haven't found a way to emulate polymorphics kinds yet, and I feel like I need them. Other than than - probably no. Michael --- On *Mon, 5/18/09, David Menendez /d...@zednenem.com/* wrote:

[Haskell-cafe] Question about IO, interact functions,

2009-05-19 Thread David Leimbach
main = interact (unlines . lines) This *appears* to somewhat reliably get me functionality that looks like take a line of input, and print it out. Is this behavior something I can rely on working? I like the idea that lines can pull lines lazily from getContents which lazily consume the input.

Re: [Haskell-cafe] Question about IO, interact functions,

2009-05-19 Thread Jason Dusek
2009/05/19 David Leimbach leim...@gmail.com: ...I'm concerned that relying on a pure function like unlines . lines to sequence IO is a bit too implicit in nature. You aren't relying on `unlines . lines` to do the sequencing; you're relying on them to process a string. That the characters

Re: [Haskell-cafe] showing a user defined type

2009-05-19 Thread Ryan Ingram
On Tue, May 19, 2009 at 7:07 AM, michael rice nowg...@yahoo.com wrote: A little further along in The Little MLer the ints function is replaced by other functions like primes and fibs, which also return Links: fun primes(n)   = if is_prime(n+1)  then Link(n+1,primes)  else primes(n+1) fun

[Haskell-cafe] Re: Question about IO, interact functions,

2009-05-19 Thread Ertugrul Soeylemez
David Leimbach leim...@gmail.com wrote: main = interact (unlines . lines) This *appears* to somewhat reliably get me functionality that looks like take a line of input, and print it out. Is this behavior something I can rely on working? I like the idea that lines can pull lines lazily from

[Haskell-cafe] Gtk2Hs + Sourceview on Windows

2009-05-19 Thread mwinter
Hi, I have ghc 6.10.1 and gtk2hs 0.10.0 installed on my windows vista computer. Both were installed using the installer on the webpages. I am able to use gtk, glade etc but not sourceview or cairo. If I compile the examples in the gtk2hs example folder, I get not in scope error messages for

[Haskell-cafe] fast Eucl. dist. - Haskell vs C

2009-05-19 Thread Patrick Perry
Hi Kenneth, I wrote a benchmark similar to yours using the haskell blas library I wrote (latest version is on github at http://github.com/patperry/blas/tree/master , an older version is on hackage). The pure Haskell implementation is not very good, and the problem seems to be repeated

Re: [Haskell-cafe] Free theorems for dependent types?

2009-05-19 Thread Masahiro Sakai
From: Eugene Kirpichov ekirpic...@gmail.com Date: Sun, 17 May 2009 23:10:12 +0400 Is there any research on applying free theorems / parametricity to type systems more complex than System F; namely, Fomega, or calculus of constructions and alike? You may be interested in this: The Theory of

Re: [Haskell-cafe] showing a user defined type

2009-05-19 Thread michael rice
Hi Ryan, I'm afraid you've lost me. Maybe if you showed how this would be used in ML I would get the picture. Michael --- On Tue, 5/19/09, Ryan Ingram ryani.s...@gmail.com wrote: From: Ryan Ingram ryani.s...@gmail.com Subject: Re: [Haskell-cafe] showing a user defined type To: michael rice

[Haskell-cafe] Haskell programmers in São Carlos - SP - Brazil?

2009-05-19 Thread Maurí­cio
Anybody else around here? Best, Maurício ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] How i use GHC.Word.Word8 wit Int ?

2009-05-19 Thread z_a...@163.com
Hi, friends rollDice :: Word8 - IO Word8 rollDice n = do bracket (openFile /dev/random ReadMode) (hClose) (\hd - do v - fmap B.unpack (B.hGet hd 1) let v1 = Data.List.head v return $ (v1 `mod` n) + 1) . blueIdx - rollDice $ length [1..33]

Re: [Haskell-cafe] How i use GHC.Word.Word8 wit Int ?

2009-05-19 Thread Felipe Lessa
On Wed, May 20, 2009 at 08:40:15AM +0800, z_a...@163.com wrote: I know length [1..33] is Int not Word8, but Word8 is enough here. Just saying '33' is enough here. :) -- Felipe. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Haskell progr ammers in São Carlos - SP - Brazil?

2009-05-19 Thread Diego Souza
Not exactly São Carlos: São Paulo - SP. On Tue, May 19, 2009 at 09:28:55PM -0300, Maurí­cio wrote: Anybody else around here? Best, Maurício ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] How i use GHC.Word.Word8 wit Int ?

2009-05-19 Thread Bernie Pope
2009/5/20 z_a...@163.com z_a...@163.com: Hi, friends rollDice :: Word8 - IO Word8 rollDice n = do   bracket (openFile /dev/random ReadMode) (hClose)       (\hd - do v -  fmap B.unpack (B.hGet hd 1)                  let v1 =  Data.List.head v                  return $ (v1 `mod` n) + 1)

Re: [Haskell-cafe] How to use Data.ByteString ?

2009-05-19 Thread Brandon S. Allbery KF8NH
On May 19, 2009, at 10:20 , Chaddaï Fouché wrote: On Tue, May 19, 2009 at 8:46 AM, Brandon S. Allbery KF8NH allb...@ece.cmu.edu wrote: On May 19, 2009, at 01:42 , Jason Dagit wrote: I've often seen this bit of scary code in VB: Dim i as Integer = 5 If i = 5 Then ' Do something, because 5 = 5

Re: [Haskell-cafe] How i use GHC.Word.Word8 wit Int ?

2009-05-19 Thread Johannes Laire
On Wed, May 20, 2009 at 3:40 AM, z_a...@163.com z_a...@163.com wrote: Hi, friends rollDice :: Word8 - IO Word8 rollDice n = do   bracket (openFile /dev/random ReadMode) (hClose)       (\hd - do v -  fmap B.unpack (B.hGet hd 1)                  let v1 =  Data.List.head v                  

Re: [Haskell-cafe] How i use GHC.Word.Word8 wit Int ?

2009-05-19 Thread Lee Duhem
2009/5/20 Bernie Pope florbit...@gmail.com: Oh right. I didn't see your proposal (did it get sent to the list?). Yes, I just push the Replay button, not the Sorry for the confusion. It's my fault, sorry. lee ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Performance Problem with Typeable

2009-05-19 Thread Michael D. Adams
I've opened a ticket for this (http://hackage.haskell.org/trac/ghc/ticket/3245), but someone else will have to do the investigation into the problem. Michael D. Adams On Thu, May 14, 2009 at 10:59 AM, Simon Peyton-Jones simo...@microsoft.com wrote: Interesting.  Would anyone care to make a Trac

[Haskell-cafe] Tree traversal / stack overflow

2009-05-19 Thread Matthew Eastman
Hi, I've been writing some code to calculate the stretch factor of a tree of points. What it means is that for every node in a tree (lets call it 'pivot'), I have to traverse the same tree (lets call each node 'current') and sum d_t(pivot, current) / d(pivot, current) for each node,