Re: [Haskell-cafe] mixing wxhaskell state and file io

2007-02-04 Thread Martin DeMello
On 2/5/07, Matthew Brecknell <[EMAIL PROTECTED]> wrote: I'm not familiar with wxHaskell, but I don't think wxHaskell is your problem here. It looks like you are confusing yourself with overuse of "do" notation, and perhaps a lack of understanding of the monad laws. Whenever you see this: v <- e

Re: [Haskell-cafe] How is laziness defined?

2007-02-04 Thread Matthew Brecknell
TJ said: > I went through the entry on laziness on the wikipedia wikibook. Very > nice. The wikibook sure has grown a lot since I last visited. > > http://en.wikibooks.org/wiki/Haskell/Laziness Thanks for the link. I hadn't seen that before. Although it covers irrefutable (lazy) pattern matching

Re: [Haskell-cafe] How is laziness defined?

2007-02-04 Thread TJ
I went through the entry on laziness on the wikipedia wikibook. Very nice. The wikibook sure has grown a lot since I last visited. http://en.wikibooks.org/wiki/Haskell/Laziness I believe I've got it now. By it I mean the understanding of laziness in Haskell. Even though Haskell is, strictly spea

Re: [Haskell-cafe] How is laziness defined?

2007-02-04 Thread ajb
G'day all. tjay.dreaming: > So it's just IO which makes things run huh? OK that's basically what I > said there. Cool. Yeah, but you said "output". Sending a signal to another process in Unix is I/O, which would force the process id to be evaluated, but there's no output as such. Cheers, Andre

Re: [Haskell-cafe] How is laziness defined?

2007-02-04 Thread Donald Bruce Stewart
tjay.dreaming: > On 2/5/07, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote: > >Quoting TJ <[EMAIL PROTECTED]>: > > > >> I would think that with 100% laziness, nothing would happen until the > >> Haskell program needed to output data to, e.g. the console. Quite > >> obviously that's not it. So how is l

Re: [Haskell-cafe] How is laziness defined?

2007-02-04 Thread Matthew Brecknell
> I would think that with 100% laziness, nothing would happen until the > Haskell program needed to output data to, e.g. the console. In many cases, that's exactly what it's like. > Quite obviously that's not it. So how is laziness defined in Haskell? In fact, Haskell is not defined as lazy, it

Re: [Haskell-cafe] How is laziness defined?

2007-02-04 Thread TJ
On 2/5/07, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote: Quoting TJ <[EMAIL PROTECTED]>: > I would think that with 100% laziness, nothing would happen until the > Haskell program needed to output data to, e.g. the console. Quite > obviously that's not it. So how is laziness defined in Haskell? I

Re: [Haskell-cafe] How is laziness defined?

2007-02-04 Thread Andrew Wagner
I found it useful to work through an example where lazy evaluation was important, and wrote it up in a tutorial. It may or may not help you, no guarantees, but here it is: http://www.haskell.org/haskellwiki/Haskell/Lazy_Evaluation Any comments are welcome! Andrew On 2/4/07, TJ <[EMAIL PROTECTED]

Re: [Haskell-cafe] How is laziness defined?

2007-02-04 Thread ajb
G'day all. Quoting TJ <[EMAIL PROTECTED]>: > I would think that with 100% laziness, nothing would happen until the > Haskell program needed to output data to, e.g. the console. Quite > obviously that's not it. So how is laziness defined in Haskell? It means that the program behaves as if "things

[Haskell-cafe] How is laziness defined?

2007-02-04 Thread TJ
I would think that with 100% laziness, nothing would happen until the Haskell program needed to output data to, e.g. the console. Quite obviously that's not it. So how is laziness defined in Haskell? I remember vaguely someone saying that pattern matching on a value forces it to be evaluated. Is

Re: [Haskell-cafe] Connected!

2007-02-04 Thread Nick
Bulat Ziganshin wrote: Hello haskell-cafe, i've just got ADSL connection here! it's slow (64k) and not cheap, but at least it is completely different from dial-up i've used before That's great! I'm using GPRS, so you can imagine how painful it is :-) ps Ru = Добро пожаловать в "Декларативное п

[Haskell-cafe] Re: Win32 help please

2007-02-04 Thread John Ky
Hi, I tried as suggested: hsc2hs mywin32.hsc ghc -c -O -fffi mywin32.hs which allows me to use ghci. And if I add a main function, I can also do this: hsc2hs mywin32.hsc ghc -fffi mywin32.hs -package Win32 Thanks everyone for the help. -John _

Re: [Haskell-cafe] mixing wxhaskell state and file io

2007-02-04 Thread Matthew Brecknell
Martin DeMello said: > I'm having a lot of trouble mixing file io and wxhaskell's > varCreate/Get/Set functions. I have functions > > readWords :: String -> IO WordMap > wordGrid :: WordMap -> Layout > > And within my GUI code, the following compiles (ignores the variable, > basically): > > wor

Re: [Haskell-cafe] Re: nested maybes

2007-02-04 Thread J. Garrett Morris
On 2/4/07, Martin Huschenbett <[EMAIL PROTECTED]> wrote: Hi, I've often got the same pattern with nested Maybes but inside the IO monad (sure this could be every other monad too). Assuming that I've got functions: This is where my favorite part of the mtl steps in: monad transformers. First,

[Haskell-cafe] Re: nested maybes

2007-02-04 Thread Martin Huschenbett
Hi, I've often got the same pattern with nested Maybes but inside the IO monad (sure this could be every other monad too). Assuming that I've got functions: getInput :: IO (Maybe Input) processInput :: Input -> IO (Maybe Result) printError :: IO () printResult :: Result -> IO () I observed m

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread J. Garrett Morris
On 2/4/07, Udo Stenzel <[EMAIL PROTECTED]> wrote: J. Garrett Morris wrote: > On 2/4/07, Udo Stenzel <[EMAIL PROTECTED]> wrote: Well, depends on whether we are allowed to define new combinators. I sometimes use -- Kleisli composition infixl 1 @@ (@@) :: Monad m => (a -> m b) -> (b -> m c) -> (a

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Donald Bruce Stewart
u.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 t

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] Strange behaviour with writeFile

2007-02-04 Thread Donald Bruce Stewart
cmb21: > fo/haskell-cafe>, > > Errors-To: [EMAIL PROTECTED] > Status: O > Content-Length: 778 > Lines: 27 > > Hi, > > I am observing some rather strange behaviour with writeFile. > > Say I have the following code: > > answer <- AbstractIO.readFile "filename" > l

Re: [Haskell-cafe] mixing wxhaskell state and file io

2007-02-04 Thread Donald Bruce Stewart
martindemello: > I'm having a lot of trouble mixing file io and wxhaskell's > varCreate/Get/Set functions. I have functions > > readWords :: String -> IO WordMap > wordGrid :: WordMap -> Layout > > And within my GUI code, the following compiles (ignores the variable, > basically): > > words <-

[Haskell-cafe] (no subject)

2007-02-04 Thread C Rodrigues
_ FREE online classifieds from Windows Live Expo – buy and sell with people you know http://clk.atdmt.com/MSN/go/msnnkwex001001msn/direct/01/?href=http://expo.live.com?s_cid=Hotmail_tagline_12/06

[Haskell-cafe] Generalizing three programs

2007-02-04 Thread Andrew Wagner
Hi everyone, I've got an interesting problem here I'm trying to solve. Actually, I've got several problems which seem to have a very similar structure. I want to find a way to abstract them to solve other problems which can be thought about in the same way. Here they are: http://hpaste.org/307 htt

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Neil Mitchell
Hi This is true. Some time ago I swore off the use of fromRight and fromLeft in favor of maybe, and have been forgetting about the other functions in Data.Maybe ever since. I think you mean you swore off fromJust. Unfortunately when people started to debate adding fromLeft and fromRight they

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread J. Garrett Morris
On 2/4/07, Udo Stenzel <[EMAIL PROTECTED]> wrote: J. Garrett Morris wrote: Small improvement (Data.Maybe is underappreciated): > exists str wmap = isJust exists' >where exists' = > do x <- Map.lookup (sort str) wmap > find (== str) (snd x) This is true. Some t

Re: [Haskell-cafe] List operation question

2007-02-04 Thread Robert Dockins
On Sunday 04 February 2007 14:24, Nicolas Frisby wrote: > I've always thought that when certain operations are of particular > interest, it's time to use more appropriate data structures, right? > Lists are great and simple and intuitive, but if you need such > operations as shifts, something like

Re: [Haskell-cafe] Win32 help please

2007-02-04 Thread Thomas Davie
On 4 Feb 2007, at 17:59, Stefan O'Rear wrote: On Sun, Feb 04, 2007 at 10:42:23PM +1100, John Ky wrote: # hsc2hs mywin32.hsc # ghc -fffi mywin32.hs C:/system/ghc/ghc-6.6/libHSrts.a(Main.o):Main.c:(.text+0x1b): undefined reference to `__stginit_ZCMain' C:/system/ghc/ghc-6.6/libHSrts.a(Main.o)

Re: [Haskell-cafe] List operation question

2007-02-04 Thread Bryan Donlan
Eric Olander wrote: Hi, I'm still somewhat new to Haskell, so I'm wondering if there are better ways I could implement the following functions, especially shiftl: >> moves the first element to the end of the list shiftr :: [a] -> [a] shiftr [] = [] shiftr (x:y) = y ++ [x]

Re: [Haskell-cafe] List operation question

2007-02-04 Thread Lennart Augustsson
I agree. If performance is important enough to worry about is shiftl traverses the list once or twice then it's time to switch to a better data type. On Feb 4, 2007, at 19:27 , Yitzchak Gale wrote: Nicolas Frisby wrote: I've always thought that when certain operations are of particular in

Re: [Haskell-cafe] Strange behaviour with writeFile

2007-02-04 Thread Udo Stenzel
C.M.Brown wrote: > I've found that: > > let (answer2, remainder) = parseAnswer (force answer) > > where > > force :: Eq a => a -> a > force x = if x==x then x else x > > Seems to do the trick. ...but I'd advise against using it. If the power fails at the right time, you're left with no file

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Udo Stenzel
J. Garrett Morris wrote: > Maybe has a Monad instance, so you can write this as follows (untested): > > exists str wmap = boolFromMaybe exists' >where exists' = > do x <- Map.lookup (sort str) wmap > find (== str) (snd x) > boolFromMaybe (Just _) = True >

Re: [Haskell-cafe] List operation question

2007-02-04 Thread Yitzchak Gale
Nicolas Frisby wrote: I've always thought that when certain operations are of particular interest, it's time to use more appropriate data structures, right? Lists are great and simple and intuitive, but if you need such operations as shifts, something like a deque is the way to go. This sounds

Re: [Haskell-cafe] List operation question

2007-02-04 Thread Nicolas Frisby
I've always thought that when certain operations are of particular interest, it's time to use more appropriate data structures, right? Lists are great and simple and intuitive, but if you need such operations as shifts, something like a deque is the way to go. I'm not a data structure pro, but I'

Re: [Haskell-cafe] Another Space Leak

2007-02-04 Thread Anatoly Zaretsky
On 2/4/07, Dominic Steinitz <[EMAIL PROTECTED]> wrote: test1 :: Int -> [Word8] test1 n = foldl' (zipWith xor) [0x01..0x40] (blockWord8sIn512 (pad (replicate n 0x55))) test2 :: Int -> [Word8] test2 n = foldl' (zipWith xor) [0x01..0x40] (bws (pad (replicate n 0x55))) The problem really is here:

[Haskell-cafe] mixing wxhaskell state and file io

2007-02-04 Thread Martin DeMello
I'm having a lot of trouble mixing file io and wxhaskell's varCreate/Get/Set functions. I have functions readWords :: String -> IO WordMap wordGrid :: WordMap -> Layout And within my GUI code, the following compiles (ignores the variable, basically): words <- varCreate (do {w <- readWords "wor

Re: [Haskell-cafe] List operation question

2007-02-04 Thread Lennart Augustsson
Not much better. You could define shiftl such that is does a single traversal and returns both the last element and all but the last. That will save you one traversal. On Feb 4, 2007, at 18:44 , Eric Olander wrote: Hi, I'm still somewhat new to Haskell, so I'm wondering if there are

Re: [Haskell-cafe] Suggestions for a hReadUntilStr implementation

2007-02-04 Thread Matt Revelle
Greg, Thanks, this'll be great to play around with. Cheers, Matt On 2/4/07, Greg Fitzgerald <[EMAIL PROTECTED]> wrote: Matt, > should finish evaluating when either the timer has run out or I recommend changing my implementation of hReadUntilStr so that the deadline is calculated upfront (have

[Haskell-cafe] List operation question

2007-02-04 Thread Eric Olander
Hi, I'm still somewhat new to Haskell, so I'm wondering if there are better ways I could implement the following functions, especially shiftl: moves the first element to the end of the list shiftr :: [a] -> [a] shiftr [] = [] shiftr (x:y) = y ++ [x] moves the last element to the he

[Haskell-cafe] Re: nested maybes

2007-02-04 Thread Max Vasin
> Maybe has a Monad instance, so you can write this as follows (untested): > exists str wmap = boolFromMaybe exists' > where exists' = > do x <- Map.lookup (sort str) wmap >find (== str) (snd x) > boolFromMaybe (Just _) = True > boolFromMaybe Nothing

[Haskell-cafe] Another Space Leak

2007-02-04 Thread Dominic Steinitz
Many thanks for the help on the original space leak which is now fixed -see the function pad below and test runs in small constant space. However, that has merely revealed the next space leak. The problem appears to be blockWord8sIn512 :: [Word8] -> [[Word8]] blockWord8sIn512 = unfoldr g

Re: [Haskell-cafe] Win32 help please

2007-02-04 Thread Stefan O'Rear
On Sun, Feb 04, 2007 at 10:42:23PM +1100, John Ky wrote: > # hsc2hs mywin32.hsc > # ghc -fffi mywin32.hs > C:/system/ghc/ghc-6.6/libHSrts.a(Main.o):Main.c:(.text+0x1b): undefined > reference to `__stginit_ZCMain' > C:/system/ghc/ghc-6.6/libHSrts.a(Main.o):Main.c:(.text+0x3f): undefined > reference

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread kahl
> > > \begin{code} > > catWithLen :: [a] -> (Int -> [a]) -> [a] > > catWithLen xs f = h 0 xs > > where > > h k [] = f k > > h k (x : xs) = case succ k of-- forcing evaluation > > k' -> x : h k' xs > > \end{code} > > > > Thanks but this gives

Re: [Haskell-cafe] Strange behaviour with writeFile

2007-02-04 Thread C.M.Brown
Hi Neil, > When you add that extra line the act of writing out the remainer > causes the rest of the input to be fully evaluated and hence the > filehandle is closed. Ah, yes of course :) I've found that: let (answer2, remainder) = parseAnswer (force answer) where force :: Eq a => a -> a for

Re: [Haskell-cafe] Strange behaviour with writeFile

2007-02-04 Thread Neil Davies
Its about the lazyness of reading the file. The handles on the file associated (underlying readFile) is still open - hence the resource being in use. When you add that extra line the act of writing out the remainer causes the rest of the input to be fully evaluated and hence the filehandle is clo

[Haskell-cafe] Strange behaviour with writeFile

2007-02-04 Thread C.M.Brown
Hi, I am observing some rather strange behaviour with writeFile. Say I have the following code: answer <- AbstractIO.readFile "filename" let (answer2, remainder) = parseAnswer answer if remainder == "" && answer2 == "" then do AbstractIO.putStrLn $ "completed" else do AbstractIO.putS

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Mattias Bengtsson
On Sun, 2007-02-04 at 19:54 +0530, Martin DeMello wrote: > I have a Data.Map.Map String -> (Layout, [String]) as follows: > > type Anagrams = [String] > type Cell = (Layout, Anagrams) > type WordMap = Map.Map String Cell > > exists str wmap = > let a = Map.lookup (sort str) wmap in > case

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread J. Garrett Morris
Maybe has a Monad instance, so you can write this as follows (untested): exists str wmap = boolFromMaybe exists' where exists' = do x <- Map.lookup (sort str) wmap find (== str) (snd x) boolFromMaybe (Just _) = True boolFromMaybe Nothing = False

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Lemmih
On 2/4/07, Martin DeMello <[EMAIL PROTECTED]> wrote: I have a Data.Map.Map String -> (Layout, [String]) as follows: type Anagrams = [String] type Cell = (Layout, Anagrams) type WordMap = Map.Map String Cell exists str wmap = let a = Map.lookup (sort str) wmap in case a of Not

[Haskell-cafe] nested maybes

2007-02-04 Thread Martin DeMello
I have a Data.Map.Map String -> (Layout, [String]) as follows: type Anagrams = [String] type Cell = (Layout, Anagrams) type WordMap = Map.Map String Cell exists str wmap = let a = Map.lookup (sort str) wmap in case a of Nothing -> False Just x -> case (find (== str) (sn

Re: [Haskell-cafe] Re: Space Leak Help

2007-02-04 Thread Anatoly Zaretsky
On 2/4/07, Dominic Steinitz <[EMAIL PROTECTED]> wrote: pad causes a stack overflow and pad1 uses up about 6m of heap. pad = pad' 0 where pad' l [] = [0x80] ++ ps where pl = (64-(l+9)) `mod` 64 ps = replicate pl 0x00 pad' l (x:xs) = x : pad' (l+1) xs pad = pa

Re: [Haskell-cafe] Re: Space Leak Help

2007-02-04 Thread Claus Reinke
pad causes a stack overflow and pad1 uses up about 6m of heap. pad1 xs = xs ++ [0x80] ++ ps where l = length xs pl = (64-(l+9)) `mod` 64 ps = replicate pl 0x00 wild guess: if you compute the length when the consumer reaches ps, you hold on to a copy of xs longer than needed, w

[Haskell-cafe] Win32 help please

2007-02-04 Thread John Ky
Hi, I'm interested in writing accessing some Win32 functions not available from GHC. I wrote this short little file and tried to compile: mywin32.hsc module MyWin32 where #include Then tried to compile it like this: # hsc2hs mywin32.hsc # ghc -fffi mywin32.hs C:/system/ghc/ghc-6.6/libHSrt

[Haskell-cafe] Re: Space Leak Help

2007-02-04 Thread Dominic Steinitz
If anyone wants to play with this, here's a version of the leak that doesn't need any libraries or extensions. pad causes a stack overflow and pad1 uses up about 6m of heap. Dominic. module Main(main) where import Data.Word import Data.Bits import Data.List pad = pad' 0 where pad' l [] = [0

Re: [Haskell-cafe] Alternate instance Show (Maybe a)?

2007-02-04 Thread ajb
G'day all. Quoting Sergey Zaharchenko <[EMAIL PROTECTED]>: > Yes, I think another Show-like class will probably be a better > solution... This is the one that I use. Very simple. import Text.PrettyPrint.HughesPJ class Pretty a where -- Equivalent of showsPrec prettyP :

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread Stefan O'Rear
On Sun, Feb 04, 2007 at 09:45:12AM +, Dominic Steinitz wrote: > > pad :: Num a => [a] -> [a] > > pad = pad' 0 > > where pad' l [] | l `seq` False = undefined Stupid typo, that should be: where pad' l _ | l `seq` False = undefined > > pad' l [] = [0x80] ++ ps ++ lb > > w

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread Dominic Steinitz
On Sunday 04 February 2007 08:28, Stefan O'Rear wrote: > On Sun, Feb 04, 2007 at 08:20:23AM +, Dominic Steinitz wrote: > > Someone suggested > > > > pad :: Num a => [a] -> [a] > > pad = pad' 0 > > where pad' !l [] = [0x80] ++ ps ++ lb > > where pl = (64-(l+9)) `mod` 64 > >

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread Stefan O'Rear
On Sun, Feb 04, 2007 at 08:30:44AM +, Dominic Steinitz wrote: > On Saturday 03 February 2007 19:42, [EMAIL PROTECTED] wrote: > > I would try something along the following lines (untested): > > > > \begin{spec} > > catWithLen xs f = xs ++ f (length xs) > > \end{spec} > > > > \begin{code} > > cat

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread Dominic Steinitz
On Saturday 03 February 2007 19:42, [EMAIL PROTECTED] wrote: > > I have re-written SHA1 so that is more idiomatically haskell and it is > > easy to see how it implements the specification. The only problem is I > > now have a space leak. I can see where the leak is but I'm less sure > > what to

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread Stefan O'Rear
On Sun, Feb 04, 2007 at 08:20:23AM +, Dominic Steinitz wrote: > Someone suggested > > pad :: Num a => [a] -> [a] > pad = pad' 0 > where pad' !l [] = [0x80] ++ ps ++ lb > where pl = (64-(l+9)) `mod` 64 > ps = replicate pl 0x00 > lb = i2osp 8 (8*l) >

Re: [Haskell-cafe] Space Leak Help

2007-02-04 Thread Dominic Steinitz
On Saturday 03 February 2007 19:56, Pepe Iborra wrote: > pad :: [Word8] -> [Word8] > pad xs = pad' xs 0 > > pad' (x:xs) l = x : pad' xs (succ l) > pad' [] l = [0x80] ++ ps ++ lb >     where >        pl = (64-(l+9)) `mod` 64 >        ps = replicate pl 0x00 >        lb = i2osp 8 (8*l) Pepe, Thanks b

Re: [Haskell-cafe] Suggestions for a hReadUntilStr implementation

2007-02-04 Thread Greg Fitzgerald
Matt, should finish evaluating when either the timer has run out or I recommend changing my implementation of hReadUntilStr so that the deadline is calculated upfront (have a look at System.Time), and then reducing the number of milliseconds for hReadUntilChar with each call to it. Thanks, Gre