Re: [Haskell-cafe] Haskell showcase in 5 minutes

2012-02-28 Thread Arnaud Bailly
Thanks for your support. I would really like to do this but 1) the talk is
tomorrow evening and 2) I do not have time in the interval to learn yesod
and/or gloss enough to be confident that I will not botch anything in a 5
minutes time frame.

I did recently a 2-hours long talk with same purpose (introducing Haskell
to an audience of mixed-level Scala programmers), using some code to
produce sound and music, up to a web server for generating wav files from
"scores", and I had to make giant steps in the last 15 minutes to get to
the web stuff. There was a lot of questions right from the start on various
"strange" aspects of the language : type inference, laziness, generalized
tail recursion, monadic I/O, point-free definitions and I barely managed to
keep some time to show how easy it is to write a web server with simple
HTML combinators (I discovered miku in the process).

I timed myself on the menu problem and I am a little bit under 5 minutes,
given I want to explain quite a few things in the process: what you can do
with lists, what you can do with pairs, how to simply generate all the
combinations of elements of a list, how to map a function on list, how to
use list-comprehensions to integrate everything into a concise form and how
to avoid combinatorial blow-up through laziness.

I also would love to have the time to show some cool concurrency stuff
following your suggestion. I will try to pack this tomorrow.

Thanks a lot again for your advices,

Arnaud

2012/2/28 Ertugrul Söylemez 

> Arnaud Bailly  wrote:
>
> > Thanks Yves for your advice. And I agree with you that too much
> > laziness may be mind-blowing for most of the audience, yet this is one
> > of the characteristics of Haskell, whether or not we like it and
> > whatever troubles it can induce.
> >
> > I really think the knapsack is simple, not too far away from real
> > world and might be demonstrated with live code in 5 minutes. I will
> > have a look anyway at more "spectacular" stuff like gloss or yesod but
> > I fear this is out of scope.
>
> Gloss is definitely not out of scope.  It is to simple 2D graphics what
> Yesod is to web applications.  I write two-minutes visualizations using
> it all the time.  Of course if you want to show something great, you
> shouldn't fear learning it first.
>
> Also showing the language features, despite their greatness, makes
> people go like:  "Ok, that's great, but I can do it in my language using
> ".  If you really don't want to go for
> something amazing like Diagrams, Gloss or Yesod, I really suggest at
> least bringing the run-time system into the game.  Show concurrency, STM
> and parallel evaluation.  Show how you can write a full-featured finger
> server in five minutes that is fast, secure and amazingly readable.
> Something like that.
>
> Math problems amaze Haskellers, not programmers in general.  Show how
> Haskell solves practical problems, for which there is no simple solution
> in more common languages.  Don't show why Haskell is also good.  Show
> why Haskell is /a lot better/.
>
>
> 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] Does somebody know about these functions?

2012-02-28 Thread Stephen Tetley
On 28 February 2012 17:06, Johan Holmquist  wrote:

> Function 'withPair' takes a pair and applies a function to it's first
> element, another function to it's second element and finally combines
> the results with yet another function.
>
> withPair :: (a' -> b' -> c) -> (a -> a') -> (b -> b') -> (a,b) -> c
> withPair f fa fb (a,b) = fa a `f` fb b
>

withPair is the Dovekie function from combinatory logic but with a
pair for the non-combinator arguments (a,b) and the arg order changed
to be more convenient to program with.

There was a thread about inter[*] on the beginners list last month


http://www.haskell.org/pipermail/beginners/2012-January/009329.html

[*] or an inter-like function depending how you want to treat the
initial value. I made a mistake with my suggestion.

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


Re: [Haskell-cafe] Installing gloss

2012-02-28 Thread Ivan Lazar Miljenovic
On 29 February 2012 08:40, Richard O'Keefe  wrote:
> Gloss having been mentioned, I thought I'd look into it.
>
> m% cabal install gloss
> Resolving dependencies...
> cabal: cannot configure gloss-1.6.1.1. It requires base ==4.5.*
> For the dependency on base ==4.5.* there are these packages: base-4.5.0.0.
> However none of them are available.
> base-4.5.0.0 was excluded because of the top level dependency base -any
>
> What did I do wrong?

I believe the newest version of gloss requires GHC-7.4; the 1.5 series
builds with older versions of GHC.

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



-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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


[Haskell-cafe] Installing gloss

2012-02-28 Thread Richard O'Keefe
Gloss having been mentioned, I thought I'd look into it.

m% cabal install gloss
Resolving dependencies...
cabal: cannot configure gloss-1.6.1.1. It requires base ==4.5.*
For the dependency on base ==4.5.* there are these packages: base-4.5.0.0.
However none of them are available.
base-4.5.0.0 was excluded because of the top level dependency base -any

What did I do wrong?

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


[Haskell-cafe] Use Template Haskell recover inside the IO monad

2012-02-28 Thread Federico Mastellone
I'm new to Template Haskell and just started playing with it.
I have Haskell platform 2011.4.0 and I get this error when I try to run this 
simple code.

main = do
code <- runQ $ recover (return []) th
putStrLn (pprint code)
putStrLn (show code)

th :: Q [Dec]
th = [d| 
sum a b = a + b 
|]

Template Haskell error: Can't do `recover' in the IO monad
POC.hs: user error (Template Haskell failure)

How can I get declarations with the "recover" function so I can print a custom 
error message using "location"?
If I can't do it inside the IO monad, how can I do a program to pretty print 
Haskell code?

Thanks!


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


Re: [Haskell-cafe] Does somebody know about these functions?

2012-02-28 Thread Johan Holmquist
>> Except when l == [], but the second equation can be replaced by this nicer 
>> one.
>
> Even then. :) (zipWith f l (tail l)) first tries to match l with pattern 
> (a:as), and if that
> fails it will not touch its other argument (tail l).

Hm, you're right, it did work for empty lists. I wonder if one dare
trust it to always be so.

/Johan

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


Re: [Haskell-cafe] question about conduit source

2012-02-28 Thread Alexander V Vershilov
Hello.

Naming operator >=< instead of >=> is a good idea.
But this functions are looks very good and will make code easier to understand. 

Also I'll try using non-STM channel (as Michael adviced) because in such a task 
I don't need all STM power.

Thanks for response.

--
Alexander


Tue, Feb 28, 2012 at 02:58:46PM -0500, Clark Gaebel wrote
> First of all, I'd probably name that operator >=<, since >=> is Kleisli
> composition in Control.Monad.
>
> Second, you're going to need new threads for this, since you'll be reading 
> from
> two sources concurrently. This isn't as big a problem as you might think,
> because Haskell threads are dirt cheap, orders of magnitude cheaper than
> pthread threads. If you're using multiple threads with conduits, I just wrote 
> a
> library to help you out with that! As Michael already mentioned, stm-conduit
> could do this synchronization for you. This turns your >=< function into:
> 
> infixl 5 >=<
> (>=<) :: ResourceIO m
>   => Source m a
>   -> Source m a
>   -> ResourceT m (Source m a)
> sa >=< sb = do c <- liftIO . atomically $ newTMChan
>    _ <- resourceForkIO $ sa $$ sinkTMChan c
>    _ <- resourceForkIO $ sb $$ sinkTMChan c
>    return $ sourceTMChan c
> 
> which returns a new source, combining two sources.
> 
> This can further be generalized to combining any number of sources:
> 
> mergeSources :: ResourceIO m
>  => [Source m a]
>  -> ResourceT m (Source m a)
> mergeSources sx = do c <- liftIO . atomically $ newTMChan
>    mapM_ (\s -> resourceForkIO $ s $$ sinkTMChan c) sx
>    return $ sourceTMChan c
> 
> Hope this helps somewhat,
>   - clark
>
> On Tue, Feb 28, 2012 at 11:04 AM, Alexander V Vershilov <
> alexander.vershi...@gmail.com> wrote:
> >
> > Hello, cafe.
> >
> > Is it possible to read data from different concurrent sources,
> > i.e. read data from source as soon as it become avaliable, e.g.
> >
> >  runResourceT $ (source1 stdin $= CL.map Left)
> >                   >=> (source2 handle $= CL.map Right)
> >              $= application
> >              $$ sink
> >    where >=> - stands for concurrent combining of sources
> >
> > It would be good if it can be sources of different types (handle or
> > STM channel, etc..).
> >
> > Currently I've found no good way to handle with this situation,
> > except of using STM Channels for collecting data
> >
> >   source1 ---+            |
> >              |   sink     |                       output sink
> >              +---] Channel [---> application->]
> >              |          source
> >   source2 ---+            |
> >
> > From this point of view application takes concurent data, but this
> > implementation requires additional thread per data processing. Also
> > in many cases it will require run additional runResourceT (see later
> > example).
> >
> > So if there any possible simplifications? Or ideas how to make (>=>)
> > operator.
> >
> > Example:
> >
> > So I've got next code in my network-conduit based application:
> >
> >   main :: IO ()
> >   main = do
> >     pool <- createDBPool "..." 10
> >     let r = ServerInit pool
> >     forkIO $ forever clientConsole --read channel list and send "Left"
> >     flip runReaderT r $
> >       runTCPServer (ServerSettings 3500 Nothing) (protoServer)
> >
> >   myServer src sink = do
> >    ch <- liftIO $ atomically $ newTBMChan 16
> >    initState <- lift $ ask
> >    _  <- liftIO $ fork . (flip runReaderT initState) $
> >                   runResourceT $ src $= C.sequence decode
> >                                      $= CL.map Right $$ sinkTBMChan ch
> >    sourceTBMChan ch
> >                 $= process $= C.sequence encode $$ sinkHandle stdout
> >
> > But in this situation I don't know if freeing of all resources are
> guaranteed,
> > because I'm running additional resourceT in main resourceT scope.
> >
> > So can you advice is it possible to make concurrent sources now with 
> > currenly
> > implemented library?
> > If it's not possible but worth of implementing, so I can make that 
> > functions?
> > Is it correct to runResourceT inside another resourceT?
> >
> > --
> > Best regards,
> >   Alexander V Vershilov
> >
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >


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


Re: [Haskell-cafe] Does somebody know about these functions?

2012-02-28 Thread Holger Siegel

Am 28.02.2012 um 20:21 schrieb Johan Holmquist:

>>> inter :: (a -> a -> b) -> [a] -> [b]
>>> inter f [] = []
>>> inter f l  = map (uncurry f) $ zip l (tail l)
>> 
>> This is the same as
>> 
>> inter :: (a -> a -> b) -> [a] -> [b]
>> inter f l = zipWith f l (tail l)
> 
> Except when l == [], but the second equation can be replaced by this nicer 
> one.

Even then. :) (zipWith f l (tail l)) first tries to match l with pattern 
(a:as), and if that
fails it will not touch its other argument (tail l).


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


Re: [Haskell-cafe] question about conduit source

2012-02-28 Thread Clark Gaebel
Finally, I've uploaded a new version of stm-conduit [1] with these
combinators included. You should "cabal update" and then "cabal install
stm-conduit" to get the latest version, and now you can vertically compose
your sources!

Regards,
  - clark

[1] http://hackage.haskell.org/package/stm-conduit-0.2.3.0

On Tue, Feb 28, 2012 at 2:58 PM, Clark Gaebel
wrote:

> First of all, I'd probably name that operator >=<, since >=> is Kleisli
> composition in Control.Monad.
>
> Second, you're going to need new threads for this, since you'll be reading
> from two sources concurrently. This isn't as big a problem as you might
> think, because Haskell threads are dirt cheap, orders of magnitude cheaper
> than pthread threads. If you're using multiple threads with conduits, I
> just wrote a library to help you out with that! As Michael already
> mentioned, stm-conduit could do this synchronization for you. This turns
> your >=< function into:
>
> infixl 5 >=<
> (>=<) :: ResourceIO m
>   => Source m a
>   -> Source m a
>   -> ResourceT m (Source m a)
> sa >=< sb = do c <- liftIO . atomically $ newTMChan
>_ <- resourceForkIO $ sa $$ sinkTMChan c
>_ <- resourceForkIO $ sb $$ sinkTMChan c
>return $ sourceTMChan c
>
> which returns a new source, combining two sources.
>
> This can further be generalized to combining any number of sources:
>
> mergeSources :: ResourceIO m
>  => [Source m a]
>  -> ResourceT m (Source m a)
> mergeSources sx = do c <- liftIO . atomically $ newTMChan
>mapM_ (\s -> resourceForkIO $ s $$ sinkTMChan c) sx
>return $ sourceTMChan c
>
> Hope this helps somewhat,
>   - clark
>
>
> On Tue, Feb 28, 2012 at 11:04 AM, Alexander V Vershilov <
> alexander.vershi...@gmail.com> wrote:
> >
> > Hello, cafe.
> >
> > Is it possible to read data from different concurrent sources,
> > i.e. read data from source as soon as it become avaliable, e.g.
> >
> >  runResourceT $ (source1 stdin $= CL.map Left)
> >   >=> (source2 handle $= CL.map Right)
> >  $= application
> >  $$ sink
> >where >=> - stands for concurrent combining of sources
> >
> > It would be good if it can be sources of different types (handle or
> > STM channel, etc..).
> >
> > Currently I've found no good way to handle with this situation,
> > except of using STM Channels for collecting data
> >
> >   source1 ---+|
> >  |   sink |   output sink
> >  +---] Channel [---> application->]
> >  |  source
> >   source2 ---+|
> >
> > From this point of view application takes concurent data, but this
> > implementation requires additional thread per data processing. Also
> > in many cases it will require run additional runResourceT (see later
> > example).
> >
> > So if there any possible simplifications? Or ideas how to make (>=>)
> > operator.
> >
> > Example:
> >
> > So I've got next code in my network-conduit based application:
> >
> >   main :: IO ()
> >   main = do
> > pool <- createDBPool "..." 10
> > let r = ServerInit pool
> > forkIO $ forever clientConsole --read channel list and send "Left"
> > flip runReaderT r $
> >   runTCPServer (ServerSettings 3500 Nothing) (protoServer)
> >
> >   myServer src sink = do
> >ch <- liftIO $ atomically $ newTBMChan 16
> >initState <- lift $ ask
> >_  <- liftIO $ fork . (flip runReaderT initState) $
> >   runResourceT $ src $= C.sequence decode
> >  $= CL.map Right $$ sinkTBMChan ch
> >sourceTBMChan ch
> > $= process $= C.sequence encode $$ sinkHandle stdout
> >
> > But in this situation I don't know if freeing of all resources are
> guaranteed,
> > because I'm running additional resourceT in main resourceT scope.
> >
> > So can you advice is it possible to make concurrent sources now with
> currenly
> > implemented library?
> > If it's not possible but worth of implementing, so I can make that
> functions?
> > Is it correct to runResourceT inside another resourceT?
> >
> > --
> > Best regards,
> >   Alexander V Vershilov
> >
> > ___
> > 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] question about conduit source

2012-02-28 Thread Clark Gaebel
First of all, I'd probably name that operator >=<, since >=> is Kleisli
composition in Control.Monad.

Second, you're going to need new threads for this, since you'll be reading
from two sources concurrently. This isn't as big a problem as you might
think, because Haskell threads are dirt cheap, orders of magnitude cheaper
than pthread threads. If you're using multiple threads with conduits, I
just wrote a library to help you out with that! As Michael already
mentioned, stm-conduit could do this synchronization for you. This turns
your >=< function into:

infixl 5 >=<
(>=<) :: ResourceIO m
  => Source m a
  -> Source m a
  -> ResourceT m (Source m a)
sa >=< sb = do c <- liftIO . atomically $ newTMChan
   _ <- resourceForkIO $ sa $$ sinkTMChan c
   _ <- resourceForkIO $ sb $$ sinkTMChan c
   return $ sourceTMChan c

which returns a new source, combining two sources.

This can further be generalized to combining any number of sources:

mergeSources :: ResourceIO m
 => [Source m a]
 -> ResourceT m (Source m a)
mergeSources sx = do c <- liftIO . atomically $ newTMChan
   mapM_ (\s -> resourceForkIO $ s $$ sinkTMChan c) sx
   return $ sourceTMChan c

Hope this helps somewhat,
  - clark

On Tue, Feb 28, 2012 at 11:04 AM, Alexander V Vershilov <
alexander.vershi...@gmail.com> wrote:
>
> Hello, cafe.
>
> Is it possible to read data from different concurrent sources,
> i.e. read data from source as soon as it become avaliable, e.g.
>
>  runResourceT $ (source1 stdin $= CL.map Left)
>   >=> (source2 handle $= CL.map Right)
>  $= application
>  $$ sink
>where >=> - stands for concurrent combining of sources
>
> It would be good if it can be sources of different types (handle or
> STM channel, etc..).
>
> Currently I've found no good way to handle with this situation,
> except of using STM Channels for collecting data
>
>   source1 ---+|
>  |   sink |   output sink
>  +---] Channel [---> application->]
>  |  source
>   source2 ---+|
>
> From this point of view application takes concurent data, but this
> implementation requires additional thread per data processing. Also
> in many cases it will require run additional runResourceT (see later
> example).
>
> So if there any possible simplifications? Or ideas how to make (>=>)
> operator.
>
> Example:
>
> So I've got next code in my network-conduit based application:
>
>   main :: IO ()
>   main = do
> pool <- createDBPool "..." 10
> let r = ServerInit pool
> forkIO $ forever clientConsole --read channel list and send "Left"
> flip runReaderT r $
>   runTCPServer (ServerSettings 3500 Nothing) (protoServer)
>
>   myServer src sink = do
>ch <- liftIO $ atomically $ newTBMChan 16
>initState <- lift $ ask
>_  <- liftIO $ fork . (flip runReaderT initState) $
>   runResourceT $ src $= C.sequence decode
>  $= CL.map Right $$ sinkTBMChan ch
>sourceTBMChan ch
> $= process $= C.sequence encode $$ sinkHandle stdout
>
> But in this situation I don't know if freeing of all resources are
guaranteed,
> because I'm running additional resourceT in main resourceT scope.
>
> So can you advice is it possible to make concurrent sources now with
currenly
> implemented library?
> If it's not possible but worth of implementing, so I can make that
functions?
> Is it correct to runResourceT inside another resourceT?
>
> --
> Best regards,
>   Alexander V Vershilov
>
> ___
> 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] Haskell showcase in 5 minutes

2012-02-28 Thread Ertugrul Söylemez
Arnaud Bailly  wrote:

> Thanks Yves for your advice. And I agree with you that too much
> laziness may be mind-blowing for most of the audience, yet this is one
> of the characteristics of Haskell, whether or not we like it and
> whatever troubles it can induce.
>
> I really think the knapsack is simple, not too far away from real
> world and might be demonstrated with live code in 5 minutes. I will
> have a look anyway at more "spectacular" stuff like gloss or yesod but
> I fear this is out of scope.

Gloss is definitely not out of scope.  It is to simple 2D graphics what
Yesod is to web applications.  I write two-minutes visualizations using
it all the time.  Of course if you want to show something great, you
shouldn't fear learning it first.

Also showing the language features, despite their greatness, makes
people go like:  "Ok, that's great, but I can do it in my language using
".  If you really don't want to go for
something amazing like Diagrams, Gloss or Yesod, I really suggest at
least bringing the run-time system into the game.  Show concurrency, STM
and parallel evaluation.  Show how you can write a full-featured finger
server in five minutes that is fast, secure and amazingly readable.
Something like that.

Math problems amaze Haskellers, not programmers in general.  Show how
Haskell solves practical problems, for which there is no simple solution
in more common languages.  Don't show why Haskell is also good.  Show
why Haskell is /a lot better/.


Greets,
Ertugrul

-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/


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


Re: [Haskell-cafe] Does somebody know about these functions?

2012-02-28 Thread Johan Holmquist
>> inter :: (a -> a -> b) -> [a] -> [b]
>> inter f [] = []
>> inter f l  = map (uncurry f) $ zip l (tail l)
>
> This is the same as
>
>  inter :: (a -> a -> b) -> [a] -> [b]
>  inter f l = zipWith f l (tail l)

Except when l == [], but the second equation can be replaced by this nicer one.

> and you can use it to define the good old Fibonacci sequence:
>
>  fibs = 0 : 1 : inter (+) fibs

Another use :-)

(sorry Holger for duplicate -- hit wrong answer button at first)


Together, these functions can be used to define a variant of groupBy
that does the "expected thing" in the case of groupBy (<) for example.

groupBy f l = gby $ zip (undefined : inter f l) l where
gby [] = []
gby ((_,x):ps) = withPair (:) ((x:) . map snd) gby (span fst ps)


>>> groupBy (<) [1,2,3, 2,3, 1,2]
[[1,2,3],[2,3],[1,2]]

/Johan

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


Re: [Haskell-cafe] Does somebody know about these functions?

2012-02-28 Thread Holger Siegel

Am 28.02.2012 um 18:06 schrieb Johan Holmquist:

> Two functions that I see useful are described here and I would like to
> know if they are defined in some more or less standard Haskell
> library. Hoogle (http://www.haskell.org/hoogle) did not reveal
> anything about that.
> 
> 
> Function 'inter' applies given function to each succeeding pair of
> elements of a list.
> 
> inter :: (a -> a -> b) -> [a] -> [b]
> inter f [] = []
> inter f l  = map (uncurry f) $ zip l (tail l)

This is the same as

  inter :: (a -> a -> b) -> [a] -> [b]
  inter f l = zipWith f l (tail l)

and you can use it to define the good old Fibonacci sequence:

  fibs = 0 : 1 : inter (+) fibs


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


Re: [Haskell-cafe] GSoc-2012: Lock-free Data Structures

2012-02-28 Thread Sergiu Ivanov
Hello,

On Tue, Feb 21, 2012 at 8:11 AM, Ryan Newton  wrote:
>
> Oops, I've attached the PDF.  It's a good overview that includes a bunch of
> the key ideas that appear in recent work in the area.

Very cool article, thank you!  I genuinely enjoyed reading it :-)

> Absolutely!  Feel free to make a pull request.

I'm going to play with the existing structures first.  However, I
can't see a list of issues anywhere.  Could you suggest a place where
I could look for indications of some issues which I could fix for
starters?

Sergiu

P.S.  Sorry for my sluggishness :-(

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


Re: [Haskell-cafe] Does somebody know about these functions?

2012-02-28 Thread Brent Yorgey
On Tue, Feb 28, 2012 at 06:06:25PM +0100, Johan Holmquist wrote:
> 
> inter :: (a -> a -> b) -> [a] -> [b]
> inter f [] = []
> inter f l  = map (uncurry f) $ zip l (tail l)

I've never seen this function defined anywhere, but it looks nice.

> withPair :: (a' -> b' -> c) -> (a -> a') -> (b -> b') -> (a,b) -> c
> withPair f fa fb (a,b) = fa a `f` fb b

Note that

  withPair f g h === uncurry f . (g *** h)

although using withPair is probably nicer (it certainly involves fewer
parentheses).

-Brent

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


Re: [Haskell-cafe] Vim plugin for ghc-mod

2012-02-28 Thread Yves Parès
Hi,
I downloaded those vim extensions, and I just wonder how I could have done
before syntastic ;)

Is there a vim plugin useful for runtime (putting breakpoints, seeing if an
expression has been evaluated or if it's still a thunk?)

I believe it exists for emacs.

2012/2/16 Nicolas Wu 

> On 16 February 2012 08:51, Kazu Yamamoto  wrote:
> > eagletmt implemented a Vim plugin for ghc-mod:
> >
> >https://github.com/eagletmt/ghcmod-vim
> >
> > Happy Haskell programming on Vim!
>
> Note that there's also support for ghc-mod using [syntastic][1] for
> vim, which is well supported for Haskell and other languages too.
>
> Nick
>
> [1]: https://github.com/scrooloose/syntastic
>
> ___
> 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] question about conduit source

2012-02-28 Thread Michael Snoyman
On Tue, Feb 28, 2012 at 6:04 PM, Alexander V Vershilov
 wrote:
> Hello, cafe.
>
> Is it possible to read data from different concurrent sources,
> i.e. read data from source as soon as it become avaliable, e.g.
>
>  runResourceT $ (source1 stdin $= CL.map Left)
>                   >=> (source2 handle $= CL.map Right)
>              $= application
>              $$ sink
>    where >=> - stands for concurrent combining of sources
>
> It would be good if it can be sources of different types (handle or
> STM channel, etc..).
>
> Currently I've found no good way to handle with this situation,
> except of using STM Channels for collecting data
>
>   source1 ---+            |
>              |   sink     |                       output sink
>              +---] Channel [---> application->]
>              |          source
>   source2 ---+            |
>
> From this point of view application takes concurent data, but this
> implementation requires additional thread per data processing. Also
> in many cases it will require run additional runResourceT (see later
> example).

There's not really any way to do what you're looking to do *without*
spawning a separate thread (or using some evented system directly, but
I'm assuming that's not the case). If what you're looking to do is
block until data is available from source1, and block until data is
available from source2, you're going to have to use separate threads
and some kind of synchronization. STM Channels seem like a good fit,
and normal Chans would probably work as well.

Clark Gaebel has already put together stm-conduit[1], maybe he would
be interested in adding some additional functions for this use case.

[1] 
http://hackage.haskell.org/packages/archive/stm-conduit/0.2.2.1/doc/html/Data-Conduit-TMChan.html

> So if there any possible simplifications? Or ideas how to make (>=>)
> operator.
>
> Example:
>
> So I've got next code in my network-conduit based application:
>
>   main :: IO ()
>   main = do
>     pool <- createDBPool "..." 10
>     let r = ServerInit pool
>     forkIO $ forever clientConsole --read channel list and send "Left"
>     flip runReaderT r $
>       runTCPServer (ServerSettings 3500 Nothing) (protoServer)
>
>   myServer src sink = do
>    ch <- liftIO $ atomically $ newTBMChan 16
>    initState <- lift $ ask
>    _  <- liftIO $ fork . (flip runReaderT initState) $
>                   runResourceT $ src $= C.sequence decode
>                                      $= CL.map Right $$ sinkTBMChan ch
>    sourceTBMChan ch
>                 $= process $= C.sequence encode $$ sinkHandle stdout
>
> But in this situation I don't know if freeing of all resources are guaranteed,
> because I'm running additional resourceT in main resourceT scope.

You can nest ResourceT as much as you want. Each time you call
runResourceT, the resources allocated in that block will be freed. I
haven't analyzed your code in detail, but it seems fine to me. The
only real way you can stop ResourceT from freeing resources is by
never triggering the final release, which can be done by either:

1. Having your entire application live inside ResourceT. In such a
case, your resources will still be freed, it will just happen at the
very end of your application.
2. Use resourceForkIO and let the child threads live indefinitely.

>
> So can you advice is it possible to make concurrent sources now with currenly
> implemented library?
> If it's not possible but worth of implementing, so I can make that functions?
> Is it correct to runResourceT inside another resourceT?
>
> --
> Best regards,
>   Alexander V Vershilov
>
> ___
> 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] Does somebody know about these functions?

2012-02-28 Thread Johan Holmquist
Two functions that I see useful are described here and I would like to
know if they are defined in some more or less standard Haskell
library. Hoogle (http://www.haskell.org/hoogle) did not reveal
anything about that.


Function 'inter' applies given function to each succeeding pair of
elements of a list.

inter :: (a -> a -> b) -> [a] -> [b]
inter f [] = []
inter f l  = map (uncurry f) $ zip l (tail l)

Example usage:

  and $ inter (<=) l   -- checks if 'l' is ordered

  inter (,) l   -- gives succeeding pairs


Function 'withPair' takes a pair and applies a function to it's first
element, another function to it's second element and finally combines
the results with yet another function.

withPair :: (a' -> b' -> c) -> (a -> a') -> (b -> b') -> (a,b) -> c
withPair f fa fb (a,b) = fa a `f` fb b

Example usage:

  words [] = []
  words s  = withPair (:) id words (break isSpace $ dropWhile isSpace s)

  lines [] = []
  lines s  = withPair (:) id lines (break (== '\n') s)

  mapPair = withPair (,)

This function can abstract away the (in my opinion ugly) pattern (as
seen in the examples):

  foo list = let (a,b) =  list in  a `` foo b


Anyone knows about these two functions or variants thereof?

Cheers
/Johan

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


[Haskell-cafe] Haskell showcase in 5 minutes

2012-02-28 Thread Doug McIlroy
Sorry, a typo in the url for the power-series example.
It should have been
http://www.cs.dartmouth.edu/~doug/powser.html

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


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

2012-02-28 Thread Johan Tibell
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 
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


Re: [Haskell-cafe] Haskell showcase in 5 minutes

2012-02-28 Thread David Virebayre
Le 28 février 2012 14:45, Doug McIlroy  a écrit :
> Here's an example that fits comfortably in 5 minutes--if
> your audience knows elementary calculus:
> http://www.cs.dartmouth.edu/~doug/powswer.html

404 invalid url !

David.

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


Re: [Haskell-cafe] Haskell showcase in 5 minutes

2012-02-28 Thread Joel Burget
There was a typo in the link, here's the corrected version
http://www.cs.dartmouth.edu/~doug/powser.html

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


Re: [Haskell-cafe] Theorems for free!

2012-02-28 Thread Patrick Browne
 Hi,  I apologize if the formatting or content of my previous email caused offence.  Hopefully my question is better phrased and presented this time.  Below is my attempt to code the first example from Walder’s Theorems for free! paper[1].     {-# LANGUAGE ExistentialQuantification #-}  import Data.Char  r :: forall a . [a] -> [a]  r = reverse  g :: Char -> Int  g = ord    (map g . r $ ['a','b','c']) == (r . map g $ ['a','b','c'])      I am not sure about what is being proved.   Wadler says:    It is possible to conclude that r satisifies the following theorem    r must work on lists of X for any types X.      So does evaluation demonstrate type level satisfiability?  Thanks,  Pat    [1] homepages.inf.ed.ac.uk/wadler/papers/free/free.ps

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


[Haskell-cafe] Haskell showcase in 5 minutes

2012-02-28 Thread Doug McIlroy
Here's an example that fits comfortably in 5 minutes--if
your audience knows elementary calculus:
http://www.cs.dartmouth.edu/~doug/powswer.html
It depends critically on lazy evaluation, which knocks out
a lot of competing languages right from the start.

The five-minute version would begin with power-series
addition--trivial.
Then comes multiplication--an eye-opener. No subscripts! No worry
about how many terms to carry in intermediate results.

That's about all you have time to really derive. Go on
to mention that division is about equally easy.  Then
allude to substitution (also called composition) and its
inverse, reversion.  Lots of finicky papers have been
written about reversion over more than two centuries.
Throw that one-liner on the screen side-by-side with
Algorithm S (which is only pseudocode!) from Knuth
section 4.7.  That should convince the most skeptical
observer.

Doug

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


Re: [Haskell-cafe] Haskell showcase in 5 minutes

2012-02-28 Thread Heinrich Apfelmus

Arnaud Bailly wrote:

Hello Cafe,

I will be (re)presenting Haskell in a "Batlle Language" event Wednesday
evening: A fun and interactive contest where various programming language
champions try to attract as much followers as possible in 5 minutes.

Having successfully experimented the power of live coding in a recent
Haskell introduction for the Paris Scala User Group, I would like to do the
same but given the time frame I need a simpler example than the music
synthesizer program.

So I would like to tap in the collective wisdom looking for some concise,
eye-opening, mind-shaking and if possible fun example of what one can
achieve in Haskell. Things that sprung to my mind are rather dull: prime
factors, fibonacci numbers.


A morse code decoder, perhaps?

  http://apfelmus.nfshost.com/articles/fun-with-morse-code.html



Best 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] Haskell showcase in 5 minutes

2012-02-28 Thread Magnus Therning
On Tue, Feb 28, 2012 at 14:05, Arnaud Bailly  wrote:
> Thanks Yves for your advice. And I agree with you that too much laziness may
> be mind-blowing for most of the audience, yet this is one of the
> characteristics of Haskell, whether or not we like it and whatever troubles
> it can induce.
>
> I really think the knapsack is simple, not too far away from real world and
> might be demonstrated with live code in 5 minutes. I will have a look anyway
> at more "spectacular" stuff like gloss or yesod but I fear this is out of
> scope.

If it suits the medium, you could always throw up a one-liner (e.g.
fibonacci from a recursive list) at the end and just leave it there
without explanation, for the audience to feel the awesomeness of
Haskell ;)

/M

-- 
Magnus Therning                      OpenPGP: 0xAB4DFBA4
email: mag...@therning.org   jabber: mag...@therning.org
twitter: magthe               http://therning.org/magnus

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


Re: [Haskell-cafe] Haskell showcase in 5 minutes

2012-02-28 Thread Arnaud Bailly
Thanks Yves for your advice. And I agree with you that too much laziness
may be mind-blowing for most of the audience, yet this is one of the
characteristics of Haskell, whether or not we like it and whatever troubles
it can induce.

I really think the knapsack is simple, not too far away from real world and
might be demonstrated with live code in 5 minutes. I will have a look
anyway at more "spectacular" stuff like gloss or yesod but I fear this is
out of scope.

Regards,
Arnaud

On Tue, Feb 28, 2012 at 12:27 PM, Yves Parès  wrote:

> Nevermind, I think I found:
> http://jduchess.org/duchess-france/blog/battle-language-a-la-marmite/
>
> You could try the JSON parser exercise. (
> https://github.com/revence27/JSON-hs) Or anything else with Parsec, it's
> a pretty good power-showing library.
>
>
> 2012/2/28 Yves Parès 
>
>> Where exactly does that event take place?
>> Is it open to public?
>>
>> And I strongly disadvise fibonacci, quicksort and other mind-blowing
>> reality-escapist stuff. Show something real world and practical.
>>
>> 2012/2/27 Arnaud Bailly 
>>
>>>  Hello Cafe,
>>>
>>> I will be (re)presenting Haskell in a "Batlle Language" event Wednesday
>>> evening: A fun and interactive contest where various programming language
>>> champions try to attract as much followers as possible in 5 minutes.
>>>
>>> Having successfully experimented the power of live coding in a recent
>>> Haskell introduction for the Paris Scala User Group, I would like to do the
>>> same but given the time frame I need a simpler example than the music
>>> synthesizer program.
>>>
>>> So I would like to tap in the collective wisdom looking for some
>>> concise, eye-opening, mind-shaking and if possible fun example of what one
>>> can achieve in Haskell. Things that sprung to my mind are rather dull:
>>> prime factors, fibonacci numbers.
>>>
>>> Thanks in advance,
>>> Arnaud
>>>
>>> ___
>>> 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] question about conduit source

2012-02-28 Thread Alexander V Vershilov
Hello, cafe.

Is it possible to read data from different concurrent sources,
i.e. read data from source as soon as it become avaliable, e.g.

 runResourceT $ (source1 stdin $= CL.map Left)
   >=> (source2 handle $= CL.map Right)
  $= application
  $$ sink
where >=> - stands for concurrent combining of sources

It would be good if it can be sources of different types (handle or
STM channel, etc..).

Currently I've found no good way to handle with this situation,
except of using STM Channels for collecting data

   source1 ---+|
  |   sink |   output sink
  +---] Channel [---> application->]
  |  source
   source2 ---+|

From this point of view application takes concurent data, but this 
implementation requires additional thread per data processing. Also
in many cases it will require run additional runResourceT (see later
example).

So if there any possible simplifications? Or ideas how to make (>=>)
operator.

Example:

So I've got next code in my network-conduit based application:

   main :: IO ()
   main = do
 pool <- createDBPool "..." 10
 let r = ServerInit pool
 forkIO $ forever clientConsole --read channel list and send "Left"
 flip runReaderT r $
   runTCPServer (ServerSettings 3500 Nothing) (protoServer)

   myServer src sink = do
ch <- liftIO $ atomically $ newTBMChan 16
initState <- lift $ ask
_  <- liftIO $ fork . (flip runReaderT initState) $
   runResourceT $ src $= C.sequence decode
  $= CL.map Right $$ sinkTBMChan ch
sourceTBMChan ch
 $= process $= C.sequence encode $$ sinkHandle stdout

But in this situation I don't know if freeing of all resources are guaranteed,
because I'm running additional resourceT in main resourceT scope.

So can you advice is it possible to make concurrent sources now with currenly
implemented library?
If it's not possible but worth of implementing, so I can make that functions?
Is it correct to runResourceT inside another resourceT?

--
Best regards,
   Alexander V Vershilov


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


Re: [Haskell-cafe] Haskell showcase in 5 minutes

2012-02-28 Thread Yves Parès
Nevermind, I think I found:
http://jduchess.org/duchess-france/blog/battle-language-a-la-marmite/

You could try the JSON parser exercise. (
https://github.com/revence27/JSON-hs) Or anything else with Parsec, it's a
pretty good power-showing library.

2012/2/28 Yves Parès 

> Where exactly does that event take place?
> Is it open to public?
>
> And I strongly disadvise fibonacci, quicksort and other mind-blowing
> reality-escapist stuff. Show something real world and practical.
>
> 2012/2/27 Arnaud Bailly 
>
>>  Hello Cafe,
>>
>> I will be (re)presenting Haskell in a "Batlle Language" event Wednesday
>> evening: A fun and interactive contest where various programming language
>> champions try to attract as much followers as possible in 5 minutes.
>>
>> Having successfully experimented the power of live coding in a recent
>> Haskell introduction for the Paris Scala User Group, I would like to do the
>> same but given the time frame I need a simpler example than the music
>> synthesizer program.
>>
>> So I would like to tap in the collective wisdom looking for some concise,
>> eye-opening, mind-shaking and if possible fun example of what one can
>> achieve in Haskell. Things that sprung to my mind are rather dull: prime
>> factors, fibonacci numbers.
>>
>> Thanks in advance,
>> Arnaud
>>
>> ___
>> 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] Haskell showcase in 5 minutes

2012-02-28 Thread Yves Parès
Where exactly does that event take place?
Is it open to public?

And I strongly disadvise fibonacci, quicksort and other mind-blowing
reality-escapist stuff. Show something real world and practical.

2012/2/27 Arnaud Bailly 

> Hello Cafe,
>
> I will be (re)presenting Haskell in a "Batlle Language" event Wednesday
> evening: A fun and interactive contest where various programming language
> champions try to attract as much followers as possible in 5 minutes.
>
> Having successfully experimented the power of live coding in a recent
> Haskell introduction for the Paris Scala User Group, I would like to do the
> same but given the time frame I need a simpler example than the music
> synthesizer program.
>
> So I would like to tap in the collective wisdom looking for some concise,
> eye-opening, mind-shaking and if possible fun example of what one can
> achieve in Haskell. Things that sprung to my mind are rather dull: prime
> factors, fibonacci numbers.
>
> Thanks in advance,
> Arnaud
>
> ___
> 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