[Haskell-cafe] Computing the memory footprint of a HashMap ByteString Int (Was: How on Earth Do You Reason about Space?)

2011-05-31 Thread Johan Tibell
Hi Aleksandar, I thought it'd be educational to do some back-of-the-envelope calculations to see how much memory we'd expect to use to store words in a HashMap ByteString Int. First, lets start by looking at how much memory one ByteString uses. Here's the definition of ByteString [1]: data By

Re: [Haskell-cafe] Enabling GADTs breaks Rank2Types code compilation - Why?

2011-05-31 Thread dm-list-haskell-cafe
At Tue, 31 May 2011 21:30:01 -0500, austin seipp wrote: > > The short story is thus: when you turn on GADTs, it also now turns on > another extension implicitly (MonoLocalBinds) which restricts let > generalization... > > You can find a little more info about the change here: > > http://hackage.

Re: [Haskell-cafe] Enabling GADTs breaks Rank2Types code compilation - Why?

2011-05-31 Thread austin seipp
Hi David, It seems to be a result of the new typechecker and more specifically the new behavior for GADTs in GHC 7. The short story is thus: when you turn on GADTs, it also now turns on another extension implicitly (MonoLocalBinds) which restricts let generalization. More specifically, it causes

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Albert Y. C. Lai
On a tangent, not doing IO, but food for thought: {-# LANGUAGE FlexibleContexts #-} import Control.Monad.State.Lazy as N import Control.Monad.State.Strict as S gen :: (MonadState [()] m) => m () gen = do gen modify (() :) many = take 3 (N.execState gen []) none = take 3 (S.execState gen []

Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread Aleksandar Dimitrov
On Tue, May 31, 2011 at 11:30:06PM +0100, John Lato wrote: > I can't reproduce the space leak here. I tried Aleksander's original code, > my iteratee version, the Ngrams version posted by Johan Tibell, and a lazy > bytestring version. I unfortunately can't post the actual corpus here, because it'

[Haskell-cafe] Enabling GADTs breaks Rank2Types code compilation - Why?

2011-05-31 Thread dm-list-haskell-cafe
I'm using GHC 7.0.2 and running into a compiler error that I cannot understand. Can anyone shed light on the issue for me? The code does not make use of GADTs and compiles just fine without them. But when I add a {-# LANGUAGE GADTs #-} pragma, it fails to compile. Here is the code: {-# L

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Antoine Latter
On Tue, May 31, 2011 at 6:10 PM, Antoine Latter wrote: > > You could use a different type: > >> type IOStream a = (a, IO (IOStream a)) > >> unfold :: ([a] -> IO a) -> IO (IOStream a) >> unfold f = >>     let go prev = do >>           next <- f prev >>           return (next, go (next:prev)) >>    

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Antoine Latter
On Tue, May 31, 2011 at 2:49 PM, Scott Lawrence wrote: > I was under the impression that operations performed in monads (in this > case, the IO monad) were lazy. (Certainly, every time I make the > opposite assumption, my code fails :P .) Which doesn't explain why the > following code fails to ter

Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread John Lato
From: "Edward Z. Yang" > > Hello Aleksandar, > > It is possible that the iteratees library is space leaking; I recall some > recent discussion to this effect. Your example seems simple enough that > you might recompile with a version of iteratees that has -auto-all enabled. > Unfortunately, it's

Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread Aleksandar Dimitrov
On Tue, May 31, 2011 at 02:13:14PM -0400, Edward Z. Yang wrote: > It is possible that the iteratees library is space leaking; I recall some > recent discussion to this effect. Your example seems simple enough that > you might recompile with a version of iteratees that has -auto-all enabled. If I

Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread Aleksandar Dimitrov
Hi Johan, > Here's how I would do it: I implemented your method, with these minimal changes (i.e. just using a main driver in the same file.) > countUnigrams :: Handle -> IO (M.Map S.ByteString Int) > countUnigrams = foldLines (\ m s -> M.insertWith (+) s 1 m) M.empty > > main :: IO () > main =

Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread Aleksandar Dimitrov
On Tue, May 31, 2011 at 11:43:27AM -0700, Brandon Moore wrote: > I can't reproduce heap usage growing with the > size of the input file. > > I made a word list from Project Gutenberg's > copy of "War and Peace" by > > tr -sc '[[:alpha:]]' '\n' < pg2600.txt > words.txt > > Using 1, 25, or 1000 re

Re: [Haskell-cafe] Decimal type-level arithmetic.

2011-05-31 Thread Serguey Zefirov
2011/6/1 Henning Thielemann : > > On Wed, 1 Jun 2011, Serguey Zefirov wrote: >> I would like to present my version of type arithmetic with decimal >> encoding: http://thesz.mskhug.ru/svn/hhdl/TyleA.hs > How does it compare to >  http://hackage.haskell.org/package/type-level > ? My version is sligh

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Scott Lawrence
Apparently: Prelude> let r = (fmap (1:) r) :: IO [Integer] Prelude> fmap (take 5) r *** Exception: stack overflow Thanks - I'll just have to stay out of IO for this, then. On Tue, May 31, 2011 at 17:05, Stephen Tetley wrote: > 2011/5/31 Scott Lawrence : > >> Evaluation here also doesn't termina

Re: [Haskell-cafe] Decimal type-level arithmetic.

2011-05-31 Thread Henning Thielemann
On Wed, 1 Jun 2011, Serguey Zefirov wrote: I would like to present my version of type arithmetic with decimal encoding: http://thesz.mskhug.ru/svn/hhdl/TyleA.hs How does it compare to http://hackage.haskell.org/package/type-level ? ___ Haskell-Ca

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Stephen Tetley
2011/5/31 Scott Lawrence : > Evaluation here also doesn't terminate (or, (head $ unfoldM (return . > head)) doesn't), although I can't figure out why. fmap shouldn't need to > fully evaluate a list to prepend an element, right? I'm afriad fmap doesn't get to choose - if the monad is strict then b

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Daniel Fischer
On Tuesday 31 May 2011 22:35:26, Yves Parès wrote: > He intended to show that, indeed, it is not, or else side-effects would > never be performed On the other hand, IO is lazy in the values it produces. Going with the IO a = State RealWorld a fiction, IO is state-strict but value-lazy. The side-e

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Scott Lawrence
On 05/31/2011 04:48 PM, Artyom Kazak wrote: > > Oh, sorry. I was unclear. I have meant "assuming IO is lazy", as Yves > wrote. Ah, ok. That makes more sense. > > And saying "some hacks" I meant unsafeInterleaveIO, which lies beneath > the laziness of, for example, getContents. Which explains w

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Gregory Crosswhite
On 5/31/11 12:49 PM, Scott Lawrence wrote: I was under the impression that operations performed in monads (in this case, the IO monad) were lazy. Whether they are lazy or not depends entirely on the definition of the monad. For example, if you look up the ST and State monads you will find th

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Artyom Kazak
Scott Lawrence писал(а) в своём письме Tue, 31 May 2011 23:29:49 +0300: On 05/31/2011 04:20 PM, Artyom Kazak wrote: Suppose iRecurse looks like this: iRecurse = do x <- launchMissiles r <- iRecurse return 1 As x is never needed, launchMissiles will never execute. It obviously

[Haskell-cafe] Decimal type-level arithmetic.

2011-05-31 Thread Serguey Zefirov
I would like to present my version of type arithmetic with decimal encoding: http://thesz.mskhug.ru/svn/hhdl/TyleA.hs It is not worth Cabal package in its current state, but I hope it would be useful for someone. It is easy to use, just say Plus (D1 :. D2 :. D0) D8 to get a type of 128. Or you ca

Re: [Haskell-cafe] Thoughts about currying and optimisations

2011-05-31 Thread Yves Parès
> It can introduce space leaks if the computationally expensive test is replaced with a reference to a space expensive value. You mean if the rest of stuffX's body keeps a reference to that value, I suppose? (I suppose, or else that value would be useless). Ok, so GHC does detect that case and opt

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Yves Parès
No, I think Artyom meant "assuming IO is lazy". He intended to show that, indeed, it is not, or else side-effects would never be performed 2011/5/31 Scott Lawrence > On 05/31/2011 04:20 PM, Artyom Kazak wrote: > > Suppose iRecurse looks like this: > > iRecurse = do > > x <- launchMissiles

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Anthony Cowley
On Tue, May 31, 2011 at 3:49 PM, Scott Lawrence wrote: > I was under the impression that operations performed in monads (in this > case, the IO monad) were lazy. (Certainly, every time I make the > opposite assumption, my code fails :P .) Which doesn't explain why the > following code fails to ter

Re: [Haskell-cafe] *GROUP HUG*

2011-05-31 Thread Yves Parès
> "come on! it's fun! i can write foldr with foldl!" And when you try to explain that to your java-ITC-formatted friends, they utterly surprisingly seem not to care about it ^^ 2011/5/31 Adrien Haxaire > Le 31/05/2011 21:15, Alberto G. Corona a écrit : > > Haskell is an academic asset as well

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Scott Lawrence
On 05/31/2011 04:20 PM, Artyom Kazak wrote: > Suppose iRecurse looks like this: > iRecurse = do > x <- launchMissiles > r <- iRecurse > return 1 > > As x is never needed, launchMissiles will never execute. It obviously is > not what is needed. Prelude> let launchMissiles = putStrLn

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Artyom Kazak
Suppose iRecurse looks like this: iRecurse = do x <- launchMissiles r <- iRecurse return 1 As x is never needed, launchMissiles will never execute. It obviously is not what is needed. But in Haskell, standart file input|output is often lazy. It's a combination of buffering and

[Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Scott Lawrence
I was under the impression that operations performed in monads (in this case, the IO monad) were lazy. (Certainly, every time I make the opposite assumption, my code fails :P .) Which doesn't explain why the following code fails to terminate: iRecurse :: (Num a) => IO a iRecurse = do recur

Re: [Haskell-cafe] *GROUP HUG*

2011-05-31 Thread Adrien Haxaire
Le 31/05/2011 21:15, Alberto G. Corona a écrit : Haskell is an academic asset as well as a fun asset. I fully agree. These are two of the three reasons which made me choose haskell as the functional language to learn. Coding fortran all day, I wanted a new approach on programming. The strong

Re: [Haskell-cafe] Can't figure out cmap in hmatrix

2011-05-31 Thread Mats Klingberg
31 maj 2011 kl. 09.59 Alberto Ruiz wrote: > I have just uploaded to Hackage the bug-fixed version. That works fine. Thanks for a nice package! Mats ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-c

Re: [Haskell-cafe] Thoughts about currying and optimisations

2011-05-31 Thread Edward Z. Yang
I believe this transformation is called the 'full laziness' optimization. It can introduce space leaks if the computationally expensive test is replaced with a reference to a space expensive value. Edward Excerpts from Yves Parès's message of Tue May 31 15:14:07 -0400 2011: > Hello Café, > An ide

Re: [Haskell-cafe] *GROUP HUG*

2011-05-31 Thread Alberto G. Corona
fluency in Scala is an industry asset, since it runs in the Java VM, while Haskell is an academic asset as well as a fun asset. The value of an industry asset grows with the lack of competence of others. Therefore competing guys are not welcome. There are enoug crocodiles in the pond. Alberto.

[Haskell-cafe] Thoughts about currying and optimisations

2011-05-31 Thread Yves Parès
Hello Café, An idea came to me: unless the compiler notices that stuffA and stuffB are equivalent, would it be correct to suppose that A is better than B? stuffA x = if someComputationallyExpensiveTest x then doSomething else doSomethingElse stuffB x y = if someComputationallyExpensiveTest x

Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread Brandon Moore
Wait, do ByteStrings show up on a heap profile, if the space is allocated with malloc? Anyway, I think my tests still show that the memory used by the process doesn't grow simply by adding more data, if you are no longer added keys to the map. - Original Message - > From: Brandon Moore

Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread Brandon Moore
I can't reproduce heap usage growing with the size of the input file. I made a word list from Project Gutenberg's copy of "War and Peace" by tr -sc '[[:alpha:]]' '\n' < pg2600.txt > words.txt Using 1, 25, or 1000 repetitions of this ~3MB wordlist shows about 100MB of address space used according

Re: [Haskell-cafe] *GROUP HUG*

2011-05-31 Thread Evan Laforge
On Tue, May 31, 2011 at 11:31 AM, Ozgur Akgun wrote: > Evan, > On 24 May 2011 19:57, Evan Laforge wrote: >> >> On the catMaybes thing, I have a function 'mapMaybe = Maybe.catMaybes >> . map'.  I turns out I only ever used catMaybes after mapping a Maybe >> function, so I hardly ever use catMaybes

Re: [Haskell-cafe] *GROUP HUG*

2011-05-31 Thread Ozgur Akgun
Evan, On 24 May 2011 19:57, Evan Laforge wrote: > On the catMaybes thing, I have a function 'mapMaybe = Maybe.catMaybes > . map'. I turns out I only ever used catMaybes after mapping a Maybe > function, so I hardly ever use catMaybes anymore. I suppose it should > have been maybeMap for consis

Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread Edward Z. Yang
Hello Aleksandar, It is possible that the iteratees library is space leaking; I recall some recent discussion to this effect. Your example seems simple enough that you might recompile with a version of iteratees that has -auto-all enabled. Unfortunately, it's not really a safe bet to assume your

Re: [Haskell-cafe] Sub class and model expansion

2011-05-31 Thread Ryan Ingram
On Tue, May 31, 2011 at 1:40 AM, Patrick Browne wrote: > Continuing the thread on model expansion. > I have changed the example trying to focus on expanding models of M in G > Why is the operation ! ok or RHS but not visible on LHS of G? > The equation itself does not seem to suffer from the depen

Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread Johan Tibell
Hi Aleksandar, On Tue, May 31, 2011 at 6:10 PM, Aleksandar Dimitrov wrote: > Say, we have an input file that contains a word per line. I want to find all > unigrams (unique words) in that file, and associate with them the amount of > times they occurred in the file. This would allow me, for examp

Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread Aleksandar Dimitrov
> In Lag/Drag/Void/Use profiling, Lag is actually heap cells that are created > too _early_.  (Drag are those that are kept for longer than necessary.)  Lots > of Lag generally means your program is too strict - it is forcing structure > long before it needs to.  To fix it, you need to make things

Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread malcolm.wallace
ad a) heap consumption is too high for two reasons: firstly, the actual data I care about is much less than there's data on the heap. Secondly, about half the heap space is in LAG state. Here are profiles that will illustrate this: http://imgur.com/wBWmJ&XN1mW

Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread Aleksandar Dimitrov
On Tue, May 31, 2011 at 06:10:00PM +0200, Aleksandar Dimitrov wrote: > ad a) heap consumption is too high for two reasons: firstly, the actual data I > care about is much less than there's data on the heap. Secondly, about half > the > heap space is in LAG state. Here are profiles that will illust

[Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread Aleksandar Dimitrov
Dear Cafe, (Excuse the probably very ranty email; I am, unfortunately, at the end of my wits, and I hope that as fellow programmers, you will understand that this is among the most dreadful situations for our kind to be in.) Say, we have an input file that contains a word per line. I want to find

Re: [Haskell-cafe] ANN: quickcheck-properties

2011-05-31 Thread Mario Blažević
On 11-05-30 05:05 AM, Alexey Khudyakov wrote: On 30.05.2011 12:26, Bas van Dijk wrote: On 30 May 2011 00:14, Alexey Khudyakov wrote: It always puzzled me why there are no packages for for testing general type classes laws. (Monoid laws, monad laws etc). It looks like ideal case for quickcheck a

[Haskell-cafe] PhD studentship in Nottingham

2011-05-31 Thread Graham Hutton
Dear all, I are currently advertising a PhD studentship in functional programming -- the advert is copied below, and attached. If you know of any good candidates who many be interested in this, or there is a local mailing list for advertising such things, I would be much obliged if you could pass

Re: [Haskell-cafe] Sub class and model expansion

2011-05-31 Thread Patrick Browne
Continuing the thread on model expansion. I have changed the example trying to focus on expanding models of M in G Why is the operation ! ok or RHS but not visible on LHS of G? The equation itself does not seem to suffer from the dependent type problem of my previous post. class M a where (!) ::

Re: [Haskell-cafe] Can't figure out cmap in hmatrix

2011-05-31 Thread Alberto Ruiz
On 05/30/2011 10:33 PM, Carter Schonwald wrote: this is actually a bug in the type of cmap, a fix is due in the next release (at least thats what Alberto indicated to me when I asked about this a monthish ago) (note how you have the container type c e, but we want c a and c b ). Instead use the

Re: [Haskell-cafe] What's the advantage of writing Haskell this way?

2011-05-31 Thread Lyndon Maydwell
Heh. Looks like there will be about five class constraints, but it will still be more general. There must be some higher level abstraction that is less ugly. On Tue, May 31, 2011 at 3:45 PM, Yves Parès wrote: > Maybe you are looking for a more generic way to concatenate it: > There is fold :: (F

Re: [Haskell-cafe] Please add a method for optimized concat to the Semigroup class

2011-05-31 Thread Yitzchak Gale
Edward Kmett wrote: > I felt I should probably mention that ultimately what was done is I moved > NonEmpty all the way down into semigroups and chose >> sconcat :: NonEmpty a -> a > at it was the closest analogue to the current mconcat behavior. > So, request accomodated. ;) Indeed, this is an exc

Re: [Haskell-cafe] What's the advantage of writing Haskell this way?

2011-05-31 Thread Yves Parès
Maybe you are looking for a more generic way to concatenate it: There is fold:: (Foldable t, Monoid m) => t m -> m

Re: [Haskell-cafe] What's the advantage of writing Haskell this way?

2011-05-31 Thread Lyndon Maydwell
I think this is because mconcat expects a list. On Tue, May 31, 2011 at 3:31 PM, John Ky wrote: > Thanks Malcom. > I suspected that much, so I added it: > data Stream m a > = Chunks (m a) > | EOF > deriving (Show, Eq) > instance (Monad m, MonadPlus m, Monoid (m a)) => Monoid (Stream m a) where >

Re: [Haskell-cafe] What's the advantage of writing Haskell this way?

2011-05-31 Thread John Ky
Thanks Malcom. I suspected that much, so I added it: data Stream m a = Chunks (m a) | EOF deriving (Show, Eq) instance (Monad m, MonadPlus m, Monoid (m a)) => Monoid (Stream m a) where mempty = Chunks mempty mappend (Chunks xs) (Chunks ys) = Chunks (xs `mappend` ys) mappend _ _ = EOF instance (