Compiling a cabal project with LLVM on GHC 7.10 RC1

2015-01-07 Thread Brandon Simmons
I've tried:

  $ cabal install --only-dependencies -w
/usr/local/bin/ghc-7.10.0.20141222  --enable-tests --enable-benchmarks
--ghc-option=-fllvm --ghc-option=-static
  $ cabal configure -w /usr/local/bin/ghc-7.10.0.20141222
--enable-tests --enable-benchmarks --ghc-option=-fllvm
--ghc-option=-static
  $ cabal build
  Building foo-0.3.0.0...
  Preprocessing library foo-0.3.0.0...

  when making flags consistent: Warning:
  Using native code generator rather than LLVM, as LLVM is
incompatible with -fPIC and -dynamic   on this platform

I don't see anything referencing PIC in the output of cabal build
-v. I can build a hello world program, just fine with `ghc --make`:

  $ /usr/local/bin/ghc-7.10.0.20141222 --make -O2 -fllvm   Main.hs
  [1 of 1] Compiling Main ( Main.hs, Main.o )
  Linking Main ...

Thanks,
Brandon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Behavior of touch#

2014-12-15 Thread Brandon Simmons
The `primitive` package exports a lifted version of the undocumented `touch#`

http://hackage.haskell.org/package/ghc-prim-0.3.1.0/docs/GHC-Prim.html

which has type:

touch :: PrimMonad m = a - m ()

I'd like to know if this works correctly in general, or will it suffer
from the same gotches w/r/t unboxing as with addFinalizer and Weak
references? i.e. must it only be passed an unboxed type?

Brandon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Defining a custom newByteArray primop that uses calloc?

2014-11-25 Thread Brandon Simmons
In my tests, using calloc from:


https://hackage.haskell.org/package/missing-foreign-0.1.1/docs/Foreign-Marshal-MissingAlloc.html

was about twice as fast as allocating and zeroing the same amount of
memory with `newByteArray` + any of `copy/set/fillMutableByteArray`
(all three were nearly identical). Is there a way I can reasonably
define my own `newByteArray` that uses calloc?

FWIW here are a couple of the benchmarks I'm working with in criterion:

arrTestSet :: Int - IO ()
arrTestSet len = do
let eBytes = (P.sizeOf (undefined::Int))*len
a - P.newAlignedPinnedByteArray
eBytes
(P.alignment (undefined :: Int))
void $ P.setByteArray a 0 len (1::Int)

arrTestCallocAndWrite :: Int - IO ()
arrTestCallocAndWrite len = do
ptr - callocBytes (len*(P.sizeOf(undefined::Int))) :: IO (Ptr Int)
pokeElemOff ptr 0 1
free ptr

Thanks,
Brandon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Avoiding BlockedIndefinitelyOnSTM exceptions

2014-07-18 Thread Brandon Simmons
 I have what may sound like an unusual request: I would like to
 automatically avoid `BlockedIndefinitelyOnSTM` exceptions with a
 primitive that looks something like this:

Have you seen ezyang's post here? Lots of hairy details that are
probably relevant

http://blog.ezyang.com/2011/07/blockedindefinitelyonmvar/

Brandon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Why no `instance (Monoid a, Applicative f)= Monoid (f a)` for IO?

2014-07-15 Thread Brandon Simmons
On Mon, Jul 14, 2014 at 10:55 PM, Edward Kmett ekm...@gmail.com wrote:
 There are monads for which you want another Monoid, e.g. Maybe provides a
 different unit, because it pretends to lift a Semigroup into a Monoid.

 There are also monoids that take a parameter of kind * that would overlap
 with this instance.

 So we can't (and shouldn't) have the global Monoid instance like you give
 there first.

Right, sorry. I just meant that as a bit of context. My proposal is adding
`instance Monoid a = Monoid (IO a)`.


 As for the particular case of IO a, lifting may be a reasonable option
 there.

 A case could be made for adding an `instance Monoid a = Monoid (IO a)`, but
 for such a ubiquitously used type, expect that this wouldn't be an easy
 sell.

 You'd possibly have to deal with everyone and their brother coming out of
 the woodwork offering up every other Monoid they happened to use on IO.

 Why?

 IO provides a notion of failing action you could use for zero and you can
 build an (|) like construction on it as well, so the 'multiplicative'
 structure isn't the _only_ option for your monoid.

Can you give an example of what you mean here? Would that be something
involving exceptions?


 Even within the multiplicative structure using the monoid isn't necessarily
 ideal as you might leak more memory with an IO a monoid that lifts () than
 you would with working specifically on IO ().

 You can argue the case that the choice you made is a sensible default
 instance by instance, but when there isn't a real canonical choice we do
 tend to err on the side of leaving things open as orphans are at least
 possible, but once the choice is made it is very very hard to unmake.

Right like Sum/Product for Num types. But here there's good reason, I
think, to choose one instance over others, because we already have the
monoid structure of Applicative and Monad. You can still have a
wrapper newtype with different instances for the alternatives, as was
done with Applicative for [] and ZipList.

But I might be misunderstanding, since I'm not really sure what the
alternative instances you mention would look like.

Thanks,
Brandon


 I say this mostly so you know the kinds of objections proposals like this
 usually see, not to flat out reject the idea of the particular case of this
 instance for IO.

 I will say the global 'instance (Applicative f, Monoid m) = Monoid (f m)'
 won't fly for overlap reasons though.

 -Edward


 On Mon, Jul 14, 2014 at 6:55 PM, Brandon Simmons
 brandon.m.simm...@gmail.com wrote:

 It seems to me that this should be true for all `f a` like:

   instance (Monoid a, Applicative f)= Monoid (f a) where
   mappend = liftA2 mappend
   mempty = pure mempty

 But I can't seem to find the particular `instance (Monoid a)= Monoid
 (IO a)` anywhere. Would that instance be incorrect, or does it live
 somewhere else?

 FWIW I noticed this when I started thinking about an instance I wanted
 for 'contravariant':

   instance (Monoid a, Applicative f)= Monoid (Op (f a) b) where
   mempty = Op $ const $ pure mempty
   mappend (Op f) (Op g) = Op (\b- liftA2 mappend (f b) (g b))

 at which point I realized (I think) all `f a` are monoidal, and so we
 ought to be able to get the instance above with just a deriving
 Monoid.

 Brandon
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Why no `instance (Monoid a, Applicative f)= Monoid (f a)` for IO?

2014-07-14 Thread Brandon Simmons
It seems to me that this should be true for all `f a` like:

  instance (Monoid a, Applicative f)= Monoid (f a) where
  mappend = liftA2 mappend
  mempty = pure mempty

But I can't seem to find the particular `instance (Monoid a)= Monoid
(IO a)` anywhere. Would that instance be incorrect, or does it live
somewhere else?

FWIW I noticed this when I started thinking about an instance I wanted
for 'contravariant':

  instance (Monoid a, Applicative f)= Monoid (Op (f a) b) where
  mempty = Op $ const $ pure mempty
  mappend (Op f) (Op g) = Op (\b- liftA2 mappend (f b) (g b))

at which point I realized (I think) all `f a` are monoidal, and so we
ought to be able to get the instance above with just a deriving
Monoid.

Brandon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Using mutable array after an unsafeFreezeArray, and GC details

2014-05-12 Thread Brandon Simmons
On Mon, May 12, 2014 at 4:32 AM, Simon Marlow marlo...@gmail.com wrote:
 On 09/05/2014 19:21, Brandon Simmons wrote:

 A couple of updates: Edward Yang responded here, confirming the sort
 of track I was thinking on:


 http://blog.ezyang.com/2014/05/ghc-and-mutable-arrays-a-dirty-little-secret/

 And I can report that:
1) cloning a frozen array doesn't provide the benefits of creating a
 new array and freezing
2) and anyway, I'm seeing some segfaults when cloning, freezing,
 reading then writing in my library

 I'd love to learn if there are any other approaches I might take, e.g.
 maybe with my own CMM primop variants?


 I'm not sure exactly what your workload looks like, but if you have arrays
 that tend to be unmodified for long periods of time it's sometimes useful to
 keep them frozen but thaw before mutating.

The idea is I'm using two atomic counters to coordinate concurrent
readers and writers along an infinite array (a linked list of array
segments that get allocated as needed and garbage collected as we go).
So currently each cell in each array is written to only once, with a
CAS.


 How large are your arrays? Perhaps the new small array type (in HEAD but not
 7.8) would help?

Thanks, maybe so! The arrays can be any size, but probably not smaller
than length 64 (this will be static, at compile-time).

I read through https://ghc.haskell.org/trac/ghc/ticket/5925, and it
seems like the idea is to improve array creation. I'm pretty happy
with the speed of cloning an array (but maybe cloneSmallArray will be
even faster still).

It also looks like stg_casSmallArrayzh (in PrimOps.cmm) omits the card
marking (maybe the idea is if the array is already at ~128 elements or
less, then the card-marking is all just overhead?).

Brandon


 Cheers,
 Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Using mutable array after an unsafeFreezeArray, and GC details

2014-05-09 Thread Brandon Simmons
A couple of updates: Edward Yang responded here, confirming the sort
of track I was thinking on:

  http://blog.ezyang.com/2014/05/ghc-and-mutable-arrays-a-dirty-little-secret/

And I can report that:
  1) cloning a frozen array doesn't provide the benefits of creating a
new array and freezing
  2) and anyway, I'm seeing some segfaults when cloning, freezing,
reading then writing in my library

I'd love to learn if there are any other approaches I might take, e.g.
maybe with my own CMM primop variants?

Thanks,
Brandon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Using mutable array after an unsafeFreezeArray, and GC details

2014-05-09 Thread Brandon Simmons
On May 9, 2014 5:13 PM, Edward Z. Yang ezy...@mit.edu wrote:

 Hello Brandon,

 Excerpts from Brandon Simmons's message of 2014-05-08 16:18:48 -0700:
  I have an unusual application with some unusual performance problems
  and I'm trying to understand how I might use unsafeFreezeArray to help
  me, as well as understand in detail what's going on with boxed mutable
  arrays and GC. I'm using the interface from 'primitive' below.
 
  First some basic questions, then a bit more background
 
  1) What happens when I do `newArray s x = \a- unsafeFreezeArray a
   return a` and then use `a`? What problems could that cause?

 Your code as written wouldn't compile, but assuming you're talking about
 the primops newArray# and unsafeFreezeArray#, what this operation does
 is allocate a new array of pointers (initially recorded as mutable), and
 then freezes it in-place (by changing the info-table associated with
 it), but while maintaining a pointer to the original mutable array.
 Nothing bad
 will happen immediately, but if you use this mutable reference to mutate
 the pointer array, you can cause a crash (in particular, if the array
 makes it to the old generation, it will not be on the mutable list and
 so if you mutate it, you may be missing roots.)

  2) And what if a do a `cloneMutableArray` on `a` and likewise use the
  resulting array?

 If you do the clone before freezing, that's fine for all use-cases;
 if you do the clone after, you will end up with the same result as (1).

  Background: I've been looking into an issue [1] in a library in which
  as more mutable arrays are allocated, GC dominates (I think I verified
  this?) and all code gets slower in proportion to the number of mutable
  arrays that are hanging around.
 
  I've been trying to understand how this is working internally. I don't
  quite understand how the remembered set works with respect to
  MutableArray. As best I understand: the remembered set in generation G
  points to certain objects in older generations, which objects hold
  references to objects in G. Then for MutableArrays specifically,
  card-marking is used to mark regions of the array with garbage in some
  way.
 
  So my hypothesis is the slowdown is associated with the size of the
  remembered set, and whatever the GC has to do on it. And in my tests,
  freezing the array seems to make that overhead (at least the overhead
  proportional to number of arrays) disappear.

 You're basically correct.  In the current GC design, mutable arrays of
 pointers are always placed on the mutable list.  The mutable list of
 generations which are not being collected are always traversed; thus,
 the number of pointer arrays corresponds to a linear overhead for minor
GCs.

 Here is a feature request tracking many of the infelicities that our
 current GC design has:  https://ghc.haskell.org/trac/ghc/ticket/7662
 The upshot is that the Haskell GC is very nicely tuned for mostly
 immutable workloads, but there are some bad asymptotics when your
 heap has lots of mutable objects.  This is generally a hard problem:
 tuned GC implementations for mutable languages are a lot of work!
 (Just ask the JVM implementors.)


Very helpful, thanks! And take some internet points.

  Now I'm really lost in the woods though. My hope is that I might be
  able to safely use unsafeFreezeArray to help me here [3]. Here are the
  particulars of how I use MutableArray in my algorithm, which are
  somewhat unusual:
- keep around a small template `MutableArray Nothing`
- use cloneMutableArray for fast allocation of new arrays
- for each array only a *single* write (CAS actually) happens at each
position
 
  In fact as far as I can reason, there ought to be no garbage to
  collect at all until the entire array becomes garbage (the initial
  value is surely shared, especially since I'm keeping this template
  array around to clone from, right?). In fact I was even playing with
  the idea of rolling a new CAS that skips the card-marking stuff.

 I don't understand your full workload, but if you have a workload that
 involves creating an array, mutating it over a short period of time,
 and then never mutating it afterwards, you should simply freeze it after
 you are done writing it.  Once frozen, the array will no longer be kept
 on the mutable list and you won't pay for it when doing GC.  However,
 the fact that you are doing a CAS makes it seem to me that your workflow
 may be more complicated than that...

Yes I think for my use case the overhead required to determine when the
array can be frozen would not be worth it. I think I have some other knobs
I can twist here.

I'll keep an eye on that ticket and maybe chime in if I have any ideas.

Thanks,
Brandon


 Cheers,
 Edward
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Using mutable array after an unsafeFreezeArray, and GC details

2014-05-08 Thread Brandon Simmons
I have an unusual application with some unusual performance problems
and I'm trying to understand how I might use unsafeFreezeArray to help
me, as well as understand in detail what's going on with boxed mutable
arrays and GC. I'm using the interface from 'primitive' below.

First some basic questions, then a bit more background

1) What happens when I do `newArray s x = \a- unsafeFreezeArray a
 return a` and then use `a`? What problems could that cause?

2) And what if a do a `cloneMutableArray` on `a` and likewise use the
resulting array?

Background: I've been looking into an issue [1] in a library in which
as more mutable arrays are allocated, GC dominates (I think I verified
this?) and all code gets slower in proportion to the number of mutable
arrays that are hanging around.

I've been trying to understand how this is working internally. I don't
quite understand how the remembered set works with respect to
MutableArray. As best I understand: the remembered set in generation G
points to certain objects in older generations, which objects hold
references to objects in G. Then for MutableArrays specifically,
card-marking is used to mark regions of the array with garbage in some
way.

So my hypothesis is the slowdown is associated with the size of the
remembered set, and whatever the GC has to do on it. And in my tests,
freezing the array seems to make that overhead (at least the overhead
proportional to number of arrays) disappear.

Now I'm really lost in the woods though. My hope is that I might be
able to safely use unsafeFreezeArray to help me here [3]. Here are the
particulars of how I use MutableArray in my algorithm, which are
somewhat unusual:
  - keep around a small template `MutableArray Nothing`
  - use cloneMutableArray for fast allocation of new arrays
  - for each array only a *single* write (CAS actually) happens at each position

In fact as far as I can reason, there ought to be no garbage to
collect at all until the entire array becomes garbage (the initial
value is surely shared, especially since I'm keeping this template
array around to clone from, right?). In fact I was even playing with
the idea of rolling a new CAS that skips the card-marking stuff.

Any guidance is appreciated.

Thanks,
Brandon


[1]: 
http://stackoverflow.com/questions/23462004/code-becomes-slower-as-more-boxed-arrays-are-allocated
[2]: 
http://www.haskell.org/pipermail/glasgow-haskell-users/2012-March/022142.html
[3]: 
https://ghc.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/GC/EagerPromotion
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: New INLINE pragma syntax idea, and some questions

2012-08-04 Thread Brandon Simmons
On Sat, Aug 4, 2012 at 6:22 AM, Dan Doel dan.d...@gmail.com wrote:

 On Aug 3, 2012 11:13 PM, Brandon Simmons brandon.m.simm...@gmail.com
 wrote:
 In particular I don't fully understand why these sorts of contortions...


 http://hackage.haskell.org/packages/archive/base/latest/doc/html/src/GHC-List.html#foldl

 ...are required. It seems like a programmer has to throw equational
 reasoning, separation of concerns, and all the little elegant bits
 about the language out the window just to indicate something boring to
 the compiler.

 Disclaimer: The following is less a proposal meant to be taken
 seriously, and more me trying to better understand things.

 Could the following be used as syntax for indicating inlining? Rather
 than relying on the syntactic LHS, instead let that be specified in
 the type signature...

 foldl:: (a - b - a) - a - [b] - {-# INLINE #-} a
 foldl f z [] =  z
 foldl f z (x:xs) = foldl f (f z x) xs

 ...indicating, in this case, that foldl should be inlined when
 fully-applied means its first three arguments (I guess that's the
 intent of the original version linked above?). Then (waves hands) the
 compiler could do the necessary transformations that the programmer
 had to do to foldl above. Maybe what I'm proposing is actually a
 separate NORECURSIVE_TRANSFORM pragma or something

 That's not quite the effect. What has been done to foldl there is known as
 the static argument transform. It avoids passing constant arguments along in
 recursion. f is the only static argument to foldl (foldr by contrast has
 two).

I think I didn't pick a very good example there. The only thing that
bothers me about this foldl is the presence of z0 xs0, which I think
are only there on the LHS to indicate to GHC where it should inline.

The static argument transform itself seems like just good
programming practice (don't repeat yourself, abstract out common
things), and the implications on optimized code make a lot of sense,
so I think that doesn't bother me.


 This can be important for multiple reasons. Sometimes it frees up registers.
 Here, we may inline foldl and possibly specialize the loop to a statically
 known f. That is often a big win. For instance, if you write sum with foldl,
 you can inline, do a worker wrapper transform, and work on unboxed integers
 with raw adds (probably) instead of going through multiple layers of
 indirection.

 There was some work on making GHC automatically SAT, but of it's a bit
 tricky with regard to when it's worth it, so I don't think it's been put in.

 I have code that relies on this sort of thing a lot, so if someone comes up
 with a good way to automate it, I wouldn't complain.

 Dan

Thanks for the details and clarifications!

Brandon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


New INLINE pragma syntax idea, and some questions

2012-08-03 Thread Brandon Simmons
I've been wondering for some time about the details of how GHC uses
syntax with inlining, and how other transformations come into play in
the process (I recently asked a question on SO if anyone wants some
karma: http://stackoverflow.com/q/11690146/176841). I know this is a
big topic and there's probably a lot more out there I should read.

In particular I don't fully understand why these sorts of contortions...


http://hackage.haskell.org/packages/archive/base/latest/doc/html/src/GHC-List.html#foldl

...are required. It seems like a programmer has to throw equational
reasoning, separation of concerns, and all the little elegant bits
about the language out the window just to indicate something boring to
the compiler.

Disclaimer: The following is less a proposal meant to be taken
seriously, and more me trying to better understand things.

Could the following be used as syntax for indicating inlining? Rather
than relying on the syntactic LHS, instead let that be specified in
the type signature...

foldl:: (a - b - a) - a - [b] - {-# INLINE #-} a
foldl f z [] =  z
foldl f z (x:xs) = foldl f (f z x) xs

...indicating, in this case, that foldl should be inlined when
fully-applied means its first three arguments (I guess that's the
intent of the original version linked above?). Then (waves hands) the
compiler could do the necessary transformations that the programmer
had to do to foldl above. Maybe what I'm proposing is actually a
separate NORECURSIVE_TRANSFORM pragma or something.

An alternative if including the pragma in the type sig. isn't sound,
is to allow it in the function definition left-hand side, after the
bindings we would like applied before inlining.

Brandon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Understanding behavior of BlockedIndefinitelyOnMVar exception

2011-07-26 Thread Brandon Simmons
On Tue, Jul 26, 2011 at 1:25 AM, Edward Z. Yang ezy...@mit.edu wrote:
 Hello Brandon,

 The answer is subtle, and has to do with what references are kept in code,
 which make an object considered reachable.  Essentially, the main thread
 itself keeps the MVar live while it still has forking to do, so that
 it cannot get garbage collected and trigger these errors.

Ah, okay. That seems like an obvious explanation for the exceptions
to be raised at the same time in the forked threads.


 Here is a simple demonstrative program:

    main = do
        lock - newMVar ()
        forkIO (takeMVar lock)
        forkIO (takeMVar lock)
        forkIO (takeMVar lock)


(snip)


 But in the meantime (esp. between invocation 2 and 3), the MVar cannot be
 garbage collected, because it is live on the stack.

 Could GHC have been more clever in this case?  Not in general, since deciding
 whether or not a reference will actually be used or not boils down to the
 halting problem.

    loop = threadDelay 100  loop -- prevent blackholing from discovering this
    main = do
        lock - newEmptyMVar
        t1 - newEmptyMVar
        forkIO (takeMVar lock  putMVar t1 ())
        forkIO (loop `finally` putMVar lock ())
        takeMVar t1

 Maybe we could do something where MVar references are known to be writer ends
 or read ends, and let the garbage collector know that an MVar with only read
 ends left is a deadlocked one.  However, this would be a very imprecise
 analysis, and would not help in your original code (since all of your 
 remaining
 threads had the possibility of writing to the MVar: it doesn't become clear
 that they can't until they all hit their takeMVar statements.)

I think this is the crux of what I was confused about. I had assumed
read vs. write was being taken into account by the runtime in raising
BlockedIndefinitelyOnMVar. This makes it obvious:

loop = threadDelay 100  loop -- prevent blackholing from discovering this
main = do
   lock - newEmptyMVar
   forkIO (loop `finally` takeMVar lock)
   takeMVar lock


Given that, I still can't say I understand what is happening in my
original code. I'll try to work out an even simpler example on my own.

Thanks for  the thoughtful response,
Brandon



 Cheers,
 Edward


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Understanding behavior of BlockedIndefinitelyOnMVar exception

2011-07-25 Thread Brandon Simmons
On Sun, Jul 24, 2011 at 10:02 PM, Felipe Almeida Lessa
felipe.le...@gmail.com wrote:
 On Sun, Jul 24, 2011 at 7:56 PM, Brandon Simmons
 brandon.m.simm...@gmail.com wrote:
 What I think I've learned here is that the BlockedIndefinitelyOnMVar
 exception is raised in all the blocked threads at once as it were.
 That despite the fact that the handler code in 'lockPrint' restores
 the lock for successive threads.

 This would also seem to imply that putMVar's in an exception handler
 don't stop the runtime from raising the BlockedIndefinitelyOnMVar. But
 that doesn't really seem right.

 Does anything change if you somehow force a GC sometime after good2?
  Perhaps with some calculation generating garbage, perhaps with
 performGC.  IIRC, the runtime detects BlockedIndefinitelyOnMVar on GC.
  But I'm probably wrong =).

Here is a variation that calls 'performGC' after the first thread is
forked. It prints the exception simultaneously right before  the last
'threadDelay':

main2 = do
lock - newMVar ()
forkIO $ lockPrint good1 lock

threadDelay 100
forkIO $ badLockPrint bad lock

-- these both raise blocked indefinitely exception
threadDelay 100
forkIO $ lockPrint good2 lock
performGC
threadDelay 100
forkIO $ lockPrint good3 lock

threadDelay 100

Perhaps laziness is confusing the issue as well?

Thanks and sorry for the delayed response,
Brandon Simmons




 Cheers,

 --
 Felipe.


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Understanding behavior of BlockedIndefinitelyOnMVar exception

2011-07-25 Thread Brandon Simmons
On Sun, Jul 24, 2011 at 10:07 PM, Edward Z. Yang ezy...@mit.edu wrote:
 Excerpts from Felipe Almeida Lessa's message of Sun Jul 24 22:02:36 -0400 
 2011:
 Does anything change if you somehow force a GC sometime after good2?
  Perhaps with some calculation generating garbage, perhaps with
 performGC.  IIRC, the runtime detects BlockedIndefinitelyOnMVar on GC.
  But I'm probably wrong =).

 That's correct.

   resurrectThreads is called after garbage collection on the list of
   threads found to be garbage.  Each of these threads will be woken
   up and sent a signal: BlockedOnDeadMVar if the thread was blocked
   on an MVar, or NonTermination if the thread was blocked on a Black
   Hole.

 Cheers,
 Edward


Thanks, Edward. I'm going to take a look at the GHC source and see if
I can grok any of it. Any comment on whether it is correct behavior to
have the exception raised in all the threads attempting a readMVar at
once (if that's actually what's happening), even though an exception
handler will fill the MVar for subsequent threads?

I think I'm not totally clear on what qualifies as indefinitely

Thanks again,
Brandon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Understanding behavior of BlockedIndefinitelyOnMVar exception

2011-07-24 Thread Brandon Simmons
I'm trying to really understand how the BlockedIndefinitelyOnMVar
exception works in concurrent code as I would like to rely on it as a
useful runtime signal in a concurrency library I'm working on.

Here is some code illustrating a function restoring an abandoned lock
in a single-threaded program and works as I would expect:

 START CODE 
module Main
where

import Control.Concurrent
import Control.Exception

-- This raises the exception only once and the lock is successfully restored:
main1 = do
lock - newMVar ()
lockPrint good1 lock
badLockPrint bad lock
-- exception is raised and lock is restored here:
lockPrint good2 lock
-- no exception raised:
lockPrint good3 lock
readMVar lock

lockPrint :: String - MVar () - IO ()
lockPrint name v =
do e - try $ takeMVar v :: IO (Either BlockedIndefinitelyOnMVar ())
   -- either print exception, or print name:
   either print (const $ putStrLn name) e
   `finally`  putMVar v ()

-- perhaps simulates an operation that died before it could return a lock:
badLockPrint :: String - MVar () - IO ()
badLockPrint s v = do
takeMVar v
putStrLn s
-- Forgot to return the lock here!:
 END CODE 


Now here is a variation of 'main' that forks the operations:


 START CODE 
main0 = do
lock - newMVar ()
forkIO $ lockPrint good1 lock

threadDelay 100
forkIO $ badLockPrint bad lock

-- these both raise blocked indefinitely exception
threadDelay 100
forkIO $ lockPrint good2 lock
threadDelay 100
forkIO $ lockPrint good3 lock

threadDelay 100
 END CODE 


What I think I've learned here is that the BlockedIndefinitelyOnMVar
exception is raised in all the blocked threads at once as it were.
That despite the fact that the handler code in 'lockPrint' restores
the lock for successive threads.

This would also seem to imply that putMVar's in an exception handler
don't stop the runtime from raising the BlockedIndefinitelyOnMVar. But
that doesn't really seem right.

Can anyone comment on the two conclusions above?

FWIW, this was an interesting related thread:
http://comments.gmane.org/gmane.comp.lang.haskell.glasgow.user/18667

Thanks,
Brandon Simmons
http://coder.bsimmons.name

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users