RE: [Haskell-cafe] STM, orElse and timed read from a channel

2005-11-29 Thread Simon Marlow
On 29 November 2005 06:29, Tomasz Zielonka wrote:

> On Mon, Nov 28, 2005 at 11:27:46PM +, Joel Reymont wrote:
>> Folks,
>> 
>> How would you implement a timed read from a channel with STM? I would
>> like to return Timeout if nothing was read from a TChan in X ms.
>> 
>> Is this a basic two-thread timeout implementation or is there a more
>> elegant way of implementing this using `orElse`?
> 
> Here is a basic two-thread implementation:
>  
> http://www.haskell.org/pipermail/haskell-cafe/2005-January/008303.html
> 
> The other approach I see is to create a TVar that would be updated
> with current time every 0.1 s (or something like that), but that would
> be rather inefficient.
> 
> You could also create a time-out manager thread (with a priority
> queue, etc), so you don't have to spawn a thread for every timeout.

Interestingly, GHC already has a timeout thread - the I/O manager thread
handles threadDelay too.  It wouldn't be too hard to adapt it to do STM
timeouts too, with a function like

   registerTimeout :: Int -> STM (TVar Bool)

and you wait for your timeout by waiting for the TVar to contain True.

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


Re: [Haskell-cafe] STM, orElse and timed read from a channel

2005-11-29 Thread Joel Reymont

Simon,

How is this easier than just calling threadDelay?

Ideally, I would be looking for something like reading from a TVar  
with a timeout. So that you either get a Nothing (timeout) or the  
value from the TVar. Can I implement it using the GHC timeout thread?


Thanks, Joel

On Nov 29, 2005, at 9:20 AM, Simon Marlow wrote:

Interestingly, GHC already has a timeout thread - the I/O manager  
thread
handles threadDelay too.  It wouldn't be too hard to adapt it to do  
STM

timeouts too, with a function like

   registerTimeout :: Int -> STM (TVar Bool)

and you wait for your timeout by waiting for the TVar to contain True.


--
http://wagerlabs.com/





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


R: [Haskell-cafe] Hacking Haskell in Nightclubs?

2005-11-29 Thread Santoemma Enrico
Doing music is a hard low level problem, a concurrency problem and is also an 
interesting problem for intelligent and behavioural computation.

If it's true that Haskell can do its best on the second and third aspect, the 
undertaking seems to wrap with foreing interface one of the many good C 
libraries for low level audio/midi management.

Btw, about the third aspect I liked your approach to model animations through 
behaviour in your book School of expressions.

So now the questions seem to be: how difficult is today to wrap a C library? 
Which is the right tool to do it? C->Haskell?

Salus,
Enrico

> -Messaggio originale-
> Da: [EMAIL PROTECTED]
> [mailto:[EMAIL PROTECTED] conto di Paul Hudak
> Inviato: martedì 29 novembre 2005 3.36
> A: Echo Nolan
> Cc: haskell-cafe@haskell.org; [EMAIL PROTECTED]
> Oggetto: Re: [Haskell-cafe] Hacking Haskell in Nightclubs?
> 
> 
> Although Haskore (haskell.org/haskore) doesn't currently support 
> real-time music, it's something I've thought about numerous 
> times in the 
> past, and wish I had the time to do it...
> 
>-Paul Hudak
> 
> 
> Echo Nolan wrote:
> > Hello all,
> > I read an article on using perl for live improvised synthesis a
> > while ago (http://www.perl.com/pub/a/2004/08/31/livecode.html). Does
> > anyone have thoughts in doing this is haskell? Would strong 
> typing make
> > "jazzy" programming too difficult?
> > Regards,
> > Echo Nolan
> 
> -- 
> Professor Paul Hudak
> Department of Computer ScienceOffice: (203) 432-1235
> Yale University   FAX:(203) 432-0593
> P.O. Box 208285   email:  [EMAIL PROTECTED]
> New Haven, CT 06520-8285  WWW:www.cs.yale.edu/~hudak
> ___
> 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: R: [Haskell-cafe] Hacking Haskell in Nightclubs?

2005-11-29 Thread Philippa Cowderoy
On Tue, 29 Nov 2005, Santoemma Enrico wrote:

> Doing music is a hard low level problem, a concurrency problem and is 
> also an interesting problem for intelligent and behavioural computation.
> 
> If it's true that Haskell can do its best on the second and third 
> aspect, the undertaking seems to wrap with foreing interface one of the 
> many good C libraries for low level audio/midi management.
> 

That's not so bad if we can afford a little latency. If need be we can 
even have a separate thread or process being fed data from haskell land.

-- 
[EMAIL PROTECTED]

'In Ankh-Morpork even the shit have a street to itself...
 Truly this is a land of opportunity.' - Detritus, Men at Arms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] STM, orElse and timed read from a channel

2005-11-29 Thread Simon Marlow
threadDelay is IO-only; there's no way to use threadDelay in an STM
transaction.  For example, if you want to wait for a TVar to go from
Nothing to Just x with a timeout, you could do this:

  readOrTimeout :: TVar (Maybe a) -> Int -> STM (Maybe a)
  readOrTimeout t secs = do
timeout <- registerTimeout secs
let check_timeout = do 
  b <- readTVar timeout
  if b then return Nothing else retry
check_t = do
  m <- readTVar t
  case m of
Nothing -> retry
Just x  -> return x
atomically $ check_timeout `orElse` check_t

Cheers,
Simon

On 29 November 2005 10:11, Joel Reymont wrote:

> Simon,
> 
> How is this easier than just calling threadDelay?
> 
> Ideally, I would be looking for something like reading from a TVar
> with a timeout. So that you either get a Nothing (timeout) or the
> value from the TVar. Can I implement it using the GHC timeout thread?
> 
>   Thanks, Joel
> 
> On Nov 29, 2005, at 9:20 AM, Simon Marlow wrote:
> 
>> Interestingly, GHC already has a timeout thread - the I/O manager
>> thread handles threadDelay too.  It wouldn't be too hard to adapt it
>> to do STM timeouts too, with a function like
>> 
>>registerTimeout :: Int -> STM (TVar Bool)
>> 
>> and you wait for your timeout by waiting for the TVar to contain
>> True. 

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


Re: [Haskell-cafe] STM, orElse and timed read from a channel

2005-11-29 Thread Tomasz Zielonka
On Tue, Nov 29, 2005 at 12:00:03PM -, Simon Marlow wrote:
> threadDelay is IO-only; there's no way to use threadDelay in an STM
> transaction.  For example, if you want to wait for a TVar to go from
> Nothing to Just x with a timeout, you could do this:
> 
>   readOrTimeout :: TVar (Maybe a) -> Int -> STM (Maybe a)
>   readOrTimeout t secs = do
> timeout <- registerTimeout secs
> let check_timeout = do 
>   b <- readTVar timeout
>   if b then return Nothing else retry
> check_t = do
>   m <- readTVar t
>   case m of
> Nothing -> retry
> Just x  -> return x
> atomically $ check_timeout `orElse` check_t

Wouldn't it be
readOrTimeout :: TVar (Maybe a) -> Int -> IO (Maybe a)
  ^^
?

Alternatively, it would be nice to have a new STM primitive:

wailUntil :: ClockTime -> STM ()

so you would wait until some time-point passes, not for a number of
time-units (waiting for a number of time-units wouldn't work because of
retries). I think it could be efficiently implemented, wouldn't it?

Best regards
Tomasz

-- 
I am searching for a programmer who is good at least in some of
[Haskell, ML, C++, Linux, FreeBSD, math] for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] STM, orElse and timed read from a channel

2005-11-29 Thread Simon Marlow
On 29 November 2005 12:08, Tomasz Zielonka wrote:

> On Tue, Nov 29, 2005 at 12:00:03PM -, Simon Marlow wrote:
>> threadDelay is IO-only; there's no way to use threadDelay in an STM
>> transaction.  For example, if you want to wait for a TVar to go from
>> Nothing to Just x with a timeout, you could do this:
>> 
>>   readOrTimeout :: TVar (Maybe a) -> Int -> STM (Maybe a)  
>> readOrTimeout t secs = do timeout <- registerTimeout secs
>> let check_timeout = do
>>   b <- readTVar timeout
>>   if b then return Nothing else retry
>> check_t = do
>>   m <- readTVar t
>>   case m of
>> Nothing -> retry
>> Just x  -> return x
>> atomically $ check_timeout `orElse` check_t
> 
> Wouldn't it be
> readOrTimeout :: TVar (Maybe a) -> Int -> IO (Maybe a)
>   ^^
> ?

Sorry, yes.

> Alternatively, it would be nice to have a new STM primitive:
> 
> wailUntil :: ClockTime -> STM ()
> 
> so you would wait until some time-point passes, not for a number of
> time-units (waiting for a number of time-units wouldn't work because
> of retries). I think it could be efficiently implemented, wouldn't it?

Interesting.  You could use that do wait for idle time, for example:

   atomically $ do
  t <- readTVar last_mouse_click
  waitUntil (t+1000)
  ... 

so this transaction only completes when some idle time has passed since
the last mouse click.

But you could also implement this using registerTimeout, albeit with
some more code and an extra thread, and waitUntil requires an
implementation in the runtime which is not entirely trivial.

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


[Haskell-cafe] STM commit hooks

2005-11-29 Thread Einar Karttunen
Hello

I have been playing with STM and want to log transactions to disk. 
Defining a logging function like:

log h act = unsafeIOToSTM $ hPrint h act

works most the time. Aborts can be handled with:

abort h = log h Abort >> retry
atomic' h act = atomically (act `orElse` abort h)

But is it possible to handle a commit?

commit h = unsafeIOToSTM (hPrint h Commit >> hSync h)
atomically2 h act = atomically ((act >> commit h) `orElse` abort h)

This won't work because the transaction is validated and 
maybe aborted after the commit is logged to disk.

Another alternative would be:

atomically3 h act = atomically (act `orElse` abort h) >> atomically (commit h)

But this does not work either. Given Trx1 and Trx2, the following may occur:

1) Trx1 commits

2) Trx2 commits (and depends on Trx1)
3) Trx2 commit is logged to disk


This means that the log would be inconsistent. Is there a way to implement
the commit that works?

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


Re: [Haskell-cafe] STM, orElse and timed read from a channel

2005-11-29 Thread Joel Reymont

Simon,

Where is this "registerTimeout" in the GHC code?

Thanks, Joel

On Nov 29, 2005, at 12:29 PM, Simon Marlow wrote:


But you could also implement this using registerTimeout, albeit with
some more code and an extra thread, and waitUntil requires an
implementation in the runtime which is not entirely trivial.


--
http://wagerlabs.com/





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


RE: [Haskell-cafe] STM, orElse and timed read from a channel

2005-11-29 Thread Simon Marlow
On 29 November 2005 12:47, Joel Reymont wrote:

> Where is this "registerTimeout" in the GHC code?

Well, it's not there yet :-)  But I've hacked up an implementation this
morning so it might be in GHC 6.6.

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


Re: [Haskell-cafe] STM, orElse and timed read from a channel

2005-11-29 Thread Joel Reymont

Would you share your implementation for us advanced users?

I could use Tomasz's workaround in the meantime but isn't GHC 6.6  
supposed to be out in a year?


On Nov 29, 2005, at 12:52 PM, Simon Marlow wrote:


On 29 November 2005 12:47, Joel Reymont wrote:


Where is this "registerTimeout" in the GHC code?


Well, it's not there yet :-)  But I've hacked up an implementation  
this

morning so it might be in GHC 6.6.

Cheers,
Simon


--
http://wagerlabs.com/





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


[Haskell-cafe] Re: wxHaskell and do statements

2005-11-29 Thread mempko

Malcolm Wallace wrote:

mempko <[EMAIL PROTECTED]> writes:

Hello, I have a program that just will not compile and I cannot figure 
out why.


Wrong indentation.  Tab stops are 8 spaces in Haskell, but your code
seems to assume 6 spaces.


-
module Main where

import Graphics.UI.WX

main :: IO ()
main = start hello

hello :: IO ()
hello = do f <- frame [text := "Super Window"]
lab <- staticText f [text:= "Hello"]


The 'lab <-' actually lines up with 'frame', not with 'f <-' as intended.

Regards,
Malcolm



I found that using ';' at the end of expressions helped and also adding 
a "return()" statement. You were also right that it did not line up, 
thank you. Now does haskell understand tabs, or does my editor have to 
convert the tabs to spaces?



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


Re: [Haskell-cafe] Re: wxHaskell and do statements

2005-11-29 Thread Sebastian Sylvan
On 11/29/05, mempko <[EMAIL PROTECTED]> wrote:
> Malcolm Wallace wrote:
> > mempko <[EMAIL PROTECTED]> writes:
> >
> >> Hello, I have a program that just will not compile and I cannot figure
> >> out why.
> >
> > Wrong indentation.  Tab stops are 8 spaces in Haskell, but your code
> > seems to assume 6 spaces.
> >
> >> -
> >> module Main where
> >>
> >> import Graphics.UI.WX
> >>
> >> main :: IO ()
> >> main = start hello
> >>
> >> hello :: IO ()
> >> hello = do f <- frame [text := "Super Window"]
> >>  lab <- staticText f [text:= "Hello"]
> >
> > The 'lab <-' actually lines up with 'frame', not with 'f <-' as intended.
> >
> > Regards,
> > Malcolm
>
>
> I found that using ';' at the end of expressions helped and also adding
> a "return()" statement. You were also right that it did not line up,
> thank you. Now does haskell understand tabs, or does my editor have to
> convert the tabs to spaces?

IIRC Haskell assumes a tab is 8 spaces.
IMO that's way too much. Haskell tends to take up quite a bit of
horizontal real-estate so I usually go with 2 spaces.

At any rate, I set my editor to convert them to spaces.

/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Hacking Haskell in Nightclubs?

2005-11-29 Thread rd
Real-time audio is much simpler these days due to SuperCollider, a
truly excellent cross platform audio synthesis server by James
McCartney.

  http://www.audiosynth.com
  http://supercollider.sf.net

To communicate with the server one only needs to implement the most
basic aspects of the Open Sound Control (OSC) byte protocol (in
particular none of the pattern matching is required).

  http://www.opensoundcontrol.org/

To define 'instruments' there is a SuperCollider specific byte
protocol for describing Unit Generator (UGen) graphs.

I have an initial Haskell implementation of both these protocols at:

  http://www.slavepianos.org/rd/f/207949/
  darcs get http://www.slavepianos.org/rd/sw/sw-69/

If SuperCollider is running on the local host at the usual port then:

  Hsc*> play' sc ab
  Hsc*> stop' sc

should play (and then stop playing) the famous 'Analog Bubbles' test
sound:

ab = out AR 0 $ combn AR s 0.2 0.2 4
where s = sinosc AR (midicps f) 0 * 0.1
  f = lfsaw KR 0.4 0 * 24 + o
  o = lfsaw KR (MCE [8, 7.23]) 0 * 3 + 80

The Hsc module can also write UGen graphs to the 'dot' language, so
graphs can be drawn automatically, which can be useful for debugging.

I have been working with scheme and SuperCollider for some time, but
have been using haskell recently and generally like it very well.  I
don't think static typing is an issue.

OSC messages can be timestamped, and SuperCollider has a sample
accurate scheduling queue, so language timing jitter can easily be
worked around.  I think that the SuperCollider model is an excellent
fit with languages like Haskell.

Regards,
Rohan

On Mon Nov 28 21:35:38 EST 2005 Paul Hudak wrote:

> Although Haskore (haskell.org/haskore) doesn't currently support
> real-time music, it's something I've thought about numerous times in the
> past, and wish I had the time to do it...
>
>-Paul Hudak
>
>
> Echo Nolan wrote:
> > Hello all,
> > I read an article on using perl for live improvised synthesis a
> > while ago (http://www.perl.com/pub/a/2004/08/31/livecode.html). Does
> > anyone have thoughts in doing this is haskell? Would strong typing make
> > "jazzy" programming too difficult?


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


[Haskell-cafe] :t main

2005-11-29 Thread Scherrer, Chad
I've been reading some of the articles about comonads, and I thought the idea 
of giving main the type OI () -> () was pretty interesting. So I was wondering, 
would it be possible to allow the type of main to be inferred? It seems like 
IO ()
OI () -> ()
OI () -> IO ()

all make sense (at least I think they do). One particularly nice side effect of 
this (pardon the pun) is that a good number of useful programs can be written as

getContentsW :: OI () -> a
doSomeStuff :: (Show b) => a -> b
print :: (Show b) => b -> IO ()
main = print . doSomeStuff . getContentsW

so much less understanding about monads et al is required to do some basic 
stuff. I think it would be much easier in this case to make the transition to 
Haskell.

Also, has anyone given any thought to syntactic sugar for comonads? Since 
arrows and monads share the (<-) symbol, it seems like a nice unification could 
be possible... Maybe (-<) alone could be used similarly?

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


Re: [Haskell-cafe] Hacking Haskell in Nightclubs?

2005-11-29 Thread Paul Hudak

[EMAIL PROTECTED] wrote:

Real-time audio is much simpler these days due to SuperCollider, a
truly excellent cross platform audio synthesis server by James
McCartney.
...
OSC messages can be timestamped, and SuperCollider has a sample
accurate scheduling queue, so language timing jitter can easily be
worked around.  I think that the SuperCollider model is an excellent
fit with languages like Haskell.


Thanks, this is just what I've been waiting for!  I believe the 
time-stamping of events, and a suitable scheduling queue, are critical 
for making real-time music.  With the work you've done I suspect it 
would be pretty easy to build a SuperCollider backend for Haskore.


  -Paul


Regards,
Rohan

On Mon Nov 28 21:35:38 EST 2005 Paul Hudak wrote:

Although Haskore (haskell.org/haskore) doesn't currently support
real-time music, it's something I've thought about numerous times in the
past, and wish I had the time to do it...
-Paul Hudak

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