Re: [Haskell] Probably a trivial thing for people knowing Haskell

2008-10-20 Thread Udo Stenzel
Friedrich wrote: Ok to be more concrete is the laziness hidden here? check_line line sum count = let match = matchRegex regexp line in case match of Just strs - (sum + read (head strs) :: Integer, count + 1) Nothing - (sum, count) Yes, part of

Re: [Haskell] Probably a trivial thing for people knowing Haskell

2008-10-20 Thread Udo Stenzel
Friedrich wrote: Taral [EMAIL PROTECTED] writes: Wow, talk about doing everything by hand. :) There are a lot of utility functions that make your life easier. Try this: Given a strict pair, it should work: import Control.Monad import Data.Char import Data.List import

Re: [Haskell] Re: Trying to install binary-0.4

2007-10-21 Thread Udo Stenzel
Duncan Coutts wrote: New tarball releases of Cabal-1.2.1, bytestring-0.9, binary-0.4.1, tar and others (zlib, bzlib, iconv) will appear on hackage in the next few days. I just tried one of them, iconv. First it wants a recent cabal; that's fine, I installed the darcs version. Then I get

Re: [Haskell] Re: Trying to install binary-0.4

2007-10-18 Thread Udo Stenzel
Don Stewart wrote: If I understand correctly, the main issue for Udo is simply that the MonadFix instance is required by his code, and isn't available in binary 0.3 -- the version to be used on earlier GHCs. Is that right Udo? No, the issue is that nothing works. It turns out that I actually

Re: [Haskell] Re: Trying to install binary-0.4

2007-10-14 Thread Udo Stenzel
Bjorn Bringert wrote: The tar package uses System.PosixCompat from the unix-compat package to also work under non-posix systems (read Windows). This dependency is listed in the tar.cabal file (see http://hackage.haskell.org/ packages/archive/tar/0.1/tar.cabal). System.Posix was never

Re: [Haskell] Re: Trying to install binary-0.4

2007-10-14 Thread Udo Stenzel
Ian Lynagh wrote: People interested in making it easy to use new versions of packages with old compiler releases can make a small script that installs empty Cabal packages called bytestring, containers, array, etc. That completely misses the fact that bytestring cannot be upgraded, no matter

Re: [Haskell] Re: Trying to install binary-0.4

2007-10-13 Thread Udo Stenzel
Simon Marlow wrote: - Provide a known good cabal. Make sure it installs on GHC 6.6 and 6.4. Cabal 1.2 works all the way back to GHC 6.2. The recommended way to build new packages with an old GHC will be to upgrade Cabal first. Can it be installed by a user? Because I think my GHC 6.4

Re: [Haskell] Re: Trying to install binary-0.4

2007-10-12 Thread Udo Stenzel
Udo Stenzel wrote: - install exactly one version of cabal, 1.1.6.2, and *remove* all others, - ask ghc-pkg for the description of base, then edit Data.ByteString out of that and re-register it, I forgot, I also tried tar-1.0 on GHC 6.6, and had the same problem there. Even after updating

[Haskell] Re: Trying to install binary-0.4

2007-10-11 Thread Udo Stenzel
Don Stewart wrote: Since you're not using ghc 6.8, you should use binary 0.3 :) That was PC for sorry, GHC 6.6 is no longer supported and don't even ask about 6.4 The other day I tried to install the tar library on a GHC 6.4. It's nearly impossible. The old base library gets in the way of

Re: [Haskell-cafe] XmlSerializer.deserialize?

2007-06-26 Thread Udo Stenzel
Hugh Perkins wrote: Is reflection hard in Haskell? In C# its easy, and its one of the most powerful features of C# That's another way of saying that the truly powerful features are missing from C#... Yes, but I'm kindof stuck giving useful input to makeConstrM, so if anyone has any ideas?

Re: [Haskell-cafe] dangerous inlinePerformIO in Data.Binary(?)

2007-06-17 Thread Udo Stenzel
Roberto Zunino wrote: Floating out (newBuffer defaultSize) as in | foo = newBuffer defaultSize | | toLazyByteString m = S.LPS $ inlinePerformIO $ do | buf - foo | return (runBuilder (m `append` flush) (const []) buf) would still be safe, AFAICS. Floating out buf instead should

[Haskell-cafe] dangerous inlinePerformIO in Data.Binary(?)

2007-06-14 Thread Udo Stenzel
Greetings, I was trying to understand the magic inside Data.Binary, and found two somewhat suspicious uses of inlinePerformIO, which imho has a far too innocuous name: | toLazyByteString :: Builder - L.ByteString | toLazyByteString m = S.LPS $ inlinePerformIO $ do | buf - newBuffer

Re: [Haskell] Fwd: Mutually dependent functions

2007-06-12 Thread Udo Stenzel
Michael Speer wrote: test x y = ( World , x , x ++ ++ y ) main = let ( a , b , c ) = test Hello a in do print $ ( a , b , c ) This works, but in your code you actually wrote let ( ( a, b, c ), ( d, e, f ), ( g, h, i ) ) = ( foo, bar, baz ) with the right side involving

Re: [Haskell-cafe] Re: Just for a laugh...

2007-06-02 Thread Udo Stenzel
Andrew Coppin wrote: Note that the challenge asks for the internal bitmap representation of an IEEE double-precision integer Actually it didn't. It asked for the machine's internal representation of a double precision float, and you are not guaranteed that this representation conforms to IEEE

Re: [Haskell] Re: Newbie: what are the advantages of Haskell?

2007-04-28 Thread Udo Stenzel
Michael T. Richter wrote: I wish I knew the language better so I could start working on those libraries. Which ones? those libraries cannot come into existence until someone says what's actually missing. (The bulk of CPAN is crap and is certainly not worth being reimplemented.) -Udo --

Re: [Haskell] Newbie: what are the advantages of Haskell?

2007-04-28 Thread Udo Stenzel
[EMAIL PROTECTED] wrote: what are the advantages of haskell over semi-functional programming languages such as Perl, Common Lisp, etc.? A fundamental building block that is superior in maintainability and reusability to objects and procedures, a type system that is actually of help and not a

Re: [Haskell-cafe] run-time type testing in haskell?

2007-04-28 Thread Udo Stenzel
Eric wrote: (1) Have Handlers implement a method handle(m: Msg). To add new types of message, we declare message types which extend Msg. The Handler then uses runtime type testing to decide how to deal with each message. The advantage of this design is that we can add new Handler and new

Re: [Haskell-cafe] Is Excel a FP language?

2007-04-25 Thread Udo Stenzel
Albert Y. C. Lai wrote: I say Excel is a functional language. If there needs to be the quoted distinction, fine: Excel the language is a functional language, and Excel the application is an interpreter of said language. Excel has functions, but does it treat functions as it treats other

Re: [Haskell-cafe] Re: Haskell version of Norvig's Python Spelling Corrector

2007-04-24 Thread Udo Stenzel
Pete Kazmier wrote: train:: [B.ByteString] - WordFreq train words = frequencyMap where frequencyMap = foldr incWordCount M.empty words incWordCount w m = M.insertWith (+) w 1 m So is 'incWordCount' strict in its second argument? I'm still not sure exactly

Re: [Haskell-cafe] Re: Haskell version of Norvig's Python Spelling Corrector

2007-04-24 Thread Udo Stenzel
Bryan O'Sullivan wrote: Udo Stenzel wrote: There is another bug of this sort in your code. Consider incWordCount w m = M.insertWith (+) w 1 m There is no reason to evaluate the sum inside the map, instead an unevaluated thunk is put in there. Would not Data.Map.insertWith

Re: [Haskell-cafe] Why Perl is more learnable than Haskell

2007-04-12 Thread Udo Stenzel
kynn wrote: (I don't need elegant factorial or Fibonacci functions in my everyday work.) I think you do. Most of your utility programs probably fit into the simple frame of main = interact $ unlines . map f . lines for suitable f. Of course, f is hardly ever the factorial function, but it

Re: [Haskell-cafe] runInteractiveCommand

2007-04-09 Thread Udo Stenzel
Sergey Perminov wrote: I wished to get output of unix commands in haskell code. So i wrote: -- import System.IO import System.Process eval :: String - IO String eval s = do (_,hOutput,_,hProcess) -

Re: [Haskell-cafe] newbie concatenating monad question

2007-03-24 Thread Udo Stenzel
Leandro Penz wrote: buildStuff = func1 ++ func2 ++ func3 ++ func4 My idea is to have a monad with a concatenating , so that I can: bulidStuff = do func1 func2 func3 func4 buildStuff = concat [ func1, func2, func3, func4 ] Remember, functional

Re: [Haskell-cafe] Newbie vs. laziness

2007-03-21 Thread Udo Stenzel
Alex Queiroz wrote: I don't quite get how ($!) works. I have this function: ids - liftM (map fromSql . concat ) $! quickQuery con query [] There's a difference between an IO action and the result of said action, and similarly there's a difference between making sure an action is

Re: [Haskell-cafe] LGPL libraries

2007-03-06 Thread Udo Stenzel
Neil Mitchell wrote: As others have said though, I wouldn't worry overly about it. The whole concept of static linking being wrong, but dynamic linking being fine, when you can flip between the modes just by changing compiler, is just silly. You don't infringe (or uninfringe) copyright with a

Re: [Haskell-cafe] Re: nested maybes

2007-02-05 Thread Udo Stenzel
Benjamin Franksen wrote: Udo Stenzel wrote: Sure, you're right, everything flowing in the same direction is usually nicer, and in central Europe, that order is from the left to the right. What a shame that the Haskell gods chose to give the arguments to (.) and ($) the wrong order

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Udo Stenzel
J. Garrett Morris wrote: On 2/4/07, Udo Stenzel [EMAIL PROTECTED] wrote: exists s wmap = isJust $ Map.lookup (sort s) wmap = find (== s) . snd If you're going to write it all on one line, I prefer to keep things going the same direction: Hey, doing it this way saved me a full two

Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-26 Thread Udo Stenzel
John Ky wrote: On 1/25/07, BBrraannddoonn SS.. AAllllbbeerryy KKFF88NNHH [EMAIL PROTECTED] wrote: I'm probably missing something, but: (a) Why not: data ANode = Branch { name :: String, description :: String, children :: [AnyNode] }

Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Udo Stenzel
Yitzchak Gale wrote: You're right, it is not in the docs. I don't think anyone would have planned it that way. StateT is strict only because there happens to be a line in a do-expression that looks like: (a, s') - runStateT m s The tuple pattern-match causes the strictness.

Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Udo Stenzel
Ross Paterson wrote: This (like StateT) gives you strictness in the pair, but doesn't give the strictness in the state that the original poster wanted. I think the OP wanted both. If State is lazy in the pair, a long chain of the form (a = (b = (c = ... = z))) gets build up and blows the stack

Re: [Haskell-cafe] Composing functions with runST

2007-01-03 Thread Udo Stenzel
Yitzchak Gale wrote: Here is a concrete example: Let's say you want to shuffle a large list randomly, within a larger application that lives inside some MTL monad stack. Among other things, your monad m satisfies (RandomGen g, MonadState g m), perhaps after a lift. Well, it turns out

Re: [Haskell-cafe] Arrays performance

2007-01-01 Thread Udo Stenzel
[EMAIL PROTECTED] wrote: I'm timing the following script.I'm not expert to evaluate th O'ness of this code, I hope someone can do it. The program clusters n integers in m buckets based on their distance. Anyway I thing should be linear.So I timed som executions changing the first arg. [...]

Re: [Haskell-cafe] Composing functions with runST

2007-01-01 Thread Udo Stenzel
Yitzchak Gale wrote: It seems to me that a natural notion of a state transformer in the ST monad is the type: STRef s st - ST s a Are there any useful functions of this type? I guess, your intention is that this transformer makes no other use of the ST monad than reading or writing a single

Re: [Haskell-cafe] Re: Seeking advice on a style question

2006-12-29 Thread Udo Stenzel
Steve Schafer wrote: Here's the essence of the problem. If I have this: process1 x y = let u = foo x y; v = bar u; w = baz v in w I can easily rewrite it in point-free style: process1 = baz . bar . foo That should have been process1 = (.) (baz . bar) . foo

Re: [Haskell-cafe] State separation/combination pattern question

2006-12-22 Thread Udo Stenzel
Reto Kramer wrote: What I'm really looking for is not so much the chaining of StateT compositions, but rather the isolation of StateA from StateB while they both flow from the search loop into the respective library calls (foo, bar) transparently to the application programmer. How about

Re: [Haskell-cafe] Dynamic types through unsafeCoerce

2006-12-13 Thread Udo Stenzel
Alfonso Acosta wrote: On 12/13/06, Udo Stenzel [EMAIL PROTECTED] wrote: Finished! Look Ma, no existentials, no Typeable, no wrappers, even the types have become simple! I like the fact that type parameters are removed, which makes them homegeneus and solves the problem of storing them

Re: [Haskell-cafe] Dynamic types through unsafeCoerce

2006-12-12 Thread Udo Stenzel
Alfonso Acosta wrote: If anyone finds a way of implementing something equivalent to this code without unsafeCoerce# and ... * Not changing chooseDesc or finding an equivalent * Not splitting or changing Descriptor type (I already found an equivalent way which uses existentials and in

Re: [Haskell-cafe] Dynamic types through unsafeCoerce

2006-12-09 Thread Udo Stenzel
Alfonso Acosta wrote: I've been using Data.Dynamic but the Typeable requirement doesn't go well with FFI declarations (which don't accept type contexts). You wouldn't need a Typeable context anyway; what's biting you is that Dynamic is not one of the primitive types that can pass across the

Re: [Haskell-cafe] Beginner: IORef constructor?

2006-12-01 Thread Udo Stenzel
TJ wrote: -- module Global where import Data.IORef theGlobalVariable = newIORef [] testIt = do ref - theGlobalVariable original - readIORef ref print original writeIORef ref [1,2,3]

Re: [Haskell-cafe] Difficult memory leak in array processing

2006-11-23 Thread Udo Stenzel
Niko Korhonen wrote: I have the following code whose purpose is to add dither (noise) to a given array. The code looks very straightforward but apparently it has a memory leak somewhere. No, it doesn't. It can't, because it doesn't even compile. After correcting the obvious (lo,

Re: [Haskell-cafe] Re: Debugging partial functions by the rules

2006-11-15 Thread Udo Stenzel
Donald Bruce Stewart wrote: So how do we help out the beginners, other than warning about fromJust, and providing a useful error message as we can, for when they just go ahead and use head anyway? Kill head and tail right now and provide a safe equivalent? Either uncons :: [a] - Maybe

Re: [Haskell-cafe] split string into n parts

2006-10-23 Thread Udo Stenzel
jim burton wrote: I want to split a string into 5 parts of equal length, with the last fifth padded if necessary, but can't get it right - here's what I've got - fifths s = unwords.take 5.unfoldr (Just . splitAt l) $ s ++ repeat ' ' where l = (length s + 4) `div` 5 Of course no Haskeller

Re: [Haskell-cafe] memory, garbage collection and other newbie's issues

2006-10-22 Thread Udo Stenzel
Andrea Rossato wrote: Now, the state will not be entirely consumed/evaluated by the user, and so it will not become garbage. Am I right? No. The state cannot become garbage, because there is still a reference to it. As long as runStateT has not returned, any part of the state can still be

Re: [Haskell-cafe] memory, garbage collection and other newbie's issues

2006-10-21 Thread Udo Stenzel
Andrea Rossato wrote: I did not get an appreciable improvement with performGC, as you can see from here: http://gorgias.mine.nu/haskell/a.out.withPerformGC.ps But I found a solution: just write the opml state component to a file! Obviously the values in question were not garbage, rather

Re: [Haskell-cafe] Debugging Newton's method for square roots

2006-10-15 Thread Udo Stenzel
Vraj Mohan wrote: my_sqrt :: Float - Float my_sqrt x = improve 1 x where improve y x = if abs (y * y - x) epsilon then y else improve ((y + (x/y))/ 2) x epsilon = 0.1 This works for several

Re: [Haskell-cafe] [off-topic / administrative] List Reply-to

2006-10-11 Thread Udo Stenzel
Mikael Johansson wrote: On Tue, 10 Oct 2006, Misha Aizatulin wrote: Here is an argument against Reply-To munging. I'd say I agree with it: http://www.unicom.com/pw/reply-to-harmful.html * It provides no benefit to the user of a reasonable mailer. [...] 1) get multiple copies of mails

Re: [Haskell-cafe] [off-topic / administrative] List Reply-to

2006-10-11 Thread Udo Stenzel
Robert Dockins wrote: FWIW, I'm using Apple's Mail.app, and it doesn't have a reply-to- list. In fact, I don't know of a mail client off the top of my head that does Mutt does. But that's to be expected, considering that it was written because the author was fed up with the poor handling of

Re: [Haskell-cafe] Haskell performance (again)!

2006-10-08 Thread Udo Stenzel
Yang wrote: type Poly = [(Int,Int)] addPoly1 :: Poly - Poly - Poly addPoly1 p1@(p1h@(p1c,p1d):p1t) p2@(p2h@(p2c,p2d):p2t) | p1d == p2d = (p1c + p2c, p1d) : addPoly1 p1t p2t | p1d p2d = p1h : addPoly1 p1t p2 | p1d p2d = p2h : addPoly1 p1 p2t addPoly1 p1 [] = p1 addPoly1 [] p2 =

Re: [Haskell-cafe] cutting long strings into lines

2006-09-30 Thread Udo Stenzel
Matthias Fischmann wrote: although this wasn't the original problem, i like it, too :). but now i am stuck in finding an optimal implementation for lines. Isn't the obvious one good enough? lines [] = [] lines s = go s where go [] = [[]] go ('\n':s) = [] : lines s go (c:s) = let

Re: [Haskell-cafe] Slow IO

2006-09-13 Thread Udo Stenzel
Daniel Fischer wrote: Most certainly not. I'm pretty sure this is to a bug in your code. Something retains a data structure which is actually unneeded. Probably Apparently. And my money is on a load of lines from the file (of which I need only the first and last Char). Then you're

Re: [Haskell-cafe] foreach

2006-09-13 Thread Udo Stenzel
Lemmih wrote: main = do args - getArgs flip mapM_ args $ \arg - flip mapM_ [1..3] $ \n - putStrLn $ show n ++ ) ++ arg Or even: main = do args - getArgs putStr $ unlines [ show n ++ ) ++ arg | arg - args, n - [1..3] ] I'm really at a loss

Re: [Haskell-cafe] Slow IO

2006-09-13 Thread Udo Stenzel
Ketil Malde wrote: Daniel Fischer [EMAIL PROTECTED] writes: Maybe I've misused the word segfault. I think so. A segfault is the operating-system complaining about an illegal memory access. If you get them from Haskell, it is likely a bug in the compiler or run-time system (or you were

Re: [Haskell-cafe] Slow IO

2006-09-12 Thread Udo Stenzel
Daniel Fischer wrote: The programme consumed more and more memory (according to top), kswapd started to have a higher CPU-percentage than my programme, programme died, system yelling 'Speicherzugriffsfehler', top displays 'kswapddefunct'. I believe that means my programme demanded more

Re: [Haskell-cafe] HaXml and ghci unresolved symbol

2006-09-11 Thread Udo Stenzel
Andrea Rossato wrote: It seems related to dynamic linking: I created a separated module (Xml.hs) that imports Text.XML.HaXml and parses a xml string. I then created a file (xml.hs) that imports Xml and prints name, defined in Xml.hs. The expected output should be elementTest. Whatever it is,

Re: [Haskell-cafe] HaXml and ghci unresolved symbol

2006-09-10 Thread Udo Stenzel
Andrea Rossato wrote: [12:03:[EMAIL PROTECTED]:~/devel/haskell/xml]$ ghci -package HaXml xml1.hs [logo] Loading package base-1.0 ... linking ... done. Loading package haskell98-1.0 ... linking ... done. Loading package HaXml-1.13.1 ... linking ... done. Skipping Main ( xml1.hs,

Re: [Haskell-cafe] NaN, Infinity literals

2006-09-07 Thread Udo Stenzel
Tamas K Papp wrote: Is there a way to use NaN and Infinity as literals, or at least to test if a value is NaN or Infinity? *Main let nan=0/0 *Main nan NaN *Main nan==0/0 False so storing the value does not work... Not sure what you mean here. In IEEE floating point, NaN is not equal

Re: [Haskell-cafe] Why does this program eat RAM?

2006-09-05 Thread Udo Stenzel
John Goerzen wrote: I have the below program, and I'm trying to run it on an input of about 90MB. It eats RAM like crazy, and I can't figure out why. wordfreq inp = Map.toList $ foldl' updatemap (Map.empty::Map.Map String Int) inp where updatemap nm word = Map.insertWith updatefunc

Re: Re[2]: [Haskell-cafe] Why does this program eat RAM?

2006-09-05 Thread Udo Stenzel
Bulat Ziganshin wrote: Data.HashTable may be a faster alternative for Map (if ordering isn't required) Or it may not. Finding a good hash function for the words John is counting, is a challenge itself. Finding a good one that doesn't look at each character at least once, might be outright

Re: [Haskell-cafe] [Parsec] No identEnd in ParsecToken?

2006-09-05 Thread Udo Stenzel
Stephane Bortzmeyer wrote: I'm trying to use Parsec for a language which have identifiers where the '-' character is allowed only inside identifiers, not at the start or the end. identifier = do start - letter rest - many (alphaNum | char '-') end - letter return

Re: [Haskell-cafe] Re: Re: A free monad theorem?

2006-09-03 Thread Udo Stenzel
Lennart Augustsson wrote: Well, bind is extracting an 'a'. I clearly see a '\ a - ...'; it getting an 'a' so it can give that to g. Granted, the extraction is very convoluted, but it's there. Oh, that can be remedied... m = g = m . flip g In fact, why even mention m? (=) = (. flip)

Re: [Haskell-cafe] Re: Re: A free monad theorem?

2006-09-02 Thread Udo Stenzel
Benjamin Franksen wrote: Sure. Your definition of bind (=): ... applies f to something that it has extracted from m, via deconstructor unpack, namely a. Thus, your bind implementation must know how to produce an a from its first argument m. I still have no idea what you're driving at, but

Re: [Haskell-cafe] Exercise in point free-style

2006-09-01 Thread Udo Stenzel
Julien Oster wrote: While we're at it: The best thing I could come up for func2 f g l = filter f (map g l) is func2p f g = (filter f) . (map g) Which isn't exactly point-_free_. Is it possible to reduce that further? Sure it is: func2 f g l = filter f (map g l) func2 f g = (filter

Re: [Haskell-cafe] ReadP question

2006-08-31 Thread Udo Stenzel
Chris Kuklewicz wrote: I just tried to mimic regular expression matching with ReadP and got what seems like a non-terminating program. Is there another way to use ReadP to do this? -- Simulate (a?|b+|c*)*d regular expression test = star (choice [quest (c 'a') ,plus

Re: [Haskell-cafe] state and exception or types again...

2006-08-29 Thread Udo Stenzel
Andrea Rossato wrote: Il Mon, Aug 28, 2006 at 09:28:02PM +0100, Brian Hulley ebbe a scrivere: data Eval_SOI a = SOIE {runSOIE :: State - (a, State, Output, Bool)} well, I thought that this was not possible: (=) :: m a - (a - m b) - m b And you are right. In case of an exception, you don't

Re: [Haskell-cafe] [Parsec] A combinator to match between M and N times?

2006-08-29 Thread Udo Stenzel
Stephane Bortzmeyer wrote: Parsec provides count n p to run the parser p exactly n times. I'm looking for a combinator countBetween m n p which will run the parser between m and n times. It does not exist in Parsec. infixr 2 : (:) = ap . ap (return (:)) countBetween 0 0 _ = return []

Re: [Haskell] [Haskell - I/O] Problem with 'readFile'

2006-08-27 Thread Udo Stenzel
L. J. wrote: Hi, I use the operation 'readFile' [...] How can I break that semi-closed handle for to write in the preaviously readed file? Thank you. Not at all. But you can get the same effect you get from 'readFile' if you use 'openFile' and 'hGetContents'. If you do the latter, you can

Re: Re[2]: [Haskell] [Haskell - I/O] Problem with 'readFile'

2006-08-27 Thread Udo Stenzel
Bulat Ziganshin wrote: length mates_str `seq` return () it's the same. i recommend you to use: return $! tail mates_str 'tail' should be slightly faster than 'len' ...but also slightly less correct. You probably meant 'last'. (But it's still an ugly and dangerous programming

Re: [Haskell-cafe] difference between type and newtype

2006-08-26 Thread Udo Stenzel
Andrea Rossato wrote: this is what I'm trying to do, sort of: turn the code at the button into the do-notation.[1] type MSO a = State - (a, State, Output) mkMSO :: a - MSO a mkMSO a = \s - (a, s, ) bindMSO :: MSO a - (a - MSO b) - MSO b bindMSO m f = \x - let (a, y, s1)

Re: [Haskell-cafe] Space leak whilst implementing streams

2006-08-26 Thread Udo Stenzel
[EMAIL PROTECTED] wrote: I found a way to remove this space leak, however, I do not really understand why there was a space leak in the first place. I would really appreciate any light that could be shed on this. instance ArrowChoice SF where left (SF f) = SF (\xs - combine xs (f [y

Re: [Haskell-cafe] stack overflow when using ST monad

2006-08-24 Thread Udo Stenzel
Hi Gregory, Gregory Wright wrote: step :: Tag s - ST s (Maybe Integer) step t = do c - readSTRef (count t) s - readSTRef (state t) writeSTRef (count t) (c - 1) writeSTRef (state t) (nextState s) if (c = 0) then return Nothing else return (Just c)

Re: [Haskell-cafe] Writing binary files

2006-08-21 Thread Udo Stenzel
Neil Mitchell wrote: I'm trying to write out a binary file, in particular I want the following functions: hPutInt :: Handle - Int - IO () hGetInt :: Handle - IO Int For the purposes of these functions, Int = 32 bits, and its got to roundtrip - Put then Get must be the same. How

Re: [Haskell-cafe] Last statement in 'do' must be an expression error.

2006-08-17 Thread Udo Stenzel
Szymon Z??bkiewicz wrote: The compiler tells me thats there's an error on line 10: The last statement in a 'do' construct must be an expression I think, you have reached the point where treating do-notation as magic won't help you. Remember, do nr1 - read (prompt enter 1. number: )

Re: [Haskell-cafe] How can we detect and fix memory leak due to lazyness?

2006-08-08 Thread Udo Stenzel
Ahn, Ki Yung wrote: Recently, I'm facing the dark side of laziness -- the memory leak because of laziness. Are there standardized approaches for detecting and fixing these kind of problems? Not really. As Don S. already said, try heap profiling. The function that is too lazy will show up

Re: [Haskell-cafe] creating tree with level subnodes and incrementing number?

2006-08-08 Thread Udo Stenzel
Marc Weber wrote: I've tried as an exercise to learn how to use the state monad to create a tree this way: createTree :: Int - Int - (Tree Int, Int) createTree 4 = runState $ State $ \s - (Node s [] , s+1) -- stop at level 4 createTree level = runState (do item - State $ (\s - (s,s+1))

Re: [Haskell-cafe] Why Not Haskell? (sidenote on licensing)

2006-08-07 Thread Udo Stenzel
Matthias Fischmann wrote: But if GPL is stuck to any part of the code and manages to infect the rest, the client can make you sign as many NDAs as there can be. The GPL still entitles you to sell it. Nonsense. The GPL says, *if* you distribute a binary, *then* you also have to distribute the

Re: [Haskell-cafe] Why Not Haskell? (sidenote on licensing)

2006-08-07 Thread Udo Stenzel
Matthias Fischmann wrote: And it's really not as easy to control as you suggest: If you ever take in a single patch under the GPL, This kind of thing doesn't happen by accident. Patches don't magically creep into your code, you have to apply them deliberately and you should always know whether

Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread Udo Stenzel
Hans van Thiel wrote: I'm wondering why I can't find any commercial Haskell applications on the Internet. Is there any reason for this? Of course. Corporations are conservative to the point of being boneheaded. So to avoid risk, they all went on the internet and said, Gee, I can't find any

Re: [Haskell-cafe] Why shouldn't variable names be capitalized?

2006-08-04 Thread Udo Stenzel
Martin Percossi wrote: Paul Hudak wrote: foo x y = ... We know that x and y are formal parameters, whereas if they were capitalized we'd know that they were constructors. I agree that naming can be abused. But I think it should be *me* ... Oh, you like to decide lexical ambiguities.

Re: [Haskell-cafe] Filtering a big list into the IO monad

2006-08-03 Thread Udo Stenzel
Gabriel Sztorc wrote: I want to filter a list with a predicate that returns a IO value, something that filterM is supposed to do. The problem is, filterM overflows the stack for really big lists Are you sure it's filterM's fault? Can you post the code in question? Stack overflows are

Re: [Haskell-cafe] Re: [Parsec] Backtracking with try does not work for me?

2006-08-01 Thread Udo Stenzel
Stephane Bortzmeyer wrote: The first would be to test whether bb is followed by eof or comma before accepting it. notFollowedBy actually does the opposite (checking that there are no more letters). Are you sure that you don't actually want * many1 letter `sepBy1` comma ? Just asking,

Re: [Haskell-cafe] [Parsec] Backtracking with try does not work for me?

2006-07-31 Thread Udo Stenzel
Stephane Bortzmeyer wrote: minilang = do char 'a' try (optional (do {comma ; char 'b'})) optional (do {comma ; char 'c'}) eof return OK * CUT HERE *** parse error at (line 1, column 2): unexpected c expecting b Apparently,

Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-29 Thread Udo Stenzel
Andrew Pimlott wrote: On Thu, Jul 27, 2006 at 09:59:37PM +0200, Udo Stenzel wrote: In fact, that's consistent with the current documentation, because * getFileName foo == foo * getFileName foo/ == I have to disagree with that. No, you don't. That's the current behaviour of Neil

Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-28 Thread Udo Stenzel
Andrew Pimlott wrote: On Wed, Jul 26, 2006 at 05:06:41PM -0400, David Roundy wrote: This doesn't apply uniformly to all programs--except that we can say that any path with a trailing '/' is intended to be a directory, and if it's not, then that's an error. I thought some more about this,

Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-26 Thread Udo Stenzel
Andrew Pimlott wrote: The drive functions stand on their own as a chunk, and are possibly not well suited to a Posix system, but are critical for a Windows system. Why are they critical for portable code? I am fine with Windows-specific functions, but I think it's a mistake to bundle

Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-26 Thread Udo Stenzel
Duncan Coutts wrote: On Wed, 2006-07-26 at 15:29 +0200, Udo Stenzel wrote: Exactly. I believe, a FilePath should be an algebraic datatype. We've had this discussion before. The main problem is that all the current IO functions (readFile, etc) use the FilePath type, which is just

Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-26 Thread Udo Stenzel
Andrew Pimlott wrote: Maybe the trailing slash is important enough to take into account. No, not the trailing slash. The difference between a directory and its contents is important enough. This is ususally encoded using a trailing slash, but I'd rather not worry about that detail in a

Re: Re[2]: [Haskell-cafe] REALLY simple STRef examples

2006-07-20 Thread Udo Stenzel
Chad Scherrer wrote: But why should this... sumArrays [] = error Can't apply sumArrays to an empty list sumArrays (x:xs) = runSTArray (result x) where result x = do x0 - thaw x mapM_ (x0 +=) xs return x0 work differently than this...

Re: [Haskell-cafe] Defining show for a function type.

2006-07-10 Thread Udo Stenzel
Johan Grönqvist wrote: I would like use a list (as stack) that can contain several kinds of values. data Element = Int Int | Float Float | Func : Machine - Machine | ... Now I would like to have this type be an instance of the class Show, so that I can see what the stack contains in

Re: [Haskell] rawSystem unpredictable with signals

2006-07-06 Thread Udo Stenzel
John Goerzen wrote: When I hit Ctrl-C while the child process is running, sometimes: 1) rawSystem returns ExitSuccess or 2) rawSystem raises an IOError saying the child terminated with a signal I am totally at a loss as to explain this difference in behavior. I would prefer

Re: [Haskell-cafe] A question about stack overflow

2006-06-27 Thread Udo Stenzel
Neil Mitchell wrote: Or if you don't want to go for a fold next, in a style more similar to the original: maximum [] = undefined maximum [x] = x maximum (a:b:xs) = maximum (max a b : xs) It even reproduces the stack overflow, though for a different reason. Better write it this way:

Re: [Haskell-cafe] Simple matrix

2006-06-22 Thread Udo Stenzel
Bjorn Lisper wrote: Here is one way to do it. First, you have to interpret operations on matrices as being elementwise applied. E.g, (*) is interpreted as zipWith (zipWith (*)) rather than matrix multiply What's this, the principle of greatest surprise at work? Nonono, (*) should be matrix

Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-22 Thread Udo Stenzel
[EMAIL PROTECTED] wrote: apparently - Clean has better handling of strictness issues [saying at the same time that he/she doesn't use Clean...] Uhm... well... and does it? From what I've heard, Clean has the same mechanism as Haskell, which is the 'seq' primitive. Clean just adds some

Re: [Haskell-cafe] user type declarations in Haskell

2006-06-22 Thread Udo Stenzel
Vladimir Portnykh wrote: I am trying to define the following types data MyStringType a = String deriving (Eq, Ord, Show) data QADouble a = Double deriving (Eq, Ord, Show) These are not what you think they are. MyStringType has a phantom type parameter and only one value, which is the

Re: [Haskell-cafe] Simple matrix

2006-06-22 Thread Udo Stenzel
Bjorn Lisper wrote: - your definition of fromInteger will behave strangely with the elementwise extended operations, like (+). 1 + [[1,2],[3,4]] will become [[2,2],[3,5]] rather than [[2,3],[4,5]]. Array languages supporting this kind of overloading invariably have the second form of

Re: [Haskell-cafe] what do you think of haskell ? (yes, it's a bit general ...:)

2006-06-15 Thread Udo Stenzel
minh thu wrote: but i consider to move back to c/c++. I'm led to believe that you just haven't got the hang of the things that just aren't there in C, such as Monads and higher order functions. So you cannot yet see what you would miss in C. (And I guess, you're not feeling at home in C++

Re: [Haskell-cafe] Combinations

2006-06-06 Thread Udo Stenzel
[EMAIL PROTECTED] wrote: I need a functions which takes as argument a list of lists like this one: [[1,2],[3],[4]] and gives me a list of list with all the possible combinations like this one: [[1,3,4],[2,3,4]] sequence Finding out why it is named that strangely is left as an

Re: [Haskell-cafe] Problem trying to get class Bounded to work

2006-05-23 Thread Udo Stenzel
Jacques Carette wrote: Bulat Ziganshin wrote: malloc :: Storable a = IO (Ptr a) malloc = doMalloc undefined where doMalloc :: Storable b = b - IO (Ptr b) doMalloc dummy = mallocBytes (sizeOf dummy) Is there any reason to not code this as malloc :: Storable a = IO

Re: [Haskell-cafe] parsing machine-generated natural text

2006-05-21 Thread Udo Stenzel
Evan Martin wrote: Here's the beginning of the file, where it's not obvious to me how to distinguish elements in the :: section from the rest of the file. :: Judge: USDP Game: dip Variant: standard :: Deadline: F1901M Mon 20 Feb 2006 20:00 PST :: URL:

Re: [Haskell-cafe] parsing machine-generated natural text

2006-05-21 Thread Udo Stenzel
Jason Dagit wrote: reserved units. | reserved unit. I always struggle with when I need to use 'try' with parsec. My understanding is that if 'unit.' appears in the input the first parser will parse up to the '.' and then fail and consume the input up to that point, leaving the

Re: [Haskell-cafe] parsing machine-generated natural text

2006-05-20 Thread Udo Stenzel
Evan Martin wrote: Unfortunately, the output is intended to be human-readable, and this makes parsing it a bit of a pain. Here are some sample lines from its output: France: Army Marseilles SUPPORT Army Paris - Burgundy. Russia: Fleet St Petersburg (south coast) - Gulf of Bothnia.

  1   2   >