[Haskell-cafe] Re: Question on rank-N polymorphism

2009-06-09 Thread oleg
Ryan Ingram discussed a question of writing fs f g = (f fst, g snd) so that fs ($ (1, 2)) type checks. This is not that difficult: {-# LANGUAGE RankNTypes, MultiParamTypeClasses -#} {-# LANGUAGE FunctionalDependencies, FlexibleInstances #-} class Apply f x y | f x - y where apply ::

Re: [Haskell-cafe] Deprecated packages on Hackage?

2009-06-09 Thread Ketil Malde
Erik de Castro Lopo mle...@mega-nerd.com writes: Finally, if a package is deprecated it might be usefult to have a reason as well so the hackage entry might say: Deprecated : true (replaced by package XXX) or Deprecated : true (needs maintainer) Or just Deprecated: (reason)?.

Re: [Haskell-cafe] How to compile base?

2009-06-09 Thread Jochem Berndsen
Henk-Jan van Tuyl wrote: I tried to compile base-4.0.0.0 (on Windows XP) as follows: [...]\base\4.0.0.0runhaskell Setup configure command line: module `Prelude' is not loaded It seems that Base needs another way to compile, how? AFAIK base is shipped with GHC, and cannot be compiled

Re: [Haskell-cafe] Incremental XML parsing with namespaces?

2009-06-09 Thread Krzysztof Skrzętnicki
On Mon, Jun 8, 2009 at 20:39, John Millikinjmilli...@gmail.com wrote: I'm trying to convert an XML document, incrementally, into a sequence of XML events. A simple example XML document: doc xmlns=org:myproject:mainns xmlns:x=org:myproject:otherns    titleDoc title/title    x:refabc1234/x:ref

[Haskell-cafe] Dutch HUG meeting tonight in Amsterdam

2009-06-09 Thread Chris Eidhof
Hi everyone, Tonight there will be another meeting of the Dutch Haskell Users' Group! This time we'll meet in Amsterdam, in the library. On the wiki [1] you can find the details of how to reach it. We'll be at the top floor and shouldn't be hard to recognize. The meeting is set to begin

Re: [Haskell-cafe] Incremental XML parsing with namespaces?

2009-06-09 Thread Krzysztof Skrzętnicki
And just to provide an example of working program: --- module Main where import Text.XML.Expat.Qualified import Text.XML.Expat.Namespaced import Text.XML.Expat.Tree import qualified Data.ByteString.Lazy as BSL main = do f - BSL.readFile doc1.xml let (tree,error) = parseTree

[Haskell-cafe] Unification for rank-N types

2009-06-09 Thread Vladimir Reshetnikov
Hi, I have the following code: --- {-# LANGUAGE RankNTypes #-} f :: ((forall a. a - a) - b) - b f x = x id g :: (forall c. Eq c = [c] - [c]) - ([Bool],[Int]) g y = (y [True], y [1]) h :: ([Bool],[Int]) h = f g

[Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread ptrash
Hi, I am using the System.Random method randomRIO. How can I convert its output to an Int? Thanks... -- View this message in context: http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23940249.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Tobias Olausson
You can not convert an IO Int to Int, or at least, you shouldn't. However, you can do as follows: test :: IO () test = do int - randomRIO -- or whatever it is called print $ useInt int useInt :: Int - Int useInt x = x+10 //Tobias 2009/6/9 ptrash ptr...@web.de: Hi, I am using the

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Jochem Berndsen
ptrash wrote: Hi, I am using the System.Random method randomRIO. How can I convert its output to an Int? Thanks... You cannot [1], you should read up on monads and I/O in Haskell, for example http://haskell.org/haskellwiki/IO_inside [1] Yes, you can, but no, you don't want to. Regards,

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Yusaku Hashimoto
On 2009/06/09, at 19:33, Tobias Olausson wrote: You can not convert an IO Int to Int, or at least, you shouldn't. However, you can do as follows: test :: IO () test = do int - randomRIO -- or whatever it is called print $ useInt int useInt :: Int - Int useInt x = x+10 Or, you can

[Haskell-cafe] Re: Unification for rank-N types

2009-06-09 Thread Vladimir Reshetnikov
One more example: This does not type-check: --- {-# LANGUAGE RankNTypes, ImpredicativeTypes #-} f :: [forall a. t a - t a] - t b - t b f = foldr (.) id --- Couldn't match expected type

[Haskell-cafe] Re: A generics question

2009-06-09 Thread Henry Laxen
Sterling Clover s.clover at gmail.com writes: Try it with the following type signature and it should work fine: convert :: (Data a) = Int - a - a Of course, as has been noted, SYB is a rather big sledgehammer for the insect in question. Cheers, S. Thank you Sterling. That is

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread ptrash
Ok, thanks for the information. -- View this message in context: http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23942344.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com. ___ Haskell-Cafe mailing list

[Haskell-cafe] Combine to List to a new List

2009-06-09 Thread ptrash
Hi, I have the following two lists: a = [1,2,3] b = [A,B,C] I want a combination of the to lists: c = [(1,A), (2, B), (3, C)] How can I do this? I have tried c = [(x,y) | x - a, y - b] But this just returns me a list with every possible combination of the 2 lists. Thanks... -- View

Re: [Haskell-cafe] Combine to List to a new List

2009-06-09 Thread Andrew Wagner
Try c = zip a b On Tue, Jun 9, 2009 at 9:05 AM, ptrash ptr...@web.de wrote: Hi, I have the following two lists: a = [1,2,3] b = [A,B,C] I want a combination of the to lists: c = [(1,A), (2, B), (3, C)] How can I do this? I have tried c = [(x,y) | x - a, y - b] But this just

RE: [Haskell-cafe] Combine to List to a new List

2009-06-09 Thread Dimitris Vekris
Probably you might need the zip function.Check here:http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:zip Date: Tue, 9 Jun 2009 06:05:57 -0700 From: ptr...@web.de To: haskell-cafe@haskell.org Subject: [Haskell-cafe] Combine to List to a new List Hi, I have the

Re: [Haskell-cafe] Combine to List to a new List

2009-06-09 Thread ptrash
Hey, cool. Thanks! -- View this message in context: http://www.nabble.com/Combine-to-List-to-a-new-List-tp23942440p23942633.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com. ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Applying Data.Map

2009-06-09 Thread michael rice
Hi Toby, Thanks for the helpful comments. I'd gotten used to arithmetic operator sections (+2), (*2), etc. but hadn't picked up on the generality of using them with *any* infix function. I can also see the benefit of using List.Group. However, I'm uncertain about how to import just fromList

Re: [Haskell-cafe] Combine to List to a new List

2009-06-09 Thread Mattias Bengtsson
On Tue, 2009-06-09 at 06:05 -0700, ptrash wrote: Hi, I have the following two lists: a = [1,2,3] b = [A,B,C] I want a combination of the to lists: c = [(1,A), (2, B), (3, C)] How can I do this? What you want is a function with the following type signature: [t1] - [t2] - [(t1,t2)]

Re: [Haskell-cafe] Applying Data.Map

2009-06-09 Thread Thomas ten Cate
On Tue, Jun 9, 2009 at 15:23, michael ricenowg...@yahoo.com wrote: import Data.Map (Map)   (fromList,!)  ??? import qualified Data.Map as Map  (fromList,!) ??? Because ! is an operator, you need to enclose it in parentheses. Also, the (Map) in the import is already the list of things you are

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread ptrash
Hmm...it am not getting through it. I just want to generate a random number and then compare it with other numbers. Something like r = randomRIO (1, 10) if (r 5) then... else ... -- View this message in context: http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23943301.html Sent from

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Magnus Therning
On Tue, Jun 9, 2009 at 2:52 PM, ptrashptr...@web.de wrote: Hmm...it am not getting through it. I just want to generate a random number and then compare it with other numbers. Something like r = randomRIO (1, 10) if (r 5) then... else ... You have to do it inside the IO monad, something

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Henning Thielemann
On Tue, 9 Jun 2009, ptrash wrote: I am using the System.Random method randomRIO. How can I convert its output to an Int? in general: http://haskell.org/haskellwiki/How_to_get_rid_of_IO about randomIO: http://haskell.org/haskellwiki/Avoiding_IO#State_monad

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Daniel Fischer
Am Dienstag 09 Juni 2009 15:57:24 schrieb Magnus Therning: On Tue, Jun 9, 2009 at 2:52 PM, ptrashptr...@web.de wrote: Hmm...it am not getting through it. I just want to generate a random number and then compare it with other numbers. Something like r = randomRIO (1, 10) if (r 5)

Re: [Haskell-cafe] Incremental XML parsing with namespaces?

2009-06-09 Thread Henning Thielemann
John Millikin wrote: On Mon, Jun 8, 2009 at 3:39 PM, Henning Thielemannlemm...@henning-thielemann.de wrote: I think you could use the parser as it is and do the name parsing later. Due to lazy evaluation both parsers would run in an interleaved way. I've been trying to figure out how to get

Re: [Haskell-cafe] Applying Data.Map

2009-06-09 Thread michael rice
In the import statements, it wasn't clear to me that I could import types as well as functions, and Map is a type. All clear now. Thanks. Michael --- On Tue, 6/9/09, Thomas ten Cate ttenc...@gmail.com wrote: From: Thomas ten Cate ttenc...@gmail.com Subject: Re: [Haskell-cafe] Applying

Re: [Haskell-cafe] How to improve below code?

2009-06-09 Thread Neil Brown
Andy Stewart wrote: So have a better solution to avoid write above ugly code How about: data Page a = Page {pageName :: IORef String ,pageId:: Int ,pageBuffer:: a ,pageBox :: VBox } class PageBuffer a where pageBufferClone :: a -

[Haskell-cafe] How to improve below code?

2009-06-09 Thread Andy Stewart
Hi all, I have below source code, i use Dynamic for `pageBuffer`. In implement of function `pageClone`, after `case pt of`, i need write like this, and this code looks ugly, if `PageTyep` have 100 type, i need write those ugly code 100 times. case pt of TStringBuffer -

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Krzysztof Skrzętnicki
On Tue, Jun 9, 2009 at 16:14, Daniel Fischerdaniel.is.fisc...@web.de wrote: Am Dienstag 09 Juni 2009 15:57:24 schrieb Magnus Therning: On Tue, Jun 9, 2009 at 2:52 PM, ptrashptr...@web.de wrote: Hmm...it am not getting through it. I just want to generate a random number and then compare it

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread jerzy . karczmarczuk
Magnus Therning writes: ptrash wrote: ...am not getting through it. I just want to generate a random number and then compare it with other numbers. Something like r = randomRIO (1, 10) if (r 5) then... else ... You have to do it inside the IO monad, something like myFunc = do

Re[2]: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Bulat Ziganshin
Hello jerzy, Tuesday, June 9, 2009, 8:23:04 PM, you wrote: Please, tell him first about random streams, which he can handle without IO. Or, about ergodic functions (hashing contraptions which transform ANY parameter into something unrecognizable). When he says : I know all that, THEN hurt

[Haskell-cafe] please comment on my parser, can I do this cleaner?

2009-06-09 Thread Thomas Hartman
All I want to do is split on commas, but not the commas inside () or tags. I have been wanting to master parsec for a long time and this simple exercise looked like a good place to start. The code below does the right thing. Am I missing any tricks to make this simpler/neater? Thanks, thomas.

Re: [Haskell-cafe] nubBy seems broken in recent GHCs

2009-06-09 Thread Cale Gibbard
2009/6/6 Bertram Felgenhauer bertram.felgenha...@googlemail.com: Interesting. This was changed in response to    http://hackage.haskell.org/trac/ghc/ticket/2528 | Tue Sep  2 11:29:50 CEST 2008  Simon Marlow marlo...@gmail.com |   * #2528: reverse the order of args to (==) in nubBy to match

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Jorge Branco Branco Aires
Bulat Ziganshin wrote: Hello jerzy, Tuesday, June 9, 2009, 8:23:04 PM, you wrote: Please, tell him first about random streams, which he can handle without IO. Or, about ergodic functions (hashing contraptions which transform ANY parameter into something unrecognizable). When he says : I

Re: [Haskell-cafe] please comment on my parser, can I do this cleaner?

2009-06-09 Thread Daniel Fischer
Am Dienstag 09 Juni 2009 20:29:09 schrieb Thomas Hartman: All I want to do is split on commas, but not the commas inside () or tags. I have been wanting to master parsec for a long time and this simple exercise looked like a good place to start. The code below does the right thing. Am I

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Luke Palmer
2009/6/9 Krzysztof Skrzętnicki gte...@gmail.com On Tue, Jun 9, 2009 at 16:14, Daniel Fischerdaniel.is.fisc...@web.de wrote: If you're doing much with random generators, wrap it in a State monad. To avoid reinventing the wheel one can use excellent package available on Hackage:

Re: [Haskell-cafe] How to improve below code?

2009-06-09 Thread Ryan Ingram
On Tue, Jun 9, 2009 at 7:21 AM, Neil Brownnc...@kent.ac.uk wrote: data Page a =   Page {pageName      :: IORef String        ,pageId        :: Int        ,pageBuffer    :: a        ,pageBox       :: VBox        } class PageBuffer a where  pageBufferClone :: a - IO (a, VBox) pageClone ::

[Haskell-cafe] FlexibleContexts and FlexibleInstances

2009-06-09 Thread Niklas Broberg
Dear all, This post is partly a gripe about how poor the formal documentation for various GHC extensions is, partly a gripe about how GHC blurs the lines between syntactic and type-level issues as well as between various extensions, and partly a gripe about how the Haskell 98 report is sometimes

Re: [Haskell-cafe] Incremental XML parsing with namespaces?

2009-06-09 Thread Iavor Diatchki
Hi, you may also want to look at: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/xml It knows about namespaces and, also, it's parser is lazy. -Iavor On Mon, Jun 8, 2009 at 11:39 AM, John Millikinjmilli...@gmail.com wrote: I'm trying to convert an XML document, incrementally, into a

Re: [Haskell-cafe] please comment on my parser, can I do this cleaner?

2009-06-09 Thread Thomas Hartman
Thanks. It seems my original parser also works against FOO,BAR,BAZ if you only modify atom = string ,           | ( many1 $ noneOf (), ) -- add , Indeed, what to call the thingies in a parser is a source of some personal consternation. What is a token, what is an atom, what is an expr? It all

[Haskell-cafe] Re: I love purity, but it's killing me.

2009-06-09 Thread Chung-chieh Shan
Paul L nine...@gmail.com wrote in article 856033f20906082224s2b7d5391gdc7a4ed913004...@mail.gmail.com in gmane.comp.lang.haskell.cafe: The open question is whether there exists such a solution that's both elegant and efficient at maintain proper sharing in the object language. What is your

[Haskell-cafe] help with a question

2009-06-09 Thread haonan21
I'm very new to haskell hugs and would appreciate it if someone could help me out here. I've been giving 2 questions. 1.) A and B are two sets of integers. Implement a function to obtain the integers that belong to both sets. Test your function fully. 2.) Define and test a function f, which,

Re: [Haskell-cafe] help with a question

2009-06-09 Thread Michael Vanier
haonan21 wrote: I'm very new to haskell hugs and would appreciate it if someone could help me out here. I've been giving 2 questions. 1.) A and B are two sets of integers. Implement a function to obtain the integers that belong to both sets. Test your function fully. 2.) Define and test a

Re: [Haskell-cafe] Re: Building network package on Windows

2009-06-09 Thread Bryan O'Sullivan
On Mon, Jun 8, 2009 at 10:18 PM, Iavor Diatchki iavor.diatc...@gmail.comwrote: OK, I think that I found and fixed the problem. As Thomas pointed out, the configure script is not wrong. The problem turned out to be the foreign import for getnameinfo (this was the missing symbol). So it was