[Haskell-cafe] Re: hamming distance allocation

2010-04-21 Thread Heinrich Apfelmus
Arnoldo Muller wrote:
 
 I believe these problems are one of the major sources of frustration for
 Haskell newbies. Things that could work in X language easily suddenly
 become problems in Haskell. When you overcome these issues then you feel
 happy again that you chose Haskell as the main programming language of your
 research project.

Well, the difference between X and Haskell is pretty much unavoidable.
If you care about space and time usage, then there is no way around
learning about lazy evaluation and Haskell's execution model.

 Is there any guide that explains more about the bad consumption pattern.
 Are there any general rules defined to avoid these issues? It helped me to
 re-read the chapter on profiling in the Real World Haskell book to sorta
 understand the problem. Is there a more detailed definition of the problem
 than in RWH?

Two of the most commonly occurring patterns are

  1) foldl' vs foldl

  2) average xs = sum xs / length xs
 vs
 average = uncurry (/) . foldl' (\(!s,!n) x - (s+x,n+1)) (0,0)

Other than that, most Haskell books offer a clear exposition of the
reduction model. For instance, there is

   Graham Hutton. Programming in Haskell, chapter 12.
   Richard Bird. Introduction to Functional Programming using Haskell
   2nd edition, chapter 7.

The wikibook contains some preliminary material, too.

   http://en.wikibooks.org/wiki/Haskell/Graph_reduction



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Re: Re: instance Eq (a - b)

2010-04-21 Thread Max Rabkin
On Wed, Apr 21, 2010 at 1:44 AM, Edward Kmett ekm...@gmail.com wrote:
 Eq doesn't state anywhere that the instances should be structural, though in
 general where possible it is a good idea, since you don't have to worry
 about whether or not functions respect your choice of setoid.

Wikipedia's definition of structural equality is an object-oriented
one, but if by structural equality you mean the natural equality on
algebraic datatypes (as derived automatically), I don't believe this
is quite the case. If the type is abstract, surely the Eq instance
need only be a quotient w.r.t. the operations defined on it. Thus, for
example, two Sets can be considered equal if they contain the same
elements, rather than having identical tree shapes (except that
Data.Set exports unsafe functions, like mapMonotonic which has an
unchecked precondition).

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


Re: [Haskell-cafe] ANN: forkable-monad 0.1

2010-04-21 Thread Limestraël
Nice initiative!

By the way, since this is a monad, I think a better place than
Control.Concurrent.Forkable would be Control.Monad.Forkable.
It's just a suggestion.



 2010/4/21 David Anderson d...@natulte.net

 Dear Haskellers,

 I'm happy, and only slightly intimidated, to announce the initial
 release of forkable-monad.

 The short version is that forkable-monad exports a replacement forkIO
 that lets you do this:

 type MyMonad = ReaderT Config (StateT Ctx IO)

 startThread :: MyMonad ThreadId
 startThread = forkIO threadMain

 threadMain :: MyMonad ()
 threadMain = forever $ liftIO $ putStrLn Painless monad stack forking!

 Note the lack of monad stack deconstruction and reconstruction to
 transport it over to the new thread. You'll find the details in the
 Haddock documentation for the module.

 forkable-monad is available:

 * On hackage: http://hackage.haskell.org/package/forkable-monad
 * Via cabal: cabal install forkable-monad
 * Source and issue tracker: http://code.google.com/p/forkable-monad/

 Feedback is of course welcome. As this is my first published Haskell
 code and Hackage upload, I expect there will be quite a bit!

 - Dave
 ___
 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] ANN: forkable-monad 0.1

2010-04-21 Thread Neil Brown

Hi,

This is quite a neat generalisation of forkIO, and something I've wanted 
in the past.


My comment would be about the MonadIO m requirement for ForkableMonad.  
I understand that conceptually it's a nice thing to have.  But 
practically, I don't think it's necessary, and could be a little 
restrictive -- I could imagine potentially having a newtype-wrapped 
monad that doesn't have a MonadIO instance, but does have a 
ForkableMonad instance.  I tried removing the MonadIO constraint, and it 
works as long as you add a Monad constraint either to the class or to 
the ReaderT and StateT instances.  That depends if you can imagine an 
instance of ForkableMonad that wasn't a Monad (an applicative 
perhaps)... probably not, especially given the name.


In short: I recommend changing MonadIO m to Monad m on the class.

I came up with this instance for ContT:

instance (ForkableMonad m) = ForkableMonad (ContT r m) where
 forkIO act = lift $ forkIO (runContT act (const $ return undefined))

I don't know if that's useful and/or correct, though.

Thanks,

Neil.

David Anderson wrote:

Dear Haskellers,

I'm happy, and only slightly intimidated, to announce the initial
release of forkable-monad.

The short version is that forkable-monad exports a replacement forkIO
that lets you do this:

type MyMonad = ReaderT Config (StateT Ctx IO)

startThread :: MyMonad ThreadId
startThread = forkIO threadMain

threadMain :: MyMonad ()
threadMain = forever $ liftIO $ putStrLn Painless monad stack forking!

Note the lack of monad stack deconstruction and reconstruction to
transport it over to the new thread. You'll find the details in the
Haddock documentation for the module.

forkable-monad is available:

* On hackage: http://hackage.haskell.org/package/forkable-monad
* Via cabal: cabal install forkable-monad
* Source and issue tracker: http://code.google.com/p/forkable-monad/

Feedback is of course welcome. As this is my first published Haskell
code and Hackage upload, I expect there will be quite a bit!

- Dave
___
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] Re: Re: instance Eq (a - b)

2010-04-21 Thread Edward Kmett
On Wed, Apr 21, 2010 at 5:25 AM, Max Rabkin max.rab...@gmail.com wrote:

 On Wed, Apr 21, 2010 at 1:44 AM, Edward Kmett ekm...@gmail.com wrote:
  Eq doesn't state anywhere that the instances should be structural, though
 in
  general where possible it is a good idea, since you don't have to worry
  about whether or not functions respect your choice of setoid.

 Wikipedia's definition of structural equality is an object-oriented
 one, but if by structural equality you mean the natural equality on
 algebraic datatypes (as derived automatically), I don't believe this
 is quite the case. If the type is abstract, surely the Eq instance
 need only be a quotient w.r.t. the operations defined on it. Thus, for
 example, two Sets can be considered equal if they contain the same
 elements, rather than having identical tree shapes (except that
 Data.Set exports unsafe functions, like mapMonotonic which has an
 unchecked precondition).


Yes. My point about why falling back on structural equality is a good idea
when possible, is that then you don't have to work so hard to make sure that
x == y =  f x == f y holds. When your equality instance isn't structural
you need to effectively prove a theorem every time you work with the
structure to avoid violating preconceptions. My post was acknowledging the
expedience of such methods.

I think we are using a lot of words to agree with one another. ;)

-Edward Kmett




 --Max

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


[Haskell-cafe] Re: ANN: forkable-monad 0.1

2010-04-21 Thread Heinrich Apfelmus
David Anderson wrote:
 Dear Haskellers,
 
 I'm happy, and only slightly intimidated, to announce the initial
 release of forkable-monad.
 
 The short version is that forkable-monad exports a replacement forkIO
 that lets you do this:
 
 type MyMonad = ReaderT Config (StateT Ctx IO)
 
 startThread :: MyMonad ThreadId
 startThread = forkIO threadMain
 
 threadMain :: MyMonad ()
 threadMain = forever $ liftIO $ putStrLn Painless monad stack forking!
 
 Note the lack of monad stack deconstruction and reconstruction to
 transport it over to the new thread. You'll find the details in the
 Haddock documentation for the module.

Nice work!

It appears to me that this is subsumed by the recent  MonadMorphIO
proposal that Anders Kaseorg came up with, though?

   http://article.gmane.org/gmane.comp.lang.haskell.libraries/12902


   fork :: MonadMorphIO m = m () - m ()
   fork m = morphIO $ \down - forkIO (down m  return ())
down (return ())


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] ANN: scan-0.1.0.4, a style scanner for Haskell sources

2010-04-21 Thread Christian Maeder
I think, I've addressed the points made by Henning and Sebastian.

(Don't forget to cabal update.)

Cheers Christian

 Dear Haskell friends,
 
 I like to announce a Haskell style scanner at
 http://hackage.haskell.org/package/scan
 
 documented under http://projects.haskell.org/style-scanner/
 
 It's best used in conjunction with hlint
 http://community.haskell.org/~ndm/hlint/
 
 and gives many suggestions regarding the file format.
 
 Feedback is welcome.
 
 Thanks Christian
 
 (Discussions should only be posted to either haskell-cafe@ or beginners@)
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bulk Synchronous Parallel

2010-04-21 Thread Gregory Crosswhite
You know, I looked into Erlang, and while it looks intriguing it isn't great 
for my purposes because I want to be able to call Fortran routines to do the 
heavy number-crunching, and Erlang doesn't have a good standard FFI like 
Haskell.

Also, I really don't want to use a dynamically typed language again if I can 
help it.  ;-)

Cheers,
Greg


On Apr 20, 2010, at 10:14 PM, Alexander Solla wrote:

 
 On Apr 20, 2010, at 11:05 AM, Jason Dusek wrote:
 
 Thanks for the link;  my ultimate interest, though, is in an architecture
 that could scale to multiple machines rather than multiple cores with shared
 memory on a single machine.  Has there been any interest and/or progress in
 making DPH run on multiple machines and other NUMA architectures?
 
 I wonder what it would take to do this.
 
 Erlang.  ;0)
 ___
 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] Bulk Synchronous Parallel

2010-04-21 Thread Aaron D. Ball
On Tue, Apr 20, 2010 at 14:05, Jason Dusek jason.du...@gmail.com wrote:

  One approach is some compiler magic that provides you with an RTS
  that can communicate with other RTSen over TCP and chunks the computation
  appropriately.

The approaches to Haskell multi-host parallelism I've seen all seem to
be (a) dead and (b) overly complicated, which I can't help but suspect
are related.

I don't need a tool that automatically figures out how to distribute
any workload in an intelligent way and handles all the communication
for me.  If I have the basic building block, which is the ability to
serialize a Haskell expression with its dependencies and read them
into another Haskell instance where I can evaluate them, I can handle
the other pieces, which are

- passing strings back and forth in whatever way is convenient
- deciding how to divide up my workload.

In the Ruby universe, DRb combines the serialization and passing
strings around job and lets me figure out how to divide up the work,
and it would be delightful if there were something similarly simple in
the Haskell world.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bulk Synchronous Parallel

2010-04-21 Thread Don Stewart
aarondball+haskell:
 On Tue, Apr 20, 2010 at 14:05, Jason Dusek jason.du...@gmail.com wrote:
 
   One approach is some compiler magic that provides you with an RTS
   that can communicate with other RTSen over TCP and chunks the computation
   appropriately.
 
 The approaches to Haskell multi-host parallelism I've seen all seem to
 be (a) dead and (b) overly complicated, which I can't help but suspect
 are related.

Eden is active, afaik,

http://www.mathematik.uni-marburg.de/~eden/ 

They just had a hackathon in St Andrews, 

http://hackage.haskell.org/trac/ghc/wiki/HackPar
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bulk Synchronous Parallel

2010-04-21 Thread Aaron D. Ball
On Wed, Apr 21, 2010 at 14:14, Don Stewart d...@galois.com wrote:

 Eden is active, afaik,

    http://www.mathematik.uni-marburg.de/~eden/

Unfortunately, Eden is one of the examples I had in mind when
referring to distributed Haskell projects as overly complicated and
[for practical purposes] dead.  Their last release available for
download was in 2006.  Their beta is available upon request, which
doesn't raise my confidence in the level of active development or
openness of the project.  From the notes here:

 They just had a hackathon in St Andrews,

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

they don't seem to have even a source code repository yet, and they
appear to be bogged down in that complexity I mentioned.  It looks
like they want to engage large, academically interesting problems and
produce papers, as opposed to producing small tools that solve simple
problems in simple ways.

The practical solution, as a result, continues to be use another language.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-21 Thread Bas van Dijk
On Tue, Apr 20, 2010 at 12:56 PM, Simon Marlow marlo...@gmail.com wrote:
 On 09/04/2010 12:14, Bertram Felgenhauer wrote:

 Simon Marlow wrote:

 On 09/04/2010 09:40, Bertram Felgenhauer wrote:

      timeout t io = mask $ \restore -  do
          result- newEmptyMVar
          tid- forkIO $ restore (io= putMVar result)
          threadDelay t `onException` killThread tid
          killThread tid
          tryTakeMVar result

 I'm worried about the case when this function is called with exceptions
 already blocked. Then 'restore' will be the identity, and exceptions
 will continue to be blocked inside the forked thread.

 You could argue that this is the responsibility of the whole chain of
 callers (who'd have to supply their own 'restore' functions that will
 have to be incorporated into the 'io' action), but that goes against
 modularity. In my opinion there's a valid demand for an escape hatch
 out of the blocked exception state for newly forked threads.

 It could be baked into a variant of the forkIO primitive, say

     forkIOwithUnblock :: ((IO a -  IO a) -  IO b) -  IO ThreadId

 I agree with the argument here.  However, forkIOWithUnblock reintroduces the
 wormhole, which is bad.

 The existing System.Timeout.timeout does it the other way around: the forked
 thread sleeps and then sends an exception to the main thread. This version
 work if exceptions are masked, regardless of whether we have
 forkIOWithUnblock.

 Arguably the fact that System.Timeout.timeout uses an exception is a visible
 part of its implementation: the caller must be prepared for this, so it is
 not unreasonable for the caller to also ensure that exceptions are unmasked.
  But it does mean that a library cannot use System.Timeout.timeout invisibly
 as part of its implementation.  If we had forkIOWithUnblock that would solve
 this case too, as the library code can use a private thread in which
 exceptions are unmasked.  This is quite a nice solution too, since a private
 ThreadId is not visible to anyone else and hence cannot be the target of any
 unexpected exceptions.

 So I think I'm convinced that forkIOWithUnblock is necessary.  It's a shame
 that it can be misused, but I don't see a way to avoid that.

 Cheers,
        Simon


I can see how forkIOWithUnblock (or forkIOWithUnnmask) can introduce a wormhole:

unmaskHack1 :: IO a - IO a
unmaskHack1 m = do
  mv - newEmptyMVar
  tid - forkIOWithUnmask $ \unmask - putMVar mv unmask
  unmask - takeMVar mv
  unmask m

We can try to solve it using a trick similar to the ST monad:

{-# LANGUAGE Rank2Types #-}

import qualified Control.Exception as Internal (unblock)
import Control.Concurrent (forkIO, ThreadId)
import Control.Concurrent.MVar (newEmptyMVar, putMVar, takeMVar)

newtype Unmask s = Unmask (forall a. IO a - IO a)

forkIOWithUnmask :: (forall s. Unmask s - IO ()) - IO ThreadId
forkIOWithUnmask f = forkIO $ f $ Unmask Internal.unblock

apply :: Unmask s - IO a - IO a
apply (Unmask f) m = f m

thisShouldWork = forkIOWithUnmask $ \unmask - apply unmask (return ())

The following shouldn't work and doesn't because we get the following
type error:

Inferred type is less polymorphic than expected. Quantified type
variable `s' is mentioned in the environment.

unmaskHack2 :: IO a - IO a
unmaskHack2 m = do
  mv - newEmptyMVar
  tid - forkIOWithUnmask $ \unmask - putMVar mv unmask
  unmask - takeMVar mv
  apply unmask m

However we can still hack the system by not returning the 'Unmask s'
but returning the IO computation 'apply unmask m' as in:

unmaskHack3 :: IO a - IO a
unmaskHack3 m = do
  mv - newEmptyMVar
  tid - forkIOWithUnmask $ \unmask - putMVar mv (apply unmask m)
  unmaskedM - takeMVar mv
  unmaskedM -- (or use join)

AFAIK the only way to solve the latter is to also parametrize IO with s:

data IO s a = ...

newtype Unmask s = Unmask (forall s2 a. IO s2 a - IO s2 a)

forkIOWithUnmask :: (forall s. Unmask s - IO s ()) - IO s2 ThreadId
forkIOWithUnmask f = forkIO $ f $ Unmask Internal.unblock

apply :: Unmask s - IO s2 a - IO s a
apply (Unmask f) m = f m

With this unmaskHack3 will give the desired type error.

Of course parameterizing IO with s is a radical change that will break
_a lot of_ code. However besides solving the latter problem the extra
s in IO also create new opportunities. Because all the advantages of
ST can now also be applied to IO. For example we can have:

scope :: (forall s. IO s a) - IO s2 a

data LocalIORef s a

newLocalIORef :: a - IO s (LocalIORef s a)
readLocalIORef :: LocalIORef s a - IO s a
writeLocalIORef :: LocalIORef s a - a - IO s a

regards,

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


Re: [Haskell-cafe] Bulk Synchronous Parallel

2010-04-21 Thread Jason Dusek
2010/4/21 Aaron D. Ball aarondb...@gmail.com:
 I don't need a tool that automatically figures out how to distribute
 any workload in an intelligent way and handles all the communication
 for me.

  You are right in general. Only if you want to rely on purity and a
  few source code annotations to get you parallelism relatively
  cheaply do you care about these compiler approaches. This is something
  that Haskell can do that Ruby, C and friends really can not do -- thus
  I mention it.

 If I have the basic building block, which is the ability to
 serialize a Haskell expression with its dependencies and read them
 into another Haskell instance where I can evaluate them, I can handle
 the other pieces, which are

 - passing strings back and forth in whatever way is convenient
 - deciding how to divide up my workload.

  Do add also, configuring servers and their connections.

 In the Ruby universe, DRb combines the serialization and passing
 strings around job and lets me figure out how to divide up the work,
 and it would be delightful if there were something similarly simple in
 the Haskell world.

  I think Holumbus has got some promising stuff for user-managed
  distributed workers:

http://holumbus.fh-wedel.de/trac/browser/distribution

  What do you think?

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


Re: [Haskell-cafe] Bulk Synchronous Parallel

2010-04-21 Thread Bas van Dijk
On Wed, Apr 21, 2010 at 8:07 PM, Aaron D. Ball
aarondball+hask...@gmail.com wrote:
 If I have the basic building block, which is the ability to
 serialize a Haskell expression with its dependencies and read them
 into another Haskell instance where I can evaluate them, I can handle
 the other pieces

How I wish we had Clean's dynamics[1]!

regards,

Bas

[1] See section 8 of the Clean report:
http://clean.cs.ru.nl/download/Clean20/doc/CleanLangRep.2.1.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bulk Synchronous Parallel

2010-04-21 Thread Don Stewart
v.dijk.bas:
 On Wed, Apr 21, 2010 at 8:07 PM, Aaron D. Ball
 aarondball+hask...@gmail.com wrote:
  If I have the basic building block, which is the ability to
  serialize a Haskell expression with its dependencies and read them
  into another Haskell instance where I can evaluate them, I can handle
  the other pieces
 
 How I wish we had Clean's dynamics[1]!

You could imagine shipping GHCi bytecode between processes, much as
Clean could do.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: Agata-0.2.0

2010-04-21 Thread Neil Mitchell
Hi Jonas,

 As far as i can tell, derive only works for regular and linear
 recursive types and Regular uses frequencies to regulate size. (Also
 Regular doesn't seem to work for QuickCheck-2).

Derive will generate instances for all types, but uses a fairly
standard formulation (pick between each constructor equally), meaning
that in some cases the generators won't be that good, and will tend to
generate infinite branches.

 Another feature of Agata generators is improved scalability compared
 to other QuickCheck generators, especially for nested collection data
 types (analog to a and such). The details of how this works in
 Agata will one day be explained in the documentation, but the
 principle is explained in my masters thesis[1].

Very neat :-)

I'd welcome an instance generator based on your ideas as a patch to
Derive. Derive provides 3 things:

* Infrastructure - given a definition, it provides tests, ability to
run as template haskell, ability to write to files, auto-generated
documentation etc. I hope to add more infrastructure, such as the
ability to run derivations via a website, so the user need not even
install derive.

* Derivation inference - a method infer derivations given a single
example (explained in this paper:
http://community.haskell.org/~ndm/downloads/paper-deriving_a_relationship_from_a_single_example-04_sep_2009.pdf)

* Lots of instances, about 34 different ones.

I/you/we could replace the Arbitrary instance with one based on your
implementation. You don't have to use the derivation inference (and it
probably wouldn't be suitable), but you do get to benefit from the
rest of the infrastructure. People can then run your program via the
command line, integrate easily with preprocessors etc - and still do
the Template Haskell bit too.

 [1] http://gupea.ub.gu.se/bitstream/2077/22087/1/gupea_2077_22087_1.pdf

Nice, I'll have a read (if it's in English)

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


[Haskell-cafe] ANN: GPipe-Collada - Collada for Haskell!

2010-04-21 Thread Tobias Bexelius

Hi,

 

I've uploaded GPipe-Collada-0.1.0 to hackage 
(http://hackage.haskell.org/package/GPipe-Collada-0.1.0) that enables you to 
load Collada files to be used with GPipe.

 

Check out Graphics.GPipe.Collada.Utils.viewScene for an example on how to use 
loaded Collada scenes 
(http://hackage.haskell.org/packages/archive/GPipe-Collada/0.1.0/doc/html/Graphics-GPipe-Collada-Utils.html#5).
 

 

For more information regarding Collada, including free sample files, visit 
http://www.collada.org.

 

 

Cheers!

Tobias
  
_
Surfa tryggt med Internet Explorer 8
http://www.microsoft.com/sverige/windows/internet-explorer/default.aspx___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: forkable-monad 0.1

2010-04-21 Thread David Anderson
On Wed, Apr 21, 2010 at 4:09 PM, Limestraël limestr...@gmail.com wrote:
 Nice initiative!

Thanks!

 By the way, since this is a monad, I think a better place than
 Control.Concurrent.Forkable would be Control.Monad.Forkable.
 It's just a suggestion.

I'm not entirely happy with the location with the module, but with the
current implementation where the type class defines only forkIO, I
think it should live in Control.Concurrent. Since it doesn't define a
new monad, but only a concurrency-specific restriction on existing
monads, it seems that Control.Monad would be the wrong home.

Am I missing something?

Cheers,
- Dave




 2010/4/21 David Anderson d...@natulte.net

 Dear Haskellers,

 I'm happy, and only slightly intimidated, to announce the initial
 release of forkable-monad.

 The short version is that forkable-monad exports a replacement forkIO
 that lets you do this:

 type MyMonad = ReaderT Config (StateT Ctx IO)

 startThread :: MyMonad ThreadId
 startThread = forkIO threadMain

 threadMain :: MyMonad ()
 threadMain = forever $ liftIO $ putStrLn Painless monad stack forking!

 Note the lack of monad stack deconstruction and reconstruction to
 transport it over to the new thread. You'll find the details in the
 Haddock documentation for the module.

 forkable-monad is available:

 * On hackage: http://hackage.haskell.org/package/forkable-monad
 * Via cabal: cabal install forkable-monad
 * Source and issue tracker: http://code.google.com/p/forkable-monad/

 Feedback is of course welcome. As this is my first published Haskell
 code and Hackage upload, I expect there will be quite a bit!

 - Dave
 ___
 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


[Haskell-cafe] Philadelphia Haskell hackathon -- reduced hotel rate ends Friday April 23!

2010-04-21 Thread Brent Yorgey
There is still plenty of space to register [1] for Hac phi 2010, but
time is running out to get a hotel room at a reduced rate --- if you
want the special rate for the block of rooms we have reserved at the
Club Quarters, you must contact the hotel by this Friday, April 23.
Instructions are on the wiki [2].

If you have been thinking of coming but are not sure, let me emphasize
that last year's Hac phi was great fun---it will be an excellent time
to make new friends, expand your brain, eat good food, and of course
write some Haskell.  You are welcome and encouraged to attend whether
you just want to learn Haskell or have been using it for 10 years!
You also do not have to come for the whole time; feel free to come
just for a day or even an afternoon.  The original announcement is
below.

-Brent

--

Hac phi 2010 is a Haskell hackathon/get-together to be held May 21-23
at the University of Pennsylvania in Philadelphia.  The hackathon will
officially kick off at 2:30 Friday afternoon, and go until 5pm on
Sunday (with breaks for sleep, of course).  Last year's Hac phi was a
lot of fun, and many people have already expressed interest in coming
back this year.  I want to stress that everyone is welcome---you do
not have to be a Haskell guru to attend!  Helping hack on someone
else's project could be a great way to increase your Haskell-fu.

If you plan on coming, please officially register [1].  Registration,
travel, lodging and many other details can be found on the Hac phi
wiki [2].  Note that we're in a different space this year and may have
to cap attendance, so register early.

We're also looking for a few people interested in giving short (15-20
min.) talks, probably on Saturday afternoon.  Anything of interest to
the Haskell community is fair game---a project you've been working on,
a paper, a quick tutorial.  If you'd like to give a talk, add it on
the wiki [3].

Hope to see you in Philadelphia!

-The Hac φ team

[1] http://haskell.org/haskellwiki/Hac_φ/Register
[2] http://haskell.org/haskellwiki/Hac_φ
[3] http://haskell.org/haskellwiki/Hac_φ/Talks

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


[Haskell-cafe] FRP for game programming / artifical life simulation

2010-04-21 Thread Ben Christy
I have an interest in both game programming and artificial life. I have
recently stumbled on Haskell and would like to take a stab at programming a
simple game using FRP such as YAMPA or Reactive but I am stuck. I am not
certain which one I should choose. It seems that Reactive is more active but
is it suitable for game programming. Also has anyone attempted to implement
neural networks using FRP if so again which of these two approaches to FRP
would you suggest?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: forkable-monad 0.1

2010-04-21 Thread David Anderson
On Wed, Apr 21, 2010 at 4:39 PM, Neil Brown nc...@kent.ac.uk wrote:
 Hi,

 This is quite a neat generalisation of forkIO, and something I've wanted in
 the past.

 My comment would be about the MonadIO m requirement for ForkableMonad.  I
 understand that conceptually it's a nice thing to have.  But practically, I
 don't think it's necessary, and could be a little restrictive -- I could
 imagine potentially having a newtype-wrapped monad that doesn't have a
 MonadIO instance, but does have a ForkableMonad instance.  I tried removing
 the MonadIO constraint, and it works as long as you add a Monad constraint
 either to the class or to the ReaderT and StateT instances.  That depends if
 you can imagine an instance of ForkableMonad that wasn't a Monad (an
 applicative perhaps)... probably not, especially given the name.

 In short: I recommend changing MonadIO m to Monad m on the class.

Hmm, I see. Originally I defined the MonadIO constraint because it
seemed the best way to state that the monad stack should have IO at
its core, to allow for calling the classic forkIO at some point. That
said, the argument for a newtyped stack that doesn't implement MonadIO
does make some sense.

Change submitted and pushed at
http://code.google.com/p/forkable-monad/source/detail?r=89 . Thanks!

 I came up with this instance for ContT:

 instance (ForkableMonad m) = ForkableMonad (ContT r m) where
  forkIO act = lift $ forkIO (runContT act (const $ return undefined))

 I don't know if that's useful and/or correct, though.

Hmm. Good question. I haven't quite wrapped my head around ContT yet,
but I'll make a note to meditate over your implementation. If it makes
sense in the context of forking threads, I'll add it to the
collection.

Thanks again,
- Dave

 David Anderson wrote:

 Dear Haskellers,

 I'm happy, and only slightly intimidated, to announce the initial
 release of forkable-monad.

 The short version is that forkable-monad exports a replacement forkIO
 that lets you do this:

 type MyMonad = ReaderT Config (StateT Ctx IO)

 startThread :: MyMonad ThreadId
 startThread = forkIO threadMain

 threadMain :: MyMonad ()
 threadMain = forever $ liftIO $ putStrLn Painless monad stack forking!

 Note the lack of monad stack deconstruction and reconstruction to
 transport it over to the new thread. You'll find the details in the
 Haddock documentation for the module.

 forkable-monad is available:

 * On hackage: http://hackage.haskell.org/package/forkable-monad
 * Via cabal: cabal install forkable-monad
 * Source and issue tracker: http://code.google.com/p/forkable-monad/

 Feedback is of course welcome. As this is my first published Haskell
 code and Hackage upload, I expect there will be quite a bit!

 - Dave
 ___
 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] Re: ANN: forkable-monad 0.1

2010-04-21 Thread David Anderson
[-haskell]

On Wed, Apr 21, 2010 at 5:54 PM, Heinrich Apfelmus
apfel...@quantentunnel.de wrote:
 David Anderson wrote:
 Dear Haskellers,

 I'm happy, and only slightly intimidated, to announce the initial
 release of forkable-monad.

 The short version is that forkable-monad exports a replacement forkIO
 that lets you do this:

 type MyMonad = ReaderT Config (StateT Ctx IO)

 startThread :: MyMonad ThreadId
 startThread = forkIO threadMain

 threadMain :: MyMonad ()
 threadMain = forever $ liftIO $ putStrLn Painless monad stack forking!

 Note the lack of monad stack deconstruction and reconstruction to
 transport it over to the new thread. You'll find the details in the
 Haddock documentation for the module.

 Nice work!

 It appears to me that this is subsumed by the recent  MonadMorphIO
 proposal that Anders Kaseorg came up with, though?

   http://article.gmane.org/gmane.comp.lang.haskell.libraries/12902


   fork :: MonadMorphIO m = m () - m ()
   fork m = morphIO $ \down - forkIO (down m  return ())
                                down (return ())

Hmm, quite possibly. It is also quite similar to another
implementation of forkable monad stacks I came across after finishing
this first version of the library, and to what I had tentatively
called unliftIO with a slightly different type, in another
experiment in messing with forking monad stacks.

So, it seems that I am reinventing wheels that others have generalized
better :-). That's fine, it's the expected result of launching and
iterating, especially given my current command of Haskell. So I should
now focus on reducing the reinvention.

Most of the discussion that followed the message that you linked is
currently beyond my understanding of category theory. However, I
should probably go and talk to the maintainer of MonadCatchIO-* about
extracting something like MonadMorphIO into a package, and making both
their exception handling modules and this forking module reuse it.

Thanks for the pointer!
- Dave

 Regards,
 Heinrich Apfelmus

 --
 http://apfelmus.nfshost.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] FRP for game programming / artifical life simulation

2010-04-21 Thread Luke Palmer
On Wed, Apr 21, 2010 at 4:47 PM, Ben Christy ben.chri...@gmail.com wrote:
 I have an interest in both game programming and artificial life. I have
 recently stumbled on Haskell and would like to take a stab at programming a
 simple game using FRP such as YAMPA or Reactive but I am stuck. I am not
 certain which one I should choose. It seems that Reactive is more active but
 is it suitable for game programming. Also has anyone attempted to implement
 neural networks using FRP if so again which of these two approaches to FRP
 would you suggest?

I am in the process of writing a game using FRP.  I haven't followed
reactive in a while, but last I checked it had some rather annoying
issues, such as joinE (monad join on events) not working and an open
space leak.  So we are using a Yampa-like approach, but not
specifically Yampa.  However most of the game logic is *not* in AFRP
(arrowized FRP) style, it is just there to give a nice foundation
and top level game loop, playing much the same role as IO does in many
Haskell programs (but it is implemented purely!).

The workhorse of our game has so far been generalized differentials.
 While not entirely rigorous, they have provided a very nice framework
in which to express our thoughts and designs, and are very good at
highly dynamic situations which appear in games.  For example, with
arrows it is painful to maintain a list of moving actors such that can
be added and removed.  With differentials this is quite natural.

I haven't published the differential library yet, I am waiting until
we have used them enough to discover essential techniques and find a
nice bases for primitives.  But I will give a sketch here.  Let the
types be your guide, as I am implementing from memory without a
compiler :-P

 import qualified Data.Accessor.Basic as Acc
 import Data.VectorSpace
 import Control.Comonad

A differential is implemented as a function that takes a timestep and
returns an update function.  Don't expose the D constructor; step is
okay to expose, it's kind of a generalized linear approximation.

 newtype D a = D { step :: Double - a - a }

 instance Monoid (D a) where
 mempty = D (const id)
 mappend da db = D (\dt - step da dt . step db dt)

Given a differential for a component of a value, we can construct a
differential for that value.

 accessor :: Acc.T s a - D a - D s
 accessor acc da = D (Acc.modify acc . step da)

Given a differential for each component of a tuple, we can find the
differential for the tuple.

 product :: D a - D b - D (a, b)
 product da db = D (\dt (x,y) - (step da dt x, step db dt y))

A differential can depend on the current value.

 dependent :: (a - D a) - D a
 dependent f = D (\dt x - step (f x) dt x)

Vectors can be treated directly as differentials over themselves.

 vector :: (VectorSpace v, Scalar v ~ Double) = v - D v
 vector v = D (\dt x - x ^+^ dt *^ v)

Impulses allow non-continuous burst changes, such as adding/removing
an element from a list of actors. This is the only function that bugs
me.  Incorrectly using it you can determine the framerate, which is
supposed be hidden.  But if used correctly; i.e. only trigger them on
passing conditions, they can be quite handy.  But my eyes and ears are
open for alternatives.

 impulse :: (a - a) - D a
 impulse f = D (const f)

If we can can find the differential for an element of some comonad
given its context, we can find the differential for the whole
structure.  (Our game world is a comonad, that's why this is in
here)

 comonad :: (Comonad w) = (w a - D a) - D (w a)
 comonad f = D (\dt - let h w = step (f w) dt (extract w) in extend h)

I add new primitives at the drop of a hat. I would like to find a nice
combinator basis, but as yet, one hasn't jumped out at me. It might
require some tweaking of the concept.

The arrow we are using is implemented in terms of differentials:

 data Continuous a b = forall s. Continuous s (s - a - (b, D s))

 instance Category Continuous where
 id = Continuous () (\() x - (x, mempty))
 Continuous sg0 g . Continuous sf0 f = MkC (sg0,sf0) $ \(sg,sf) x -
 let !(y, df) = f sf x -- mind the strict patterns
 !(z, dg) = g sg y in
 (z, product dg df)

Exercise: implement the Arrow and ArrowLoop instances.

And here is where it comes together.  Integration over generalized
differentials is a continuous arrow:

 integral :: Continuous (D a) a
 integral a0 = Continuous a0 (,)

So our game loop looks something like:

 dGameState :: Input - D GameState
 dGameState = ... -- built out of simpler Ds of its components

 mainGame = proc input - do
 gameState - integral initialGameState - dGameState input
 returnA - drawGameState gameState

This is my first experience with functional game programming, and so
far I love it!  It makes so much more sense than the imperative
alternative.  But the techniques are quite new and different as well,
and sometimes it takes a lot of thinking to figure out how to do
something that 

Re: [Haskell-cafe] Bulk Synchronous Parallel

2010-04-21 Thread Peter Gammie
On Thu, Apr 22, 2010 at 4:07 AM, Aaron D. Ball
aarondball+hask...@gmail.com wrote:

 I don't need a tool that automatically figures out how to distribute
 any workload in an intelligent way and handles all the communication
 for me.  If I have the basic building block, which is the ability to
 serialize a Haskell expression with its dependencies and read them
 into another Haskell instance where I can evaluate them, I can handle
 the other pieces, which are

 - passing strings back and forth in whatever way is convenient
 - deciding how to divide up my workload.

Alice/ML is the place to look for this technology.

http://www.ps.uni-saarland.de/alice/

The project may be dead (I don't know), but they did have the most
sophisticated take on pickling that I've seen. It's an ML variant,
with futures, running on top of the same platform used by Mozart/Oz of
CTM fame.

Why do you want to pass strings around?

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


[Haskell-cafe] Adopting MissingPy?

2010-04-21 Thread John Goerzen

Hi folks,

MissingPy is a library I wrote a little while back that allows you to 
call Python code from Haskell.  It's on Hackage and, as far as I know, 
still works.


Trouble is, the need I used to have for it is gone. So I no longer use 
it myself for anything, and thus it is starting to bitrot.


Would anyone like to take over maintenance of this project?

Thanks,

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