Re: [Haskell-cafe] Any precedent or plan for guaranteed-safe Eq and Ord instances?

2013-10-06 Thread Ryan Newton
Thanks for the responses all.

I'm afraid the point about GHC.Generics got lost here.  I'll respond and
then rename this as a specific library proposal.

I don't want to fix the world's Eq instances, but I am ok with requiring
that people derive Generic for any data they want to put in an LVar
container.  (From which I can give them a SafeEq instance.)

It's not just LVish that is in this boat any library that tries to
provide deterministic parallelism outside of the IO monad has some very
fine lines to walk.  Take a look at Accelerate.  It is deterministic (as
long as you run only with the CUDA backend and only on one specific GPU...
otherwise fold topologies may look different and non-associative folds may
leak).  Besides, runAcc does a huge amount of implicit IO (writing to
disk, calling nvcc, etc)!  At the very least this could fail if the disk if
full.  But then again, regular pure computations fail when memory runs
out... so I'm ok grouping these in the same bucket for now.  Determinism
modulo available resources.

A possible problem with marking instance Eq as an unsafe feature is that
 many modules would be only Trustworthy instead of Safe.


My proposal is actually more narrow than that.  My proposal is to mark
GHC.Generics as Unsafe.

That way I can define my own SafeEq, and know that someone can't break it
by making a Generic instance that lies.  It is very hard for me to see why
people should be able to make their own Generic instances (that might lie
about the structure of the type), in Safe-Haskell.


 That would go against my every purely functional module is automatically
 safe because the compiler checks that it cannot launch the missiles
 understanding of Safe Haskell.


Heh, that may already be violated by the fact that you can't use other
extensions like OverlappingInstances, or provide your own Typeable
instances.



 Actually, Eq instances are not unsafe per se, but only if I also use some
 other module that assumes certain properties about all Eq instances in
 scope. So in order to check safety, two independent modules (the provider
 and the consumer of the Eq instance) would have to cooperate.


I've found, that this is a very common problem that we have when trying to
make our libraries Safe-Haskell compliant -- often we want to permit and
deny combinations of modules.  I don't have a solution I'm afraid.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Converting MPTC+fundeps to type family / problem with polymorphic constant. Roles?

2013-10-06 Thread Ryan Newton
The abstract-par class has used multi-parameter type classes with fundeps:


http://hackage.haskell.org/package/abstract-par-0.3.1/docs/Control-Monad-Par-Class.html#g:1

And I'm trying to port it to use type families.  But the following
combination seems to be completely unusable for me right now:

class ParFuture m  = ParIVar m  where
  new  :: forall a . m (Future m a)

You can see the error when you try loading this file at this line:

https://github.com/iu-parfunc/lvars/blob/b60cafb941ea8f2f333ada9b5206cd21211eae26/haskell/par-classes/Control/Par/Class.hs#L159

Future is a type-function from the superclass.  I can't seem to use new
in any way at any type without getting:

Control/Par/Class.hs:161:9:
Could not deduce (Future m a ~ Future m a0)
from the context (ParIVar m, FutContents m a)
  bound by the type signature for
 newFull_ :: (ParIVar m, FutContents m a) = a - m (IVar m
a)
  at Control/Par/Class.hs:151:13-74
NB: `Future' is a type function, and may not be injective
The type variable `a0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Expected type: m (IVar m a)
  Actual type: m (Future m a0)
In the expression: (new :: m (IVar m a))
In a pattern binding: _ = (new :: m (IVar m a))
In an equation for `newFull_':
newFull_ a
  = do { return undefined }
  where
  _ = (new :: m (IVar m a))
Failed, modules loaded: none.

Ok, so it seems like the type of new may just be intrinsically unusable.
 There is no way, by constraining the output of the new function for the
type system to infer what input to the Future type function was.  (Type
function not reversable / injective.)

So am I just stuck?  I don't want a dummy, unused argument just to
communicate the type information to new.  Is this just a place where *MPTC
+ fundeps works but type familes do not?  *Or is there some way that roles
can save the day here?  Do I need to *say that the 'a' parameter has a
representation role*?

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


Re: [Haskell-cafe] Converting MPTC+fundeps to type family / problem with polymorphic constant. Roles?

2013-10-06 Thread Ryan Newton
Oops, right after I sent I realized the answer ;-).  I needed to delete one
character to uncurry the type function.  That is:

   type Future m

instead of

   type Future m a

The fixed version is here:

https://github.com/iu-parfunc/lvars/blob/2b733d3044fde861e9c9b181258e7f9865afa204/haskell/par-classes/Control/Par/Class.hs#L60

I'm still not totally sure what thought process and design guidelines I
should internalize for next time... perhaps: make sure type families have
the minimum number of arguments that they need.

Best,
  -Ryan



On Sun, Oct 6, 2013 at 8:27 PM, Ryan Newton rrnew...@gmail.com wrote:

 The abstract-par class has used multi-parameter type classes with
 fundeps:


 http://hackage.haskell.org/package/abstract-par-0.3.1/docs/Control-Monad-Par-Class.html#g:1

 And I'm trying to port it to use type families.  But the following
 combination seems to be completely unusable for me right now:

 class ParFuture m  = ParIVar m  where

   new  :: forall a . m (Future m a)


 You can see the error when you try loading this file at this line:


 https://github.com/iu-parfunc/lvars/blob/b60cafb941ea8f2f333ada9b5206cd21211eae26/haskell/par-classes/Control/Par/Class.hs#L159

 Future is a type-function from the superclass.  I can't seem to use
 new in any way at any type without getting:

 Control/Par/Class.hs:161:9:
 Could not deduce (Future m a ~ Future m a0)
 from the context (ParIVar m, FutContents m a)
   bound by the type signature for
  newFull_ :: (ParIVar m, FutContents m a) = a - m (IVar
 m a)
   at Control/Par/Class.hs:151:13-74
 NB: `Future' is a type function, and may not be injective
 The type variable `a0' is ambiguous
 Possible fix: add a type signature that fixes these type variable(s)
 Expected type: m (IVar m a)
   Actual type: m (Future m a0)
 In the expression: (new :: m (IVar m a))
 In a pattern binding: _ = (new :: m (IVar m a))
 In an equation for `newFull_':
 newFull_ a
   = do { return undefined }
   where
   _ = (new :: m (IVar m a))
 Failed, modules loaded: none.

 Ok, so it seems like the type of new may just be intrinsically unusable.
  There is no way, by constraining the output of the new function for the
 type system to infer what input to the Future type function was.  (Type
 function not reversable / injective.)

 So am I just stuck?  I don't want a dummy, unused argument just to
 communicate the type information to new.  Is this just a place where *MPTC
 + fundeps works but type familes do not?  *Or is there some way that
 roles can save the day here?  Do I need to *say that the 'a' parameter
 has a representation role*?

 Thanks,
   -Ryan


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


Re: [Haskell-cafe] Any precedent or plan for guaranteed-safe Eq and Ord instances?

2013-10-06 Thread Ryan Newton
Tillmann,

Thanks, that is in interesting use case for handwritten Generics.

I'm not fully dissuaded though, simply because:

(1) it can't be too common!  Especially when you intersect the people who
have done or will do this with the people who care about SafeHaskell.
 (Again, if they don't, they won't mind this tiny Unsafe toggle.)

(2) even people who fall in this intersection still have the recourse of
doing what they need to do and asserting TrustWorthy.  SafeHaskell is
good at supporting this kind of individual exception.

Whereas in my case I have no recourse!  Because my problem not about
asserting that a particular module is TrustWorthy, but rather about keeping
other users (running in -XSafe) from breaking my library.



On Sun, Oct 6, 2013 at 6:54 PM, Tillmann Rendel 
ren...@informatik.uni-marburg.de wrote:

 Hi,


 Ryan Newton wrote:

 It is very hard for me to
 see why people should be able to make their own Generic instances (that
 might lie about the structure of the type), in Safe-Haskell.


 I guess that lying Generics instances might arise because of software
 evolution. Let's say we start with an abstract data type of binary trees.

   module Tree (Tree, node, empty, null, split) where
 data Tree a = Node (Tree a) (Tree a) | Empty
   deriving Generics

 node = Node

 empty = Empty

 null Empty = True
 null _ = False

 split (Node a b) = (a, b)

 size Empty = 0
 size (Node x y) = size x + size y

 Note that this data type is not really abstract, because we export the
 Generics instance, so clients of this module can learn about the
 implementation of Tree. This is not a big deal, because the chosen
 implementation happens to correspond to the abstract structure of binary
 trees anyway. So I would expect that generic code will work fine. For
 example, you could use generic read and show functions to serialize trees,
 and get a reasonable data format.

 Now, we want to evolve our module by caching the size of trees. We do
 something like this:

   module Tree (Tree, node, empty, null, split) where
 data Tree a = Tree !Int (RealTree a)

 data RealTree a = Node (Tree a) (Tree a) | Empty

 tree (Node a b) = Tree (size a + size b) t
 tree Empty = Tree 0 Empty

 node x y = tree (Node x y)

 empty = tree Empty

 null (Tree _ Empty) = True
 null _ = False

 split (Tree _ (Node a b)) = (a, b)

 size (Tree n _) = n

 Except for the Generics instance, we provide the exact same interface and
 behavior to our clients, we just traded some space for performance. But
 what Generics instance should we provide? If we just add deriving
 Generics to the two datatypes, we leak the change of representation to our
 clients. For example, a client that serialized a tree with a generic show
 function based on the old Tree cannot hope to deserialize it back with a
 generic read function based on the new Tree. The size information would be
 missing, and the structure would be different.

 If we write a Generics instance by hand, however, I guess we can make it
 present the exact same structure as the derived Generics instance for the
 old Tree. With this lying instance, the generic read function will happily
 deserialize the old data. The size will be computed on the fly, because our
 hand-written Generics instance will introduce calls to our smart
 constructors.


   Tillmann
 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@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


Re: [Haskell-cafe] [ANN] lvish 1.0 -- successor to monad-par

2013-10-03 Thread Ryan Newton
Hi Ben,

We made a small update
releasehttp://hackage.haskell.org/package/lvish-1.0.0.2that links
the github, and also links a mirror for the haddocks, since
something weird seems to be going on with Hackage 2:

   http://www.cs.indiana.edu/~rrnewton/haddock/lvish/
   https://github.com/iu-parfunc/lvars



On Wed, Oct 2, 2013 at 1:05 PM, Ben Gamari bgamari.f...@gmail.com wrote:

 Ryan Newton rrnew...@gmail.com writes:

  Hi all,
 
  I'm pleased to announce the release of our new parallel-programming
  library, LVish:
 
  hackage.haskell.org/package/lvish
 
  It provides a Par monad similar to the monad-par package, but
 generalizes
  the model to include data-structures other than single-assignment
 variables
  (IVars).  For example, it has lock-free concurrent data structures for
 Sets
  and Maps, which are constrained to only grow monotonically during a given
  runPar (to retain determinism).  This is based on work described in our
  upcoming POPL 2014 paper:
 
 Do you have any aidea why the Haddocks don't yet exist. If I recall
 correctly, under Hackage 1 the module names wouldn't be made links until
 Haddock generation had completed. Currently the lvish modules' point to
 non-existent URLs.

 Also, is there a publicly accessible repository where further
 development will take place?

 Cheers,

 - Ben


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


[Haskell-cafe] Any precedent or plan for guaranteed-safe Eq and Ord instances?

2013-10-01 Thread Ryan Newton
Hello all,

Normally, we don't worry *too* much about incorrect instances of standard
classes (Num, Eq, Ord) etc.  They make the user's program wrong, but they
don't compromise the type system.

Unfortunately, with the LVish parallel programming library we do have a
situation where incorrect instances of Eq and Ord can cause the types to
lie.  In particular, something that claims to be a pure, non-IO type, can
actually yield a different result on different runs, including throwing
exceptions on some runs but not others.

So what's the best way to lock down SafeEq and SafeOrd instances,
taking control away from the user (at least with -XSafe is turned on)?

We could derive our own SafeEq and SafeOrd instances based on GHC.Generics.
 BUT, that only helps if we can forbid the user from writing their own
incorrect Generics instances when Safe Haskell is turned on.  It looks like
GHC.Generics is currently marked as TrustWorthy:


http://www.haskell.org/ghc/docs/7.4.1/html/libraries/ghc-prim-0.2.0.0/GHC-Generics.html

So could we get GHC.Generics marked as Unsafe and enable some more
limited interface that is Trustworthy?  (Allowing the user ONLY to do
'deriving Generic').

This would be similar to the new policy in GHC 7.8 of only allowing derived
Typeable instances...

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


Re: [Haskell-cafe] Any precedent or plan for guaranteed-safe Eq and Ord instances?

2013-10-01 Thread Ryan Newton
Here are some examples:

-
data Foo = Bar | Baz

instance Eq Foo where
  _ == _ = True

instance Ord Foo where
  compare Bar Bar = EQ
  compare Bar Baz = LT
  compare _   _   = error I'm partial!
-

These would allow LVish's runPar to non-determinstically return Bar or
Baz (thinking they're the same based on Eq).  Or it would allow runPar to
nondeterministically crash based on different schedulings hitting the
compare error or not [1].

FYI here's LVish:

http://www.cs.indiana.edu/~rrnewton/haddock/lvish/
https://github.com/iu-parfunc/lvars

(More info in this POPL paper:
http://www.cs.indiana.edu/~rrnewton/papers/2013_07_LVish_quasiDet_working_draft.pdf
)

   -Ryan

[1] If you're curious why this happens, its because the Ord instance is
used by, say, Data.Set and Data.Map for the keys.  If you're inserting
elements in an arbitrary order, the final contents ARE deterministic, but
the comparisons that are done along the way ARE NOT.



On Tue, Oct 1, 2013 at 4:13 PM, Ryan Newton rrnew...@gmail.com wrote:

 Hello all,

 Normally, we don't worry *too* much about incorrect instances of standard
 classes (Num, Eq, Ord) etc.  They make the user's program wrong, but they
 don't compromise the type system.

 Unfortunately, with the LVish parallel programming library we do have a
 situation where incorrect instances of Eq and Ord can cause the types to
 lie.  In particular, something that claims to be a pure, non-IO type, can
 actually yield a different result on different runs, including throwing
 exceptions on some runs but not others.

 So what's the best way to lock down SafeEq and SafeOrd instances,
 taking control away from the user (at least with -XSafe is turned on)?

 We could derive our own SafeEq and SafeOrd instances based on
 GHC.Generics.  BUT, that only helps if we can forbid the user from writing
 their own incorrect Generics instances when Safe Haskell is turned on.  It
 looks like GHC.Generics is currently marked as TrustWorthy:


 http://www.haskell.org/ghc/docs/7.4.1/html/libraries/ghc-prim-0.2.0.0/GHC-Generics.html

 So could we get GHC.Generics marked as Unsafe and enable some more
 limited interface that is Trustworthy?  (Allowing the user ONLY to do
 'deriving Generic').

 This would be similar to the new policy in GHC 7.8 of only allowing
 derived Typeable instances...

   -Ryan


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


[Haskell-cafe] [ANN] lvish 1.0 -- successor to monad-par

2013-10-01 Thread Ryan Newton
Hi all,

I'm pleased to announce the release of our new parallel-programming
library, LVish:

hackage.haskell.org/package/lvish

It provides a Par monad similar to the monad-par package, but generalizes
the model to include data-structures other than single-assignment variables
(IVars).  For example, it has lock-free concurrent data structures for Sets
and Maps, which are constrained to only grow monotonically during a given
runPar (to retain determinism).  This is based on work described in our
upcoming POPL 2014 paper:


http://www.cs.indiana.edu/~rrnewton/papers/2013_07_LVish_quasiDet_working_draft.pdf

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


Re: [Haskell-cafe] Proposal: Partitionable goes somewhere + containers instances

2013-09-30 Thread Ryan Newton
 so the simple O(1) split would produce three submaps, the middle one
 having only one element. This operation would not be very
 parallelization-friendly.


Actually, I'm perfectly happy with that in this case!

   - A decent work-stealing system can tolerate a fairly large number of
   excessively small, trivial computations. It's having *only* those that's
   a big problem.  (Which is what you often get if your parallel container ops
   spawn a task per element.)
   - Since Maps support O(1) size, the consumer of the split-up-map could
   choose to sequentially execute the singleton maps if desired.

Personally, I'm most interested in set-like operations and don't need any
order guarantees.  But that's another dimension in which one could chop up
the API...

Maybe this does deserve its own module in the namespace, and maybe its own
package, as Edward suggested.

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


Re: [Haskell-cafe] What class for splittable data / balanced-fold?

2013-09-30 Thread Ryan Newton
Oops, this email got stuck in the pipe (flaky internet):


foldMap _ Tip = mempty  foldMap f (Bin _ _ v l r) = Foldable.foldMap f l 
 `mappend` f v `mappend` Foldable.foldMap f r


Btw, from my perspective, one problem with relying on foldMap is that it
treats the whole structure uniformly, whereas the split approach would let
one, for example, bottom out to a sequential implementation at a certain
granularity.  Perhaps that is the boilerplate for controlling recursion
that you referred to... but isn't it sometimes necessary?

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


Re: [Haskell-cafe] Proposal: Partitionable goes somewhere + containers instances

2013-09-30 Thread Ryan Newton
Edward,

The problem is that I need *something* more from the containers library to
be able to construct this as a separate library.  I don't think I can use
foldMap to implement a Splittable/Partitionable instance for Data.Set,
namely because I specifically want to do O(1) work instead of any kind of
full traversal of the structure.

Is the least possible disruption here to just have a Data.Map.Internal that
exposes Tip and Bin?  It can be marked with suitable warnings at the top of
the module.

Or would the preference to be to expose something more abstract of type
Map k a - [Map k a] that chops it into the natural pieces? [1]

  -Ryan

[1] Btw, it seems like returning a tuple here might make deforestation more
likely than returning a list... right?


On Mon, Sep 30, 2013 at 9:52 AM, Edward Kmett ekm...@gmail.com wrote:

 Upon consideration from a package management perspective this is probably
 easiest done by building a new small package to provide the functionality
 you want. That way we don't haphazardly change the transitive dependencies
 of a big chunk of the ecosystem and it can rest atop the various containers
 libraries. This also gives you a lot of opportunity to iterate on the API
 in public without incurring the instant rigidity of the Haskell Platform.


 On Sun, Sep 29, 2013 at 11:06 PM, Ryan Newton rrnew...@gmail.com wrote:

 Thanks Edward.  Good point about Brent's 'split' package.  That would be
 a really nice place to put the class.  But it doesn't currently depend on
 containers or vector so I suppose the other instances would need to go
 somewhere else.  (Assuming containers only exported monomorphic versions.)

 Maybe a next step would be proposing some monomorphic variants for the
 containers package.

 I think the complicated bit will be describing how best-efforty
 splitting variants are:

- Is it guaranteed O(1) time and allocation?
- Is the provided Int an upper bound?  Lower(ish) bound?  Or just a
hint?

 With some data structures, there will be a trade-off between partition
 imbalance and the work required to achieve balance.  But with some data
 structures it is happily not a problem (e.g. Vector)!

 But whether there's one variant or a few, I'd be happy either way, as
 long as I get at least the cheap one (i.e. prefer imbalance to
 restructuring).

   -Ryan




 On Sun, Sep 29, 2013 at 8:20 AM, Edward Kmett ekm...@gmail.com wrote:

 I don't know that it belongs in the standard libraries, but there
 could definitely be a package for something similar.

 ConstraintKinds are a pretty hefty extension to throw at it, and the
 signature written there prevents it from being used on ByteString, Text,
 etc.

 This can be implemented with much lighter weight types though!


 class Partitionable t where






 partition :: Int - t - [t]







 Now ByteString, Text etc. can be instances and no real flexibility is
 lost, as with the class associated constraint on the argument, you'd
 already given up polymorphic recursion.

 There still remain issues. partition is already established as the
 filter that returns both the matching and unmatching elements, so the
 name is wrong.

 This is a generalization of Data.List.splitEvery, perhaps it is worth
 seeing how many others can be generalized similarly and talk to Brent about
 adding, say, a Data.Split module to his split package in the platform?

 -Edward





 On Sun, Sep 29, 2013 at 4:21 AM, Ryan Newton rrnew...@gmail.com wrote:

 subject change

 On Sun, Sep 29, 2013 at 3:31 AM, Mike Izbicki m...@izbicki.me wrote:

 I've got a Partitionable class that I've been using for this purpose:

 https://github.com/mikeizbicki/ConstraintKinds/blob/master/src/Control/ConstraintKinds/Partitionable.hs


 Mike -- Neat, that's a cool library!

 Edward --  ideally, where in the standard libraries should the
 Partitionable comonoid go?

 Btw, I'm not sure what the ideal return type for comappend is, given
 that it needs to be able to bottom out.  Mike, our partition function's
 list return type seems more reasonable.  Or maybe something simple would be
 this:

 *class Partitionable t where*
 *  partition :: t - Maybe (t,t)*

 That is, at some point its not worth splitting and returns Nothing, and
 you'd better be able to deal with the 't' directly.

 So what I really want is for the *containers package to please get
 some kind of Partitionable instances! * Johan  others, I would be
 happy to provide a patch if the class can be agreed on. This is important
 because currently the balanced tree structure of Data.Set/Map is an 
 *amazing
 and beneficial property* that is *not* exposed at all through the API.

For example, it would be great to have a parallel traverse_ for
 Maps and Sets in the Par monad.  The particular impetus is that our
 new and enhanced Par monad makes extensive use of Maps and Sets, both the
 pure, balanced ones, and lockfree/inplace ones based on concurrent skip
 lists:

 http://www.cs.indiana.edu/~rrnewton

[Haskell-cafe] Proposal: Partitionable goes somewhere + containers instances

2013-09-29 Thread Ryan Newton
subject change

On Sun, Sep 29, 2013 at 3:31 AM, Mike Izbicki m...@izbicki.me wrote:

 I've got a Partitionable class that I've been using for this purpose:

 https://github.com/mikeizbicki/ConstraintKinds/blob/master/src/Control/ConstraintKinds/Partitionable.hs


Mike -- Neat, that's a cool library!

Edward --  ideally, where in the standard libraries should the
Partitionable comonoid go?

Btw, I'm not sure what the ideal return type for comappend is, given that
it needs to be able to bottom out.  Mike, our partition function's list
return type seems more reasonable.  Or maybe something simple would be this:

*class Partitionable t where*
*  partition :: t - Maybe (t,t)*

That is, at some point its not worth splitting and returns Nothing, and
you'd better be able to deal with the 't' directly.

So what I really want is for the *containers package to please get some
kind of Partitionable instances! * Johan  others, I would be happy to
provide a patch if the class can be agreed on. This is important because
currently the balanced tree structure of Data.Set/Map is an *amazing and
beneficial property* that is *not* exposed at all through the API.
   For example, it would be great to have a parallel traverse_ for Maps and
Sets in the Par monad.  The particular impetus is that our new and enhanced
Par monad makes extensive use of Maps and Sets, both the pure, balanced
ones, and lockfree/inplace ones based on concurrent skip lists:

http://www.cs.indiana.edu/~rrnewton/haddock/lvish/

Alternatively, it would be ok if there were a Data.Map.Internal module
that exposed the Bin/Tip, but I assume people would rather have a clean
Partitionable instance...

Best,
  -Ryan


On Sun, Sep 29, 2013 at 3:31 AM, Mike Izbicki m...@izbicki.me wrote:

 I've got a Partitionable class that I've been using for this purpose:


 https://github.com/mikeizbicki/ConstraintKinds/blob/master/src/Control/ConstraintKinds/Partitionable.hs

 The function called parallel in the HLearn library will automatically
 parallelize any homomorphism from a Partionable to a Monoid.  I
 specifically use that to parallelize machine learning algorithms.

 I have two thoughts for better abstractions:

 1)  This Partitionable class is essentially a comonoid.  By reversing the
 arrows of mappend, we get:

 comappend :: a - (a,a)

 By itself, this works well if the number of processors you have is a power
 of two, but it needs some more fanciness to get things balanced properly
 for other numbers of processors.  I bet there's another algebraic structure
 that would capture these other cases, but I'm not sure what it is.

 2) I'm working with parallelizing tree structures right now (kd-trees,
 cover trees, oct-trees, etc.).  The real problem is not splitting the
 number of data points equally (this is easy), but splitting the amount of
 work equally.  Some points take longer to process than others, and this
 cannot be determined in advance.  Therefore, an equal split of the data
 points can result in one processor getting 25% of the work load, and the
 second processor getting 75%.  Some sort of lazy Partitionable class that
 was aware of processor loads and didn't split data points until they were
 needed would be ideal for this scenario.

 On Sat, Sep 28, 2013 at 6:46 PM, adam vogt vogt.a...@gmail.com wrote:

 On Sat, Sep 28, 2013 at 1:09 PM, Ryan Newton rrnew...@gmail.com wrote:
  Hi all,
 
  We all know and love Data.Foldable and are familiar with left folds and
  right folds.  But what you want in a parallel program is a balanced fold
  over a tree.  Fortunately, many of our datatypes (Sets, Maps) actually
 ARE
  balanced trees.  Hmm, but how do we expose that?

 Hi Ryan,

 At least for Data.Map, the Foldable instance seems to have a
 reasonably balanced fold called fold (or foldMap):

   fold t = go t
 where   go (Bin _ _ v l r) = go l `mappend` (v `mappend` go r)

 This doesn't seem to be guaranteed though. For example ghc's derived
 instance writes the foldr only, so fold would be right-associated for
 a:

  data T a = B (T a) (T a) | L a deriving (Foldable)

 Regards,
 Adam
 ___
 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] What class for splittable data / balanced-fold?

2013-09-29 Thread Ryan Newton
Thanks, that's interesting to know (re: Fortress).

Interestingly, in my Fortress days we looked at both using a split-like
 interface and at a more foldMap / reduce - like interface, and it seemed
 like the latter worked better – it requires a lot less boilerplate for
 controlling recursion, and better matches the fanout of whatever structure
 you're actually using underneath.


Ok, we'll have to try that.  I may be underestimating the power of a
newtype and a monoid instance to expose the structure..  I was wrong about
this before [1].  Here's the foldMap instance for Data.Map:

  foldMap _ Tip = mempty  foldMap f (Bin _ _ v l r) = Foldable.foldMap
f l `mappend` f v `mappend` Foldable.foldMap f r

Simon Marlow in his recent Haxl talk also had a domain where they
wanted a symmetric (non-monadic) parallel spawn operation...

But it remains pretty hard for me to reason about the operational
behavior of these things... especially since foldMap instances may
vary.

Thanks,

   -Ryan

[1] For example, here is a non-allocating traverseWithKey_ that I
failed to come up with:


-- Version of traverseWithKey_ from Shachaf Ben-Kiki
-- (See thread on Haskell-cafe.)
-- Avoids O(N) allocation when traversing for side-effect.

newtype Traverse_ f = Traverse_ { runTraverse_ :: f () }
instance Applicative f = Monoid (Traverse_ f) where
  mempty = Traverse_ (pure ())
  Traverse_ a `mappend` Traverse_ b = Traverse_ (a * b)
-- Since the Applicative used is Const (newtype Const m a = Const m), the
-- structure is never built up.
--(b) You can derive traverseWithKey_ from foldMapWithKey, e.g. as follows:
traverseWithKey_ :: Applicative f = (k - a - f ()) - M.Map k a - f ()
traverseWithKey_ f = runTraverse_ .
 foldMapWithKey (\k x - Traverse_ (void (f k x)))
foldMapWithKey :: Monoid r = (k - a - r) - M.Map k a - r
foldMapWithKey f = getConst . M.traverseWithKey (\k x - Const (f k x))
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: Partitionable goes somewhere + containers instances

2013-09-29 Thread Ryan Newton
Thanks Edward.  Good point about Brent's 'split' package.  That would be a
really nice place to put the class.  But it doesn't currently depend on
containers or vector so I suppose the other instances would need to go
somewhere else.  (Assuming containers only exported monomorphic versions.)

Maybe a next step would be proposing some monomorphic variants for the
containers package.

I think the complicated bit will be describing how best-efforty splitting
variants are:

   - Is it guaranteed O(1) time and allocation?
   - Is the provided Int an upper bound?  Lower(ish) bound?  Or just a hint?

With some data structures, there will be a trade-off between partition
imbalance and the work required to achieve balance.  But with some data
structures it is happily not a problem (e.g. Vector)!

But whether there's one variant or a few, I'd be happy either way, as long
as I get at least the cheap one (i.e. prefer imbalance to restructuring).

  -Ryan




On Sun, Sep 29, 2013 at 8:20 AM, Edward Kmett ekm...@gmail.com wrote:

 I don't know that it belongs in the standard libraries, but there could
 definitely be a package for something similar.

 ConstraintKinds are a pretty hefty extension to throw at it, and the
 signature written there prevents it from being used on ByteString, Text,
 etc.

 This can be implemented with much lighter weight types though!


 class Partitionable t where

 partition :: Int - t - [t]


 Now ByteString, Text etc. can be instances and no real flexibility is
 lost, as with the class associated constraint on the argument, you'd
 already given up polymorphic recursion.

 There still remain issues. partition is already established as the filterthat 
 returns both the matching and unmatching elements, so the name is
 wrong.

 This is a generalization of Data.List.splitEvery, perhaps it is worth
 seeing how many others can be generalized similarly and talk to Brent about
 adding, say, a Data.Split module to his split package in the platform?

 -Edward





 On Sun, Sep 29, 2013 at 4:21 AM, Ryan Newton rrnew...@gmail.com wrote:

 subject change

 On Sun, Sep 29, 2013 at 3:31 AM, Mike Izbicki m...@izbicki.me wrote:

 I've got a Partitionable class that I've been using for this purpose:

 https://github.com/mikeizbicki/ConstraintKinds/blob/master/src/Control/ConstraintKinds/Partitionable.hs


 Mike -- Neat, that's a cool library!

 Edward --  ideally, where in the standard libraries should the
 Partitionable comonoid go?

 Btw, I'm not sure what the ideal return type for comappend is, given that
 it needs to be able to bottom out.  Mike, our partition function's list
 return type seems more reasonable.  Or maybe something simple would be this:

 *class Partitionable t where*
 *  partition :: t - Maybe (t,t)*

 That is, at some point its not worth splitting and returns Nothing, and
 you'd better be able to deal with the 't' directly.

 So what I really want is for the *containers package to please get some
 kind of Partitionable instances! * Johan  others, I would be happy to
 provide a patch if the class can be agreed on. This is important because
 currently the balanced tree structure of Data.Set/Map is an *amazing and
 beneficial property* that is *not* exposed at all through the API.
For example, it would be great to have a parallel traverse_ for Maps
 and Sets in the Par monad.  The particular impetus is that our new and
 enhanced Par monad makes extensive use of Maps and Sets, both the pure,
 balanced ones, and lockfree/inplace ones based on concurrent skip lists:

 http://www.cs.indiana.edu/~rrnewton/haddock/lvish/

 Alternatively, it would be ok if there were a Data.Map.Internal module
 that exposed the Bin/Tip, but I assume people would rather have a clean
 Partitionable instance...

 Best,
   -Ryan


 On Sun, Sep 29, 2013 at 3:31 AM, Mike Izbicki m...@izbicki.me wrote:

 I've got a Partitionable class that I've been using for this purpose:


 https://github.com/mikeizbicki/ConstraintKinds/blob/master/src/Control/ConstraintKinds/Partitionable.hs

 The function called parallel in the HLearn library will automatically
 parallelize any homomorphism from a Partionable to a Monoid.  I
 specifically use that to parallelize machine learning algorithms.

 I have two thoughts for better abstractions:

 1)  This Partitionable class is essentially a comonoid.  By reversing
 the arrows of mappend, we get:

 comappend :: a - (a,a)

 By itself, this works well if the number of processors you have is a
 power of two, but it needs some more fanciness to get things balanced
 properly for other numbers of processors.  I bet there's another algebraic
 structure that would capture these other cases, but I'm not sure what it is.

 2) I'm working with parallelizing tree structures right now (kd-trees,
 cover trees, oct-trees, etc.).  The real problem is not splitting the
 number of data points equally (this is easy), but splitting the amount of
 work equally.  Some points take longer to process

[Haskell-cafe] What class for splittable data / balanced-fold?

2013-09-28 Thread Ryan Newton
Hi all,

We all know and love Data.Foldable and are familiar with left folds and
right folds.  But what you want in a parallel program is a balanced fold
over a tree.  Fortunately, many of our datatypes (Sets, Maps) actually ARE
balanced trees.  Hmm, but how do we expose that?

It seems like it would be nice to have a* standard class t*hat allows you
to split a datatype into roughly even halves, until you get down to the
leaves.  This goes along with Guy Steele's argument that we should use
append lists as primitive rather than cons-lists, and it's why we
added append-lists
within the monad-par
libraryhttp://hackage.haskell.org/package/monad-par-extras-0.3.3/docs/Control-Monad-Par-AList.html
.

Does this class exist already?  A random google search brought up this
module by the name
Data.Splittablehttp://hackage.haskell.org/package/unfoldable-0.2.0/docs/Data-Splittable.html,
but it's not quite the right thing.

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


[Haskell-cafe] Reminder: today is the deadline for HIW talk proposals (Haskell Implementor's Workshop)

2013-08-13 Thread Ryan Newton
If you would like to give a talk pertaining to Haskell implementation
(including libraries).  Please submit a short abstract below.

See you in Boston!
  -Ryan

* Call for Talks*
   ACM SIGPLAN Haskell Implementors' Workshop

http://haskell.org/haskellwiki/HaskellImplementorsWorkshop/2013
Boston, USA, September 22th, 2013
The workshop will be held in conjunction with ICFP 2013
http://www.icfpconference.org/icfp2013/

Important dates

Proposal Deadline:  13th August2013 (by midnight, any timezone)
Notification:   27th August2013
Workshop:   22th September 2013
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Call for talks: Haskell Implementors Workshop 2013, Sept 22, Boston

2013-07-30 Thread Ryan Newton
Please pass on this announcement!  The deadline is in two weeks.*
*
*
*
* Call for Talks*
   ACM SIGPLAN Haskell Implementors' Workshop

http://haskell.org/haskellwiki/HaskellImplementorsWorkshop/2013
Boston, USA, September 22th, 2013
The workshop will be held in conjunction with ICFP 2013
http://www.icfpconference.org/icfp2013/

*Important dates*

Proposal Deadline:  *13th August2013 (by midnight, any timezone)*
Notification:   27th August2013
Workshop:   22th September 2013

The Haskell Implementors' Workshop is to be held alongside ICFP 2013
this year in Boston. There will be no proceedings; it is an informal
gathering of people involved in the design and development of Haskell
implementations, tools, libraries, and supporting infrastructure.

This relatively new workshop reflects the growth of the user community:
there is a clear need for a well-supported tool chain for the
development, distribution, deployment, and configuration of Haskell
software. The aim is for this workshop to give the people involved with
building the infrastructure behind this ecosystem an opportunity to bat
around ideas, share experiences, and ask for feedback from fellow
experts.

We intend the workshop to have an informal and interactive feel, with a
flexible timetable and plenty of room for ad-hoc discussion, demos, and
impromptu short talks.


Scope and target audience
-

It is important to distinguish the Haskell Implementors' Workshop from
the Haskell Symposium which is also co-located with ICFP 2013. The
Haskell Symposium is for the publication of Haskell-related research. In
contrast, the Haskell Implementors' Workshop will have no proceedings --
although we will aim to make talk videos, slides and presented data
available with the consent of the speakers.

In the Haskell Implementors' Workshop, we hope to study the underlying
technology. We want to bring together anyone interested in the
nitty-gritty details behind turning plain-text source code into a
deployed product. Having said that, members of the wider Haskell
community are more than welcome to attend the workshop -- we need your
feedback to keep the Haskell ecosystem thriving.

The scope covers any of the following topics. There may be some topics
that people feel we've missed, so by all means submit a proposal even if
it doesn't fit exactly into one of these buckets:

  * Compilation techniques
  * Language features and extensions
  * Type system implementation
  * Concurrency and parallelism: language design and implementation
  * Performance, optimisation and benchmarking
  * Virtual machines and run-time systems
  * Libraries and tools for development or deployment


Talks
-

At this stage we would like to invite proposals from potential speakers
for a relatively short talk. We are aiming for 20 minute talks with 10
minutes for questions and changeovers. We want to hear from people
writing compilers, tools, or libraries, people with cool ideas for
directions in which we should take the platform, proposals for new
features to be implemented, and half-baked crazy ideas. Please submit a
talk title and abstract of no more than 200 words.

Submissions should be made via EasyChair.  The website is:
  https://www.easychair.org/conferences/?conf=hiw2013

If you don't have an account you can create one here:
  https://www.easychair.org/account/signup.cgi

Because the submission is an abstract only, please click the abstract
only button when you make your submission.  There is no need to
attach a separate file.

We will also have a lightning talks session which will be organised on
the day. These talks will be 2-10 minutes, depending on available time.
Suggested topics for lightning talks are to present a single idea, a
work-in-progress project, a problem to intrigue and perplex Haskell
implementors, or simply to ask for feedback and collaborators.


Organisers
--

  * Ryan Newton(Indiana University)
  * Neal Glew  (Intel Labs)
  * Edward Yang(Stanford University)
  * Thomas Schilling   (University of Kent)
  * Geoffrey Mainland  (Drexel University)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Who uses Travis CI and can help write a cookbook for those guys?

2013-06-28 Thread Ryan Newton
The Travis folks have decided they want to support Haskell better (multiple
compiler versions):

  https://github.com/travis-ci/travis-ci/issues/882#issuecomment-20165378

(Yay!)  They're asking for someone to help them up with setup scripts.
 They mention their cookbook collection here:

   https://github.com/travis-ci/travis-cookbooks

In that thread above, I pasted our little script that fetches and installs
multiple GHC versions, but I have little experiences with cloud
technologies  VMs.  Can someone jump in and help push this forward?

As a community I'm sure it would be great to get a higher percentage of
Hackage packages using simple, hosted continuous testing... I'd personally
like to replace my Jenkins install if they can get the necessary GHC
versions in there.

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


Re: [Haskell-cafe] Two GHC-related GSoC Proposals

2013-05-30 Thread Ryan Newton
What's the plan for what control / synchronization structures you'll use in
part 2 of the plan to implement a parallel driver?

Is the idea just to use an IO thread for each compile and block them on
MVars when they encounter dependencies?  Or you can use a pool of worker
threads and a work queue, and only add modules to the work queue when all
their dependencies are met (limits memory use)... many options for
executing a task DAG.  Fortunately the granularity is coarse.

  -Ryan



On Sun, Apr 21, 2013 at 10:34 PM, Patrick Palka patr...@parcs.ath.cxwrote:

 Good points. I did not take into account whether proposal #2 may be worth
 it in light of -fllvm. I suppose that even if the LLVM codegen is able to
 perform similar optimizations, it would still be beneficial to implement
 proposal #2 as a core-to-core pass because the transformations it performs
 would expose new information to subsequent core-to-core passes. Also,
 Haskell has different overflow rules than C does (whose rules I assume
 LLVM's optimizations are modeled from): In Haskell, integer overflow is
 undefined for all integral types, whereas in C it's only undefined for
 signed integral types. This limits the number of optimizations a C-based
 optimizer can perform on unsigned arithmetic.

 I'm not sure how I would break up the parallel compilation proposal into
 multiple self-contained units of work. I can only think of two units:
 making GHC thread safe, and writing the new parallel compilation driver.
 Other incidental units may come up during development (e.g. parallel
 compilation might exacerbate 
 #4012http://hackage.haskell.org/trac/ghc/ticket/4012),
 but I still feel that three months of full time work is ample time to
 complete the project, especially with existing familiarity with the code
 base.

 Thanks for the feedback.


 On Sun, Apr 21, 2013 at 5:55 PM, Carter Schonwald 
 carter.schonw...@gmail.com wrote:

 Hey Patrick,
 both are excellent ideas for work that would be really valuable for the
 community!
 (independent of whether or not they can be made into GSOC sided chunks )

 ---
 I'm actually hoping to invest some time this summer investigating
 improving the numerics optimization story in ghc. This is in large part
 because I'm writing LOTs of numeric codes in haskell presently (hopefully
 on track to make some available to the community ).

 That said, its not entirely obvious (at least to me) what a tractable
 focused GSOC sized subset of the numerics optimization improvement would
 be, and that would have to also be a subset that has real performance
 impact and doesn't benefit from eg using -fllvm rather than -fasm .
 -

 For helping pave the way to better parallel builds, what are some self
 contained units of work on ghc (or related work on cabal) that might be
 tractable over a summer? If you can put together a clear roadmap of work
 chunks that are tractable over the course of the summer, I'd favor
 choosing that work, especially if you can give a clear outline of the plan
 per chunk and how to evaluate the success of each unit of work.

 basically: while both are high value projects, helping improve the
 parallel build tooling (whether in performance or correctness or both!) has
 a more obvious scope of community impact, and if you can layout a clear
 plan of work that GHC folks agree with and seems doable, i'd favor that
 project :)

 hope this feedback helps you sort out project ideas

 cheers
 -Carter




 On Sun, Apr 21, 2013 at 12:20 PM, Patrick Palka patr...@parcs.ath.cxwrote:

 Hi,

 I'm interested in participating in the GSoC by improving GHC with one of
 these two features:

 1) Implement native support for compiling modules in parallel (see 
 #910http://hackage.haskell.org/trac/ghc/ticket/910).
 This will involve making the compilation pipeline thread-safe, implementing
 the logic for building modules in parallel (with an emphasis on keeping
 compiler output deterministic), and lots of testing and benchmarking. Being
 able to seamlessly build modules in parallel will shorten the time it takes
 to recompile a project and will therefore improve the life of every GHC
 user.

 2) Improve existing constant folding, strength reduction and peephole
 optimizations on arithmetic and logical expressions, and optionally
 implement a core-to-core pass for optimizing nested comparisons (relevant
 tickets include #2132 http://hackage.haskell.org/trac/ghc/ticket/2132,
 #5615 
 http://hackage.haskell.org/trac/ghc/ticket/5615,#4101http://hackage.haskell.org/trac/ghc/ticket/4101).
 GHC currently performs some of these simplifications (via its BuiltinRule
 framework), but there is a lot of room for improvement. For instance, the
 core for this snippet is essentially identical to the Haskell source:

 foo :: Int - Int - Int - Int
 foo a b c = 10*((b+7+a+12+b+9)+4) + 5*(a+7+b+12+a+9) + 7 + b + c

 Yet the RHS is actually equivalent to

 20*a + 26*b + c + 467

 And:

 bar :: Int - Int - Int
 bar a b = a + b - a - 

[Haskell-cafe] ANN: hsbencher-1.1, with Fusion Table upload

2013-05-29 Thread Ryan Newton
I'm pleased to announce a new benchmarking framework, HSBencher.  It's an
early prototype, but it's flexible, extensible and uploads benchmark data
to Google Fusion Tables.

Right now the fusion table upload depends on a pre-release version of
handa-gdata (0.6.2), which you can get at one of these locations:
https://code.google.com/p/hgdata/
https://github.com/rrnewton/hgdata_mirror
(It should be released soon.)

Here's a blog post explaining HSBencher's usage:

http://parfunk.blogspot.com/2013/05/towards-cloud-based-crowd-sourced.html

Hackage:
http://hackage.haskell.org/package/hsbencher

Github (see README)
https://github.com/rrnewton/hsbencher
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to throw an error if using cabal-install version XYZ?

2013-05-23 Thread Ryan Newton
Great!  Thanks.  I adapted that trick and it worked fine:

https://github.com/rrnewton/haskell-lockfree-queue/blob/cb8ca1a5d8b4c02e45eeca54fbc66f0c58aeff56/AtomicPrimops/Setup.hs



On Wed, May 22, 2013 at 11:53 PM, Carter Schonwald 
carter.schonw...@gmail.com wrote:

 Hey Ryan,
 I ran into a related issue, heres a a way you can do this safe IN the
 cabal file (or at least you can modify my hack for your purposes)

 heres a link to the workaround I did for making LLVM-hs work across =
 1.17 and  1.17 cabal, but you could abuse it to make sure setup.hs barfs
 on old cabal
 https://github.com/bos/llvm/blob/master/base/Setup.hs#L89-L116

 heres a quick one off gist that takes my trick and does something helpful
 for you variant + makes sure the tool can't build otherwise

 https://gist.github.com/cartazio/5632636

 I just wrote a snippet that you can just add to your setup.hs and it
 should guarantee the setup.hs will barf with a helpful error message on
 cabal  1.17.0


 On Wed, May 22, 2013 at 10:50 PM, Ryan Newton rrnew...@gmail.com wrote:

 A cabal-install bug https://github.com/haskell/cabal/issues/1284 was
 fixed recently that pertains to building C libraries with profiling.

 As a result, I want a certain 
 packagehttp://hackage.haskell.org/package/atomic-primops-0.1.0.2to test if 
 cabal-install  0.17.0 is used, and throw a preemptive error.
  Otherwise this package fails in weird ways at runtime (it's a nasty one).

 I noticed with some surprise the following sequence:

 *   $ cabal --version*
 *   cabal-install version 1.16.0.2*
 *   using version 1.16.0.3 of the Cabal library*
 *   $ cabal clean*
 *   $ cabal install*
 *   $ cat dist/build/autogen/cabal_macros.h  | grep VERSION_Cabal*
 *   #define VERSION_Cabal 1.17.0*

 Alright, so that, in retrospect, makes sense.  The version is which *my*
 library is linked with is the relevant one, not the one cabal-install was
 linked with [1].

 So the natural next thought is to move the MIN_VERSION_Cabal test into
 Setup.hs, and force cabal to use it by setting the build type to Custom.
  But... I just learned from this ticket that the cabal macros are not
 available in Setup.hs:

http://hackage.haskell.org/trac/hackage/ticket/326

 Uh oh, what's left?

  -Ryan

 [1] P.S. Personally I'm now using a bash function like below, to force
 the two versions to be the same:

 function safe_cabal_install () {
   VER=`cabal --version | tail -n1 | awk '{ print $3 }'`
   cabal install --constraint=Cabal==$VER $*
 }


 ___
 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


[Haskell-cafe] How to throw an error if using cabal-install version XYZ?

2013-05-22 Thread Ryan Newton
A cabal-install bug https://github.com/haskell/cabal/issues/1284 was
fixed recently that pertains to building C libraries with profiling.

As a result, I want a certain
packagehttp://hackage.haskell.org/package/atomic-primops-0.1.0.2to
test if cabal-install  0.17.0 is used, and throw a preemptive error.
 Otherwise this package fails in weird ways at runtime (it's a nasty one).

I noticed with some surprise the following sequence:

*   $ cabal --version*
*   cabal-install version 1.16.0.2*
*   using version 1.16.0.3 of the Cabal library*
*   $ cabal clean*
*   $ cabal install*
*   $ cat dist/build/autogen/cabal_macros.h  | grep VERSION_Cabal*
*   #define VERSION_Cabal 1.17.0*

Alright, so that, in retrospect, makes sense.  The version is which *my*
library is linked with is the relevant one, not the one cabal-install was
linked with [1].

So the natural next thought is to move the MIN_VERSION_Cabal test into
Setup.hs, and force cabal to use it by setting the build type to Custom.
 But... I just learned from this ticket that the cabal macros are not
available in Setup.hs:

   http://hackage.haskell.org/trac/hackage/ticket/326

Uh oh, what's left?

 -Ryan

[1] P.S. Personally I'm now using a bash function like below, to force the
two versions to be the same:

function safe_cabal_install () {
  VER=`cabal --version | tail -n1 | awk '{ print $3 }'`
  cabal install --constraint=Cabal==$VER $*
}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] What symbol / atom/ interned-string package is currently preferred?

2013-05-07 Thread Ryan Newton
Hi cafe,

I use symbols all the time when manipulating code.  I vacillate between
using stringtable-atom, symbol, and simple-atom.  Unfortunately:

   - Stringtable-atom is has a broken build right now (GHC 7.6).  (Also
   I've had some crashes with it in the past.)
   - simple-atom has dependency upper bounds that restrict it to GHC = 7.0
   - symbol has a design flaw, which is that it exposes the constructor
   for Symbol, which reveals the (nondeterministic) unique Int IDs.  I.e. it
   is not SafeHaskell.

I submitted a pull request to relax simple-atom, but perhaps there are
other packages people use with which I am not aware?

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


[Haskell-cafe] Can any hackage library do JWT signing

2013-04-09 Thread Ryan Newton
I want to enable a Haskell benchmarking bot that would upload its data to a
Google Fusion Table each time it runs.  That seems to require the
service-to-service mode for Google's OAuth2:

   https://developers.google.com/accounts/docs/OAuth2ServiceAccount

There are a bunch of libraries on Hackage for different flavors of OAuth.
 But I haven't yet found one that handles this signing of JWT headers and
claimsets.  Is there something I'm missing?

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


[Haskell-cafe] ANNOUNCE: hydra-print-0.1.0.0

2013-04-06 Thread Ryan Newton
Hello cafe,

This is an NCurses front end for visualizing a dynamic collection of text
streams (e.g. as produced by make -j or cabal -j).  It just splits the
window when more streams appear.

   http://hackage.haskell.org/package/hydra-print
   http://parfunk.blogspot.com/2013/04/hydra-print.html

Right now I'm using it for the monad-par benchmark script, but I hope to
provide a cabal patch soon.

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


[Haskell-cafe] FunPtr to C function with #arguments determined at runtime?

2013-02-17 Thread Ryan Newton
Hello cafe,

I've been poking around and I haven't seen this addressed anywhere except
obliquely in the end of section 8.5.1 of the report, where it says that
variable argument C functions aren't supported:

   http://www.haskell.org/onlinereport/haskell2010/haskellch8.html

The scenario is pretty simple.  I generate C code at runtime.  I compile it
to a .so.  I know how many arguments it expects (but only at runtime), and
I get a FunPtr back from 'dlsym'.  How do I call it?

I was hoping there would be some Raw lower level FFI layer that I could
use to invoke a C function without automagic marshaling and all the other
goodness provided by the normal foreign import mechanism.

Failing that, will I just have to generate complex wrappers on the C side
which I call N times to load up N arguments into some stateful container
before finally launching the function?

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


Re: [Haskell-cafe] FunPtr to C function with #arguments determined atruntime?

2013-02-17 Thread Ryan Newton

  The scenario is pretty simple.  I generate C code at runtime.  I compile
 it
  to a .so.  I know how many arguments it expects (but only at runtime),
 and
  I get a FunPtr back from 'dlsym'.  How do I call it?
 I feel that I might be confused about the problem, but since I don't
 see anyone direct answers -- in order to call a FunPtr, you can use
 foreign import ccall dynamic, to create a regular function.   As
 described in the library documentation for Foreign.Ptr, which I bet
 you've seen, so you know this.

You can cast the FunPtr to whatever type you like, so you can call the
 function with an argument list different from its initial declaration.


My problem is that I can't create a type representing what I want at the
Haskell type-check time, and I need such a type for either casting or a
foreign import.  For example, let's say the function takes a number of Int
arguments between 1 and 1000.  If I find out at runtime that I need a
function with 613 Int arguments, I would need to create the type (Int -
Int ... - IO ()) to cast to.  I suppose there may be some way to create
such a dependent type with Typeable/Data.Dynamic, since it's monomorphic.
 Or in theory you could dynamically generate new Haskell code to create the
type (System.Eval.Haskell)...

libffi, which Krzysztof mentioned, is a good solution:

http://www.haskell.org/haskellwiki/Library/libffi

Because it allows you to pass a list of arguments

 callFFI :: FunPtr a - RetType b - [Arg] - IO b


But it does introduce an extra dependency on a C library (read, deployment
liability).  It cabal install'd the first time on my linux box, but my
mac said The pkg-config package libffi is required but it could not be
found.  (even though libffi.dylib is definitely installed globally).

Anyway, in this case it wasn't *too *painful to just generate a bunch of
extra boilerplate C functions for (1) creating a data structure to hold the
arguments, (2) loading them in one at a time, and (3) deallocating the
structure when the call is done.  Yuck.  But no extra dependencies.

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


Re: [Haskell-cafe] a parallel mapM?

2012-10-03 Thread Ryan Newton
Several of the monad-par schedulers COULD provide a MonadIO instance and
thus liftIO, which would make them easy to use for this kind of parallel
IO business:


http://hackage.haskell.org/packages/archive/monad-par/0.3/doc/html/Control-Monad-Par-Scheds-Direct.html

And that would be a little more scalable because you wouldn't get a
separate IO thread for each parallel computation.  But, to be safe-haskell
compliant, we don't currently expose IO capabilities. I can add another
module that exposes this capability if you are interested...

  -Ryan

On Fri, Sep 28, 2012 at 4:48 PM, Alexander Solla alex.so...@gmail.comwrote:



 On Fri, Sep 28, 2012 at 11:01 AM, Greg Fitzgerald gari...@gmail.comwrote:


 I also tried Control.Parallel.Strategies [2].  While that route works,
 I had to use unsafePerformIO.  Considering that IO is for sequencing
 effects and my IO operation doesn't cause any side-effects (besides
 hogging a file handle), is this a proper use of unsafePerformIO?


 That's actually a perfectly fine use for unsafePerformIO, since the IO
 action you are performing is pure and therefore safe (modulo your file
 handle stuff).

 unsafePerformIO is a problem when the IO action being run has side effects
 and their order of evaluation matters (since unsafePerformIO will cause
 them to be run in an unpredictable order)

 One common use for unsafePerformIO is to run a query against an external
 library.  It has to be done in the IO monad, but it is a pure computation
 insofar as it has no side-effects that matter.  Doing this lets us promote
 values defined in external libraries to bona fide pure Haskell values.

 ___
 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 parallel mapM?

2012-10-03 Thread Ryan Newton


 That said, I don't see a reason for not including a separate version of
 runParIO :: ParIO a - IO a for non-deterministic computations. It seems
 really useful!


Exactly.  I should have been more explicit but that's what I meant about
adding another module.  You would import Control.Monad.Par.IO and get
runParIO + liftIO but NOT runPar.  This requires doing a newtype over Par
to create the liftIO instance for one and not the other (and preserve Safe
Haskell).  It's a pain but it's no problem.  Both types
Control.Monad.Par.Par and Control.Monad.Par.IO.ParIO will expose the same
interface (i.e. have instances of the same classes -- ParFuture,
ParIVar...), so generic algorithms like parMap will still work for either.

  -Ryan


 Regards,
   - Clark

 On Wed, Oct 3, 2012 at 10:24 AM, Ryan Newton rrnew...@gmail.com wrote:

 Several of the monad-par schedulers COULD provide a MonadIO instance and
 thus liftIO, which would make them easy to use for this kind of parallel
 IO business:


 http://hackage.haskell.org/packages/archive/monad-par/0.3/doc/html/Control-Monad-Par-Scheds-Direct.html

 And that would be a little more scalable because you wouldn't get a
 separate IO thread for each parallel computation.  But, to be safe-haskell
 compliant, we don't currently expose IO capabilities. I can add another
 module that exposes this capability if you are interested...

   -Ryan

 On Fri, Sep 28, 2012 at 4:48 PM, Alexander Solla alex.so...@gmail.comwrote:



 On Fri, Sep 28, 2012 at 11:01 AM, Greg Fitzgerald gari...@gmail.comwrote:


 I also tried Control.Parallel.Strategies [2].  While that route works,
 I had to use unsafePerformIO.  Considering that IO is for sequencing
 effects and my IO operation doesn't cause any side-effects (besides
 hogging a file handle), is this a proper use of unsafePerformIO?


 That's actually a perfectly fine use for unsafePerformIO, since the IO
 action you are performing is pure and therefore safe (modulo your file
 handle stuff).

 unsafePerformIO is a problem when the IO action being run has side
 effects and their order of evaluation matters (since unsafePerformIO will
 cause them to be run in an unpredictable order)

 One common use for unsafePerformIO is to run a query against an external
 library.  It has to be done in the IO monad, but it is a pure computation
 insofar as it has no side-effects that matter.  Doing this lets us promote
 values defined in external libraries to bona fide pure Haskell values.

 ___
 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



___
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-27 Thread Ryan Newton
Well, this one looks like it was my fault because I never read this thread
and this morning I uploaded that package (abstract-deque) with the
conditional in the test-suite.  The reason this conditional isn't there now
is that the package was hacked in place to remove tests, which is fine.

Actually, as a maintainer I'm not really clear on how to test this
behavior.  I tried cabal configure with cabal-install-0.10.2 as in the
original post and I couldn't reproduce the problem.



 For the record, abstract-deque was neither one of the packages fixed
 previously, nor does its .cabal file even contain a test section at
 all, much less one with a conditional.  So if cabal-install-0.10 is
 failing to read it, it is because of some different problem.  But I
 agree with Bryan in principle that we need a more principled approach.

 -Brent

 ___
 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] Possible bug in Criterion or Statistics package

2012-08-13 Thread Ryan Newton
Terrible!  Quite sorry that this seems to be a bug in the monad-par library.

I'm copying some of the other monad-par authors and we hopefully can get to
the bottom of this.  If it's not possible to create a smaller reproducer,
is it possible to share the original test that triggers this problem?  In
the meantime, it's good that you can at least run without parallelism.

Best,
  -Ryan

On Sun, Aug 12, 2012 at 11:20 AM, Aleksey Khudyakov 
alexey.sklad...@gmail.com wrote:

 On 10.08.2012 22:20, Till Berger wrote:

  So I am not sure if this is a bug in Criterion itself, the Statistics
 package or any dependency or if I am doing something obviously wrong. I
 would be grateful if someone could look into this as it is holding me
 back from using Criterion for benchmarking my code.

  I would suspect Statistics.Resampling.**resample. From quick glance
 criterion doesn't use any concurrent stuff. I'll try create smaller test
 case


 It looks like I'm wrong. I obtained event log from crashing program
 and resample completed its work without problems. Crash occured later.
 Next
 suspect is bootstrapBCA itself. It uses monad-par to obtain
 parallelism[1].

 I tried to create smaller test case without any success.



 [1]
 https://github.com/bos/**statistics/blob/master/**Statistics/Resampling/
 **Bootstrap.hs#L84https://github.com/bos/statistics/blob/master/Statistics/Resampling/Bootstrap.hs#L84


 Replacing runPar $ parMap with a simple map on that line seems to
 fix the bug. At least I could not reproduce it anymore on several runs
 with my original test case. So it seems to be a bug in the Par monad
 package as this change shouldn't alter the program's behaviour, should it?

  Looks like this is the case. But reducing test case to reasonable size
 (e.g. removing most of criterion and statistics could be quite difficult


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@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


Re: [Haskell-cafe] Can Haskell outperform C++?

2012-05-24 Thread Ryan Newton
Oops, forgot to reply-to-all.  This was a minor clarification on Wren's
behalf (he can correct me if I'm wrong).  But I agree with Bryan that it's
time for the thread to die:


  Do bear in mind that Java doesn't optimize ---that's the JIT's job

 What are we supposed to make of that?

 Why write that and not -- Do bear in mind that Smalltalk doesn't optimize
 that's the JIT's job -- or -- Do bear in mind that C doesn't optimize
 that's the compiler's job.


I believe this was referring to the fact that javac isn't an aggressive
optimizing compiler on the way from source to bytecode, i.e. it's the
bytecode-asm leg where the optimization effort is focused.

As an outsider to things Java that's something I've had trouble
understanding, actually.  It doesn't seem like an either-or choice to me...

   -Ryan


On Wed, May 23, 2012 at 4:26 PM, Isaac Gouy igo...@yahoo.com wrote:

  From: wren ng thornton w...@freegeek.org

  Sent: Tuesday, May 22, 2012 9:30 PM

 -snip-
  FWIW, that matches my expectations pretty well. Naive/standard Java
 performing
  slower than Smalltalk; highly tweaked Java using non-standard data types
  performing on-par with or somewhat faster than Smalltalk.

 I have no difficulty believing that if you are talking about a 1996 Java
 reference implementation and a 1996 Smalltalk JIT VM.

 I could believe that if you are comparing a naive Java program with a
 highly tweaked Smalltalk program.


  That C is 7x faster is a bit on the high end, but for something like
 tsort I could imagine it'd be possible.

 It's possible because it's possible to write a Java program to be slower
 than it need be :-)


  Do bear in mind that Java doesn't optimize ---that's the JIT's job

 What are we supposed to make of that?

 Why write that and not -- Do bear in mind that Smalltalk doesn't optimize
 that's the JIT's job -- or -- Do bear in mind that C doesn't optimize
 that's the compiler's job.


 -snip-
  But even still, in my experience of using Smalltalk, the standard data
  structures are much better done and so they will be on-par with what
 you'd
  get from hand-tuning for Java. I've spent a lot of time trying to get
 decent
  performance out of Java, not so much with Smalltalk; but the performance
 with
  Smalltalk was sufficient that it wasn't needed so badly.

 Do you have a specific example that you can share?


 ___
 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] Parallel cooperative multithreading?

2012-05-22 Thread Ryan Newton
Personally, I think cooperative concurrency is making a big comeback.
 Especially in a compiler-supporting form that relies on limited CPS
(continuation-passing-style) transformation.  There are server and web
services applications that motivate it (i.e. in Scala, F# async work flows).

In Haskell we've got ContT for capturing the continuation of one
computation (and yielding to another).  Monad-par is an example of a
framework based on ContT in which tasks cooperatively yield control
whenever their desired input data is not yet available.

  -Ryan


On Tue, May 22, 2012 at 9:55 AM, Benjamin Ylvisaker
benjam...@fastmail.fmwrote:

 Has anyone ever worked on implementing something like this in Haskell?

 http://www.cs.hmc.edu/~stone/papers/ocm-unpublished.pdf

 The outline of the idea:

 - Concurrent programming is really hard with the popular frameworks
 today.
 - For most purposes parallel programming is hard, in some part because
 it requires concurrent programming.  Of course there are attempts to do
 non-concurrent parallel programming, but I hope it's not too
 controversial to say that such frameworks are still on the fringe.
 - Cooperative concurrency is way easier than preemptive concurrency
 because between invocations of pause/yield/wait, sequential reasoning
 works.
 - Historically, cooperative concurrency only worked on a single
 processors, because running threads in parallel would break the
 atomicity of sequential blocks (between invocations of p/y/w).
 - Researchers have been poring tons of effort into efficiently running
 blocks of code atomically.
 - Hey, we can do parallel cooperative multithreading!

 The paper discusses implementations in Lua, C++ and C, but I think
 Haskell could be an awesome substrate for such a framework.  Has anyone
 thought about this?

 Ben

 ___
 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] Can Haskell outperform C++?

2012-05-21 Thread Ryan Newton

 The unconditional desire for maximum possible object code
 performance is usually very stupid, not to mention impossible to reach
 with any high level language and any multi-tasking operating system.


Definitely.  I don't know if we have a catchy term for kneejerk
optimization or if it falls under the broader umbrella of premature
optimization [including misdirected or unneeded optimization].

I do think we have the opposite problem, however, in much Haskell code --
people are using the clean, obviously correct, but inefficient code even in
standard library functions that really should be optimized like crazy!


  Haskell's average penalty compared to C is
 no reason to write the entire application in C.


Yes, this seems to be a separate disease.  Not just using low-level langs,
per se, but using them for *everything*.  I have worked at places in
industry where teams automatically use C++ for everything.  For example,
they use it for building all complete GUI applications, which surprises me
a little bit.  I would have thought in recent years that almost everyone
was using *something* else (Java,Python, whatever) to do much of the
performance-non-critical portions of their application logic.

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


Re: [Haskell-cafe] Safe Haskell at the export symbol granularity?

2012-05-17 Thread Ryan Newton
Thanks David.

I'm glad to see it was discussed in the wiki.  (Btw, my 2 cents is that I
like the comment pragmas more than new keywords.)

The issue that I think doesn't make it into the wiki is of splitting, not
modules, but* type-classes*. That's where I think it becomes a more serious
issue.

Do you think a symbol-level Safe Haskell would be able to distinguish one
method of a type class as unsafe, while the others are safe?

  -Ryan

P.S. In my two examples --
   There's only one Acc type and Accelerate's fold can pretty easily be
moved into an .Unsafe module, though it breaks the
one-giant-module-for-the-whole-programming-model thing it has going now.
 In the Par example on the other hand type classes are used to abstract
over different implementations, so that's where we run into the safe/unsafe
factoring problem.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Safe Haskell at the export symbol granularity?

2012-05-17 Thread Ryan Newton
Good point, Antoine!

I think that does the trick.

On Thu, May 17, 2012 at 10:48 AM, Antoine Latter aslat...@gmail.com wrote:

 On Thu, May 17, 2012 at 8:50 AM, Ryan Newton rrnew...@gmail.com wrote:
  Thanks David.
 
  I'm glad to see it was discussed in the wiki.  (Btw, my 2 cents is that I
  like the comment pragmas more than new keywords.)
 
  The issue that I think doesn't make it into the wiki is of splitting, not
  modules, but type-classes. That's where I think it becomes a more serious
  issue.
 
  Do you think a symbol-level Safe Haskell would be able to distinguish one
  method of a type class as unsafe, while the others are safe?
 

 You can still do this at the module level, with the down-side of
 potentially not being able to implement a class with the safe version:

  module Unsafe where
 
  class MyClass a where
safeOp :: a - Int - IO ()
unsafeOp :: a - Int - IO ()
 
  instance MyClass A where ...


  module Safe
(MyClass(safeOp))
where
 
  import Unsafe

 I think this works.

 Antoine

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


Re: [Haskell-cafe] cool tools

2012-05-17 Thread Ryan Newton
Indeed, cabal-install 0.14.0 has been *excellent* for me so far.  Thanks
Andres!

On Thu, May 17, 2012 at 10:05 AM, Chris Dornan ch...@chrisdornan.comwrote:

 I have been playing around with the latest cabal-install (0.14.0) and it is
 working really nicely. Having unpacked a cabal bundle you can now type
 'cabal install' inside the root and it will work everything out as if you
 had asked to install directly from the repo -- very nice.

 I have also noticed that GHC is suggesting alternatives when it encounters
 missing identifiers. This gives a strong sense of helpfulness that I think
 accurately reflects the long and sustained (decades-long) effort that has
 gone into making the GHC diagnostics as useful as possible.

 The tools are so good because the developers have been paying attention to
 the gripes.

 But we should sometimes say thank you too... it is much appreciated.

 Chris


 ___
 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] Can Haskell outperform C++?

2012-05-14 Thread Ryan Newton

 Well, if it's in many ways the same as C, then again it's probably not
 idiomatic Haskell.


It's just a recursive equation for mandelbrot fractals.  I should have been
precise, I didn't mean that the source is literally the *same* as the C
source (i.e. there's no for loop, no mutable variables), rather that it
presents the compiler backend with the same advantages as the C backend
would have with the equivalent loop.  That is, there's no control flow
obfuscation (dictionaries, calls to unknown targets), no problems with
laziness, and the data representations are completely known.

mandel :: Int - Complex Double - Int
mandel max_depth c = loop 0 0

  where

   loop i !z

| i == max_depth  = i

| magnitude z = 2.0  = i

| otherwise   = loop (i+1) (z*z + c)


It's also a loop that is readily recognized as a loop.  Now, to my
knowledge, GHC doesn't explicitly recognize loops in any stage of the
compiler (so as to perform loop optimizations), something which other
functional compilers sometimes do.

But, anyway, it turns out that my example above *is easily transformed from
a bad GHC performance story into a good one*.  If you'll bear with me, I'll
show how below.
   First, Manuel makes a good point about the LLVM backend.  My 6X
anecdote was from a while ago and I didn't use llvm [1].  I redid it just
now with 7.4.1+LLVM, results below.  (The below table should read correctly
in fixed width font, but you can also see the data in the spreadsheet
herehttps://docs.google.com/spreadsheet/ccc?key=0AvzAHqQmHo87dHU0T0lCb1I4MFJmM2s4RnNlamJlNkE
.)

   Time (ms)   Compiled File size   Comple+Runtime (ms)
GHC 7.4.1 O024441241K
GHC 7.4.1 O29251132K 1561
GHC 7.4.1 O2 llvm  931 1133K
GHC 7.0.4 O2 via-C 684 974K

So LLVM didn't help [1].  And in fact the deprecated via-C backend did the
best!  Compare with GCC:

G++ O0 300 9K   531
G++ O3 110 7K   347
G++ O3 recursive   116 9K

Uh oh, the 6X gap I mentioned is now closer to 9X.  And, in fact,
performing a mini language shootout on the above code, reveals that GHC
is doing worse than not only OCaml, but Chez Scheme, in spite of dynamic
type checks, and a necessarily boxed representation of complex numbers:

Chez Scheme 8.4284 2.7K notStandalone   372
OCaml  166 180K 301

At least Python does worse!

Python 2.6 1973NA   1973

*So here's the catch:*  If you check the Core and STG GHC 7.4 is actually
compiling the above loop very well.  This microbenchmark turns into just a
magnitude microbenchmark.  The implementation of Data.Complex uses an
EXTREMELY expensive method to avoid
overflowhttps://github.com/ghc/packages-base/blob/master/Data/Complex.hs#L115
 [2].

Since OCaml did well above, I took a look at their standard library's
implementation, on line 51
herehttp://caml.inria.fr/cgi-bin/viewvc.cgi/ocaml/trunk/stdlib/complex.ml?revision=11156view=markup.
 They use a nice little math trick (the extra division) that is also
mentioned on Wikipedia.  By implementing the same trick in Haskell,
replacing the standard magnitude
functionhttps://github.com/rrnewton/MandelMicrobench/blob/97c3275ad94cbce57a688817332b42f7c32c15b4/mandel_test2.hs,
we get the following results.

GHC 7.4.1 No
Overflow Avoidance   39 1127K674
GHC 741, OCaml-style
Overflow avoidance   74  1127K

Wow, now not only is the Haskell version faster than OCaml/Scheme, *but it
is 48% faster than C++*, which is appropriate to the title of this email!
 Of course, this probably means that C++'s abs is also doing something
overly expensive for overflow avoidance (or that their representation of
complex numbers is not fully unpacked and stored in registers)  I haven't
tracked it down yet.

But in any case, I'll be submitting a library patch.  *The moral, I think,
is that community members could do a great deal to help Haskell
performance by simply microbenchmarking and optimizing library routines in
base!*

Cheers,
  -Ryan

P.S. You can check out the above benchmarks from here:
 
https://github.com/rrnewton/MandelMicrobenchhttps://github.com/rrnewton/MandelMicrobench

[1] P.P.S. Most concerning to me about Haskell/C++ comparisons are David
Peixotto's findings that LLVM optimizations are not very effective on
Haskell-generated LLVM compared with typical clang-generated LLVM.

[2]  P.P.P.S. It turns out there was already a ticket (
http://hackage.haskell.org/trac/ghc/ticket/2450) regarding magnitude's
performance.  But it still has bad performance even after a small
refactoring was performed.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Safe Haskell at the export symbol granularity?

2012-05-14 Thread Ryan Newton
Separate from whether or not we actually want this -- is it feasible?

Here's my situation.  When working on parallel programming libraries in
Haskell there are very often unsafe operations one wants to do within an
otherwise pure model.  For example, Accelerate currently violates safe
haskell because it trusts the user to provide an associative function to
parallel fold.  No associativity, no referential transparency.

The solution is to put fold in a separate namespace and mark that module as
Unsafe.  Likewise for certain monad-par operations that are unsafe.  But
this factoring can have a serious impact.  Not only are extra modules
required, but extra type classes as well.  For example, if Accelerate is
ever refactored for Safe Haskell then the following ParAccelerate type
class probably should be as well:

https://github.com/simonmar/monad-par/blob/5cc656bc45dc473d7a185ec99bb156192f54d520/abstract-par-accelerate/Control/Monad/Par/Accelerate.hs#L75

I.e. ParAccelerate  ParAccelerateUnsafe for the unsafeHybrid operation.

But this starts to be death by a thousand organizational factorings!

   - The package, abstract-par-accelerate, is already factored out from
   abstract-par just to avoid an unnecessary Accelerate dependency (which
   used to mean CUDA errors).  (And *another* factoring is possibly warranted
   for whether or not the module depends on accelerate-io.)
   - The file would be separate to mark it as Safe Haskell.
   - The type class ParAccelerateUnsafe would be separate so as to put it
   in a separate file.

What's a possible solution?  If, in addition to Safe and Unsafe
modules, there were Partially Safe modules, which exported a mix of safe
and unsafe identifiers, then this could all be much cleaner.

The simple rule is that any reference whatsoever to an unsafe identifier
disqualifies the client code.  For example, in the above ParAccelerate type
class we would mark the unsafeHybrid binding with something like {-# UNSAFE
unsafeHybrid #-}.  We wouldn't even have to factor it out of the type class.

Likewise, Accelerate could mark fold as unsafe (providing safe variants
as well) without introducing module namespace bloat and confusion.

What do you think?

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


Re: [Haskell-cafe] Can Haskell outperform C++?

2012-05-10 Thread Ryan Newton

 through the trouble of writing my algorithms in C/C++, but simple-minded
 people often have a desire to get the best performance possible, in
 which case you really want to use C, C++, Fortran or whatever high level
 assembler language you like.


I think this is a bit of an unfair accusation (simple-minded).
 Performance is only relevant to certain domains, sure.  But program
performance is an entire *industry*.  And I'd argue it's of massive
importance to the world at large.  Intel has an army of AEs (application
engineers) that go out to other companies to make applications perform
better.  There are plenty of compute bound industries -- i.e. movie
companies are limited by what kind of frame they can render in ~24 hrs;
sequencing centers are limited by certain very slow bioinformatics
algorithms; you can look almost anywhere you like for examples.

As a community I think we have to face the fact that writing the hot inner
loop of your application as idiomatic Haskell is not [yet] going to give
you C/Fortran performance off the bat.  Though in some cases there's not
really anything stopping us but more backend/codegen work (I'm thinking of
arithmetically intensive loops with scalars only).  For example, the
following Mandel kernel is in many ways the *same* as the C version:

https://github.com/simonmar/monad-par/blob/662fa05b2839c8a0a6473dc490ead8dd519ddd1b/examples/src/mandel.hs#L24H

We have the types; we've got strictness (for this loop); but the C version
was 6X faster when I tested it.

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


Re: [Haskell-cafe] Annoyed at System.Random

2012-05-04 Thread Ryan Newton

 1. cprng-aes is painfully slow.

 when using the haskell AES implementation yes. with AESNI it fly, and even
 more when
 i'll have time to chunk the generation to bigger blocks (says 128 AES
 block at a time)


One data-point -- in intel-aes I needed to do bigger blocks to get decent
performance.


  2. It doesn't use NI instructions (or any C implementation, currently).

 The NI instructions support are coming. and there's ton of already
 existing C implementation
 that could just be added.


Oh, neat.  Could you share a pointer to some C code (with GCC aes
intrinsics?) that can replace what the ASM does in the intel-aes package?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Annoyed at System.Random

2012-05-04 Thread Ryan Newton

 My end goal is to have the user use transparently the fastest
 implementation available to their architecture/cpu providing they use the
 high level module. I've uploaded the cpu package which allows me to detect
 at runtime the aes instruction (and the architecture), but i've been
 distracted in implementing fast galois field arithmetics for GCM and XTS
 mode (with AES).


Yes!  A worthy goal!

I think the proposal here is that we do the build/integration work to get
something good which is portable enough and install-reliable enough to
replace 'random'.  Then people who don't care will be using a good
implementation by default.

That was my goal when I had my own small shot at this, but what I came up
with was *very* build-fragile.  (Depended on assembler being available, or
on prebuilt binaries being included for that package.)  You can see the
Setup.hs customization I attempted to do in intel-aes to compensate, but
it's not enough.

Can we write a cabal-compatible, really robust installer that will test the
users system and always fall back rather than failing?

  -Ryan

P.S. How are you doing the CPUID test for NI instructions?  I used the
*intel provided* test for this (in intel-aes) but I still had reports of
incorrect identification on certain AMD CPUs...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: meta-par, meta-par-accelerate and friends -- heterogeneous parallel programming

2012-05-04 Thread Ryan Newton
Hi all,

I'm happy to announce a release of meta-par, a parallel programming library
that is a successor to monad-par.

   - http://hackage.haskell.org/package/abstract-par
   - http://hackage.haskell.org/package/monad-par
   - http://hackage.haskell.org/package/meta-par
   - http://hackage.haskell.org/package/abstract-par-accelerate
   - http://hackage.haskell.org/package/meta-par-accelerate

The distributed programming components aren't released yet, but this blog
posts describes how to use the above packages to do hybrid CPU/GPU
programming:


http://parfunk.blogspot.com/2012/05/how-to-write-hybrid-cpugpu-programs.html

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


Re: [Haskell-cafe] Annoyed at System.Random

2012-05-03 Thread Ryan Newton
Hi Thomas,

Personally, I would love to see that happen.  It seems like the best way to
make split acceptable.

Is Brian Gladman's C implementation still best in class?  In my tests even
without AESNI it could exceed the traditional System.Random in performance (
https://github.com/rrnewton/intel-aes/wiki), while providing much better
randomness and splitability.

Re: AESNI, my attempt at using the Intel provided asm for this introduced
build fragility.  What would be the more portable way to do it?  Rewrite it
using GCC intrinsics?

   http://tab.snarc.org/posts/technical/2012-04-12-aes-intrinsics.html

  -Ryan


On Thu, May 3, 2012 at 7:43 PM, Thomas DuBuisson thomas.dubuis...@gmail.com
 wrote:

 Ryan,
 I've grown annoyed at System.Random enough (specifically, StdGen).
 How much, if any, pushback would there be if I put together a FFI
 binding to a C AES-CTR based RNG.  There are many advantages:

 0) The API wouldn't have to change (though some parts should, and some
 change is already planned)
 1) It can be fast (maybe not MT fast, but really quite good)
 2) It's secure and the splitting properties can be related to
 cryptographic problems.
 3) It could use Intel NI instructions when available.
 4) It's NIST standardized, so there exist known answer tests.
 5) We could expose a method to fill an arbitrary buffer :: Storable a
 = Ptr a - Int - IO ()
 6) The rest of the community doesn't have to do any of the work.

 I'd be tempted to pull in the 'entropy' package for seeding, but will
 make that a separate proposal.

 Cheers,
 Thomas

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


Re: [Haskell-cafe] Multi-site haddock documentation with proper links?

2012-04-25 Thread Ryan Newton
One more update:

cabal haddock exposes a --html-location flag which is useful:


http://www.haskell.org/cabal/users-guide/installing-packages.html#setup-haddock

Another way of invoking haddock is through cabal install.  It looks like
cabal install --enable-documentation and cabal install --haddock are
not documented here, but they work:


http://www.haskell.org/cabal/users-guide/installing-packages.html#paths-in-the-simple-build-system

With cabal 0.14.0 and haddock 2.10.0, they work even when installing
multiple packages at once using trailing slashes (cabal install foo/ bar/
baz/).

We can then achieve the effect of haddock --html-location=URL with
the --haddock-html-location=URL flag to cabal install.  (There is also an
--htmldir flag available but its effect is somewhat confusing.  As far as
I can tell it seems to affect where the .haddock files are put, not where
the .html in installed or where the links point to. )

So that's it.  The result is that it's easy to build ONE package's
documentation and host it on a different server but with all links to other
modules pointing to hackage.  Regarding the original goal it looks like a
sed style hack will still be required to allow a set of sibling packages
to point to one another.

  -Ryan

On Tue, Apr 24, 2012 at 8:51 PM, Ryan Newton rrnew...@gmail.com wrote:

 This is sort of related to ticket #130:

http://trac.haskell.org/haddock/ticket/130

 And this one seems to hint at a solution to the problem in the more
 extensive syntax for --read-interface.

   http://hackage.haskell.org/trac/ghc/ticket/3810

 (My local haddock-2.10.0 --help doesn't mention this.  But I'll give it a
 whirl.)



 On Tue, Apr 24, 2012 at 8:34 PM, Ryan Newton rrnew...@gmail.com wrote:

 Hello cafe,

 For various reasons, some packages don't build documentation on hackage:

http://hackage.haskell.org/package/accelerate

 Therefore I want to locally install documentation for a set of packages
 like this and host them on a separate website.  I want all of these ~ten
 packages' haddock documentation to be properly interlinked with eachother,
 but also to link to Hackage for types and classes defined in other modules.

 Is this possible?  Hackage haddocks are all interlinked, but that is
 simply because hackage is one giant local install, right?

 If it's not possible (and it seems not) do any haddock devs have pointers
 on how to implement this?

 Thanks,
   -Ryan

 P.S.  Someone recommended to me the following simple hack -- just use sed
 to rewrite the links after haddock generates the html.  I think I'll do
 that for the time being unless someone has a better suggestion.



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


Re: [Haskell-cafe] Offer to mirror Hackage

2012-04-24 Thread Ryan Newton

 There's two options I think:
 1. a machine for the central hackage server,
 2. a machine for doing package builds

 The former will require more organisation, partly because we need the
 haskell.org people to have some degree of control over the system. The
 latter is easier because the design allows for multiple clients to do
 builds rather than just one central machine. So all that requires is a
 user account to upload the data. (plus the small matter of a working
 build bot client software, which is where scoutess may help)


I wonder if this could get to the point where it could be done seti-at-home
style, farmed out via a VM image.  That is people would run the image to
provide resources (and geographic distribution) to the build server cloud.
 Maybe they get a fast local mirror as a reward.

If it were every that easy I would certainly love to run a VM!

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


Re: [Haskell-cafe] Offer to mirror Hackage

2012-04-24 Thread Ryan Newton

 I wonder if this could get to the point where it could be done
 seti-at-home style, farmed out via a VM image.  That is people would run
 the image to provide resources (and geographic distribution) to the build
 server cloud.  Maybe they get a fast local mirror as a reward.

 If it were every that easy I would certainly love to run a VM!


Surprisingly BOINC seems to *not* be virtualized and instead just runs
native applications.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Multi-site haddock documentation with proper links?

2012-04-24 Thread Ryan Newton
Hello cafe,

For various reasons, some packages don't build documentation on hackage:

   http://hackage.haskell.org/package/accelerate

Therefore I want to locally install documentation for a set of packages
like this and host them on a separate website.  I want all of these ~ten
packages' haddock documentation to be properly interlinked with eachother,
but also to link to Hackage for types and classes defined in other modules.

Is this possible?  Hackage haddocks are all interlinked, but that is simply
because hackage is one giant local install, right?

If it's not possible (and it seems not) do any haddock devs have pointers
on how to implement this?

Thanks,
  -Ryan

P.S.  Someone recommended to me the following simple hack -- just use sed
to rewrite the links after haddock generates the html.  I think I'll do
that for the time being unless someone has a better suggestion.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Multi-site haddock documentation with proper links?

2012-04-24 Thread Ryan Newton
This is sort of related to ticket #130:

   http://trac.haskell.org/haddock/ticket/130

And this one seems to hint at a solution to the problem in the more
extensive syntax for --read-interface.

  http://hackage.haskell.org/trac/ghc/ticket/3810

(My local haddock-2.10.0 --help doesn't mention this.  But I'll give it a
whirl.)



On Tue, Apr 24, 2012 at 8:34 PM, Ryan Newton rrnew...@gmail.com wrote:

 Hello cafe,

 For various reasons, some packages don't build documentation on hackage:

http://hackage.haskell.org/package/accelerate

 Therefore I want to locally install documentation for a set of packages
 like this and host them on a separate website.  I want all of these ~ten
 packages' haddock documentation to be properly interlinked with eachother,
 but also to link to Hackage for types and classes defined in other modules.

 Is this possible?  Hackage haddocks are all interlinked, but that is
 simply because hackage is one giant local install, right?

 If it's not possible (and it seems not) do any haddock devs have pointers
 on how to implement this?

 Thanks,
   -Ryan

 P.S.  Someone recommended to me the following simple hack -- just use sed
 to rewrite the links after haddock generates the html.  I think I'll do
 that for the time being unless someone has a better suggestion.

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


Re: [Haskell-cafe] Fwd: Now Accepting Applications for Mentoring Organizations for GSoC 2012

2012-04-20 Thread Ryan Newton
Did anyone end up being the co-admin?



On Thu, Mar 1, 2012 at 4:50 PM, Johan Tibell johan.tib...@gmail.com wrote:

 On Thu, Mar 1, 2012 at 1:42 PM, Ganesh Sittampalam gan...@earth.liwrote:

 On 01/03/2012 21:37, Johan Tibell wrote:
  On Thu, Mar 1, 2012 at 12:54 PM, Ganesh Sittampalam gan...@earth.li
  mailto:gan...@earth.li wrote:
 
  FYI, Edward Kmett has volunteered to do it again.
 
 
  That's great since he's the most experienced GSoC admin we have. :)
 
  There's still room for a replacement for me. I had a few people show
  interest so far.

 Maybe I'm confused about the roles, then. Were you co-admins previously,
 or something else?


 Edward and I were co-admins last year. That worked out great in my opinion.

 I want to make sure that we have at least one admin this year, otherwise
 we won't get any GSoC slots this year, hence my original email. I didn't
 know if Edward was interested or not. Now we have a few candidates,
 including Edward. My preference is to have 2+ admins, preferably with
 Edward as one of them as he has experience in the matter.

 Sorry about the confusions.

 Cheers,
   Johan


 ___
 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] Offer to mirror Hackage

2012-04-19 Thread Ryan Newton
Hello all,

Right now I'm trying to answer a simple question:

   - Would the current Haskell.org / hackage infrastructure benefit from
   the donation of a dedicated VM with good bandwidth/uptime?

Whoever already knows how to do this could configure it.

In trying to answer the above question I found this long email thread from
1.5 years ago.  Duncan said the following:

On Thu, Dec 9, 2010 at 6:47 PM, Duncan Coutts
duncan.cou...@googlemail.comwrote:

 That's certainly what we've been planning on, that anyone can run a
 mirror, no permissions needed. The issue people have raised is what
 about having public mirrors that are used automatically or
 semi-automatically by clients.


Are there any updates to this in the last year?  Is anybody running a
mirror?

The other reason I've been thinking about this is the scoutess project.
 More public testing or continuous integration facilities would require
more hardware resources.

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


[Haskell-cafe] Administrative questions about Haskell GSOC (Google Summer of Code)

2012-04-19 Thread Ryan Newton
Hello,

As someone new to the GSOC system there are some things I'm confused about.
 There's a bunch of info out there, and I certainly haven't read all of it.


Who are the program administrator and organization administrator for
the Haskell organization?  Those roles are mentioned in the manual here:

http://en.flossmanuals.net/GSoCMentoring/what-is-gsoc/

Presumably those are the people that actually click accept on the melange
site:

https://google-melange.appspot.com/gsoc/homepage/google/gsoc2012

How many slots did we get?  Is the system just to accept the top rated
student proposals?

If I can find the answers to these questions maybe I can update the Wiki
for next year so it has a bit more info for mentors and about the process
as well as students:

http://hackage.haskell.org/trac/summer-of-code/wiki/Soc2012

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


Re: [Haskell-cafe] Google Summer of Code - Lock-free data structures

2012-04-05 Thread Ryan Newton
+1 -- the reagents model is interesting and it would be good to see a
Haskell implementation.


On Thu, Apr 5, 2012 at 3:05 PM, Ben Gamari bgamari.f...@gmail.com wrote:

 Ben midfi...@gmail.com writes:

  perhaps it is too late to suggest things for GSOC --
 
  but stephen tetley on a different thread pointed at aaron turon's
  work, which there's a very interesting new concurrency framework he
  calls reagents which seems to give the best of all worlds : it is
  declarative and compositional like STM, but gives performance akin to
  hand-coded lock-free data structures.  he seems to have straddled the
  duality of isolation vs message-passing nicely, and can subsume things
  like actors and the join calculus.
 
  http://www.ccs.neu.edu/home/turon/reagents.pdf
 
  he has a BSD licensed library in scala at
 
  https://github.com/aturon/ChemistrySet
 
  if someone doesn't want to pick this up for GSOC i might have a hand
  at implementing it myself.
 
 Keep use in the loop if you do. I have a very nice application that has
 been needing a nicer approach to concurrency than IORefs but
 really can't afford STM.

 Cheers,

 - Ben


 ___
 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] Google Summer of Code - Lock-free data structures

2012-03-29 Thread Ryan Newton
On Thu, Mar 29, 2012 at 9:01 AM, Gregory Collins g...@gregorycollins.netwrote:

 On Thu, Mar 29, 2012 at 6:57 AM, Ryan Newton rrnew...@gmail.com wrote:

 The ByteArray versions will be more annoying, requiring more variations,
 but they are also less essential, because the user can always use
 ForeignPtr and bits-atomic in this case, and I believe for our concurrent
 data structures we want to store arbitrary pointers (hence casArray#).


 This is true, although using bits-atomic does a function call (i.e the
 calls are not inlined), which would be pretty bad for performance.


Yes, absolutely... I'd like to add the byte array versions.  Actually,
those don't have GC write barriers so they should be much easier to get
right!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Google Summer of Code - Lock-free data structures

2012-03-29 Thread Ryan Newton

 I think so. Atomically reading and writing a single memory location
 (which CAS does) is just a very simple transaction. But using a CAS
 instruction should be more efficient, since STM has to maintain a
 transaction log and commit transactions, which creates some overhead.


 Ah, I see. In that case, it may be worthwhile to implement the CAS
 instruction in terms of STM as well and measure the performance difference
 this makes for the final data structure. After all, STM is a lot more
 compositional than CAS, so I'd like to know whether the loss of
 expressiveness is worth the gain in performance.


There's one annoying hitch with doing apples-to-apples comparisons here.

The problem is that CAS falls short of being a hardware-accelerated version
of a simple transaction (read TVar, (==) against expected value,
conditionally update TVar), because CAS is based on pointer equality rather
than true equality.  (eq? rather than equal? for any Schemers out there.)

For this reason our Fake version of CAS -- for older GHCs and for
performance comparison -- has to use reallyUnsafePointerEquality#:


http://hackage.haskell.org/packages/archive/IORefCAS/0.2/doc/html/Data-CAS-Internal-Fake.html

But we do provide a CASable type class in that package which is precisely
for comparing the performance of:

   - Hardware CAS
   - Fake CAS -- atomicModifyIORef + ptrEquality
   - Foreign CAS -- gcc intrinsic + function call

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


Re: [Haskell-cafe] Google Summer of Code - Lock-free data structures

2012-03-28 Thread Ryan Newton
 GHC already has a CAS primitive on MutVar#, it just needs to be extended
 to MutableArray# and MutableByteArray# (at all of the bit-widths the CAS
 instruction would support, e.g. see readWordXxArray# in
 http://www.haskell.org/ghc/docs/latest/html/libraries/ghc-prim-0.2.0.0/GHC-Prim.html).
 The implementation should be almost identical to casMutVar#.
 In particular I think you need:
 casMutArray# :: MutableArray# s a - Int# - a - a - State# s - (#
 State# s, Int#, a #)
 casWord16MutByteArray :: MutableByteArray# s - Int# - Word# - Word#
 - State# s - (# State# s, Int#, Word#)


FYI, I started working on adding these.  I'm hoping to have it working in
GHC HEAD for any students who need to use it.  To my knowledge the only two
patches required to implement casMutVar# were these two (plus the
preexisting cas() definition in SMP.h):


https://github.com/ghc/ghc/commit/521b792553bacbdb0eec138b150ab0626ea6f36b

https://github.com/ghc/ghc/commit/606f6e1cfcb2e79abaadcc5ed643817d2a4585d8

The latter is a bugfix to the former.

Florian, your proposal looks good to me (
http://www.google-melange.com/gsoc/proposal/review/google/gsoc2012/florianhartwig/1).
 You touched on the major things we need to know.

I just read in your proposal that you started looking into the casMutArray#
issue as well.  How far have you gotten with that?  Do you want to work on
this together a bit?

I've got an implementation of a casArray# primop that passes a basic test,
but I'm not sure if the GC write barrier is correct:


https://github.com/rrnewton/ghc/commit/18ed460be111b47a759486677960093d71eef386

The ByteArray versions will be more annoying, requiring more variations,
but they are also less essential, because the user can always use
ForeignPtr and bits-atomic in this case, and I believe for our concurrent
data structures we want to store arbitrary pointers (hence casArray#).

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


[Haskell-cafe] Need a backup GSOC to apply for? Last minute new proposal -- memory reuse analysis for GHC

2012-03-26 Thread Ryan Newton
Hi potential GSOC'ers,

If there are multiple students interested in the project you're applying to
it's a good idea to put in more than one application.

This is a project proposal that would focus on performance analysis -- in
particular in reusing some of the tools for analyzing memory access
patterns in the context of Haskell:

   http://hackage.haskell.org/trac/summer-of-code/ticket/1619

I think this project would yield pretty good bang for the buck because
almost all the pieces are already there.  They just need to be combined,
polished, documented, and evangelized.

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


Re: [Haskell-cafe] GSoC and Data Parallel Haskell

2012-03-21 Thread Ryan Newton
The big topic would seem to be using Geoff Mainland's new simd-ghc support.

http://hackage.haskell.org/trac/ghc/wiki/SIMD

Geoff, is that already under way or is it too big a project for a GSOC?

Dmitry, do you already have GHC-internals hacking experience?

  -Ryan


On Tue, Mar 20, 2012 at 8:52 PM, Dmitry Dzhus d...@dzhus.org wrote:

 How are you gentlemen.

 I'm interested about what additions to DPH would really benefit
 the community.

 The only ticket on DPH in GSoC Trac seems a bit stale:
 http://hackage.haskell.org/trac/summer-of-code/ticket/1537.
 Any new tips?

 My field is currently molecular simulation. (I'm doing a Direct Simulation
 Monte-Carlo implementation for rarefied gas dynamics with application
 to space satellitesstuffs aerodynamics in Haskell for my Master's thesis,
 I believe using DPH as well would be my final goal as molecular simulations
 vectorize nicely. Simulation domain is partitioned into cells and
 stochastic
 collision sampling (as in DSMC) may be performed in every cell in
 parallel.)

 ___
 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] Mathematics and Statistics libraries

2012-03-21 Thread Ryan Newton
I think such libraries are high priority!

My own experience with them is not deep, but I'll echo what I think is a
common observation:

   - Matrix libraries are good
   - Statistics libs need more work

And as far as wrappers around machine learning or computer vision libs
(openCV)... I'm not really sure about the status of those.


On Wed, Mar 21, 2012 at 1:24 PM, Ben Jones ben.jamin.pw...@gmail.comwrote:

 I am a student currently interested in participating in Google Summer of
 Code. I have a strong interest in Haskell, and a semester's worth of coding
 experience in the language. I am a mathematics and cs double major with
 only a semester left and I am looking for information regarding what the
 community is lacking as far as mathematics and statistics libraries are
 concerned. If there is enough interest I would like to put together a
 project with this. I understand that such libraries are probably low
 priority, but if anyone has anything I would love to hear it.

 Thanks for reading,
   -Benjamin

 ___
 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] Google Summer of Code - Lock-free data structures

2012-03-19 Thread Ryan Newton
The MichaelScott lockefree queues in that repository pass tests and should
work.  Additional stress testing and feedback would be appreciated.  There
are some other queues in the literature that might be worth implementing
but I think other data structures are higher priority.

As Adam Foltzer mentioned in the trac ticket a really good structure would
be the concurrent bags from this paper:

   http://www.cse.chalmers.se/~tsigas/papers/Lock%20Free%20Bag%20SPAA11.pdf

We separately did a C implementation of those and they performed really
well in our bake-off of producer consumer data structures (vs. TBB queues,
and many other implementations).  By the way, we can share the code for
this little bake-off as a performance baseline for the Haskell versions.

I'm less familiar with the literature on concurrent hash tables.  TBB's
have been a little bit underwhelming in performance.  But it's definitely
an important structure.   Ditto for priority queues.

In any case, I welcome your interest in the topic, Florian!

Cheers,
   -Ryan



On Mon, Mar 19, 2012 at 7:33 AM, Florian Hartwig 
florian.j.hart...@gmail.com wrote:

 On 19 March 2012 09:56, Gregory Collins g...@gregorycollins.net wrote:
  A lock-free concurrent queue alone would be worth a summer project IMO.
 
  G

 Ryan Newton is already doing that
 (https://github.com/rrnewton/haskell-lockfree-queue).

 ___
 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] Summer of Code idea: Haskell Web Toolkit

2012-03-18 Thread Ryan Newton

 HJScript is OK, hpaste.org uses it here:
 https://github.com/chrisdone/amelie/blob/master/src/Amelie/View/Script.hs
 output here: http://hpaste.org/js/amelie.js

 Mini-summary of my experience: You're still stuck with JS semantics,
 and it can be a little odd when you confuse what level of code (JS or
 HS) you're working at, but at least it works right now and can be
 well-typed. The library needs a bit of an overhaul, the GADT of
 HJavaScript is simply flawed (take a brief look and you can see it can
 express totally invalid JS in the syntax tree and the pretty printer
 breaks operator/parens), but HJScript sorts the latter out, and I
 would make all HJScript's functions generic upon MonadJS or something,


It seems like the unavoidable fact is that HJScript is a library almost
without documentation and without examples/tests.  And for an EDSL that
would seem to be an especially big problem, almost, but not quite as bad as
being told to learn Haskell by being given a GHCI prompt and left to trial
and error.

I've been trying to generate the following line of code:

google.load(visualization, 1, {packages:[corechart]});

I don't know JS, and my reverse engineering of this one line failed in two
places:

callVoidMethod load (string visualization, string 1, JConst
{packages:[\corechart\]}) (TopLvl google)

First, there are classes like IsDeref and IsClass with no clear recipe for
how to create values and types satisfying them.  Hence TopLvl, which is
my own introduced hack:

data TopLvl = TopLvl String
instance Show TopLvl where
  show (TopLvl s) = s
instance IsClass TopLvl

Second, I couldn't figure out how to generate a dictionary/record
expression such as {packages:core chart}.  It doesn't seem to be part of
the data model of the underlying HJavaScript package:


http://hackage.haskell.org/packages/archive/HJavaScript/0.4.7/doc/html/Language-HJavaScript-Syntax.html

Although it's probably possibly to build up that record in a variable
binding through some series of assignments, though I haven't found it yet...

What would help enormously, in addition to some documentation patches
[which I will try to provide if I use the library further], would be a
parser from JS concrete syntax to the HJavaScript AST.

Anyway, at this point it seems MUCH easier to just produce strings, which
is too bad.

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


Re: [Haskell-cafe] Best way to use the google visualization (javascript) API rather than static image charts (hs-gchart)?

2012-03-18 Thread Ryan Newton
Thanks David,

As an update, HJScript is a bit of a nightmare to figure out (missing
documentation, examples).  And the model of JS values:

http://hackage.haskell.org/packages/archive/language-javascript/0.4.10/doc/html/Language-JavaScript-Parser.html#t:Node
Seems less human comprehensible than, for example, WebBits':

http://hackage.haskell.org/packages/archive/WebBits/2.0/doc/html/BrownPLT-JavaScript-Syntax.html

However, jmacro is a breeze for spitting out JS code.  The little script
below will make a simple line plot with google charts.

I'll give flot a try latter.  Zooming / panning sounds nice.

Cheers,
  -Ryan

Aforementioned script:
---

{-# LANGUAGE QuasiQuotes #-}

import Language.Javascript.JMacro

hdr :: String
hdr = html head script type=\text/javascript\ src=\
https://www.google.com/jsapi\;/script script type=\text/javascript\

ftr :: String
ftr = /script  /head  body  div id=\chart_div\ style=\width:
900px; height: 500px;\/div  /body /html


testdata :: [(String, Int, Int)]
testdata = [
  (2004, 100, 400),
  (2005, 1170, 460),
  (2006,  860, 580),
  (2007, 1030, 540)
]

-- | This provides a set of basic functional programming primitives, a few
utility functions
-- and, more importantly, a decent sample of idiomatic jmacro code. View
the source for details.
-- body :: JStat
body :: (ToJExpr a3, ToJExpr a2, ToJExpr a1, ToJExpr a) = (a, a1, a2) -
a3 - JStat
body (title,line1,line2) testdata = [$jmacro|

  google.load(visualization, 1, {packages:[corechart]});

  fun drawChart {
var dat = new google.visualization.DataTable();
dat.addColumn('string', `(title)` );
dat.addColumn('number', `(line1)` );
dat.addColumn('number', `(line2)` );

// -- Here's our data... this can get BIG:
dat.addRows( `(testdata)` );

var options = {  title: `(title)` };
var chart = new
google.visualization.LineChart(document.getElementById('chart_div'));
chart.draw(dat, options);
  }

  google.setOnLoadCallback(drawChart);
|]

main = do
  putStrLn hdr
  print$ renderJs$ body (blah,line1,line2) testdata
  putStrLn ftr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Prettier pretty-printing of data types?

2012-03-17 Thread Ryan Newton
Hi all,

I've got a question that pertains to any of these identify-region, parse,
make-expandable approaches.

The main use I'd like to use the trick for (esp. Chris's Emacs version) is
to deal with large intermediate compiler ASTs.

But if a compiler produces a long stream of output to stdout, with certain
Show-produced ASTs embedded in it, what's the most expedient way to
identify those regions that can be collapsed in the buffer and
interactively expanded?

   - The user could define heuristics for identifying those regions in a
   particular stream of output
   - If the source is available, the compiler could be tweaked to obey a
   protocol, putting delimiters around collapsable output (possibly
   non-printing control sequences??)

Or is there another hack I'm not thinking of?  What's easiest?

  -Ryan



On Wed, Mar 14, 2012 at 5:01 AM, Heinrich Apfelmus 
apfel...@quantentunnel.de wrote:

 Christopher Done wrote:

 Maybe an Emacs script to expand the nodes nicely:
 http://www.youtube.com/watch?**v=6ofEZQ7XoEAhttp://www.youtube.com/watch?v=6ofEZQ7XoEAI
  don't find mere pretty
 printing that useful compared to the “expanding” paradigm I'm used to in
 Chrome and Firebug.


 Great demo video. My recent GSoC project suggestions aims to make that
 available to non-Emacsers, via the web browser.

  
 http://hackage.haskell.org/**trac/summer-of-code/ticket/**1609http://hackage.haskell.org/trac/summer-of-code/ticket/1609


 Best regards,
 Heinrich Apfelmus

 --
 http://apfelmus.nfshost.com



 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@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


Re: [Haskell-cafe] Prettier pretty-printing of data types?

2012-03-17 Thread Ryan Newton
 Ah, great!

I gave it one very brief try with this mode:

   http://www.emacswiki.org/emacs/FoldingMode

   (folding-add-to-marks-list 'shell-mode #{{{ #}}} nil t)

But I just got not on a fold.  Maybe it doesn't compose with shell mode?
 It might be easier just to add similar functionality to a wrapper function
around Chris's folder/expander.

  -Ryan



On Sat, Mar 17, 2012 at 9:10 AM, Brandon Allbery allber...@gmail.comwrote:

 On Sat, Mar 17, 2012 at 08:55, Ryan Newton rrnew...@gmail.com wrote:


- If the source is available, the compiler could be tweaked to obey a
protocol, putting delimiters around collapsable output (possibly
non-printing control sequences??)


 I believe both emacs and vim have folding submodes which operate based on
 comments containing {{{ / }}} to bracket foldable regions.

 --
 brandon s allbery  allber...@gmail.com
 wandering unix systems administrator (available) (412) 475-9364 vm/sms


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


[Haskell-cafe] Best way to use the google visualization (javascript) API rather than static image charts (hs-gchart)?

2012-03-16 Thread Ryan Newton
Hello cafe,

I've got a benchmarking script which currently generates gnuplot scripts
(of simple lines and points) and I'd like to port it to use two** new
backends:

  (1) Chart for PDF generation and gtk viewing
  (2) Something-or-other for generating pretty interactive charts in the
browser, suitable for pasting into blog posts.

I was hopeful regarding hs-gcharts, but it looks like that only works for
the charts that generate static images given a URL, as described here:
   http://code.google.com/apis/chart/image/docs/making_charts.html

Rather than interactive ones, like this JSAPI based pie chart:
   http://code.google.com/apis/chart/interactive/docs/quick_start.html

So where to start?  Has anybody tried this before?  Perhaps the best thing
to do is just use HJScript to produce the desired JS code:


https://github.com/chrisdone/amelie/blob/master/src/Amelie/View/Script.hs
output here: http://hpaste.org/js/amelie.js

Thanks,
 -Ryan

** One would be great but I'm pretty sure no such thing currently exists.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fwd: Now Accepting Applications for Mentoring Organizations for GSoC 2012

2012-02-29 Thread Ryan Newton
Is there any official way that mentors should sign up to become part of the
org?

For one thing I heard a rumor that bigger orgs look better from Google's
end.

  -Ryan


On Tue, Feb 28, 2012 at 11:23 AM, Johan Tibell johan.tib...@gmail.comwrote:

 Hi all,

 Anyone interested in acting as an admin for haskell.org this year? I'm
 afraid I won't have time. It's not that much work (filling in some
 information, sending out some emails, making sure things happen in time.)

 -- Forwarded message --
 From: Carol Smith car...@google.com
 Date: Mon, Feb 27, 2012 at 11:47 AM
 Subject: Now Accepting Applications for Mentoring Organizations for GSoC
 2012
 To: Google Summer of Code Announce 
 google-summer-of-code-annou...@googlegroups.com


 Hi all,

 We're pleased to announce the applications for mentoring organizations
 for GoogleSummer of Code 2012 are now being accepted [1]. Please go
 Melange [2] to apply on behalf of your organization. Please note that
 the application period [3] closes on 9 March at 23:00 UTC. We will not
 accept any late applications for any reason.

 [1] -
 http://google-opensource.blogspot.com/2012/02/mentoring-organization-applications-now.html
 [2] - http://www.google-melange.com
 [3] - http://www.google-melange.com/gsoc/events/google/gsoc2012

 Cheers,
 Carol

 --
 You received this message because you are subscribed to the Google Groups
 Google Summer of Code Announce group.
 To post to this group, send email to
 google-summer-of-code-annou...@googlegroups.com.
 To unsubscribe from this group, send email to
 google-summer-of-code-announce+unsubscr...@googlegroups.com.
 For more options, visit this group at
 http://groups.google.com/group/google-summer-of-code-announce?hl=en.



 ___
 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] Functional programming podcast

2012-02-22 Thread Ryan Newton
+1

I'm always at a loss for good technical podcasts.  The popular ones that
come up (with a simple search) are such fluff!



On Wed, Feb 22, 2012 at 12:00 PM, Clint Moore cl...@ivy.io wrote:

 On Wed, Feb 22, 2012 at 5:50 AM, Christopher Done
 chrisd...@googlemail.com wrote:
  Show of hands, who would be interested in working on a podcast weekly
  or biweekly and what would you like to provide? Light banter is an
  acceptable answer. Some points that might be covered on such a podcast
  might be:
 
  * Latest FP conferences/hackathons/etc
  * Competitions
  * Interesting papers (new, or old and dug up)
  * Interesting blog posts or stackoverflow questions
  * New and interesting libraries/tech released
  * Developments in the communities, funding, business developments
  * Interviews with prominent FP chappies
 
  This bleeds over a little with Haskell Weekly News, but it's more like
  FP weekly interesting stuff, and therefore there would be a lot more
  news to pack in. It would be something to listen to while you're
  walking to work with your ipod.

 I would definitely be interested in helping out.  I'm only an
 intermediate level with Haskell, and about 5th grade with Common Lisp,
 but I wouldn't mind trying out for a speaking spot on it.  Assuming my
 voice doesn't come off as too distracting :)

 ___
 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


[Haskell-cafe] Preventing leaked open file descriptors when catching exceptions

2012-02-21 Thread Ryan Newton
Hi all,

I'm trying to run a loop that repeatedly attempts to open a file until it
succeeds.  The file is a named pipe in nonblocking mode, so the writer can
only connect after the reader has connected.  (Perhaps there is some way to
determine this by stat'ing the pipe, but I don't know it yet.)

Thus I do something like the following:

 tryUntilNoIOErr $ do
performGC
-- The reader must connect first, the writer here spins with backoff.
PIO.openFd filename PIO.WriteOnly Nothing fileFlags

I'm running GC between iterations to try to make sure I get rid of open
files.  Also, in the tryUntilNoIOErr code below I have some debugging
messages which indicate that ioeGetHandle reports no handles associated
with the exceptions I'm getting back.  (If there were handles provided I
could close them explicitly.)

In spite of these attempted precautions I'm seeing too many open files
exceptions in simple benchmarks that should only have a maximum of ONE file
open.

Any hints / pointers?

Thanks,
  -Ryan


mkBackoff :: IO (IO ())
mkBackoff =
  do tref - newIORef 1
 return$ do t - readIORef tref
writeIORef tref (min maxwait (2 * t))
threadDelay t
 where
   maxwait = 50 * 1000

tryUntilNoIOErr :: IO a - IO a
tryUntilNoIOErr action = mkBackoff = loop
 where
  loop bkoff =
handle (\ (e :: IOException) -
 do bkoff
BSS.hPutStr stderr$ BSS.pack$ got IO err:  ++ show e
case ioeGetHandle e of
  Nothing - BSS.hPutStrLn stderr$ BSS.pack$   no hndl io err.
  Just x  - BSS.hPutStrLn stderr$ BSS.pack$   HNDL on io
err! ++ show x
loop bkoff) $
   action
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Preventing leaked open file descriptors when catching exceptions

2012-02-21 Thread Ryan Newton
FYI, lsof confirms that there are indeed many many open connections to the
same FIFO:

Is there some other way to get at (and clean up) the file descriptor that
is left by System.Posix.IO.openFD after it throws an exception?

PingPipes 25115  rrnewton  124r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  125r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  126r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  127r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  128r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  129r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  130r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  131r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  132r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  133r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  134r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  135r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  136r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  137r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683
PingPipes 25115  rrnewton  138r FIFO8,2  0t0   25166171
/tmp/pipe_9083984821255795683


On Tue, Feb 21, 2012 at 11:13 AM, Ryan Newton rrnew...@gmail.com wrote:

 Hi all,

 I'm trying to run a loop that repeatedly attempts to open a file until it
 succeeds.  The file is a named pipe in nonblocking mode, so the writer can
 only connect after the reader has connected.  (Perhaps there is some way to
 determine this by stat'ing the pipe, but I don't know it yet.)

 Thus I do something like the following:

  tryUntilNoIOErr $ do
 performGC
 -- The reader must connect first, the writer here spins with backoff.
 PIO.openFd filename PIO.WriteOnly Nothing fileFlags

 I'm running GC between iterations to try to make sure I get rid of open
 files.  Also, in the tryUntilNoIOErr code below I have some debugging
 messages which indicate that ioeGetHandle reports no handles associated
 with the exceptions I'm getting back.  (If there were handles provided I
 could close them explicitly.)

 In spite of these attempted precautions I'm seeing too many open files
 exceptions in simple benchmarks that should only have a maximum of ONE file
 open.

 Any hints / pointers?

 Thanks,
   -Ryan


 mkBackoff :: IO (IO ())
 mkBackoff =
   do tref - newIORef 1
  return$ do t - readIORef tref
 writeIORef tref (min maxwait (2 * t))
 threadDelay t
  where
maxwait = 50 * 1000

 tryUntilNoIOErr :: IO a - IO a
 tryUntilNoIOErr action = mkBackoff = loop
  where
   loop bkoff =
 handle (\ (e :: IOException) -
  do bkoff
 BSS.hPutStr stderr$ BSS.pack$ got IO err:  ++ show e
 case ioeGetHandle e of
   Nothing - BSS.hPutStrLn stderr$ BSS.pack$   no hndl io
 err.
   Just x  - BSS.hPutStrLn stderr$ BSS.pack$   HNDL on io
 err! ++ show x
 loop bkoff) $
action


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


Re: [Haskell-cafe] Preventing leaked open file descriptors whencatching exceptions

2012-02-21 Thread Ryan Newton
Ah, thanks Bryan.  I hadn't looked into it enough to realize that FDs are
just ints and not ForeignPtrs w/ finalizers.

Re: Donn's point.  Well, yes, that would seem to be the case!  But since I
think a linux bug is unlikely, I'm afraid that there's something else going
on here which I am not thinking of.

I'll make a self contained test of this and send it out.


On Tue, Feb 21, 2012 at 12:53 PM, Donn Cave d...@avvanta.com wrote:

 Quoth Bryan O'Sullivan b...@serpentine.com,
  On Tue, Feb 21, 2012 at 8:16 AM, Ryan Newton rrnew...@gmail.com wrote:
 
  FYI, lsof confirms that there are indeed many many open connections to
 the
  same FIFO:
 
 
  Like all of the lowest-level I/O functions, openFD just gives you back an
  integer, and the Fd type has no notion that there's an underlying system
  resource associated with it. It's your responsibility to manage it (i.e.
  clean up manually when catching an exception).

 What's more - if I understood the hypothesis correctly, that the
 exception occurs during openFd - that fails to return an Fd because
 the open(2) system call fails to return one, so it would presumably
 be an OS level bug if there's really an open file descriptor left
 from this.

Donn

 ___
 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


[Haskell-cafe] New GSoC on Concurrent Data Structures -- was: How do I get official feedback (ratings) on my GSoC proposal?

2012-02-16 Thread Ryan Newton
Neat, thanks Johan!  (I had no idea it was so easy to post to Reddit.)
 I also put the proposed project on the trac:

http://hackage.haskell.org/trac/summer-of-code/ticket/1608

So feel free to contact me, interested students!

Cheers,
  -Ryan

On Thu, Feb 16, 2012 at 12:51 AM, Johan Tibell johan.tib...@gmail.com wrote:
 On Wed, Feb 15, 2012 at 7:40 PM, Ryan Newton rrnew...@gmail.com wrote:
 I'm interested in mentoring any projects related to concurrent data
 structure implementation.  Is it too late to propose new projects?


  http://parfunk.blogspot.com/2012/02/potential-gsoc-haskell-lock-free-data.html

 Not all all. It's quite early in fact (I tried to get people to think
 about this early on.) I'd also post it to the Haskell reddit to make
 sure it gets a bit more exposure (it's kinda buried here in this
 thread.)

 -- Johan

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


Re: [Haskell-cafe] How do I get official feedback (ratings) on my GSoC proposal?

2012-02-15 Thread Ryan Newton
I'm interested in mentoring any projects related to concurrent data
structure implementation.  Is it too late to propose new projects?


http://parfunk.blogspot.com/2012/02/potential-gsoc-haskell-lock-free-data.html

-Ryan


On Mon, Feb 13, 2012 at 7:19 PM, Johan Tibell johan.tib...@gmail.comwrote:

 Yes. I rated some myself and left a motivation for my rating and waited
 for someone to disagree. :) In general I was just trying to help students
 out by pushing down proposals that (in my experience) where too hard to
 complete in a summer or that were too narrow to benefit a larger portion of
 the community.


 ___
 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] Evaluating parallel computations in order of finishing (approximately)

2012-02-07 Thread Ryan Newton
In stream processing frameworks this is a (common) non-deterministic merge
operation.

Because it's nondeterministic it would need to happen in IO:

  parCompletionOrder :: [a] - IO [a]

But it can be nonblocking (returns immediately, and lazy IO happens in
the background).

The Chan library has a primitive, getChanContents, that encapsulates the
lazy IO and makes this very easy to do:

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurrent-Chan.html

Thus parCompletionOrder (or whatever it's called) would only need to fork
an IO thread for each element, and have all threads write to a single
channel as soon as they are done. (Where done is either evaluating
shallowly (weak-head-normal-form) or deeply (full normal form).)

Then the main thread invokes getChanContents and voila.

Cheers,
  -Ryan


On Mon, Feb 6, 2012 at 6:24 PM, Edward Amsden eca7...@cs.rit.edu wrote:

 Conal Elliot did something like this for his FRP system in the paper
 Push-Pull Functional Reactive Programming [1]. It involved a hack in
 which unsafePerformIO was used to spawn two threads to evaluate two
 events for occurrences, and return whichever returned first.

 Recall though, that monads aren't magic (despite frequent appearances
 to the contrary.) They are just functional structures that have to
 obey all of the normal restrictions of a pure functional language,
 including referential transparency. The entire point of Haskell's
 parallelism constructs is to make the returned values independent of
 parallel evaluation order. You're not going to escape that by using a
 monad, unless its one like IO which exists to order side-effects and
 isolate them in the type system.


 [1] http://conal.net/papers/push-pull-frp/


 On Mon, Feb 6, 2012 at 5:46 PM, Victor Miller victorsmil...@gmail.com
 wrote:
  Suppose that we have a list [a] of computations that we want to evaluate
 in
  parallel.  I would like to have something (probably a monad) which would
  return the list in order (roughly) of finishing:
 
  Say the monad is M.  It would be something like the state monad, in that
 it
  would be implemented by a state transformer function.  In this case the
  state would the set of computations to be evaluated.
 
  we might have a function
 
 
  include :: [a] - M a ()
 
  which would say that the monad's responsibility would be to evaluate all
 the
  members of a in parallel.  We might also have a function
 
  strategy :: Strategy - M a ()
 
  which would indicate the parallel strategy to be used.
 
  The key thing would be function, completed, which produces a list of all
 the
  computations to be evaluated as a list roughly in order of completion.
 
  That is, if, inside the M monad we finished the do with
 
  completed
 
  then we would have a value M a [a]
 
  which would be the list in order of completion.
 
  Since everything is lazy we could ask for the head of the list, and it
 would
  be the first value whose computation finished.
 
  Does such a thing exist?
 
 
  Victor
 
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Edward Amsden
 Student
 Computer Science
 Rochester Institute of Technology
 www.edwardamsden.com

 ___
 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] The State of Testing?

2012-02-07 Thread Ryan Newton
By the way, has anyone else had trouble with cabal test diverging?

I've been running into this issue with cabal 0.10.2, but ONLY in
conjunction with GHC 6.12.3.  It's hard to make a small reproducer for (and
therefore I haven't filed a bug yet), but you can see the below Jenkins run
stalled for 2.5 days, whereas it should take minutes:

http://tester-lin.soic.indiana.edu:8080/job/monad-par_github_master/JENKINS_GHC=ghc-6.12.3/17/console

Note that it *doesn't* burn CPU -- it deadlocks rather than spins.

I replaced cabal test with a direct call to the test executable and I
haven't seen this problem since.

   -Ryan


On Tue, Feb 7, 2012 at 4:23 PM, Austin Seipp mad@gmail.com wrote:

 If you're writing a library, you need to compile the library with
 `-fhpc`, i.e. put it in the library stanza, not the testsuite stanza,
 and then you can compile the test program using your library - the
 resulting 'tix' file will contain the library coverage reports. You
 can link a HPC-built library into an executable not compiled with HPC
 just fine.

 Normally I only compile the library under HPC mode, link it in a test,
 and distribute the results from that. That way your coverage reports
 don't include the test module (which may or may not be relevant.)

 I normally add a cabal flag called 'hpc' which optionally enables
 coverage reports for my library, e.g.

 flag hpc
  default: False

 library
  ...
  ...
  if flag(hpc)
ghc-options: -fhpc

 Then when you want coverage reports, just say 'cabal install -fhpc
 --enable-tests' and the resulting properties executable will spit out
 the results when run.

 On Tue, Feb 7, 2012 at 3:16 PM, Michael Craig mks...@gmail.com wrote:
  Thanks for the advice, all. I've got test-framework, quickcheck, and
 cabal's
  test-suite all working together nicely.
 
  Cabal seems to support using hpc to check test coverage. If I add -fhpc
 to
  the ghc-options under the test-suite, I get output like Test coverage
  report written to dist/hpc/html/tests/hpc_index.html and Package
 coverage
  report written to dist/hpc/html/test-0.0.0/hpc_index.html, but those
 html
  files are just empty tables. How does this work?
 
  Mike Craig
 
 
 
 
  On Thu, Feb 2, 2012 at 8:45 PM, Ivan Lazar Miljenovic
  ivan.miljeno...@gmail.com wrote:
 
  On 03/02/2012 12:22 PM, Johan Tibell johan.tib...@gmail.com wrote:
  
   On Thu, Feb 2, 2012 at 4:46 PM, Conrad Parker con...@metadecks.org
   wrote:
  
   On 3 February 2012 08:30, Johan Tibell johan.tib...@gmail.com
 wrote:
On Thu, Feb 2, 2012 at 4:19 PM, Conrad Parker 
 con...@metadecks.org
wrote:
   
I've followed what Johan Tibbell did in the hashable package:
   
   
If I had known how much confusion my childhood friends would
 unleash
on the
Internet when they, at age 7, gave me a nickname that's spelled
slightly
differently from my last name, I would have asked them to pick
another one.
;)
  
   lol, sorry, I actually double-checked the number of l's before
 writing
   that but didn't consider the b's. For future reference I've produced
 a
   handy chart:
  
  
  
   Letter | Real-name count | Nickname count
   ---+-+---
   b  | 1   | 2
   l  | 2   | 0
   ---+-+---
   SUM| 3   | 2
  
  
   Excellent. I will tattoo it on my forehead.
 
  There is, of course, a simpler (but not necessarily easier :p) solution:
  change your name to match your nickname!
 
  
  
   ___
   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
 
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Regards,
 Austin

 ___
 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] strict version of Haskell - does it exist?

2012-02-01 Thread Ryan Newton


 Even though advertised as parallel programming tools, parMap and other
 functions that work in parallel over *sequential* access data
 structures (i.e. linked lists.) We want flat, strict, unpacked data
 structures to get good performance out of parallel algorithms. DPH,
 repa, and even vector show the way.


You would think that tree data structures would be good here as well.  For
example, monad-par includes a definition of an append-based AList (like
Guy Steele argues for).

But alas that turns out to be much harder to get working well.  For most
algorithms Vectors so often end up better.

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


Re: [Haskell-cafe] Module name space question

2011-12-12 Thread Ryan Newton
I don't know why Hoogle didn't find one of the packages.  I've often
wondered about this related question:

   * Is there a place to browse the union of all namespaces in all hackage
packages?

This would show the global Haskell/Hackage  namespace as it currently
stands and I think would be useful for a number of different purposes.

  -Ryan

On Mon, Dec 12, 2011 at 8:10 AM, Yitzchak Gale g...@sefer.org wrote:

 Christoph Breitkopf wrote:
  If anyone wants to look at the code in question:
  http://www.chr-breitkopf.de/comp/IntervalMap

 Looks interesting, thanks!

  3. Are there more wothwile operations on this data structure?

 Have a look at ranged sets:

 http://hackage.haskell.org/package/Ranged-sets

 Perhaps that will inspire you with some more ideas.

 Regards,
 Yitz

 ___
 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


[Haskell-cafe] Tool to brute-force test against hackage libraries to determine lower bounds?

2011-11-09 Thread Ryan Newton
I don't know about you, but I personally haven't found the time to cast
back in time for each of my package's dependencies to find a true lower
bound version.

Do we have any tools that would do the following?

   - ask Hackage for the available versions of package foo
   - use cabal-dev to build your package against foo-X.Y.Z forall {X,Y,Z}
   (but leaving other packages unconstrained)
   - report successes and failures, including last failure before the
   present version (and therefore lower bound, exclusive)

Johan, would it make any sense to extend your Jenkins setup to do this?

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


Re: [Haskell-cafe] Tool to brute-force test against hackage libraries to determine lower bounds?

2011-11-09 Thread Ryan Newton

 What about dependency interactions? If you depend on foo and bar there
 might be versions of foo and bar that don't build together that you might
 not discover by varying their versions independently.


Indeed.  But assuming for a moment that foo  bar have correctly specified
their own dependency bounds won't the constraint solver make up for some of
this deficiency?  I.e. you specify too low a version for foo but the range
gets further restricted by cabal's constraint solver and you end up ok?

I proposed the greedy approach just because I think given current compile
times it wouldn't be possible to try all combinations ;-). **

Though I suppose a decent heuristic would compute the total # of
combinations and -- if it is manageable -- do them all.  If not, either
resort to greedy/independent testing or bring out the more complex
strategies for sampling the version space...

But enough idle speculation!  I know people have studied this problem in
earnest and I haven't read any of that.

-Ryan

** P.S. If one could carefully control how the compiler output is managed I
guess you could cut way down on the number of actual module compilations to
explore a given set of combinations.  (A particular module should only need
to be compiled once for each unique combination of its own dependencies
present in the set of combinations being examined, right?)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The type class wilderness + Separating instances and implementations into separate packages

2011-11-03 Thread Ryan Newton
 I think the best option at the moment is to break out type classes in their 
 own packages. That's what I did with hashable.
Indeed!  I greatly believe in this mantra now.  Really, my point was
only this banal one -- packages with only interfaces in them have no
dependencies and are much less likely than implementation packages to
break when the GHC version changes.

 Aside: The problem with collections is that we don't have the programming
 language means to do this well yet (although soon!). The issue is that we
 want to declare a type class where the context of the methods depends on the
 instance e.g.
 class MapLike m where
     type Ctx :: Context  -- Can't do this today!
     insert Ctx = k - v - m - m
 Java et all cheats in their container hierarchy by doing unsafe casts (i.e.
 they never solved this problem)!

Ah, interesting.  Is there a proposal to do this?  While we need to
avoid an infinite regress of generalization and abstraction (type
programming = kind programming?, etc) -- it does seem like class
contexts on types and type class instances themselves would be nice to
have *some* control over.  (In the above message, for example I was
having trouble due to not being able to hide instances on import.)

 I would hope that we could get all the important interfaces into the Haskell
 Platform eventually (and have all packages there use them).

+1!

Cheers,
  -Ryan

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


Re: [Haskell-cafe] Message

2011-11-03 Thread Ryan Newton
 I have interfaced Erlang and Haskell... And delivered it as a product.  I
 just came up with a dead-simple text based communication syntax from Erlang
 to Haskell that was very easily testable.  It allowed for complete isolation

Interesting.  I can't imagine there are too many people who have done
this.  So I must ask -- given the explicit attempt to imitate Erlang
in recent CloudHaskell work, does that come close to giving you
everything you would have wanted in this app?

(Hot code update being the big missing piece.)

Cheers,
  -Ryan

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


[Haskell-cafe] The type class wilderness + Separating instances and implementations into separate packages

2011-11-02 Thread Ryan Newton
What is the right interface for a queue?  What is the right interface for a
random number generator?

I don't know, but in both cases you will find many packages on hackage
offering different takes on the matter.  In fact, there is a wilderness of
alternative interfaces.  We've had various discussions on this list about
the number of alternative packages.

I'm fine with lots of packages, but I think it would be great if not every
package introduced a new interface as well as a new implementation.  If we
could agree as a community on common interfaces to use for some basics,
that would probably go a long way towards taming the type class wilderness.
 People have mentioned this problem before with respect to Collections
generally.

One basic part of reaching such a goal is separating interface from
implementation.  I ran into the following problems just  in the last 24
hours.  In both cases I wanted to use a type class, but didn't want to
depend on the whole package it lived in:

   - I wanted to use the Benchmarkable class in Criterion in my package.
(Criterion deserving to be a standard package.)  But I can't get that
   typeclass without depending on the whole Criterion package, which has
   several dependencies.  And in fact on the machine I was on at the time some
   of those dependencies were broken, so I decided not to use Benchmarkable.
   - I wanted to use, or at least support, an existing class for Queues.  I
   found the following:

http://hackage.haskell.org/packages/archive/queuelike/1.0.9/doc/html/Data-MQueue-Class.html

I have no idea who uses this package.  But because this package (like most
packages) includes the implementation along with the interface it
introduces additional dependency liabilities.  In this case it failed to
build on GHC 7.2 so I quickly gave up on supporting that TypeClass.

How can we enumerate packages that at least purport to provide standard
interfaces that you should both use and pick up to implement?  On a Wiki
page?

  -Ryan

P.S. I'm working on mutable concurrent Deques right now and am trying to
follow my own prescription above by creating an abstract interface in a
separate package.  See below if you would like to offer feedback on that
interface.

--

My ultimate goal is an abstract-deque parameterizable interface that
abstracts over bounded/unbounded, concurrent/non-concurrent, single, 1.5,
and double-ended queues, which would include both, say, Michael  Scott
linked queues and the Chase-Lev work-stealing deques.  An aggregated queue
package could use type families to dispatch to the best available queue
implementation for a given configuration.

I've got a couple drafts of how this might work.  They're in different
branches here:


https://github.com/rrnewton/haskell-lockfree-queue/blob/master/AbstractDeque/Data/Concurrent/Deque/Class.hs

https://github.com/rrnewton/haskell-lockfree-queue/blob/one-type-class/AbstractDeque/Data/Concurrent/Deque/Class.hs

One of them uses an associated data type family, the other an unassociated
one.  The type family has a bunch (six) phantom type parameters, and
the unassociated one allows hiding those parameters at the expense of
introducing more type classes.

MegaQueue.hs will be used to aggregate together different queue
implementations.  The end result is that someone can create a new queue by
setting all the switches on the type, as follows:

 test = do
 q :: Deque NT T SingleEnd SingleEnd Bound Safe Int - newQ
 pushL q 33
 x - tryPopR q
 print x
 return q

With those settings, requiring only single-ended rather than double-ended
queues, the above code can use the LinkedQueue (Michael and
Scott) implementation included in that repo.
   That little test, by the way, segfaults for me on Mac OS under GHC 7.2.1
even WITHOUT using casMutVar# (It's using Data.CAS.Fake presently.)  I'll
file a bug report after I sanity check it some more.

Disregarding that... the big problem in this case is the* inability to
create overlapping type family instances.  *

In this case what we dearly WANT to do is specialize some subset of the
64-mode configuration space and then have a fallback.  You can take a
look at my struggling in MegaDeque.  Both of my approaches require
specifying explicitly the modes that you don't cover.

Worse, we may want to specialize on element type as well.  For example, for
simple scalar types (or even Storable types) it may be desirable to use
something foreign, like TBB queues.  But in that case, there's no way to
enumerate the types NOT specialized.  As far as I know there is no way for
type families to accomplish this (specialize, say Int, and have a
fallback for everything else).  In general, is there a recognized
work-around for this?  For example, is this a place where using functional
dependencies instead might do the trick?

Also, there are some software-engineering issues here with respect to* where
to put the instances*.  It would be nice to 

Re: [Haskell-cafe] Amazon AWS storage best to use with Haskell?

2011-10-31 Thread Ryan Newton
For distributed execution you can look at the recent work on CloudHaskell:

   https://github.com/jepst/CloudHaskell
   http://groups.google.com/group/cloudhaskell

As for a programming model -- Philip Trinder et. al have a version of
monad-par that works in a distributed way over CloudHaskell, likewise
CloudHaskell itself provides a simple Task layer.

For a NOSQL layer -- I'm looking for the answer to that same question
myself!  We've been experimenting with Cassandra (used via the hscassandra
package based in turn on cassandra-thrift).  Already it's clear that there
are many areas that need work.  The Haskell code generated by Thrift itself
has a lot of room for improvement (for the intrepid hacker: cycles there
would be well-spent).
   We haven't tried CouchDB yet.  Please keep us posted on what you find.

I don't know if any one has a clean way for hooking a simple Haskell-ish
interface (e.g. Data.Map) up to a persistence layer.  But it seems like
there have been a bunch of papers on database supported haskell and the
like.  One of them must have solved this!

http://hackage.haskell.org/package/DSH

Cheers,
  -Ryan


On Mon, Oct 31, 2011 at 4:53 PM, dokondr doko...@gmail.com wrote:

 On Mon, Oct 31, 2011 at 6:50 PM, John Lenz l...@math.uic.edu wrote:

 CouchDB works great, although I decided to go with SimpleDB since then it
 is amazon's problem to scale and allocate disk and so forth, which I like
 better.  For couchdb, you can use my package couchdb-enumerator on hackage.


 Regarding CouchDB. So far I have my records keyed by Id and stored in
 Data.Map which I serialize to  text file. Using Data.Map functions I do
 many operations with these records including mapping functions over keys
 and values, accumulation, lookup, intersection, union etc.
 When I move this data to CouchDB and start using couchdb-enumerator to
 work with it, how natural will it be to implement all these functions that
 I use from Data.Map?
 Or maybe it makes more sense to store my serialized Data.Map as a blob in
 CouchDB? And do not use views or similar CouchDB / SimpleDB interfaces at
 all?  Just retrieve necessary blob and deserialize it to Data.Map, update
 and then store modified blob to CouchDB again?

 It would be great if somebody had time to implement Data.List, Data.Map,
 etc on top of generic  NoSQL DB interface with specific instances for
 CouchDB, SimpleDB, etc.

 ___
 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] Amazon AWS storage best to use with Haskell?

2011-10-31 Thread Ryan Newton

  Any example code of using hscassandra package would really help!


I'll ask my student.  We may have some simple examples.

Also, I have no idea as to their quality but I was pleasantly surprised to
find three different amazon related packages on Hackage (simply by
searching for the word Amazon in the package list).

   http://hackage.haskell.org/package/hS3
   http://hackage.haskell.org/package/hSimpleDB
   http://hackage.haskell.org/package/aws

It would be great to know if these work.

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


Re: [Haskell-cafe] What is the status of GPU-accelerated Haskell?

2011-10-28 Thread Ryan Newton
There are CUDA bindings:

   http://hackage.haskell.org/package/cuda

And that is what the higher-level GPU-programming package, Accelerate, is
based on:

   http://hackage.haskell.org/package/accelerate



On Thu, Oct 27, 2011 at 4:04 PM, serialhex serial...@gmail.com wrote:

 Hi, there is an OpenCL / Haskell thread floating around the ML, mostly it's
 a dew ppl talking about merging the 5 (or so) bindings to the OpenCL api and
 getting spiffy multi-threaded haskell-awesomeness out of that.  i think they
 are discussing the benefits/drawbacks of a pure-ish api conversion or a more
 haskell-ish conversion, or some combination thereof.

 either way, it exsists, and it's happening (though i'm not so sure about
 CUDA bindings...  but OpenCL will work on Nvidia  ATI cards the same)

 hex



 On Thu, Oct 27, 2011 at 3:45 PM, Rafael Gustavo da Cunha Pereira Pinto 
 rafaelgcpp.li...@gmail.com wrote:



 Hi folks,

 I just bought a NVidia Fermi-based card and remembered reading a few
 months (years?) ago about some effort to accelerate array processing in
 Haskell using GPUs.

 How is this going on? Any progresses? Do we have GPU based DPH already?
 (the last one is a joke...)

 I keep thinking on the advantages of such GPU data processing on the
 signal processing field.

 Best regards,

 Rafael Gustavo da Cunha Pereira Pinto


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




 --
 *  my blog is cooler than yours: http://serialhex.github.com
 *  The wise man said: Never argue with an idiot. They bring you down to
 their level and beat you with experience.
 *  As a programmer, it is your job to put yourself out of business. What
 you do today can be automated tomorrow. ~Doug McIlroy
 ---
 CFO: “What happens if we train people and they leave?”
 CTO: “What if we don’t and they stay?”

 ___
 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


[Haskell-cafe] Who is working on high performance threadsafe mutable data structures in Haskell?

2011-10-27 Thread Ryan Newton
Hello cafe,

In the context of the monad-par project we're just getting to the point of
trying to replace our work stealing Deque's with something more efficient
(in Haskell).

Based a quick perusal of Hackage there does not seem to be a lot of work in
this area.  Of course, for Haskell the importance of this topic may be
diminished relative to pure data structures, but for doing systems-level
work like monad par good concurrent data structures are also very important.

We are about to embark on some work to fix this problem for monad-par 
Deques, but if there are others working in this vicinity it would be nice to
team up.
   We are going to try both pure Haskell approaches using the new casMutVar#
primop as well as wrapping foreign data structures such as those provided by
TBB.  There are a whole bunch of issues with the latter -- see Appendix A
and help me out if you know how to do this.

My first goal is to get a parameterizable deque interface, implementation,
and benchmarks that makes it possible to express  variations of queues
including:

   - Double, single, and 1.5-ended (e.g. both ends can be RW or only R or W)
   - Threadsafe or single-threaded on both ends
   - Bounded or unbounded

If you require that at least the left-end support Write and the right
end support Read (excluding, for example stacks), that leaves a
configuration space of 32 options.  Some of these 32 options have much
better algorithms than others, but a general algorithm (such as Michael 
Scott queues) could satisfy all of them while leaving room to improve.
 The TBB guys have considered making their concurrent_queus configurable to
this extent but haven't gotten around to it.

Thanks,
  -Ryan


Appendix A: Using foreign data structures with Haskell


It's easy to call foreign code in Haskell, but how to use a foreign data
structure to store polymorphic Haskell values?

For example we would want a TBB concurrent_queue to store words representing
pointers into the Haskell heap.  We would need, for example:

   - (1) to pin arbitrary objects by making StablePtrs
   - (2) to communicate those to a foreign enqueue operation
   - (3) to unpin objects when the pointer is removed from a foreign
   structure (or use a reference count to determine when to unpin/free the
   StablePtr)

I don't have any experience here and would appreciate hearing from anyone
who does.  Is this a non-starter?  Will the overheads introduced by all the
StablePtr ops destroy any gains from using an efficient data structure?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Package documentation complaints -- and a suggestion

2011-10-24 Thread Ryan Newton

 Good point. On the other hand, nobody points package authors to the
 Debian documentation (and Debian also has review for newly uploaded
 packages, as far as I know).


Re: review process -- Perhaps there would be a use for a review process
somewhere between haskell-platform and the unwashed masses?

HP covers a very small percentage of packages, but a larger percentage could
probably pass some kind of review akin to the debian process.  And it would
be a good forcing function to get people to do the things they don't get
around to

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


Re: [Haskell-cafe] Best bit LIST data structure

2011-10-10 Thread Ryan Newton
On Sun, Oct 9, 2011 at 12:11 PM, Roman Beslik ber...@ukr.net wrote:

 Yes, if you do not use high-level concepts and optimize everything by hand,
 it requires a lot of testing. :)


There are probably more constructive, jibe-free ways to frame this
suggestion...

Regarding testing:  my preference for using a preexisting solution is a
product of 18 years of programming in Scheme without a large base of shared
infrastructure -- I've seen way too much roll your own X leading to
trouble.

Regarding high-performance data-structures in Haskell: I wish high-level
concepts were sufficient for their optimization.  But if you look at all the
tricks played by, for example, Johan Tibell and Greg Collins in their
excellent hashmaps and hashtables libraries, that, alas, seems not to be the
case yet.  GHC is in a good position to do inlining and specialization
(making the world safe for type classes), but it can't add unpack and
strictness annotations, nor can it change data representations themselves.

For example, to answer Yves question:

I fail to understand. Why not just:
  data BitList b = Nil | BitList Int b (BitList b)
 ??


That was a data structure unrolling to optimize the memory representation
in the common case (64 bits).  Starting with:

 type I = Int64 -- or whatever
 data BitList = Nil | BL Int I BitList

The recursive datatype can be inlined (once):

 data BitList = Nil | BL  Int I (Nil | BL Int I BitList) *-- not real syntax
*
 data BitList = Nil | BL2 Int I Nil | BL3 Int I Int I BitList* -- distribute
*
 data BitList = Nil | BL2 Int I | BL3 Int I Int I BitList *-- prune Nil*

This unrolled data structure has two advantages.  It can directly represent
the common case 64 bits with one object, and it can use half the tail
pointers for longer lists.  GHC could conceivably transform code
automatically to enable this unrolling (but it can't now).

However, there are some further observations that really require a human.
Because we are using that extra Int to track the bit position inside the I
the Nil case is redundant -- BL2 0 0 can represent empty.  Further one of
the Ints in the BL3 case is always 64 (sizeof I) and needn't be
represented.  That gives us:

 data BitList = BL2 Int I | BL3 Int I I BitList *-- prune Nil*

Which is pretty much what I used.  Actually, I skipped the double wide
second case because I was really only worried about simplifying the
representation for shorter lists and that would indeed complicate the code.

 data *(Bits b) =* BitList b

FYI, in the bit of code I sent I didn't generalize over the Bits class
because it's really an implementation detail what size chunk is used (just
like in Lazy ByteStrings).  I didn't want to pollute the interface.  That
said, the code should certainly be CSEd to make the 64/Int64 choice
swappable.

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


Re: [Haskell-cafe] Best bit LIST data structure

2011-10-09 Thread Ryan Newton
Yep, it is simple.  But I prefer to only use well-tested data structure
libraries where I can!  Here's an example simple implementation (partial --
missing some common functions):


module Data.BitList
  ( BitList
  , cons, head, tail, empty
  , pack, unpack, length, drop
  )
where

import Data.Int
import Data.Bits
import Prelude as P hiding (head,tail,drop,length)
import qualified Data.List as L
import Test.HUnit

data BitList = One  {-# UNPACK #-} !Int {-# UNPACK #-} !Int64
 | More {-# UNPACK #-} !Int {-# UNPACK #-} !Int64 BitList

instance Show BitList where
 show bl = BitList  ++ show (map (\b - case b of True - '1'; False -
'0') (unpack bl))
-- show bl = pack  ++ show (unpack bl)

empty :: BitList
empty = One 0 0

cons :: Bool - BitList - BitList
cons True  x@(One  64 _ )   = More 1 1 x
cons False x@(One  64 _ )   = More 1 0 x
cons True  x@(More 64 bv _) = More 1 1 x
cons False x@(More 64 bv _) = More 1 0 x
cons True(One   i bv)   = One  (i+1) (bv `setBit` i)
cons False   (One   i bv)   = One  (i+1) (bv   )
cons True(More  i bv r) = More (i+1) (bv `setBit` i) r
cons False   (More  i bv r) = More (i+1) (bv   ) r

-- TODO: May consider (More 0 _ _) representation to reduce extra
-- allocation when size of the BitList is fluctuating back and forth.

head :: BitList - Bool
head (One  0 _   ) = error tried to take head of an empty BitList
head (More 0 _  r) = error BitList: data structure invariant failure!
head (One  i bv  ) = bv `testBit` (i-1)
head (More i bv r) = bv `testBit` (i-1)

tail :: BitList - BitList
tail (One  0 _   ) = error tried to take the tail of an empty BitList
tail (One  i bv  ) = One  (i-1) bv
tail (More 1 bv r) = r
tail (More i bv r) = More (i-1) bv r

pack :: [Bool] - BitList
pack  []   = One 0 0
pack (h:t) = cons h (pack t)

unpack :: BitList - [Bool]
unpack (One 0 _) = []
unpack (One i bv)= (bv `testBit` (i-1)) : unpack (One (i-1) bv)
unpack (More 0 _ r)  =  unpack r
unpack (More i bv r) = (bv `testBit` (i-1)) : unpack (More (i-1) bv r)

drop :: Int - BitList - BitList
drop 0 bl   = bl
drop n bl | n = 64 = case bl of
One _ _- error drop: not enough elements in BitList
More i _ r - drop (n-i) r
drop n bl = case bl of
  One i  bv   - One  (i-n) bv
  More i bv r - More (i-n) bv r

length :: BitList - Int
length (One  i _)   = i
length (More i _ r) = i + length r


-- TODO: index, take, etc

-- TODO: functor instance, etc.



-- Testing:

t1 = pack (L.concat$ L.replicate 10 [True,False,True])

t2 = L.length $ unpack $ pack $ replicate 1000 True

t3 = pack $ replicate 1000 True
t4 = drop 500 t3
p3 = L.and (unpack t3)
p4 = L.and (unpack t4)

t5 = iterate tail t4 !! 250
t5a = length t5
t5b = L.length (unpack t5)

tests :: Test
tests =
  TestList
[
  show t1 ~=? BitList \101101101101101101101101101101\
, t2  ~=? 1000
, t5a ~=? 250
, t5b ~=? 250
, p3  ~=? True
, p4  ~=? True
]

-- TODO: QuickCheck



On Sun, Oct 9, 2011 at 7:50 AM, Roman Beslik ber...@ukr.net wrote:

  I am not aware of such a library, but IMHO this code will be very simple.
  data Bits b = BitList b = BitList Int {- number of used bits in the next
 component -} b [b]
 Write an isomorphism between @BitList b@ and @ListStep (BitList b)@
 where
  data ListStep e rc = Nil | Cons e rc


 On 07.10.11 17:52, Ryan Newton wrote:

 Hi Cafe,

 We are lucky to have a plethora of data structures out there.  But it does
 make choosing one off hackage difficult at times.  In this case I'm *not*
 looking for a O(1) access bit vector (Data.Vector.Unboxed seems to be the
 choice there), but an efficient representation for a list of bits
 (cons,head,tail).

 Let's say that you want to represent tree indices as you walk down a binary
 tree.  [Bool] is a simple choice, you only add to the front of the list (0/1
 = Left/Right), sharing the tails.  But [Bool] is quite space inefficient.

 Something like [Int] would allow packing the bits more efficiently.  A Lazy
 ByteString could amortize the space overhead even more... but in both cases
 there's a tiny bit of work to do in wrapping those structures for per-bit
 access.  That's probably the right thing but I wanted to check to see if
 there's something else recommended, perhaps more off-the-shelf.

 What about just using the Data.Bits instance of Integer?  Well, presently,
 the setBit instance for very large integers creates a whole new integer,
 shifts, and xors:

 http://haskell.org/ghc/docs/latest/html/libraries/base/src/Data-Bits.html#setBit
 (I don't know if it's possible to do better.  From quick googling GMP seems
 to use an array of limbs rather than a chunked list, so maybe there's no
 way to treat large Integers as a list and update only the front...)

 Advice appreciated!

 Thanks,
   -Ryan


 ___
 Haskell-Cafe mailing

[Haskell-cafe] Best bit LIST data structure

2011-10-07 Thread Ryan Newton
Hi Cafe,

We are lucky to have a plethora of data structures out there.  But it does
make choosing one off hackage difficult at times.  In this case I'm *not*
looking for a O(1) access bit vector (Data.Vector.Unboxed seems to be the
choice there), but an efficient representation for a list of bits
(cons,head,tail).

Let's say that you want to represent tree indices as you walk down a binary
tree.  [Bool] is a simple choice, you only add to the front of the list (0/1
= Left/Right), sharing the tails.  But [Bool] is quite space inefficient.

Something like [Int] would allow packing the bits more efficiently.  A Lazy
ByteString could amortize the space overhead even more... but in both cases
there's a tiny bit of work to do in wrapping those structures for per-bit
access.  That's probably the right thing but I wanted to check to see if
there's something else recommended, perhaps more off-the-shelf.

What about just using the Data.Bits instance of Integer?  Well, presently,
the setBit instance for very large integers creates a whole new integer,
shifts, and xors:

http://haskell.org/ghc/docs/latest/html/libraries/base/src/Data-Bits.html#setBit
(I don't know if it's possible to do better.  From quick googling GMP seems
to use an array of limbs rather than a chunked list, so maybe there's no
way to treat large Integers as a list and update only the front...)

Advice appreciated!

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


Re: [Haskell-cafe] SMP parallelism increasing GC time dramatically

2011-10-05 Thread Ryan Newton
Hi Tom,

I think debugging this sort of problem is exactly what we need to be doing
(and making easier).  Have you tried Duncan's newest version of Threadscope
by the way?

It looks like -- completely aside from the GC time -- this program is not
scaling.  The mutator time itself, disregarding GC, isn't going down much
with parallelism (with the total mutator time increasing drastically).
 Either this is completely memory bottlenecked or there is some other kind
of bad interaction (e.g. false sharing, contention on a hot lock, etc).

My inclination would be to figure this out first before worrying about the
GC time.  Is this code that you would be able to share for debugging?

I think we need to get together some general documentation on how to debug
this kind of problem.  For example, you can get some hints as to the memory
behavior by running valgrind/cachegrind on the program.  Also, what does
top say, by the way?  Is the process using 1200% CPU?

Cheers,
  -Ryan




On Wed, Oct 5, 2011 at 2:15 PM, Tom Thorne thomas.thorn...@gmail.comwrote:

 I am having some strange performance issues when using SMP parallelism,
 that I think may be something to do with GC. Apologies for the large
 readouts below but I'm not familiar enough to know what is and isn't
 relevant!

 I have a pure function that is mapped over a list of around 10 values, and
 this happens several times for each iteration of my program. It does some
 fairly intensive calculations using hmatrix, generating intermediate
 matrices along the way. The computation is significantly more complex for
 some values, so the work done by each call is not spread equally. I did some
 profiling and it seems like the program is spending about 50% of its time in
 that function. First of all, without any attempts at parallelism, I see this
 from ./Main +RTS -s

   67,142,126,336 bytes allocated in the heap
  147,759,264 bytes copied during GC
  109,384 bytes maximum residency (58 sample(s))
  354,408 bytes maximum slop
3 MB total memory in use (0 MB lost due to fragmentation)

   Generation 0: 104551 collections, 0 parallel,  1.13s,  1.11s elapsed
   Generation 1:58 collections, 0 parallel,  0.01s,  0.01s elapsed

   Parallel GC work balance: -nan (0 / 0, ideal 1)

 MUT time (elapsed)   GC time  (elapsed)
   Task  0 (worker) :0.00s( 67.06s)   0.00s(  0.00s)
   Task  1 (worker) :0.00s( 67.09s)   0.00s(  0.00s)
   Task  2 (bound)  :   66.95s( 67.09s)   1.14s(  1.12s)

   SPARKS: 0 (0 converted, 0 pruned)

   INIT  time0.00s  (  0.00s elapsed)
   MUT   time   66.95s  ( 67.09s elapsed)
   GCtime1.14s  (  1.12s elapsed)
   EXIT  time0.00s  (  0.00s elapsed)
   Total time   68.09s  ( 68.21s elapsed)

   %GC time   1.7%  (1.6% elapsed)

   Alloc rate1,002,835,517 bytes per MUT second

   Productivity  98.3% of total user, 98.2% of total elapsed

 gc_alloc_block_sync: 0
 whitehole_spin: 0
 gen[0].sync_large_objects: 0
 gen[1].sync_large_objects: 0

 This looks ok to me...

 Then if I try to use Control.Parallel to parallelise my code, simpy
 replacing a map with parMap (rdeepseq), on a 12 core machine using +RTS -N12
 -s I get this:

   66,065,148,144 bytes allocated in the heap
  197,202,056 bytes copied during GC
  181,312 bytes maximum residency (251 sample(s))
  387,240 bytes maximum slop
   12 MB total memory in use (3 MB lost due to fragmentation)

   Generation 0: 37592 collections, 37591 parallel, 245.32s, 26.67s elapsed
   Generation 1:   251 collections,   251 parallel,  3.12s,  0.33s elapsed

   Parallel GC work balance: 2.41 (24219609 / 10058220, ideal 12)

 MUT time (elapsed)   GC time  (elapsed)
   Task  0 (worker) :0.00s(  0.00s)   0.00s(  0.00s)
   Task  1 (worker) :0.00s(  0.00s)   0.00s(  0.00s)
   Task  2 (worker) :0.00s( 17.97s)   0.00s(  0.00s)
   Task  3 (worker) :0.00s( 19.35s)   0.00s(  0.00s)
   Task  4 (worker) :0.00s( 40.28s)   0.00s(  0.00s)
   Task  5 (worker) :0.00s( 45.08s)   0.00s(  0.00s)
   Task  6 (worker) :0.00s( 47.06s)   0.00s(  0.00s)
   Task  7 (worker) :   18.30s( 49.73s)  16.24s(  1.71s)
   Task  8 (worker) :0.00s( 51.22s)   0.00s(  0.00s)
   Task  9 (worker) :0.00s( 53.75s)   0.00s(  0.00s)
   Task 10 (worker) :0.00s( 54.17s)   0.00s(  0.00s)
   Task 11 (worker) :5.65s( 54.30s)   0.70s(  0.08s)
   Task 12 (worker) :0.00s( 54.41s)   0.41s(  0.04s)
   Task 13 (worker) :4.34s( 54.58s)   4.50s(  0.48s)
   Task 14 (worker) :5.82s( 54.76s)   5.91s(  0.64s)
   Task 15 (worker) :6.50s( 55.01s)   3.37s(  0.38s)
   Task 16 (worker) :7.60s( 55.21s)   8.56s(  0.94s)
   Task 

Re: [Haskell-cafe] DSL for data definition (e.g. compiling Haskell type defs into Google's protocol buffers type defs)

2011-10-04 Thread Ryan Newton
An interesting and semi-related project was just presented at ICFP by
Kathleen Fisher.  It's called Forest and uses template haskell to create
schema's for FileStores from Haskell definitions.  But they're not
plain-old-haskell type definitions...

  -Ryan


On Tue, Oct 4, 2011 at 12:11 PM, Edward Z. Yang ezy...@mit.edu wrote:

 Just making sure: have you looked at the Data.Data module yet?

 Edward

 Excerpts from Karel Gardas's message of Tue Oct 04 12:02:34 -0400 2011:
 
  Hello,
 
  I'm trying to find out if it's possible to use Haskell data type
  definition capability to define types and compile defined types into
  other languages, for example into Google's protocol buffers data
  definition language. So basically speaking I'm thinking about using
  Haskell sub-set as a data-definition DSL together with some functions
  which will generate some code based on supplied defined data types. My
  idea is:
 
  data Person = Person {
   id :: Int
   , name :: String
   , email :: Maybe String
   }
   deriving (Show, Data, Typeable)
 
  emit_proto Person 1
 
  where emit_proto is function which will translate Person data type
  definition into Google's proto language (the 1 is index from which start
  to index type's fields) by traversing data type definition and
  translating all its children plus do some header/footer generation etc:
 
  message Person {
 required int32 id = 1;
 required string name = 2;
 optional string email = 3;
  }
 
  I've looked for something like that and found SYB papers which works on
  top of data instance (i.e. actual data, not data type). I also found
  JSON lib which again works on top of data and not data type. I've tried
  to look into Data.Typetable etc, but have not found function which will
  print data type's field name and field type name (although JSON lib
  seems to use field name for JSON generation so I'll need to investigate
  this more). I've tested `typeOf' function and it's quite useful, but its
  limitation is that it's not working on ADT name:
 
  data Color = RED|GREEN|BLUE
 
  *Main typeOf Color
 
  interactive:1:8: Not in scope: data constructor `Color'
 
  *Main typeOf RED
  Main.Color
 
  and I would need that in order to translate Color defined above into
  enum like:
 
  enum Color {
 RED = 0;
 GREEN = 1;
 BLUE = 2;
  }
 
 
  My question is: do you think I'm looking into good direction (i.e.
  Data/Typeable) or do you think I'll need to use something different for
  data definition DSL (Template Haskell?, or impossible in Haskell so
  write my own language with full parser? etc?)
 
  Thanks for any idea or opinion on this!
  Karel
 

 ___
 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] Package descriptions on hackage

2011-09-12 Thread Ryan Newton
On Sun, Sep 11, 2011 at 1:14 PM, wren ng thornton w...@freegeek.org wrote:

 On 9/11/11 6:37 AM, Neil Mitchell wrote:

 Why not email the maintainers of packages you think need a better
 description - ideally giving suggestions? I'd welcome that for any of
 my packages.


 +1.


+1

Actually this thread itself is helpful.  It made me cringe and realize I was
guilty.  In my/our case I think we just overlooked it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] why is Random in System?

2011-08-19 Thread Ryan Newton
 Yep, but don't conflate determinism with splitting. In the imperative
 world, you normally know how many CPUs you have, so you initialize one PRNG
 per CPU, and simply go from there; there's no need for splitting. In the
 parallel community, people are going out of their way to *avoid*
  splitting.


I'm having trouble thinking of scenarios where per-CPU does the trick.  Do
you mean one per pthread rather than one per CPU?

In the Cilk case, you've got to deal with work stealing of course.  So you
want rand() to generate a result that is determined by the current
stack-frame's position in the binary-tree of spawns.  In the work I was
referring to:


http://groups.csail.mit.edu/sct/wiki/index.php?title=Other_Projects#Deterministic_Parallel_Random-Number_Generation

... they try a bunch of different methods and I can't remember if any of
them split the RNG eagerly as they go down the spawn tree or if they just
record the tree-index on the way down and then read it out when they
generated randoms.  (I think the latter.)

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


Re: [Haskell-cafe] why is Random in System?

2011-08-17 Thread Ryan Newton
Hi all,

I'm the maintainer of random.  If people could decide on what the
alternative name would be we could put it through the library proposal
process.  It seems that one problem at this moment is the lack of a single,
clear right answer.  Replacing one debatable not-quite-right choice with
another may not be satisfying ;-).

Also, what Thomas says is right.  The current implementation is SLOW and
WEAK, which would not seem to make a good default implementation.  The goal
is to replace it with something better so that the default random package is
strong in at least one dimension.  I think this is important because I
imagine many people use the default package, for example because they don't
want to scour hackage and try all the alternatives.

My proposal for this has been to use AES based crypto-prng.  I think that is
fast enough (i.e. faster than what's currently there), very strong, and
splittable.  New Intel and AMD hardware has hardware support for AES which
makes it even faster.  The intel-aes package provides this functionality,
with and without hardware support.  But there's work left to do in terms of
testing, making sure its cross platform, etc.  Anyone who's interested in
helping (especially with Windows support) would be warmly welcomed!

Cheers,
  -Ryan



On Wed, Aug 17, 2011 at 4:46 AM, Ertugrul Soeylemez e...@ertes.de wrote:

 Brandon Allbery allber...@gmail.com wrote:

I've noticed there's a convention to put modules having to deal
with randomness into System.Random.  I thought System was for OS
interaction?  Granted getting a random seed usually means going to
the OS, but isn't the rest of it, like generating random
sequences, distributions, selecting based on probability,
shuffling, etc. all non-OS related algorithms?
  
   System definitely does seem like an odd choice.  In most cases the
   only interaction any PRNG, even when accessed via the FFI, has with
   the system is - as you say - to get an initial seed value for a
   global instance.
 
  I'd be tempted to guess that the whole reason it's under System is the
  IO component.

 That's not really valid, is it?  After all the new 'time' package is
 also stationed under the Data tree, and it has a similarly large IO
 component.  I have to say, it seems very intuitive to me to look for it
 under Data, even though I'm not sure why.  Probably I'm just used to it.
 Time has a strong connection to the operating system and the hardware,
 so it could just as well go into the System tree.  For
 (non-cryptographic) randomness however we are dealing with numerical
 data, for which the connection to the system is mere convenience, so I
 wouldn't mind finding it under Data at all.


 Greets,
 Ertugrul


 --
 nightmare = unsafePerformIO (getWrongWife = sex)
 http://ertes.de/



 ___
 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] why is Random in System?

2011-08-17 Thread Ryan Newton
The problem with Mersenne twister is that it doesn't split well.  The main
reason for crypto prng in this package would not be to advertise to people
that System.Random can be used for security-related apps *but to make
splitting reasonably safe*.  It's not good enough to have a known-bad
generator under splitting provided as the default.  And I think we need
splitting, especially as more Haskell programs become parallel.  Would it
address your concerns to not mention the crypto nature of the standard
implementation in the System.Random documentation?

I think there's also a reasonable argument to lean towards *correctness* over
performance in Haskell's defaults.  For example, unconstrained Num bindings
default to Integer and likewise random numbers could be as strong as
possible by default, and those looking for raw rands/sec throughput could
make other informed choices.

I had thought that maybe we could bifurcate the stdgen concept into a fast
and a strong version, which could be say Mersenne Twister and AES
respectively.  But, again, the problem comes if the fast version is expected
to be splittable as well.

With SplittableGen factored out from RandomGen I suppose it would be
possible for the fast version to NOT offer splitting.  However, Mersenne
Twister is best used with an imperative interface, you can see the tension
in the pure version of the mersenne package on hackage:

  http://hackage.haskell.org/package/mersenne-random-pure64-0.2.0.3

Please also see Burton Smith's comments below in response to my proposal to
offer a MT + AES combination.

Best,
  -Ryan

-- Forwarded message --
From: Burton Smith burt...@microsoft.com
Date: Tue, Jun 28, 2011 at 1:28 PM
Subject: RE: AESNI-based splittable random number generation for Haskell
To: Newton, Ryan R ryan.r.new...@intel.com

Mersenne Twister (MT)is a poor choice in my opinion.  First, the generator
state is large (2496 bytes) and it must be copied on each call to next.
 Split is worse; it will generate twice as many bytes per call as next will.

Second, I see no good way to guarantee independence of the two generators
emanating from a split.  MT is hard to initialize anyway, and giant-stepping
it to define the newly split generator (as we did back in the 80's paper) is
not only hard for an LFSR like MT but, worse yet, it doesn't work for
Haskell or other fine-grain concurrent languages because split and next will
commute.  Other tree RNGs, e.g. SPRNG, have the same commutativity issue.
 Block ciphers address this issue head-on by reducing the split independence
problem to a crypto problem.

A better choice might be some block cipher other than AES.  Two
possibilities are XTEA and RC4.  Both are in Wikipedia.  RC4 has 256 bytes
of key state, still bigger than I would like.

Another scheme is to make the number of rounds an option.  With AESNI, this
could scream.

Burton


On Wed, Aug 17, 2011 at 12:26 PM, Ertugrul Soeylemez e...@ertes.de wrote:

 Ryan Newton rrnew...@gmail.com wrote:



 Using a cryptographically strong random number generator here is
 probably a very bad idea.  Two reasons:

 Firstly while being faster than the current implementation an AES-based
 implementation will still be considerably slower than the Mersenne
 Twister algorithm.  This may or may not be true, if hardware AES support
 is there, but don't just assume that everybody has AES instructions now.
 For example I don't have them.

 Secondly there is no standard requiring that the default random number
 generator is cryptographically safe.  Changing this particular
 implementation, which is the one most people use, to a CSPRNG will make
 people take for granted that System.Random is safe to use in
 security-related products, because it would be very convenient.  This
 will render strong security products trivially weak, when compiled with
 the wrong Haskell distribution, and you will find packages with
 statements like:  We assume that you use Ryan Newton's distribution of
 the random package.

 I would rather propose the Mersenne Twister as the default random number
 generator.  You could add AES as a secondary generator for people
 requiring cryptographic strength, but then do it properly, i.e. impure,
 because most people, when reading about a PRNG with AES anywhere in
 its name, will just assume that it's a CSPRNG.


 Greets,
 Ertugrul


 --
 nightmare = unsafePerformIO (getWrongWife = sex)
 http://ertes.de/



 ___
 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] why is Random in System?

2011-08-17 Thread Ryan Newton

 The more fundamental problem is that splitting is neither well understood
 nor generally safe, and as such it should not be in the basic Random class.


Would you mind elaborating?  Splitting was not well-understood by the
original authors of System.Random; that much is in the comments.  Nor is it
well understood by me.  But I am under the impression that it is well
understood by Burton Smith and others who have worked on the topic, and that
they assure us that using AES, RNG's under any series of splits are as
strong as those generated in a linear sequence.  (And if you show otherwise,
you have a crypto paper and quite a name for yourself.)


 And I think we need splitting, especially as more Haskell programs become
 parallel.


 I do not agree here, I'm afraid.


Could you expound on this also?  The people I know in the parallelism
community seem to care a lot about deterministic PRNG in parallel programs.
 For example, the Cilk folks at MIT and Intel who I work with are *modifying
their runtime system *just to get deterministic parallel PRNG.

For example our in our Monad Par package splittable RNG will allow us to
add a variant of the monad that provides randomness and transparently routes
the state through the forks in the parallel computation, retaining the
model's determinism.

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


Re: [Haskell-cafe] Haskell Actors, Linda, publish / subscribe models?

2011-08-15 Thread Ryan Newton
It seems that the recent Cloud Haskell paper is relevant:


http://research.microsoft.com/en-us/um/people/simonpj/papers/parallel/remote.pdf

The repo is here:

   https://github.com/jepst/CloudHaskell

I haven't tried it yet myself but would like to.

Cheers,
  -Ryan


On Mon, Aug 15, 2011 at 10:32 AM, dokondr doko...@gmail.com wrote:



 On Mon, Aug 15, 2011 at 12:36 PM, Holger Reinhardt 
 hreinha...@gmail.comwrote:

 Hi,

 the actor package seems unmaintained and probably doesn't fit your needs.
 If you want to implement some kind of publish/subscribe system over the
 network, I'd suggest you take a look at ZeroMQ[1] and AMQP[2].
 AMQP is probably easier to get started with, but it requires you to set up
 a dedicated broker, which (if you have very high throughput) might become a
 bottleneck. ZeroMQ, on the other hand, allows for a more decentralized
 architecture.

 Regards,
 Holger

 [1] http://hackage.haskell.org/package/zeromq-haskell
 [2] http://hackage.haskell.org/package/amqp


 Thanks! I will try these out.
 I wish I could find something that will provide a *single* publish /
 subscribe framework to work with threads *both* in the same and separate
 address spaces.



 ___
 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


[Haskell-cafe] Type checking oddity -- maybe my own confusion

2011-07-12 Thread Ryan Newton
Hi all,

Is there something wrong with the code below?  My anticipation was that the
type of test would include the class constraint, because it uses the
Assign constructor.  But if you load this code in GHCI you can see that the
inferred type was test :: E m - E m.

Thanks,
  -Ryan


{-# LANGUAGE GADTs #-}

class AssignCap m
data PureT
data IOT
instance AssignCap IOT

data E m where
  Assign  :: AssignCap m = V - E m - E m - E m
  Varref  :: V - E m
-- ...

type V = String

-- I expected the following type but am not getting it:
-- test :: AssignCap m = E m - E m
test x =
  case x of
   Assign v e1 e2 - Assign v e1 e2
-- And this is the same:
   Assign v e1 e2 - x
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type checking oddity -- maybe my own confusion

2011-07-12 Thread Ryan Newton
Thanks, that does help.  Very clear description.

Any good ideas about how to tweak my example to do what was intended ;-)?

The desired goal was that everywhere I construct a value using the Assign
constructor, that the resulting value's type to be tainted by the AssignCap
constraint.

Actually... to go a bit further, I thought there was some way to arrange
this so that, upon GHC type-checking the case statement, it would realize
that certain cases are forbidden based on the type, and would consider the
pattern match complete without them (or issue an error if they are present).

Thanks,
  -Ryan

On Tue, Jul 12, 2011 at 11:17 AM, Dimitrios Vytiniotis 
dimit...@microsoft.com wrote:

  Hi Ryan, 

 ** **

 Think of AssignCap as an extra argument packaged up with the Assign
 constructor. When 

 you pattern match against Assign you make the AssignCap constraint **
 available** for use in

 the RHS of the pattern; so there’s no need for quantification, you already
 have the constraint

 you want packaged inside your argument. (Back in the old times when GHC did
 not implement 

 implication constraints maybe you’d get the type you say). Does that help?
 

 ** **

 Thanks

 d-

 ** **

 ** **

 *From:* haskell-cafe-boun...@haskell.org [mailto:
 haskell-cafe-boun...@haskell.org] *On Behalf Of *Ryan Newton
 *Sent:* 12 July 2011 16:02
 *To:* Haskell Cafe
 *Subject:* [Haskell-cafe] Type checking oddity -- maybe my own confusion**
 **

 ** **

 Hi all,

 ** **

 Is there something wrong with the code below?  My anticipation was that the
 type of test would include the class constraint, because it uses the
 Assign constructor.  But if you load this code in GHCI you can see that the
 inferred type was test :: E m - E m.

 ** **

 Thanks,

   -Ryan

 ** **

 ** **

 {-# LANGUAGE GADTs #-}

 ** **

 class AssignCap m 

 data PureT  

 data IOT  

 instance AssignCap IOT 

 ** **

 data E m where 

   Assign  :: AssignCap m = V - E m - E m - E m

   Varref  :: V - E m

 -- ...

 ** **

 type V = String

 ** **

 -- I expected the following type but am not getting it:

 -- test :: AssignCap m = E m - E m

 test x = 

   case x of 

Assign v e1 e2 - Assign v e1 e2

 -- And this is the same:

Assign v e1 e2 - x

 ** **

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


[Haskell-cafe] Does this library already exist? template haskell + generate/compile C code + dlopen

2011-06-08 Thread Ryan Newton
The Nikola GPU programming system has a very neat, flexible approach to how
you compile the EDSL-generated code.  You can do it dynamically, calling
nvcc at runtime, OR it can play a trick where it calls nvcc at compile time
(via template haskell) and caches the result in a string literal within the
TH-generated Haskell code.

That is a pretty cool trick IMHO.  Moreover, we can do that with any tool
that generates C code or native code, as follows:

At compile time, via Template Haskell:

   1. call tool which creates C code
   2. create temp files and call C compiler
   3. load resulting object file as a bytestring and store it as a string
   constant

Then at runtime:

   1. put bytestring back into a file
   2. call dlopen
   3. call dlsym, get FunPtr, voila!

Anyway, I was going to put together a simple library that encapsulates the
above steps.  Such a library could be used, for example, in making this
stencil compiler project http://people.csail.mit.edu/yuantang/ available
to Haskell users as well as C++ users.  (The compiler is written in Haskell
already anyway!)
   But first I thought I'd ask if this already exists.  Also, is there a
better way to do it?  In particular, is there any way to get static linking
to work, rather than the silliness with strings, tempfiles, and dlopen.

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


  1   2   >