Re: [Haskell-cafe] Diagnosing stack overflow

2007-08-16 Thread Matthew Brecknell
Justin Bailey: I am trying to determine why my stack overflows in my medium sized program [...snip...] prefixesAtLeast :: Int - [S.ByteString] - Int prefixesAtLeast !0 !ss | null ss = 0 | all S.null ss = 0 | otherwise = -1 prefixesAtLeast !n !ss = prefixesAtLeast' n ss where

Re: [Haskell-cafe] I'm stuck in my thought experiment

2007-08-16 Thread Matthew Brecknell
Levi Stephen: [...] I was imagining a drag and drop web page designer. There are a bunch of Widgets (e.g., BlogWidget, TextWidget, MenuWidget, etc) that the user can place on the page. [...] class Widget a where render :: a - Html -- A page has a title and a Widget. -- I know this

Re: [Haskell-cafe] Diagnosing stack overflow

2007-08-18 Thread Matthew Brecknell
Justin Bailey: Would retainer profiling help me see what was building up this large thunk/closure? I'm not really familiar enough with GHC's profiling to answer that, but I'll take a guess. My guess is that profiling will only sometimes be useful in diagnosing stack overflows, because I

Re: [Haskell-cafe] Re: newbie : multi-parameter type classes

2007-08-24 Thread Matthew Brecknell
Unfortunately http://www.cse.ogi.edu/~mpj/pubs/fundeps.html is broken. http://web.cecs.pdx.edu/~mpj/pubs/fundeps.html ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Help understanding type error

2007-09-06 Thread Matthew Brecknell
Levi Stephen: I have a data type: data T a = forall b. (Show b) = T b a and I want to use/extract 'b' from this. You can't. (Well, I believe you can if you have prior knowledge of the actual type of the existentially wrapped b, and you're willing to use an unsafe coerce, but I've never

[Haskell-cafe] Re: [Haskell] Functor ((,) a)

2007-09-19 Thread Matthew Brecknell
Janis Voigtlaender: What do I have to import to get the Functor ((,) a) instance? (redirected to haskell-cafe) Control.Monad.Instances, believe it or not. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Accumulator value for and and or

2007-09-20 Thread Matthew Brecknell
PR Stanley: or = foldl (||) False and = foldl () True [...] Other than the practical convenience is there a reason for having the empty list in and and or equating to True and False? It might help to think of and as a kind of product, and or as a kind of sum, and note that: sum [] = 0

Re: [Haskell-cafe] Complexity question

2007-09-24 Thread Matthew Brecknell
Andrew Coppin: Anybody happen to know what the time complexity of transpose is? Bas van Dijk: The worst case time complexity is O(r*c) where 'r' are the number of rows and 'c' are the number of columns. I believe Bas is correct, though it might be worth elaborating on what he means by worst

Re: [Haskell-cafe] Automatic file closing after readFile

2007-10-18 Thread Matthew Brecknell
Magnus Therning: hasEmpty s = let _first_empty = s !! 0 == '\n' _last_empty = (reverse s) !! 1 == '\n' in _first_empty || _last_empty loadAndCheck fp = liftM hasEmpty $ readFile fp main = getArgs = filterM loadAndCheck = mapM_ putStrLn The one

Re: [Haskell-cafe] Automatic file closing after readFile

2007-10-18 Thread Matthew Brecknell
Magnus Therning: Still no cigar :( Yes, this is a little more subtle than I first thought. Look at liftM and filterM: liftM f m1 = do { x1 - m1; return (f x1) } filterM :: (Monad m) = (a - m Bool) - [a] - m [a] filterM _ [] = return [] filterM p (x:xs) = do flg - p x ys - filterM p xs

Re: [Haskell-cafe] Automatic file closing after readFile

2007-10-18 Thread Matthew Brecknell
Magnus Therning: Just out of curiosity, how would I go about finding this myself? (Ideally it'd be an answer other than read the source for the libraries you are using. :-) Well, I can at least try to expand a little on read the source. :-) You'll first need a solid understanding of lazy

Re: [Haskell-cafe] Function Types

2007-10-22 Thread Matthew Brecknell
PR Stanley: f x = x x :: a f x :: b therefore f :: a - b x = a and x = b therefore a = b therefore f :: a - a Simple mappings are easy to work out. It's the more detailed stuff I'm not sure about. You've got the right idea. Type inference involves a process called unification. This is

Re: [Haskell-cafe] Re: Waiting for thread to finish

2007-11-27 Thread Matthew Brecknell
Brad Clow: However, I have a more complex app, where I haven't forgotton to use the right flags :-) and the utilisation of cores is very poor. I am thinking it is due to laziness. I am currently wondering how GHC handles the case where the function that is being forked uses lazy arguments?

Re: [Haskell-cafe] Re: Waiting for thread to finish

2007-11-27 Thread Matthew Brecknell
Brad Clow: If you would like to wait on multiple threads, you can use STM like so: import Control.Concurrent import Control.Concurrent.STM import Control.Exception main = do tc - atomically $ newTVar 2 run tc (print (last [1..1])) run tc (print (last [1..11000]))

Re: [Haskell-cafe] Re: Waiting for thread to finish

2007-11-27 Thread Matthew Brecknell
Brad Clow: So does GHC implement some sychronisation given that a mutation is occuring under the covers, ie. the thunk is being replaced by the result? I believe so, but I have no idea of the details. I am using a TVar to build results of forked functions in. I had a quick go at changing to

Re: [Haskell-cafe] Waiting for thread to finish

2007-11-28 Thread Matthew Brecknell
Brad Clow: When I (deeply) force the worker thread's results to be strict, I observe both cores working, but the execution time (elapsed) slower. I can only speculate, but since you emphasise deep forcing, I wonder how deep is the structure returned from the worker thread? Could it be deep

Re: [Haskell-cafe] Trees

2007-12-03 Thread Matthew Brecknell
Adrian Neumann: data Tree a = Leaf a | Node a [Tree a] example: given a tree t and two nodes u,v, find the first common ancestor. The following solves what I think is a generalisation of this problem. That is, given a tree and a predicate on its elements, return the smallest subtree

Re: [Haskell-cafe] Re: Waiting for thread to finish

2007-12-03 Thread Matthew Brecknell
Ryan Ingram said: Interesting, although this seems like a perfect use for orelse: wait_stm :: Wait a - STM a wait_stm (Wait w) = readTVar w = maybe retry return wait :: Wait a - IO a wait w = atomically $ wait_stm w wait_first :: [Wait a] - IO (a, [Wait a]) wait_first [] = error

Re: [Haskell-cafe] Multiple statements with Where

2007-12-18 Thread Matthew Brecknell
insertjokehere wrote: where bm = bracketMatch str nstr = words (snd (bracketMatch str)) It looks like you have set your editor to make tabs look like four spaces. Haskell compilers are required to interpret tabs as being equivalent to eight spaces, so it

Re: [Haskell-cafe] Asynchronous exception wormholes kill modularity

2010-03-25 Thread Matthew Brecknell
Hi Bas, Bas van Dijk wrote: block $ do ... modifyMVar_ m f ... From a quick glanse at this code it looks like asynchronous exceptions can't be thrown to this transaction because we block them. However the unblock in modifyMVar_ opens an asynchronous exception

Re: [Haskell-cafe] (a - [b]) - [a - b] ?

2006-12-04 Thread Matthew Brecknell
Joachim Breitner: here I use that map (\n - l !!n ) [1..] == l. I hope that is valid map (\n - l !! n) [1..] is more like (tail l). Did you mean to use [0..]? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Re: Would someone explain this code to me?

2006-12-06 Thread Matthew Brecknell
What I don't understand is his use of the T constructor, both at insertSet x s = T B a y b Here it creates a new RedBlackSet and in the where statement: T _ a y b = ins s Here it's a pattern match. So if ins s returns (T x a' y' b'), then a = a'; y = y'; b =

Re: [Haskell-cafe] Large data structures

2006-12-11 Thread Matthew Brecknell
No. Haskell's lists are linked lists, enlarge creates a single new link without modifying (and copying) the original. Thanks. Is there a way to mimic this behaviour with my own code? Yes. Take a look at Data.Map. This data structure provides various operations which create a new map from

Re: [Haskell-cafe] constant functions

2006-12-27 Thread Matthew Brecknell
This is what I've been trying: always :: (a - a) - a - a always x = (\y - x) Your function implementation is correct, but the type is wrong. Try this: always :: a - b - a Or, just use the function const, from the Prelude. :-) The type system can be very handy when learning Haskell. If you

Re: [Haskell-cafe] constant functions

2006-12-27 Thread Matthew Brecknell
complement :: (a - Bool) - a - Bool complement p x = not (p x) By the signature, the first argument is a function (predicate) which when given a value returns a Bool? And the second argument is just a value? And the function returns a Bool? Indeed. In the type expression, the lower-case

Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread Matthew Brecknell
breakUp s | L.null s = [] | otherwise = h:(breakUp r) where (h,r) = L.splitAt 72 s Running this on the 2G file blows up the stack pretty quickly, taking the first 1 million records (there are 20M of them) with a big stack parameter gives about 25%

Re: [Haskell-cafe] different performance of equivalent expression

2007-01-12 Thread Matthew Brecknell
I've run into strange effect that I can not explain. I have simple expression that can be written by two equivalent ways. However one way give much performance gain over another. Here is an example: -- apply function many times (tail-recursive) many n f x = if n == 0 then x else many (n-1)

Re: [Haskell-cafe] STM and random numbers

2007-01-12 Thread Matthew Brecknell
Rather than having a separate thread computing the random numbers using IO, why not just stick an StdGen in a TVar and write a function like: type RandomVar = TVar StdGen rnd :: RandomVar - STM a rnd var = do g - readTVar var let (r,g') = random g writeTVar var g' return r The

[Haskell-cafe] Fixed-point operator (was: seq does not preclude parametricity)

2007-01-28 Thread Matthew Brecknell
On Wed, 24 Jan 2007 10:41:09 -0500, Robert Dockins wrote: newtype Mu a = Roll { unroll :: Mu a - a } omega :: a omega = (\x - (unroll x) x) (Roll (\x - (unroll x) x)) fix :: (a - a) - a fix f = (\x - f . (unroll x) x) (Roll (\x - f . (unroll x) x)) omega ones :: [Int] ones = fix (1:)

Re: [Haskell-cafe] ANNOUNCE: The Monad.Reader - Issue 6

2007-01-31 Thread Matthew Brecknell
dw :: (a - Bool) - [a] - [a] dw p = reverse . fst . foldl comb ([],False) where comb (xs,done) x | done = (x:xs, True) | p x = (xs, False) | otherwise = (x:xs, True) Which is the simplest working algorithm I could come up with;

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): words -

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 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 in

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

2007-02-05 Thread Matthew Brecknell
I said: Although it covers irrefutable (lazy) pattern matching in the second section, it does appear to miss the point that let bindings are always irrefutable. Thus, there is no difference between these two: let (x,y) = foo in ... let ~(x,y) = foo in ... Andrew Bromage said: let (x,())

Re: [Haskell-cafe] What's wrong with cgi-undecidable?

2007-02-09 Thread Matthew Brecknell
http://darcs.haskell.org/packages/cgi-undecidable/ There only 3 or 4 lines of source code, but it can't be installed. The ghc version is 6.6 . Undecidable.hs:23:0: Duplicate instance declarations: instance [overlap ok] (MonadTrans t, MonadCGI m, Monad (t m)) =

Re: [Haskell-cafe] What's wrong with cgi-undecidable?

2007-02-10 Thread Matthew Brecknell
[EMAIL PROTECTED] said: Then another problem,after I unregistered cgi-2006.9.6,the fastcgi-2006.10.9could't work well with cgi-1.0 . You might need fastcgi-1.0: http://www.cs.chalmers.se/~bringert/darcs/haskell-fastcgi Actually,I was trying my best to install hope:

Re: [Haskell-cafe] Query

2007-02-10 Thread Matthew Brecknell
vishy anand [EMAIL PROTECTED] said: hi i am going through yaht tutorial and exercise 4.6 and 4.7..i understood 4.6,but not 4.7 in which fromTuple (One a ) = Left (Left a ) and fromTuple (Two a b ) = Left (Right (a,b) ) function r written..why use Either type..cant i just say fromTuple (Two a

Re: [Haskell-cafe] Re: Optimization fun

2007-02-10 Thread Matthew Brecknell
Rafael Almeida said: I've always found the following definition of the sieve of eratosthenes the clearest definition one could write: sieve [] = [] sieve (x:xs) = x : sieve [y | y - xs, y `mod` x /= 0] It doesn't perform better than Augustsson's solution. It does fairly worse, actually,

Re: [Haskell-cafe] Re: Optimization fun

2007-02-11 Thread Matthew Brecknell
I wrote: primes :: [Int] primes = 2 : filter isPrime [3,5..] where f x p r = x p*p || mod x p /= 0 r isPrime x = foldr (f x) True primes Creighton Hogg wrote: This looks really slick to me, thanks. So if I understand correctly, the main thing that makes this work is that 'ing the

Re: Re[2]: [Haskell-cafe] Re: Optimization fun

2007-02-12 Thread Matthew Brecknell
Lennart Augustsson said: Many architectures gives both the quotient and remainder when you use the division instruction, so divMod (quotRem) shouldn't cost more than a div or mod. But if the code generator takes advantage of that is another matter. You're quite right. Bulat Ziganshin

Re: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Matthew Brecknell
Marc Weber said: I'll try to explain why I don't get it yet class (Monad m) = GetMV m a where (1) tells that the first param called 'm' is an instance of class m, right? Then it doesn't matter wether I use instance GetMV m c where or instance GetMV any name c

Re: [Haskell-cafe] Recursion in Haskell

2007-02-19 Thread Matthew Brecknell
P. R. Stanley: is there another general pattern for mylen, head or tail? mylen [] = 0 mylen (x:xs) = 1 + mylen (xs) head [] = error what head? head (x:xs) = x tail [] = error no tail tail (x:xs)= xs Benjamin Franksen: Another very common 'pattern' is to factor the recursion into a

Re: [Haskell-cafe] Safe lists with GADT's

2007-02-25 Thread Matthew Brecknell
Neil Mitchell wrote: data ConsT a data NilT data List a t where Cons :: a - List a b - List a (ConsT b) Nil :: List a NilT Stefan O'Rear wrote: data VarList a = forall t. VarList (List a t) fromListV :: [a] - VarList a fromListV [] = VarList Nil fromListV (x:xs) = case

Re: [Haskell-cafe] State monad in the wikibood article

2007-02-28 Thread Matthew Brecknell
TJ [EMAIL PROTECTED] said: In the wikibook article here: http://en.wikibooks.org/wiki/Haskell/Understanding_monads, which really does an excellent job explaining things (nuclear waste woohoo!), I am stuck at the following code snippet: container = fn = \st - let (a, st2) = container st

Re: [Haskell-cafe] splitting strings

2007-03-01 Thread Matthew Brecknell
h. said: splitS :: String - String - [String] splitS a b = splitA a b where z = length b - 1 splitA [] _ = [] splitA (c:cs) (d:ds) | c == d fst s == ds = : splitA (snd s) b | otherwise = (c : head r) : tail r where r =

Re: [Haskell-cafe] Re: [Haskell] Laziness and the IO Monad (randomness)

2007-03-02 Thread Matthew Brecknell
Dave Tapley wrote: However this latter case gets stuck in an infinite loop, terminating on a stack overflow. Kirsten Chevalier said: You didn't say which function you had narrowed down the stack overflow to, but I suspect it's here: firstTen :: IO [Int] firstTen = do infiniteNums

Re: [Haskell-cafe] is there already a function that does this?

2007-03-03 Thread Matthew Brecknell
Jared Jennings: -- Sort the [a]'s by the [b]'s. sortByKeys :: (Ord b) = [b] - [a] - [a] sortByKeys keys values = map snd $ sortBy compareFst (zip keys values) where compareFst x y = compare (fst x) (fst y) Henk-Jan van Tuyl: You can simplify that to: sortByKeys :: (Ord b) = [b] -

Re: [Haskell-cafe] Wrong Answer Computing Graph Dominators

2008-04-17 Thread Matthew Brecknell
Dan Weston wrote: Here, any path means all paths, a logical conjunction: and [True, True] = True and [True ] = True and [ ] = True Kim-Ee Yeoh wrote: Hate to nitpick, but what appears to be some kind of a limit in the opposite direction is a curious way of arguing that:

Re: [Haskell-cafe] Stronger STM primitives needed? Or am I just doing it wrong?

2008-04-22 Thread Matthew Brecknell
Ryan Ingram said: How can I implement the following operation efficiently in STM? Given a TVar now, waitFor t0 = do t - readTVar now if (t t0) then retry else return () This naive implementation has the problem that the transaction gets restarted every time now gets updated,

Re: [Haskell-cafe] Re: Stronger STM primitives needed? Or am I just doing it wrong?

2008-04-22 Thread Matthew Brecknell
Ryan Ingram said: retryUntil :: TVar a - (a - Bool) - STM () [...] the semantics would be that the transaction log, instead of saying I read from v would say I read from v and failed because v didn't satisfy this predicate. Changes to any other variable in the log would have the same

Re: [Haskell-cafe] Stronger STM primitives needed? Or am I just doing it wrong?

2008-04-23 Thread Matthew Brecknell
Ryan Ingram said: So, if have a transaction T that is waiting inside retry for a variable that it read to change, and a variable that is only accessed in a subatomic part of T is changed, we can try running the subatomic computation first. Here are the four cases: 1) The subatomic

Re: [Haskell-cafe] Stronger STM primitives needed? Or am I just doing it wrong?

2008-04-23 Thread Matthew Brecknell
I said: In that case, we can treat subatomic as a hint to the STM runtime. It could have a simpler type, and the semantics of id: subatomic :: STM a - STM a If the subatomic transaction turns out to be read-only, then we get the benefit of all four cases Ryan describes above. If it turns

Re: [Haskell-cafe] Caching the Result of a Transaction?

2008-04-26 Thread Matthew Brecknell
Conal Elliott said: Can we implement a type 'TIVal a' (preferably without unsafePerformIO) with the following interface: newIVal :: STM (TIVal a, a - STM ()) -- or IO (...) force :: TIVal a - STM a instance Functor IVal instance Applicative IVal instance Monad

Re: [Haskell-cafe] OT: Paper on increasing entropy in software systems

2008-06-15 Thread Matthew Brecknell
I was just listening to Brooks' talk at OOPSLA 2007 and in the QA part at the end he mentions a paper on increasing entropy in software systems. He mentions the authors' names but I can't quite make it out and Google hasn't been very helpful either. He says the paper #8220;must be

Re: [Haskell-cafe] STM semantics

2009-10-24 Thread Matthew Brecknell
Hi Paolino, You wrote: I have a doubt that this code works like I want because actual STM implementation exposes its effects import Control.Concurrent import Control.Concurrent.STM main = do c - atomically $ newTChan :: IO (TChan ()) r - atomically $ newTVar False forkIO $

Re: [Haskell-cafe] Names for properties of operators

2009-11-07 Thread Matthew Brecknell
Hi Neil, You wrote: [...] Is there a name for this property, which I'm numbering 1, (where (%) :: a - b - b; i.e. the operator is potentially, but not necessarily, asymmetrically typed): 1: a % (b % c) = b % (a % c) I don't know any snappy names for this, but the following might help to

Re: [Haskell-cafe] Re: ANN: hakyll-0.1

2009-12-08 Thread Matthew Brecknell
Tom Tobin wrote: I'm thinking something along these lines: The background situation: X is a library distributed under the GPL. Y is another library that uses that library and requires it in order to compile and function. 1) Is there any scenario where Y can be distributed under a non-GPL

Re: [Haskell-cafe] forkSequence, runPar, parallelize (was: Re: You are in a twisty maze of concurrency libraries, all different ...)

2009-12-09 Thread Matthew Brecknell
Antoine Latter wrote: A similar function that I'm fond of: forkExec :: IO a - IO (IO a) It's cute that forkExec already has a dual operation with just the right name (specialised to IO): join :: IO (IO a) - IO a ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Non-termination of type-checking

2010-01-27 Thread Matthew Brecknell
Ryan Ingram wrote: The compiler doesn't loop for me with GHC6.10.4; I think GADTs still had some bugs in GHC6.8. That said, this is pretty scary. Here's a simplified version that shows this paradox with just a single GADT and no other extensions. No use of fix or recursion anywhere! {-#

Re: [Haskell-cafe] Proving stuff about IORefs

2010-10-17 Thread Matthew Brecknell
Hi Ben, Ben Franksen wrote: Suppose we have a function f :: IORef a - IO b I want to prove that f r == do s1 - readIORef r r' - newIORef s1 x - f r' s3 - readIORef r' writeIORef r s3 return x I'm not sure where in your question the quantifiers for

Re: [Haskell-cafe] Typing efficient folds

2009-04-27 Thread Matthew Brecknell
Keith Battocchi wrote: data Nest a = Nil | Cons(a, (Nest (Pair a))) type Pair a = (a,a) pair f (a,b) = (f a, f b) efold :: forall n m b. (forall a. n a) - (forall a . (m a, n (Pair a)) - n a) - (forall a. Pair (m a) - m (Pair a)) - (forall l z. (l b - m (z b)) - Nest (l b) -

Re: [Haskell-cafe] Re: Typing efficient folds

2009-04-28 Thread Matthew Brecknell
Keith Battocchi wrote: Thanks for explicitly writing out the unification steps; this makes it perfectly clear where things are going wrong. I was hoping to be able to have b' ~ b, l' b' ~ (l b, l b), and z' b' ~ (z b, z b). I guess it makes sense that these types can't be inferred - is

Re: [Haskell-cafe] ok, someone check me on this (type unification from the (=)/fmap thread)

2009-05-10 Thread Matthew Brecknell
Brandon S. Allbery KF8NH wrote: I can't tell where I'm making the mistake here. In Just 3 = (+1), we have, with some alpha conversions to make the unification easier to follow: Just 3 :: Num i = Maybe i -- (1) (=) :: m a - (a - m b) - m b -- (2) (+1) :: Num n = n - n-- (3)

Re: [Haskell-cafe] Need some help with an infinite list

2009-06-16 Thread Matthew Brecknell
Thomas Davie wrote: letterCombos = map (:[]) ['a'..'z'] ++ concatMap (\c - map ((c++) . (: [])) ['a'..'z']) letterCombos Not hugely efficient, if you generate the strings in reverse then you can use (c:) rather than ((c++) . (:[])), but that may not be useful to you. Bob I think

Re: [Haskell-cafe] Need some help with an infinite list

2009-06-17 Thread Matthew Brecknell
Reid Barton wrote: I'm surprised everyone is giving clever recursive solutions rather than concatMap (\n - replicateM n ['a'..'z']) [1..] Regards, Reid Well, you've lost efficient sharing with respect to my previous solution and one other. But it's a fair call, so... tail $ concat $

Re: [Haskell-cafe] Re: Need some help with an infinite list

2009-06-18 Thread Matthew Brecknell
. Answer 1 (by Matthew Brecknell): concat $ tail $ iterate (map (:) ['a' .. 'z'] *) [[]] I actually said tail $ concat $ iterate ..., because I think the initial empty string is logically part of the sequence. Tacking tail on the front then produces the subsequence requested by the OP. I

Re: [Haskell-cafe] Re: Need some help with an infinite list

2009-06-20 Thread Matthew Brecknell
Thomas Hartman wrote: could someone explain sharing? A good tool for visualising the difference between shared and non-shared results would be vacuum, using one of its front ends, vacuum-cairo or vacuum-ubigraph. http://hackage.haskell.org/package/vacuum

Re: [Haskell-cafe] Python vs Haskell in tying the knot

2009-07-15 Thread Matthew Brecknell
Robert Greayer wrote: Isn't tying the knot (in the way 'fib' does) straightforward with closures a la Python/Ruby/Smalltalk (without mutation)? Even in a syntactically clumsy language like Java, a tying-the-knot implementation equivalent to the canonical Haskell one is not difficult, e.g.

Re: [Haskell-cafe] Parallel programming in Haskell : a reading list

2009-09-04 Thread Matthew Brecknell
Don Stewart wrote: http://donsbot.wordpress.com/2009/09/03/parallel-programming-in-haskell-a-reading-list/ Are there any good resources I'm missing? http://www.haskell.org/~simonmar/papers/concurrent-data.pdf ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] (mostly OT) Strange patterns of commas

2009-09-27 Thread Matthew Brecknell
Now see if you can tell us why this pattern is similar: [ replicate n '-' | n - [140..171] ] Hint: Look at the closed form as n gets big: http://en.wikipedia.org/wiki/Fibonacci_number#Closed_form_expression After that, you can tell us why it's a parabola. Matthias Kilian wrote: Fibonacci

[Haskell-cafe] Re: [Haskell] The initial view on typed sprintf and sscanf

2008-09-01 Thread Matthew Brecknell
oleg [1]: We demonstrate typed sprintf and typed sscanf sharing the same formatting specification. [1]http://www.haskell.org/pipermail/haskell/2008-August/020605.html Reading Oleg's post, I noticed that it is quite straightforward to generalise printing to arbitrary output types. class

Re: [Haskell-cafe] Red-Blue Stack

2008-09-25 Thread Matthew Brecknell
Matthew Eastman said: i.e. popping Blue in [Red, Red, Blue, Red, Blue] would give [Red, Red, Blue] Hmm, did you mean [Red,Blue] or [Red,Red,Red,Blue]? Judging by your implementation of remUseless, I'm guessing the latter. Here is a more straightforward approach than apfelmus'. I store

Re: [Haskell-cafe] Problems with strictness analysis?

2008-11-03 Thread Matthew Brecknell
Don Stewart: Optimisations enable strictness analysis. Luke Palmer: I was actually being an annoying purist. f is strict means f _|_ = _|_, so strictness is a semantic idea, not an operational one. Optimizations can change operation, but must preserve semantics. Henning Thielemann: Maybe I

Re: [Haskell-cafe] Is unsafePerformIO safe here?

2008-12-07 Thread Matthew Brecknell
John Ky said: Does that mean there is no place to store state while running the interpreter [...]? If all you are doing is experimenting at the GHCi prompt, then maybe this is what you are missing: ... moo - newTVarIO 1 ... :t moo moo :: TVar Integer ... atomically (readTVar moo) 1 ... You

Re: [Haskell-cafe] IO and lazyness.

2007-03-06 Thread Matthew Brecknell
Daniel McAllansmith: The problem is that hGetContents only reads the contents of the file on demand and, without the 'return $!' you don't demand the value until somewhere outside of rechf. By this point the hClose has happened and hGetContents has no access to the file = no lines = no

Re: [Haskell-cafe] Foralls in records

2007-03-13 Thread Matthew Brecknell
Adde: data TransactionT = forall c. (Connection c) = TransactionT c data Transaction a = Transaction (TransactionT - (a, TransactionT)) getConnection :: Transaction c getConnection = Transaction (\t@(TransactionT c) - (c, t)) class Connection c where connectionExecute :: c - String -

Re: [Haskell-cafe] Defining types (newbie)

2007-03-13 Thread Matthew Brecknell
John Fouhy: But if I want to combine tcEqOne and tcGtThree I run into type problems, because one of them uses Strings and the other Integers. I want to break the type dependence between the arguments of And; can I do this? Try this. You'll also need to change ThingCompare a to ThingCompare

Re: [Haskell-cafe] Defining types (newbie)

2007-03-13 Thread Matthew Brecknell
I said: Try this. You'll also need to change ThingCompare a to ThingCompare in all your function type signatures. data ThingCompare = forall a. TC (BooleanOp a) (Field a) | And ThingCompare ThingCompare | Or ThingCompare ThingCompare Sorry. For that to work, you would need

Re: [Haskell-cafe] Lazy IO and closing of file handles

2007-03-14 Thread Matthew Brecknell
Pete Kazmier: When using readFile to process a large number of files, I am exceeding the resource limits for the maximum number of open file descriptors on my system. How can I enhance my program to deal with this situation without making significant changes? AFAIU, file handles opened by

Re: [Haskell-cafe] Re: Foralls in records

2007-03-14 Thread Matthew Brecknell
Adde: Thanks, using pattern matching to avoid mentioning the type didn't even cross my mind. You are correct in assuming that I thought I could get away with getConnection :: Connection c = Transaction c. To be honest, I still don't understand why it's too polymorphic. To me it says

Re: [Haskell-cafe] Lazy IO and closing of file handles

2007-03-15 Thread Matthew Brecknell
Ketil Malde: Perhaps this is an esoteric way, but I think the nicest approach is to parse into a strict structure. If you fully evaluate each Email (or whatever structure you parse into), there will be no unevaluated thunks linking to the file, and it will be closed. Not necessarily so,

Re: [Haskell-cafe] Lazy IO and closing of file handles

2007-03-18 Thread Matthew Brecknell
Pete Kazmier: I attempted to read Oleg's fold-stream implementation [1] as this sounds quite appealing to me, but I was completely overwhelmed, especially with all of the various type signatures used. It would be great if one of the regular Haskell bloggers (Tom Moertel are you reading

[Haskell-cafe] flip fix and iterate (was: Lazy IO and closing of file handles)

2007-03-19 Thread Matthew Brecknell
Pete Kazmier: I understand the intent of this code, but I am having a hard time understanding the implementation, specifically the combination of 'fix', 'flip', and 'interate'. I looked up 'fix' and I'm unsure how one can call 'flip' on a function that takes one argument. I threw that in

Re: [Haskell-cafe] flip fix and iterate (was: Lazy IO and closing of file handles)

2007-03-19 Thread Matthew Brecknell
Bryan Burgers: On the topic of 'fix', is there any good tutorial for fix? I searched google, but mostly came up with pages including things like 'bug fix'. It's hard for me to get an intuition about it when 'fix' always stack overflows on me because I don't really know how to use it. I don't

Re: [Haskell-cafe] Matrices in Haskell

2007-03-19 Thread Matthew Brecknell
Ivan Miljenovic: As such, I'd like to know if there's any way of storing a an n-by-n matrix such that the algorithm/function to get either the rows or the columns is less than O(n^2) like transposition is. I did try using an Array, but my (admittedly hurried and naive) usage of them took

Re: [Haskell-cafe] flip fix or let

2007-03-20 Thread Matthew Brecknell
Jules Bean: If you're merely talking about top-down or bottom-up then there is also 'where' rather than 'let'. Yes, I admit I tend to prefer where over let, all else being equal. But my main concern was embedding recursive functions in do-blocks, particularly monadic loops that aren't

Re: [Haskell-cafe] fix

2007-03-20 Thread Matthew Brecknell
Pete Kazmier: Haskell has a way of making one feel dumb. This is by far the most challenging programming language I've ever used. It (or perhaps the community around it) does have a way of making you realise that the rabbit-hole really is very deep. But that's no reason to feel dumb. I won't

Re: [Haskell-cafe] infinite lists

2007-03-27 Thread Matthew Brecknell
Matthias Fischmann: g = do n - randomRIO (0,5) let l = replicate n '*' i | null l = [] | otherwise = join $ repeat l print (take 12 i) If you had written (cycle l) instead of (join $ repeat l), you would have figured it out much quicker. :-) Prelude cycle []

[Haskell-cafe] (no subject)

2007-03-27 Thread Matthew Brecknell
I'm attempting to construct an abstract data type with a generalised (deferred) representation. For a simple motivating example, say I am building an abstract data type with this representation: newtype Foo1 k e = Foo1 (Data.Map.Map k (Data.Set.Set e)) While this is a fine default

Re: [Haskell-cafe] A question about functional dependencies

2007-03-28 Thread Matthew Brecknell
[EMAIL PROTECTED]: [...] The above two instances show there exists a model of T where the functional dependency is violated. That's why both GHC 6.4 and Hugs reject the instance. Again, it is a mystery why GHC 6.6 accepts it. Actually, GHC 6.6 does reject cases like the one discussed in this

Re: [Haskell-cafe] Tracking characters and a timestamp ?

2007-04-04 Thread Matthew Brecknell
Marc Weber: main = do hSetBuffering stdin NoBuffering hGetContents stdin = mapM addTimeCode = mapM_ handleChar It seems to wait till the end of the infinite list. Why? The sequencing imposed by the IO monad means that the first mapM must complete before the second can start. To see

Re: [Haskell-cafe] Tracking characters and a timestamp ?

2007-04-04 Thread Matthew Brecknell
Marc Weber: main = do lines - liftM lines getContents mapM_ print lines -- * So this example should hang, as well, shouldn't it? It would, except for the magic of unsafeInterleaveIO. It doesn't hang because getContents uses unsafeInterleaveIO internally to return the file contents

Re: [Haskell-cafe] Weaving fun

2007-04-10 Thread Matthew Brecknell
Bas van Dijk: For my own exercise I'm writing a function 'weave' that weaves a list of lists together. For example: weave [[1,1,1], [2,2,2], [3,3]] == [1,2,3,1,2,3,1,2] weave [[1,1,1], [2,2], [3,3,3]] == [1,2,3,1,2,3,1] Note that 'weave' stops when a list is empty. This *almost* does

Re: [Haskell-cafe] Weaving fun

2007-04-10 Thread Matthew Brecknell
Dave Feustel: Talk about synchronicity! I was just wondering whether 'weaving' of infinite lists is possible. eg weave the infinite lists [2,4..], [3,6..], [5,10..] to get [2,3,4,5,6,8,9,10,..] Is this kind of lazy evaluation possible? The base library version of (concat . transpose)

Re: [Haskell-cafe] Weaving fun

2007-04-12 Thread Matthew Brecknell
Jan-Willem Maessen: Interestingly, in this particular case what we obtain is isomorphic to constructing and reversing a list. Jan-Willem's observation also hints at some interesting performance characteristics of difference lists. It's well known that difference lists give O(1) concatenation,

Re: [Haskell-cafe] unsafeInerleaveIO and randomIO

2007-04-17 Thread Matthew Brecknell
Bertram Felgenhauer: unsafeInterleaveSequence :: [IO a] - IO [a] unsafeInterleaveSequence [] = return [] unsafeInterleaveSequence (x:xs) = unsafeInterleaveIO $ liftM2 (:) x (unsafeInterleaveSequence xs) randomInts = unsafeInterleaveSequence $ repeat randomIO I took a peek at

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Matthew Brecknell
Roberto Zunino: Here passing both 3 and (\z-z) as y confuses the type inference. Christopher L Conway: polyf :: forall a t1 t. (Num (t1 - t1), Num a, Num t) = a - (t1 - t1) - t The inference assigns y the type (t1 - t1) even though it is assigned the value 3? Almost. It assigns y the

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Matthew Brecknell
Roberto Zunino: Yes, you are right, I didn't want to involve type classes and assumed 3::Int. A better example would be: polyf :: Int - a - Int polyf x y = if x==0 then 0 else if x==1 then polyf (x-1) (\z-z) else polyf (x-2) () Here, passing both () and (\z-z)

Re: [Haskell-cafe] Profiling, measuring time

2007-05-19 Thread Matthew Brecknell
Steffen Mazanek: I have written a function f, that performs a quite complex operation on its argument. Furthermore I have another function genInput that takes a number and constructs an argument for f of this size. What I want now is a list [(n,time)] that gives me for every size of

Re: [Haskell-cafe] Scope of type variables in associated types

2007-05-21 Thread Matthew Brecknell
Bertram Felgenhauer: How does class F a where data B a :: * data E a :: * wrap :: B a - E a unwrap :: E a - B a sound? 'B a' would represent the 'b' in your previous attempt, class F a b | a - b where ... I'm with Simon in thinking that this code is

  1   2   >