Re: [Haskell-cafe] defining last using foldr

2007-08-14 Thread Chaddaï Fouché
2007/8/14, Alexteslin [EMAIL PROTECTED]: Well, i have tried cons (:) operator but when it passed to foldr doesn't work because cons operator operates first character and then the list but the foldr argument takes a function (a-a-a). Maybe i am missing the point here? What Aaron was saying

Re: [Haskell-cafe] Re: defining last using foldr

2007-08-14 Thread Chaddaï Fouché
2007/8/14, Aaron Denney [EMAIL PROTECTED]: The problem with foldl is that you can't easily make it polymorphic because of how the null case is handled. foldl1 and foldr1 are trivial, true. The original last fail on empty list, it's far easier to obtain the same semantic with foldl than with

Re: [Haskell-cafe] Re: defining last using foldr

2007-08-15 Thread Chaddaï Fouché
2007/8/15, Aaron Denney [EMAIL PROTECTED]: The original last fail on empty list, it's far easier to obtain the same semantic with foldl than with foldr, in fact it isn't hard at all to make it polymorphic without hassle (contrary to the foldr case) _if_ you remember that there _is_ a

Re: [Haskell-cafe] defining last using foldr

2007-08-15 Thread Chaddaï Fouché
2007/8/15, Alexteslin [EMAIL PROTECTED]: I am really sorry, but i still can't define the function. The chapter the exercise is in precedes algebraic types or Maybe a types. And is seems that must being easy to define. If you don't have Maybe, you still have it's older brother, namely lists

Re: [Haskell-cafe] monte carlo trouble

2007-08-15 Thread Chaddaï Fouché
2007/8/15, Chad Scherrer [EMAIL PROTECTED]: If there's a way to lazily sample with replacement from a list without even requiring the length of the list to be known in advance, that could lead to a solution. I'm not sure what you mean by with replacement but I think it don't change the

Re: [Haskell-cafe] Erlang VM in Haskell

2007-08-15 Thread Chaddaï Fouché
2007/8/16, Joel Reymont [EMAIL PROTECTED]: I'm doing this to learn more about the Erlang internals and to acquire some skills in the process. I'm also hoping to be at least as fast as the existing Erlang VM (written in C) That don't seem too realistic since the Erlang development team is big

Re: [Haskell-cafe] Re: defining last using foldr

2007-08-16 Thread Chaddaï Fouché
16 Aug 2007 10:11:24 +0100, Jon Fairbairn [EMAIL PROTECTED]: snip my quote I certainly wouldn't count such a thing as a valid solution. It's always amazed me that C uses as standard a mechanism of ending strings that is so obviously an error-prone hack. I'm completely with you on that !

Re: [Haskell-cafe] Basic question....

2007-08-17 Thread Chaddaï Fouché
Not only does you lack some parens around your patterns, your function types are wrong : type Key = String data EnvItem a = EnvItem (Key, a) envKey :: EnvItem a - String envKey (EnvItem (key, value)) = key envValue :: EnvItem a - a envValue (EnvItem (key, value)) = value -- Jedaï

Re: [Haskell-cafe] Re: Basic question....

2007-08-17 Thread Chaddaï Fouché
17 Aug 2007 14:44:28 +0100, Jon Fairbairn [EMAIL PROTECTED]: Why not data EnvItem a = EnvItem {key:: Key, value:: a} It's the real solution, but I feel it was worthwhile to underscore the other mistakes (often encountered by the newbies) in types and parameters. -- Jedaï

Re: [Haskell-cafe] defining last using foldr

2007-08-17 Thread Chaddaï Fouché
For a really good article to see how foldr is in fact very powerful and how you can make it do some funny tricks, see the Monad.Reader 6th issue : http://www.haskell.org/sitewiki/images/1/14/TMR-Issue6.pdf I'll point out that you can write a lazy dropWhile with foldr in the style of the first

Re: [Haskell-cafe] defining last using foldr

2007-08-17 Thread Chaddaï Fouché
2007/8/18, Chaddaï Fouché [EMAIL PROTECTED]: For a really good article to see how foldr is in fact very powerful and how you can make it do some funny tricks, see the Monad.Reader 6th issue : http://www.haskell.org/sitewiki/images/1/14/TMR-Issue6.pdf I just saw this was already linked

Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-18 Thread Chaddaï Fouché
foo n = if n0 then [] else n : foo (n-1) bar n = aux 0 [] where aux i xs = if in then xs else aux (i+1) (i:xs) that foo is more efficient than bar because lazy evaluation of foo just puts the delayed computation in the cdr of the list, while lazy evaluation of bar has to keep track of

Re: [Haskell-cafe] IO inside CGI

2007-08-24 Thread Chaddaï Fouché
2007/8/24, Adrian Neumann [EMAIL PROTECTED]: Obviously this doesn't work because I'm trying to do IO inside CGI (right?). Is there some incantation I can perform to make this possible? Like gen - arcaneMagic parse inp As doing IO in the CGI Monad is a current need, it's an instance of

Re: [Haskell-cafe] Style

2007-08-26 Thread Chaddaï Fouché
2007/8/26, Yitzchak Gale [EMAIL PROTECTED]: Bjorn Bringert wrote: Here's a much more inefficient version, but it has the merit of being very easy to understand: tm_silly n = length $ takeWhile (=='0') $ reverse $ show $ product [1..n] Be careful with types - use Data.List.genericLength

Re: [Haskell-cafe] Style

2007-08-26 Thread Chaddaï Fouché
2007/8/26, Yitzchak Gale [EMAIL PROTECTED]: True, that is not the problem. Using length forces the result to be Int, which is different than all of the other tm's so far. So for example, try this: [n | n - [0..25], tm_silly n /= tm n] You mean to say that tm_silly returns Int, which

Re: [Haskell-cafe] Geometry

2007-08-26 Thread Chaddaï Fouché
You've got a which is the radius of the circle, and b which is the length of the arc, thus you've got the angle between the two red radiuses : u = b / a So with basic trigonometry, we can deduce a - x = a * cos(u/2) x = a *( cos(u/2) - 1) -- Jedaï ___

Re: [Haskell-cafe] Geometry

2007-08-26 Thread Chaddaï Fouché
2007/8/27, Chaddaï Fouché [EMAIL PROTECTED]: You've got a which is the radius of the circle, and b which is the length of the arc, thus you've got the angle between the two red radiuses : u = b / a So with basic trigonometry, we can deduce a - x = a * cos(u/2) x = a *( cos(u/2) - 1

Re: [Haskell-cafe] Norvig's Sudoku Solver in Haskell

2007-08-27 Thread Chaddaï Fouché
For the translation of the above OCaml code, there is not much to do, in fact it is mostly functional, and so easily translated in Haskell code, note that I add a code to handle input of the form 4.8.5.3..7..2.6.8.4..1...6.3.7.5..2.1.4.., to resolve it and

Re: [Haskell-cafe] Geometry

2007-08-27 Thread Chaddaï Fouché
2007/8/27, Steve Schafer [EMAIL PROTECTED]: b is defined to be _half_ of the chord (the semichord, I suppose). You're assuming it to be the entire chord. Based on the drawing I thought it was the length of the arc (in blue) ? -- Jedaï ___

Re: [Haskell-cafe] Looking for suggestions to improve my algorithm

2007-08-30 Thread Chaddaï Fouché
I managed it in 7 seconds (on 1500 MHz) with an idea close to yours (but I used IntSet, not IntMap), Daniel Fisher gave you some good ideas to achieve it, the real snail in this problem is the sumDivisors function. -- Jedaï ___ Haskell-Cafe mailing

Re: [Haskell-cafe] Looking for suggestions to improve my algorithm

2007-08-30 Thread Chaddaï Fouché
2007/8/30, Chaddaï Fouché [EMAIL PROTECTED]: I managed it in 7 seconds (on 1500 MHz) with an idea close to yours (but I used IntSet, not IntMap), Daniel Fisher gave you some good ideas to achieve it, the real snail in this problem is the sumDivisors function. I put my final solution

Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Chaddaï Fouché
Another interesting example of the x = f x use : coins = [1,2,5,10,20,50,100,200] beautiful = foldl (\without p - let (poor,rich) = splitAt p without with = poor ++ zipWith (++) (map (map (p:)) with)

Re: [Haskell-cafe] RE: Definition of the Haskell standard library

2007-09-01 Thread Chaddaï Fouché
As a enthusiast Perl user over the years, I note that the CPAN and the associated toolkit (the CPAN module, its shell, ExtUtils::MakeMaker and Module::Build) is pretty good at this. It has it's share of cruft (in fact a whole lot of it) but it's certainly better than most solutions in this field

Re: [Haskell-cafe] Looking for suggestions to improve my algorithm

2007-09-02 Thread Chaddaï Fouché
Right, your program is 2 times faster than mine on my machine... I wonder if there is a better structure to do this bookkeeping than IntSet (maybe Sequence slightly remanied ?), anyway it goes to show how sometimes the bookkeeping can be more expensive than the operations it's meant to prevent !

[Haskell-cafe] Array.Diff, strange oversight or myopia ?

2007-09-02 Thread Chaddaï Fouché
Data.Array.Diff don't have an instance for DiffUArray Bool, which is strange by itself since IOUArray Bool exists and it's the only IOUArray that is not mirrored in Diff. But ok, why not, I guess it might be a small oversight, so I go on to create the missing instance IArray (IOToDiffArray

Re: [Haskell-cafe] RE: Definition of the Haskell standard library

2007-09-02 Thread Chaddaï Fouché
2007/9/2, Adrian Hey [EMAIL PROTECTED]: Other meaningless measures that have been suggested are the rate of patch submissions of the number of developers involved. I seem to remember someone recently suggesting that libraries that score highly in on this regard should be elevated to blessed

Re: [Haskell-cafe] Speed of character reading in Haskell

2007-09-07 Thread Chaddaï Fouché
From what I can see of your program, it would greatly benefit from using Data.ByteString, is there an obvious reason not to use it ? (Some list operations are too expensive with ByteString but for most string processing it's perfectly fine and much faster than String). -- Jedaï

Re: [Haskell-cafe] Why isn't pattern matching lazy by default?

2007-09-19 Thread Chaddaï Fouché
2007/9/19, Miguel Mitrofanov [EMAIL PROTECTED]: Now why isn't pattern matching lazy by default? This seems odd for a newbie since everything else is lazy by default. It's even more confusing that pattern matching in 'let' _is_ lazy. No, it's not. See, in let or where constructs you

Re: [Haskell-cafe] unsafePerformIO: are we safe?

2007-09-26 Thread Chaddaï Fouché
2007/9/26, Adrian Hey [EMAIL PROTECTED]: Sebastian Sylvan wrote: Rule of thumb: If your name isn't Simon*, you shouldn't use unsafePerformIO. If this is so, maybe it's time someone (who may or may not be called Simon) gave us a realistic alternative. There can't be alternatives, unsafeIO

Re: [Haskell-cafe] unsafePerformIO: are we safe?

2007-09-26 Thread Chaddaï Fouché
2007/9/26, Adrian Hey [EMAIL PROTECTED]: Chaddaï Fouché wrote: There can't be alternatives, unsafeIO throw by the window most guarantee that Haskell can give you and you have to provide them yourself (with a proof of this part of your program), but it's inherent to the nature of the beast

Re: [Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-09-27 Thread Chaddaï Fouché
2007/9/27, Duncan Coutts [EMAIL PROTECTED]: Infrequent, but they exist, which means you can't seek x/2 bytes ahead to seek x characters ahead. All such seeking must be linear for both UTF-16 *and* UTF-8. And in [Char] for all these years, yet I don't hear people complaining. Most string

Re: [Haskell-cafe] Puzzled

2007-10-06 Thread Chaddaï Fouché
2007/10/6, Peter Verswyvelen [EMAIL PROTECTED]: But great to know about the new strictness on vars! I really should get GHC 6.8 RC1 for Windows... Just in case you misunderstood : this functionality was already there in GHC 6.4, it's just the new syntax to active it that is available only in

Re: [Haskell-cafe] string literals and haskell'

2007-10-23 Thread Chaddaï Fouché
2007/10/23, Justin Bailey [EMAIL PROTECTED]: My two cents - I haven't found another language that handles heredocs as nicely as Ruby does. Perl Heredocs do the same things and predates Ruby's (at least they do all you described and a bit more). But what would be really nice is a way to write

Re: [Haskell-cafe] Re: Comments on reading two ints off Bytestring

2007-12-24 Thread Chaddaï Fouché
2007/12/24, Paulo J. Matos [EMAIL PROTECTED]: On Dec 24, 2007 11:55 AM, Paulo J. Matos [EMAIL PROTECTED] wrote: On Dec 23, 2007 12:44 PM, Isaac Dupree [EMAIL PROTECTED] wrote: -- this should work too parseHeader3 :: BS.ByteString - Maybe (Int, Int) --note accurate type signature,

Re: [Haskell-cafe] Re: Printing and Referential transparency excuse

2007-12-24 Thread Chaddaï Fouché
2007/12/24, Cristian Baboi [EMAIL PROTECTED]: On Mon, 24 Dec 2007 11:27:11 +0200, apfelmus [EMAIL PROTECTED] wrote: Cristian Baboi wrote: How can I define a function to do the inverse operation ? g :: String - ( a - b ) This time I cannot see how referential transparency will deny

Re: [Haskell-cafe] what does @ mean?.....

2007-12-28 Thread Chaddaï Fouché
2007/12/28, Alfonso Acosta [EMAIL PROTECTED]: @ works as an aliasing primitive for the arguments of a function f x@(Just y) = ... using x in the body of f is equivalent to use Just y. Perhaps in this case is not really useful, but in some other cases it saves the effort and space of

Re: [Haskell-cafe] what does @ mean?.....

2007-12-28 Thread Chaddaï Fouché
2007/12/28, Nicholls, Mark [EMAIL PROTECTED]: So in the example given... mulNat a b | a = b = mulNat' a b b | otherwise = mulNat' b a a where mulNat' x@(S a) y orig | x == one = y | otherwise = mulNat' a (addNat orig y) orig

Re: [Haskell-cafe] ReRe: Basic question concerning data constructors

2007-12-30 Thread Chaddaï Fouché
2007/12/30, Joost Behrends [EMAIL PROTECTED]: . Now, let's say we had tried defining ClockTime with parameters as you suggested. ClockTime' :: Integer - Integer - * Do you see the problem? In order to use the ClockTime type constructor, we would have to use Integer values.

Re: [Haskell-cafe] Re: Wikipedia on first-class object

2007-12-30 Thread Chaddaï Fouché
2007/12/30, Cristian Baboi [EMAIL PROTECTED]: A simple question: Can you write the value of x to a file where x = (1:x) ? Yes, but you'll have to write it yourself, because Haskell can't decide by itself that this value is infinite and try to print it with a recursive definition, if it could

Re: [Haskell-cafe] Re: Wikipedia on first-class object

2007-12-30 Thread Chaddaï Fouché
2007/12/30, Chaddaï Fouché [EMAIL PROTECTED]: 2007/12/30, Cristian Baboi [EMAIL PROTECTED]: A simple question: Can you write the value of x to a file where x = (1:x) ? Yes, but you'll have to write it yourself, because Haskell can't decide by itself that this value is infinite and try

Re: [Haskell-cafe] How to convert number types.

2007-12-31 Thread Chaddaï Fouché
2007/12/31, L.Guo [EMAIL PROTECTED]: Hi MailList Haskell-Cafe: I am a new haskeller. And was farmilar with C. When tring to do some calculate, like this: input = 5 :: Int factor = 1.20 :: Float output = factor ** (toFloat input) I found that I do not know any function could do just what

Re: [Haskell-cafe] Field updates in a state monad

2008-01-10 Thread Chaddaï Fouché
2008/1/10, Lutz Donnerhacke [EMAIL PROTECTED]: * Michael Roth wrote: Exists there a way to write this cleaner without writing countless set_xyz helper functions? The syntactic sugar for record modifications is simply that: sugar. You might write your own modifier functions: set_bla x y

Re: [Haskell-cafe] Wire GUI

2010-06-03 Thread Chaddaï Fouché
On Wed, Jun 2, 2010 at 5:29 PM, Andrew Coppin andrewcop...@btinternet.com wrote: Thanks to the people who replied about this. I would also like to thank my ISP for classifying the entire lot as spam and not showing it to me. *sigh* Blobs sounds interesting, but seems to require wxHaskell

Re: [Haskell-cafe] lists of arbitrary depth

2010-07-14 Thread Chaddaï Fouché
On Tue, Jul 13, 2010 at 11:28 AM, Shlomi Vaknin shlomivak...@gmail.com wrote: Thank you Bob, your example clarified how actually using such data type would appear in haskell. I naively thought it would be as simple as defining a regular list, but i see it is slightly more strict than that. I

Re: [Haskell-cafe] Mutable arrays

2008-02-02 Thread Chaddaï Fouché
2008/2/2, Rodrigo Queiro [EMAIL PROTECTED]: Sorry, I was lazy. New maximum': maximum' = foldl1' max Sorry but none of those propositions change the heart of the problem : the list of elements is totally produced before she can be consumed due to the strict monadic (IO or ST) nature of getElems.

Re: [Haskell-cafe] Mutable arrays

2008-02-06 Thread Chaddaï Fouché
2008/2/6, Jeff φ [EMAIL PROTECTED]: I have solved both of these problems in Clean using a lazy list without resorting to unsafe operations. So, it seems to me that uniqueness types are more general than monads. Are you aware that your code in Clean has some issues, like the lst not being so

Re: [Haskell-cafe] Mutable arrays

2008-02-07 Thread Chaddaï Fouché
2008/2/7, Jeff φ [EMAIL PROTECTED]: I played with your foldl1MArray' last night. I noticed it can be reduced to . . . foldl1MArray' :: (MArray a e m, Ix i) = (e - e - e) - a i e - m e foldl1MArray' f a = do (l,u) - getBounds a foldl1' (liftM2 f) (map (readArray a) (range (l,u)))

Re: [Haskell-cafe] Mutable arrays

2008-02-08 Thread Chaddaï Fouché
Après avoir un peu manipulé la solution de John pour qu'elle fasse la même chose que la mienne, je peux affirmer qu'elle est légèrement moins rapide (c'est infime et normal vu que ses leftFold passent plus d'informations), mais que les deux solutions ont au moins cet avantage d'être rapides (2s

Re: [Haskell-cafe] Mutable arrays

2008-02-08 Thread Chaddaï Fouché
Sorry for the french, I was a little bit confused... On 08/02/08, Chaddaï Fouché [EMAIL PROTECTED] wrote : After I changed John's code so that it worked on the same dataset as mine, I could benchmark both of them : My solution is a bit faster (but that's a very tiny difference and to be expected

Re: [Haskell-cafe] Embedded Functions in Algebraic Data Types?

2008-02-10 Thread Chaddaï Fouché
2008/2/10, Michael Feathers [EMAIL PROTECTED]: On a lark, I loaded this into Hugs this morning, and it didn't complain: data Thing = Thing (Integer - Integer) But, I've never seen that sort of construct in an example. Do people ever embed functions in ADTs? Yes, anyway you can embed

Re: [Haskell-cafe] nub vs. find + (:) Is this abysmal code?

2008-02-10 Thread Chaddaï Fouché
2008/2/10, Michael Feathers [EMAIL PROTECTED]: How bad is this: addProduct :: [Product] - Product - [Product] addProduct inventory product = nub (product : inventory) This is pretty terrible, if the list is consumed afterward (which we assume it will be) we should have something like a

Re: [Haskell-cafe] A beginners question

2008-02-23 Thread Chaddaï Fouché
2008/2/23, Harri Kiiskinen [EMAIL PROTECTED]: Dear All, banging my head against Haskell, but liking the feeling of hurting brains. Just a simple question: If fmap (^4) [1,2,3] = \i - shows i gives 1 16 81 In the List Monad, (=) is defined as concatMap, so this code can be

Re: [Haskell-cafe] haskellwiki and Project Euler

2008-02-24 Thread Chaddaï Fouché
2008/2/24, Rodrigo Queiro [EMAIL PROTECTED]: The only time I have found the solutions page useful is when I was working on problem 100, which I'd been thinking about on and off for several months. Eventually, I gave up and looked at the solution there, and was absolutely none the wiser as to

Re: [Haskell-cafe] haskellwiki and Project Euler

2008-02-24 Thread Chaddaï Fouché
2008/2/24, Cale Gibbard [EMAIL PROTECTED]: I encourage you to put your solutions back up, that would be good. Referencing OEIS is a bit of a cheesy way to do things. (Though if it's going to be done, one could at least make use of the excellent Math.OEIS library :) Indeed !! But I don't

Re: [Haskell-cafe] Generating a random list

2008-03-01 Thread Chaddaï Fouché
2008/3/1, Milos Hasan [EMAIL PROTECTED]: OK, thanks, this is an important point. So maybe I should have done this? main = print $ foldl1' (+) $! take 100 randFloats My intuition tells me that the $! (and `seq`) just reduces one level (to WHNF?). If so, is there a way to force complete

Re: [Haskell-cafe] (flawed?) benchmark : sort

2008-03-04 Thread Chaddaï Fouché
2008/3/4, Krzysztof Skrzętnicki [EMAIL PROTECTED]: Hi I was playing with various versions of sorting algorithms. I know it's very easy to create flawed benchmark and I don't claim those are good ones. However, it really seems strange to me, that sort - library function - is actually the

Re: [Haskell-cafe] Doubting Haskell

2008-03-04 Thread Chaddaï Fouché
2008/3/4, Alan Carter [EMAIL PROTECTED]: I've written up some reflections on my newbie experience together with both versions, which might be helpful to people interested in popularizing Haskell, at: http://the-programmers-stone.com/2008/03/04/a-first-haskell-experience/ This is truly

Re: [Haskell-cafe] (flawed?) benchmark : sort

2008-03-04 Thread Chaddaï Fouché
2008/3/4, Krzysztof Skrzętnicki [EMAIL PROTECTED]: Thanks for improved code. My point was to measure which programming patterns are faster than the others so I can learn which ones I should use. However, the thing that is really bad is the fact, that even oneliner qsort_i is faster than

Re: [Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-10 Thread Chaddaï Fouché
2008/3/11, David Menendez [EMAIL PROTECTED]: I think Adrian is just arguing that a == b should imply f a == f b, for all definable f, in which case it doesn't *matter* which of two equal elements you choose, because there's no semantic difference. (Actually, it's probably not desirable to

Re: [Haskell-cafe] lexicographic order

2008-03-30 Thread Chaddaï Fouché
2008/3/30, Bulat Ziganshin [EMAIL PROTECTED]: although the last alternative, (Branch l r) = (Branch l' r') = l == l' r = r' || l = l' seems suspicious to me. isn't it the same as (Branch l r) = (Branch l' r') = l = l' Yes, it should be : (Branch l r) = (Branch l' r') = l l' ||

Re: [Haskell-cafe] lexicographic order

2008-03-31 Thread Chaddaï Fouché
2008/3/31, Simeon Mattes [EMAIL PROTECTED]: why I should take as right (a,b) = (a',b') iff (a a' or (a == a' and b = b')) and not (a,b) = (a',b') iff (a = a' or (a == a' and b = b')) The latter seems more logical, doesn't it? No, it doesn't, since in the latter (1,2) = (1,1) because 1

Re: [Haskell-cafe] [Newbie] Problem with Data.Map (or something else ?)

2008-03-31 Thread Chaddaï Fouché
2008/3/31, Bruno Carnazzi [EMAIL PROTECTED]: Dears Haskellers, As an Haskell newbie, I'm learning Haskell by trying to resolve Euler Project problems (http://projecteuler.net/ ). I'm hanging on problem 14 (Collatz problem). I've written the following program... Which does not end in

Re: [Haskell-cafe] [Newbie] Problem with Data.Map (or something else ?)

2008-04-01 Thread Chaddaï Fouché
2008/4/1, Bruno Carnazzi [EMAIL PROTECTED]: Because I don't know anything about arrays in Haskell. Thank you for pointing this, I have to read some more Haskell manuals :) A good place to learn about Haskell's array (which come in many flavours) is this wiki page :

Re: [Haskell-cafe] [GSoC] Porting HaRe to use the GHC API

2008-04-03 Thread Chaddaï Fouché
2008/4/1, Claus Reinke [EMAIL PROTECTED]: as for the project, the are actually two APIs to consider, GHC's and HaRe's, and the main stumbling points are those things that are not in those APIs (explicitly or at all): snip Many thanks for the valuable insights. I intend to work in close

Re: [Haskell-cafe] translating from fundeps into type families

2008-04-08 Thread Chaddaï Fouché
2008/4/8, Manuel M T Chakravarty [EMAIL PROTECTED]: You need to write the instance as instance (b ~ TheFoo a, Foo a) = Bar (Either a b) where bar (Left a) = foo' a bar (Right b) = foo' (foo b :: a) If you do that, the program compile, but res still raise a panic in GHC6.8.2 .

Re: Re[2]: a faster, accumulating mapM (was Re: [Haskell-cafe] mapM vs mapM_ performance)

2008-04-25 Thread Chaddaï Fouché
2008/4/25, Niklas Broberg [EMAIL PROTECTED]: Wow. A 10x slowdown for a very commonly used function that in 99.8% of all use cases has no need for the extra laziness at all. No wonder some people say Haskell is a toy language... A toy language that is still much faster than many currently

Re: [Haskell-cafe] Stack vs Heap allocation

2008-05-11 Thread Chaddaï Fouché
2008/5/10 Edsko de Vries [EMAIL PROTECTED]: The key reason why nested additions take stack space, is because (+) on Integers is *strict* in both arguments. If it were somehow non-strict instead, then the unevaluated parts of the number would be heap-allocated rather than stack-allocated. I

Re: [Haskell-cafe] Re: dropping hyphens and \n in words

2008-05-11 Thread Chaddaï Fouché
2008/5/11 Achim Schneider [EMAIL PROTECTED]: Excuse my bluntness, but I utterly fail to make sense of this. Reformulating your understanding of it would surely be beneficial. He has a routine that gives him a list of words classified by line, and he want the hyphens to be accounted for. So

Re: [Haskell-cafe] GHC API GSoc project (was: ANN: Haddock version 2.1.0)

2008-05-14 Thread Chaddaï Fouché
2008/5/15 Claus Reinke [EMAIL PROTECTED]: Feel free to CC me or the ticket with things like that. I'll be IMHO, trying to support a semantics- and comment-preserving roundtrip in (pretty . parse) would be a good way to start (David says he's going to look at the extracting

Re: [Haskell-cafe] Re: Aren't type system extensions fun? [Further analysis]

2008-05-27 Thread Chaddaï Fouché
2008/5/27 Andrew Coppin [EMAIL PROTECTED]: Gleb Alexeyev wrote: foo :: (forall a . a - a) - (Bool, String) foo g = (g True, g bzzt) So, after an entire day of boggling my mind over this, I have brought it down to one simple example: (id 'J', id True) -- Works perfectly. \f - (f 'J',

Re: [Haskell-cafe] Re: Damnit, we need a CPAN.

2008-05-30 Thread Chaddaï Fouché
2008/5/30 Achim Schneider [EMAIL PROTECTED]: I already was pleasantly surprised when discovering cabal-install, I think it deserves some more prominence, or even integration into cabal itself, to make everyone aware of the fact that there's such a thing as automatic installation and tempt

Re: [Haskell-cafe] Re: [Haskell] ANN: random-access-list-0.1

2008-06-12 Thread Chaddaï Fouché
2008/6/12 Stephan Friedrichs [EMAIL PROTECTED]: For index, don't use Monad, use Maybe (I think that's what the recent [EMAIL PROTECTED] discussion concluded, in the context of switching Data.Map back to Maybe). I was just copying the idea from Data.Map and it's usually a good thing to have

Re: [Haskell-cafe] Memory profiling

2008-06-16 Thread Chaddaï Fouché
2008/6/16 Pieter Laeremans [EMAIL PROTECTED]: Hi, Which tools do you recommand for memory profiling haskell programs on a *nix system. I'm using haskell to develop a CGI program/script. The application has to be deployed on shared hosting infrastructure. Since I would like to be a good

Re: [Haskell-cafe] message passing style like in Haskell?

2008-06-19 Thread Chaddaï Fouché
2008/6/19 jinjing [EMAIL PROTECTED]: encode xs = xs.group.map token where token x = (x.length, x.head) Working in this direction is a question of taste, but the choice of the dot for the operator is a pretty bad idea... On the other hand, my favourite would be : encode = map (length head) .

Re: [Haskell-cafe] Help with generalizing function

2008-06-25 Thread Chaddaï Fouché
2008/6/25 leledumbo [EMAIL PROTECTED]: Hi, I'm back. I have some troubles understanding your code: ( 1:1:? is never reached. ) Why would 1:1 be reached when we search for lists with a sum of 1 ?? Your derivation is incorrect, when you're reading a list comprehension you

Re: [Haskell-cafe] Newbie: Appending arrays?

2008-07-11 Thread Chaddaï Fouché
2008/7/11 Dmitri O.Kondratiev [EMAIL PROTECTED]: I don't quite understand how Data.Array.Diff work. I tried this: let arr = listArray (1,3) [1..3] :: DiffArray Int Int then: replaceDiffArray arr [(1, 777)] array (1,3) [(1,1),(2,777),(3,3)] Why when replacing first element the second one

Re: [Haskell-cafe] Newbie: Appending arrays?

2008-07-11 Thread Chaddaï Fouché
2008/7/11 Dmitri O.Kondratiev [EMAIL PROTECTED]: How does Data.Sequence http://www.haskell.org/ghc/docs/latest/html/libraries/containers/Data-Sequence.html compares with ArrayRef for appending and accessing arrays efficiently ? It doesn't since Data.Sequence doesn't use arrays, it uses a

Re: [Haskell-cafe] Profiling nested case

2008-07-18 Thread Chaddaï Fouché
2008/7/12 Mitar [EMAIL PROTECTED]: So that I can easily change the type everywhere. But it would be much nicer to write: data Quaternion a = Q !a !a !a !a deriving (Eq,Show) Only the performance of Num instance functions of Quaternion is then quite worse. You can probably use a

Re: [Haskell-cafe] ansi2html - one program, several issues

2008-07-19 Thread Chaddaï Fouché
2008/7/19 Krzysztof Skrzętnicki [EMAIL PROTECTED]: Hi all 1) Profiling shows that very simple functions are source of great memory and time consumption. However, if I turn them off and simply print their input arguments instead, the overall time and memory consumption doesn't change. But now

Re: [Haskell-cafe] ansi2html - one program, several issues

2008-07-19 Thread Chaddaï Fouché
2008/7/19 Krzysztof Skrzętnicki [EMAIL PROTECTED]: I forgot to mention that the memory consumption is several times higher than file size. On 8,3 Mb file: 532 MB total memory in use (4 MB lost due to fragmentation). Having that 8 Mb in memory is not the problem. 532 Mb is another story. In

Re: Re[2]: [Haskell-cafe] ansi2html - one program, several issues

2008-07-19 Thread Chaddaï Fouché
2008/7/20 Krzysztof Skrzętnicki [EMAIL PROTECTED]: On Sun, Jul 20, 2008 at 12:34 AM, Bulat Ziganshin [EMAIL PROTECTED] wrote: Hello Krzysztof, Sunday, July 20, 2008, 1:55:45 AM, you wrote: 532 MB total memory in use (4 MB lost due to fragmentation). i think that Parsec library should

Re: [Haskell-cafe] How come pattern match does not recognize this code style?

2009-10-26 Thread Chaddaï Fouché
On Mon, Oct 26, 2009 at 6:08 AM, Magicloud Magiclouds magicloud.magiclo...@gmail.com wrote: Ah, I see. The reason I have to use my style is the same as others: the list is too long You don't have to put everything on the same line, you just have to indent the rest of the pattern a bit more

Re: [Haskell-cafe] AND/OR Perceptron

2009-10-31 Thread Chaddaï Fouché
On Sat, Oct 31, 2009 at 8:09 PM, Ryan Ingram ryani.s...@gmail.com wrote: where is just syntactic sugar for let...in That's not perfectly true : where and let...in don't attach to the same syntactic construction, where attaches to a definition and can works for several guard clauses whereas let

Re: [Haskell-cafe] help with Haskell performance

2009-11-07 Thread Chaddaï Fouché
2009/11/7 Eugene Kirpichov ekirpic...@gmail.com: Ah, you're right. Then we need a foldl' insertWith with a strict plus. We only need a foldl' insertWith' : (+) is already strict for all the numeric types in the Prelude. -- Jedaï ___ Haskell-Cafe

Re: [Haskell-cafe] Area from [(x,y)] using foldl

2009-11-08 Thread Chaddaï Fouché
On Sun, Nov 8, 2009 at 9:04 PM, michael rice nowg...@yahoo.com wrote: Of course! Back to the drawing board. If I understand the problem correctly, I'm not convinced that foldl is the right approach (nevermind that foldl is almost never what you want, foldl' and foldr being the correct choice

Re: [Haskell-cafe] Area from [(x,y)] using foldl

2009-11-09 Thread Chaddaï Fouché
On Sun, Nov 8, 2009 at 10:30 PM, michael rice nowg...@yahoo.com wrote: This doesn't. area :: [(Double,Double)] - Double area p = abs $ (/2) $ area' (last p):p where area' [] = 0 area' ((x0,y0),(x,y):ps) = ((x0-x)*(y0+y)) + area' (x,y):ps This function is almost

Re: [Haskell-cafe] Haskell-Newbie and Char-Function

2009-12-05 Thread Chaddaï Fouché
On Sat, Dec 5, 2009 at 4:48 PM, Jochem Berndsen joc...@functor.nl wrote: MeAdAstra wrote: Hi guys, I only started learning Haskell some days ago. Maybe one of you can give me a hint on how to implement a function that needs a character in the range (a,b,...z) and an integer number k and

Re: [Haskell-cafe] Haskell-Newbie and Char-Function

2009-12-06 Thread Chaddaï Fouché
On Sat, Dec 5, 2009 at 10:02 PM, ??? ?? m...@rkit.pp.ru wrote: fct a n = (snd $ break (==a) ['a'..'z']) !! n Not bad but you forgot that it might need to wrap around, besides break isn't really the best function to use here since we don't need the first part of the pair : shift n ch =

Re: [Haskell-cafe] pointfree-trouble

2009-12-22 Thread Chaddaï Fouché
On Tue, Dec 22, 2009 at 3:09 PM, slemi 0sle...@gmail.com wrote: this works fine, but if i leave the 'a' in the last function's definition like this: reMatr = Matr . (flip (.) unMatr) The correct point free version would be : reMatr = (Matr .) . (. unMatr) -- Jedaï

Re: [Haskell-cafe] How can i set the seed random number generator ?

2009-12-22 Thread Chaddaï Fouché
On Tue, Dec 22, 2009 at 1:16 PM, Scott Turner 1hask...@pkturner.org wrote: In haskell, i just use the following function to get the random number. It seems i donot need to set the seed of random number generator manually? rollDice ::  Int - IO Int rollDice n = randomRIO(1,n) That's correct.

Re: [Haskell-cafe] Having a look at XMonad window manager

2010-01-19 Thread Chaddaï Fouché
On Mon, Jan 18, 2010 at 11:53 PM, John Millikin jmilli...@gmail.com wrote: I've been quite happy with Ubuntu's xmonad package, though I run it within a GNOME session. Have you tried the instructions on the XMonad wiki for inter-operating with GNOME?

Re: [Haskell-cafe] Strange random choice algorithm

2010-01-31 Thread Chaddaï Fouché
On Sat, Jan 30, 2010 at 9:38 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: Also, is there a more direct way of printing an array? Sure, printing immutable arrays: print arr ~ array (lo,hi) [(lo,arr!lo), ... , (hi,arr!hi)] print (assocs arr) ~ [(lo,arr!lo), ... , (hi,arr!hi)] print

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] A small puzzle: inTwain as function of foldr

2009-06-04 Thread Chaddaï Fouché
On Thu, Jun 4, 2009 at 4:22 PM, Martijn van Steenbergen mart...@van.steenbergen.nl wrote: Bonjour café, A small puzzle: Consider the function inTwain that splits a list of even length evenly into two sublists: inTwain Hello world! (Hello ,world!) Is it possible to implement inTwain such

Re: [Haskell-cafe] force evaluation beginners question

2009-06-15 Thread Chaddaï Fouché
On Mon, Jun 15, 2009 at 6:46 PM, Nico Rollenro...@web.de wrote: Hi there I'm trying to compile a code snipped that i've go from a tutorial which uses the function force. But when I'm trying to compile it ghc reports an error that it couldn't find the defenition of force. my ghc verion is

Re: [Haskell-cafe] Re: curious about sum

2009-06-18 Thread Chaddaï Fouché
On Thu, Jun 18, 2009 at 6:38 PM, Alberto G. Coronaagocor...@gmail.com wrote: My question is: Why the process does not grow also in the lazy case and instead produces a stack overflow inmediately? This question is answered in detail on the Wiki

Re: [Haskell-cafe] Using Parsec with ByteString ?

2009-06-19 Thread Chaddaï Fouché
On Fri, Jun 19, 2009 at 1:51 PM, Fernandquarantedeu...@yahoo.fr wrote: but the parser one needs to write must parse ByteStrings instead of Strings (that is, something like having a Parsec Bytestring () type, unless I'm completely misunderstanding the situation). My problem is that I do not

Re: [Haskell-cafe] Are GADTs what I need?

2009-07-13 Thread Chaddaï Fouché
On Mon, Jul 13, 2009 at 12:41 PM, Kev Mahoneymaill...@kevinmahoney.co.uk wrote: So far, I've learnt you can do this: data Value where VInt :: Integer - Value ... VWrapper :: a - Value which can let you encode arbitrary 'dynamic' types into Value. I was hoping to be able to pattern match

Re: [Haskell-cafe] Need feedback on my Haskell code

2009-07-28 Thread Chaddaï Fouché
On Tue, Jul 28, 2009 at 3:04 PM, CK Kashyapck_kash...@yahoo.com wrote: Hi Everyone, I managed to write up the line drawing function using the following links - http://www.cs.helsinki.fi/group/goa/mallinnus/lines/bresenh.html http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell I

Re: [Haskell-cafe] Need feedback on my Haskell code

2009-07-31 Thread Chaddaï Fouché
On Fri, Jul 31, 2009 at 2:12 PM, CK Kashyapck_kash...@yahoo.com wrote: I personally find map maySwitch (unfoldr go (x1,y1,0)) and map maySwitch $ unfoldr go (x1,y1,0) more intuitive. I can read it as map the maySwitch function over the list generated from the unfolding. Is there any

  1   2   >