Re: [Haskell-cafe] OS-independent auto-monitoring of a program to do things depending on resource usage at runtime

2012-08-28 Thread Gregory Collins
For a concrete example of this at work, see Johan's ekg package:
http://hackage.haskell.org/package/ekg

G

On Mon, Aug 27, 2012 at 8:12 PM, Joachim Breitner
m...@joachim-breitner.dewrote:

 Hi,

 Am Montag, den 27.08.2012, 18:20 +0200 schrieb Alberto G. Corona :
  For a caching library, I need to know the runtime usage of memory of
  the  program and the total amount of memory, the total memory used by
  all the programs etc.
 
 
   I need not do profiling or monitoring but to do different things
  inside my program depending on memory usage.
 
  The search is difficult because all searches go to profiling utilities
  which I don´t need.
 
 
  Are there some  portable way to to this? . The various monitoring
  libraries indicates that there are ways to do it, but they seem not to
  allow  runtime internal automonitoring

 you can use the GHC.Stats module, see
 http://www.haskell.org/ghc/docs/latest/html/libraries/base/GHC-Stats.html,
 and remember to pass +RTS -T to the program, or -with-rtsopts=-T to the
 compiler.

 Greetings,
 Joachim

 --
 Joachim nomeata Breitner
   m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
   xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Conduit: Where to run monad stacks?

2012-08-28 Thread Michael Snoyman
On Fri, Aug 24, 2012 at 5:03 PM, Niklas Hambüchen m...@nh2.me wrote:
 Hello Michael,

 yes, that does certainly help, and it should definitely be linked to.

 The remaining question is:

 Is it possible to have something like transPipe that runs only once for
 the beginning of the pipe?

 It seems desirable for me to have conduits which encapsulate monads.
 Imagine you have to conduits dealing with stateful encryption/decryption
 and one data-counting one in the middle, like:

 decryptConduit $= countConduit $= encryptConduit

 Would you really want to combine the three different internal monads
 into one single monad of the whole pipe, even though the internal monads
 are implementation details and not necessary for the operation of the
 whole pipe?

I don't disagree with your analysis, but I don't think it's generally
possible to implement the desired transPipe. (If someone can prove
otherwise, I'd be very happy.) It *might* be possible via some (ab)use
of `monad-control` and mutable variables, however.

 The idea with a Ref inside a Reader sounds like a workaround, but has
 the same problem of globalizing/combining effects, somewhat limiting
 composability of conduits.

I wouldn't say that we're globalizing effects at all. It should
theoretically be possible to write some function like:

stateToReader :: MonadIO m = StateT r m a - ReaderT (IORef r) m a

And then `transPipe` will function on the resulting Pipe without issue.

Michael


 Niklas

 On 24/08/12 06:51, Michael Snoyman wrote:
 I agree that the behavior is a bit confusing (Dan Burton just filed an
 issue about this[1], I'm guessing this email is related).

 I put up a wiki page[2] to hopefully explain the issue. Can you review
 it and let me know if it helps? If so, I'll link to it from the
 Haddocks.

 Michael

 [1] https://github.com/snoyberg/conduit/issues/67
 [2] https://github.com/snoyberg/conduit/wiki/Dealing-with-monad-transformers

 On Wed, Aug 22, 2012 at 11:19 PM, Niklas Hambüchen m...@nh2.me wrote:
 Today I was surprised that transPipe is called for every chunk of data
 going through my pipe, rendering the StateT I put in useless, because it
 was always restarted with the initial value.

 It would be nice to have some explanation about this, as it makes it
 easy to write compiling code that has completely unexpected behaviour.


 I wrote this function (also on http://hpaste.org/73538):

 conduitWithState :: (MonadIO m) = Conduit Int (StateT Int m) String
 conduitWithState = do
   liftIO $ putStrLn $ Counting Int-String converter ready!
   awaitForever $ \x - do
 i - lift get
 lift $ modify (+1)
 liftIO $ putStrLn $ Converting  ++ show x ++  to a string!  ++
 Processed so far:  ++ show i
 yield (show x)

 and ran it like this:

 countingConverterConduit :: (MonadIO m) = Conduit Int m String
 countingConverterConduit = transPipe (\stateTint - evalStateT stateTint
 1) conduitWithState

 main :: IO ()
 main = do
   stringList - CL.sourceList [4,1,9,7,3] $=
  countingConverterConduit $$
  CL.consume
   print stringList

 However, the output is not what I expected, but only:

 Processed so far:1
 Processed so far:1
 ...

 Dan Burton proposed a fix, making the whole sink-conduit-source
 construction run on the StateT:

 main = do
   stringList - flip evalStateT 1 $ ...


 So the question is: What is the rationale for this?

 I was expecting that if I have an IO pipe in my main conduit, I could
 easily run stuff on top of that in parts of the pipe.

 Thanks
 Niklas

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Darcs fetches too little files

2012-08-28 Thread Henk-Jan van Tuyl
On Fri, 24 Aug 2012 22:47:37 +0200, Henk-Jan van Tuyl hjgt...@chello.nl  
wrote:




I am trying to fetch wxHaskell with the command
   darcs get --lazy http://code.haskell.org/wxhaskell/
but there are much too little files downloaded; what could be the  
problem?




Albert Einstein said:
  Insanity: doing the same thing over and over again and expecting  
different results.


I repeated the command today and it worked!

Regards,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-28 Thread Bryan O'Sullivan
On Mon, Aug 27, 2012 at 10:52 AM, Bryan O'Sullivan b...@serpentine.comwrote:

 The reason you're seeing build breakage is that the .cabal files of the
 broken packages were edited in-place without communicating with any of the
 package authors.


Not to flog a dead horse, but:

Just yesterday we had a communication from someone on the Gentoo Linux
packaging team that their checksum validation for the bloomfilter package
was failing. This problem arose because of the hand-editing of the package,
but confusion arose in the bug report due to misattribution of the source
of the error.

https://github.com/haskell/cabal/issues/1017

Hand-editing uploaded tarballs: just don't do it, kids!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A first glimps on the {-# NOUPDATE #-} pragma

2012-08-28 Thread Joachim Breitner
Dear GHC users,

I am experimenting with ways to /prevent/ sharing in Haskell, e.g. to
avoid space leaks or to speed up evaluation. A first attempt was to
duplicate closures on the heap to preserve the original one, see
http://arxiv.org/abs/1207.2017 for a detailed description and
information on the prototype implementation; no GHC patching required
for that.

Currently I am trying a different angle: Simply avoid generating the
code that will update a closure after its evaluation; hence the closure
stays a thunk and will happily re-evaluate the next time it is used.

Here is a classical example. Take this function (it is basically [f..t]
but with a fixed type and no risk of existing rules firing):

myenum :: Int - Int - [Int]
myenum f t = if f = t
 then f : myenum (f + 1) t
 else []

and this example where sharing hurts performance badly:

upd_upd n = 
let l = myenum 0 n
in last l + head l

The problem is that during the evaluation of last l, the list is live
and needs to be kept in memory, although in this case, re-evaluating l
for head l would be cheaper. If n is 5000, then this takes 3845ms
on my machine, measured with criterion, and a considerable amount of
memory (3000MB).

So here is what you can do now: You can mark the value as
non-updateable. We change myenum to

myenum' :: Int - Int - [Int]
myenum' f t = if f = t then f : ({-# NOUPDATE #-} myenum' (f + 1) t) 
else []

and use that:

upd_noupd n = 
let l = myenum' 0 n
in last l + head l

The improvement is considerable: 531ms and not much memory used (18MB)


Actually, it should suffice to put the pragma in the definition of l
without touching myenum:

noupd_noupd n = 
let l = {-# NOUPDATE #-} myenum 0 n
in last l + head l

but this does not work with -O due to other optimizations in GHC. (It
does work without optimization.)


The next step would be to think of conditions under which the compiler
could automatically add the pragma, e.g. when it sees that evaluation a
thunk is very cheap but will increase memory consumption considerable.


Also this does not have to be a pragma; it could just as well be a
function noupdate :: a - a that is treated specially by the compiler,
similar to the inline function.


If you want to play around this, feel free to fetch it from the unshare
branch of my ghc repository at http://git.nomeata.de/?p=ghc.git or
https://github.com/nomeata/ghc for the GitHub-lovers. Note that the
branch is repeatedly rebased against ghc master.


Greetings,
Joachim


-- 
Dipl.-Math. Dipl.-Inform. Joachim Breitner
Wissenschaftlicher Mitarbeiter
http://pp.info.uni-karlsruhe.de/~breitner


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A first glimps on the {-# NOUPDATE #-} pragma

2012-08-28 Thread Carter Schonwald
Hey Joachim,
isn't this an example where the exact same issue could be solved via some
suitable use of a monad for ordering those two computations on l?

cheers
-Carter

On Tue, Aug 28, 2012 at 12:44 PM, Joachim Breitner breit...@kit.edu wrote:

 Dear GHC users,

 I am experimenting with ways to /prevent/ sharing in Haskell, e.g. to
 avoid space leaks or to speed up evaluation. A first attempt was to
 duplicate closures on the heap to preserve the original one, see
 http://arxiv.org/abs/1207.2017 for a detailed description and
 information on the prototype implementation; no GHC patching required
 for that.

 Currently I am trying a different angle: Simply avoid generating the
 code that will update a closure after its evaluation; hence the closure
 stays a thunk and will happily re-evaluate the next time it is used.

 Here is a classical example. Take this function (it is basically [f..t]
 but with a fixed type and no risk of existing rules firing):

 myenum :: Int - Int - [Int]
 myenum f t = if f = t
  then f : myenum (f + 1) t
  else []

 and this example where sharing hurts performance badly:

 upd_upd n =
 let l = myenum 0 n
 in last l + head l

 The problem is that during the evaluation of last l, the list is live
 and needs to be kept in memory, although in this case, re-evaluating l
 for head l would be cheaper. If n is 5000, then this takes 3845ms
 on my machine, measured with criterion, and a considerable amount of
 memory (3000MB).

 So here is what you can do now: You can mark the value as
 non-updateable. We change myenum to

 myenum' :: Int - Int - [Int]
 myenum' f t = if f = t then f : ({-# NOUPDATE #-} myenum' (f + 1)
 t) else []

 and use that:

 upd_noupd n =
 let l = myenum' 0 n
 in last l + head l

 The improvement is considerable: 531ms and not much memory used (18MB)


 Actually, it should suffice to put the pragma in the definition of l
 without touching myenum:

 noupd_noupd n =
 let l = {-# NOUPDATE #-} myenum 0 n
 in last l + head l

 but this does not work with -O due to other optimizations in GHC. (It
 does work without optimization.)


 The next step would be to think of conditions under which the compiler
 could automatically add the pragma, e.g. when it sees that evaluation a
 thunk is very cheap but will increase memory consumption considerable.


 Also this does not have to be a pragma; it could just as well be a
 function noupdate :: a - a that is treated specially by the compiler,
 similar to the inline function.


 If you want to play around this, feel free to fetch it from the unshare
 branch of my ghc repository at http://git.nomeata.de/?p=ghc.git or
 https://github.com/nomeata/ghc for the GitHub-lovers. Note that the
 branch is repeatedly rebased against ghc master.


 Greetings,
 Joachim


 --
 Dipl.-Math. Dipl.-Inform. Joachim Breitner
 Wissenschaftlicher Mitarbeiter
 http://pp.info.uni-karlsruhe.de/~breitner

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A first glimps on the {-# NOUPDATE #-} pragma

2012-08-28 Thread Carter Schonwald
You got me there. Excellent point

On Tuesday, August 28, 2012, Yves Parès wrote:

 Monad? Simple strictness anotation is enough in that case:

 upd_noupd n =
 let l = myenum' 0 n
 h = head l
 in h `seq` last l + h

 Le mardi 28 août 2012 22:39:09 UTC+2, Carter Schonwald a écrit :

 Hey Joachim,
 isn't this an example where the exact same issue could be solved via some
 suitable use of a monad for ordering those two computations on l?

 cheers
 -Carter

 On Tue, Aug 28, 2012 at 12:44 PM, Joachim Breitner brei...@kit.eduwrote:

 Dear GHC users,

 I am experimenting with ways to /prevent/ sharing in Haskell, e.g. to
 avoid space leaks or to speed up evaluation. A first attempt was to
 duplicate closures on the heap to preserve the original one, see
 http://arxiv.org/abs/1207.2017 for a detailed description and
 information on the prototype implementation; no GHC patching required
 for that.

 Currently I am trying a different angle: Simply avoid generating the
 code that will update a closure after its evaluation; hence the closure
 stays a thunk and will happily re-evaluate the next time it is used.

 Here is a classical example. Take this function (it is basically [f..t]
 but with a fixed type and no risk of existing rules firing):

 myenum :: Int - Int - [Int]
 myenum f t = if f = t
  then f : myenum (f + 1) t
  else []

 and this example where sharing hurts performance badly:

 upd_upd n =
 let l = myenum 0 n
 in last l + head l

 The problem is that during the evaluation of last l, the list is live
 and needs to be kept in memory, although in this case, re-evaluating l
 for head l would be cheaper. If n is 5000, then this takes 3845ms
 on my machine, measured with criterion, and a considerable amount of
 memory (3000MB).

 So here is what you can do now: You can mark the value as
 non-updateable. We change myenum to

 myenum' :: Int - Int - [Int]
 myenum' f t = if f = t then f : ({-# NOUPDATE #-} myenum' (f +
 1) t) else []

 and use that:

 upd_noupd n =
 let l = myenum' 0 n
 in last l + head l

 The improvement is considerable: 531ms and not much memory used (18MB)


 Actually, it should suffice to put the pragma in the definition of l
 without touching myenum:

 noupd_noupd n =
 let l = {-# NOUPDATE #-} myenum 0 n
 in last l + head l

 but this does not work with -O due to other optimizations in GHC. (It
 does work without optimization.)


 The next step would be to think of conditions under which the compiler
 could automatically add the pragma, e.g. when it sees that evaluation a
 thunk is very cheap but will increase memory consumption considerable.


 Also this does not have to be a pragma; it could just as well be a
 function noupdate :: a - a that is treated specially by the compiler,
 similar to the inline function.


 If you want to play around this, feel free to fetch it from the unshare
 branch of my ghc repository at 
 http://git.nomeata.de/?p=ghc.**githttp://git.nomeata.de/?p=ghc.gitor
 https://github.com/nomeata/ghc for the GitHub-lovers. Note that the
 branch is repeatedly rebased against ghc master.


 Greetings,
 Joachim


 --
 Dipl.-Math. Dipl.-Inform. Joachim Breitner
 Wissenschaftlicher Mitarbeiter
 http://pp.info.uni-karlsruhe.**de/~breitnerhttp://pp.info.uni-karlsruhe.de/%7Ebreitner

 __**_
 Haskell-Cafe mailing list
 haskel...@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe