Re: [Haskell-cafe] MIDI-controlled application

2011-12-28 Thread Tim Baumgartner
Hi Tom!

[...]
 
 
  Currently I'm using a monad that combines Parsec (with MIDI event
 stream) and a Writer (that writes commands that should result in IO). It's
 done in a way that during running the monad, many parses can be done and
 failing parses roll back the parser state so that a new parse can be tried.
 


 Care to share your code?


Yes, great! Have you worked with MIDI in Haskell? Perhaps
parsing/recognizing it? I think it will take a few more days (hopefully not
weeks) until I know what will be the foundation for my app. But then I will
create a project online and send you a message.
In case anybody has time to look at it, I just pasted my aforementioned
monad on hpaste. I thought about it some more and came to the conclusion
that for user-defined triggers (aka parsers), this approach is probably
sub optimal...
After Heinrich's suggestion, I worked through the slot machine example from
reactive-banana. It's a great introduction to FRP for me. The declarative
style is very appealing. I will try how it fits with my ideas.

Some of my code (thaugh probably obsolete): http://hpaste.org/55795

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


Re: [Haskell-cafe] MIDI-controlled application

2011-12-27 Thread Tim Baumgartner
Hi Stephen,

2011/12/27 Stephen Tetley stephen.tet...@gmail.com

 Hi Tim

 More problematic is that FRP models hybrid (continuous and discrete)
 systems. For me at least, MIDI seems essentially discrete - a stream
 of control events. In MIDI files control events are twinned with a
 time stamp so they can be played. Presumably events are instantaneous
 in real-time interactive MIDI - not something I've looked at.


The events all feature a time stamp and my drum set produces lots of
CRTClock events for synchronization. I didn't use the time stamps in my
Java application but I would have to for recording/recognizing rhythms.


 Working with an FRP system like Yampa might add a lot of complexity,
 which admittedly you should be able to ignore


Yes, I'm a bit afraid of that.


 but initially it might
 be difficult to identify what parts are needed for a mostly discrete
 system like MIDI. (If you are time-stamping MIDI events yourself you
 will presumably need to sample a running clock which seems like a
 continuous behaviour...)

 Unfortunately I can't think of any systems in Haskell that are more
 discrete than continuous so you might have to choose a FRP system
 anyway.


I just had a glance at Peakachu. It seemed easier than Yampa to me. I liked
the Program abstraction. Perhaps I can use this...


 Incidentally, I've been working on a MIDI animation language for the
 last couple of days based on the animation language in Paul Hudak's
 book. I've wanted continuous behaviours to model modulating volumes
 (crescendos, decrescendos) and panning, but I've found the work tough
 going for modelling the note lists where I want the system discrete in
 both input (specification) and output.


This reminds me of the Yampa based synthesizer from the paper Switched-On
Yampa. I just looked into it.


 Best wishes

 Stephen


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


[Haskell-cafe] MIDI-controlled application

2011-12-27 Thread Tim Baumgartner
Hi Haskellers!

I'm writing my first non-trivial Haskell application. I have an electronic
drum set that generates MIDI events that I process with Haskell. A simple
application of this kind might have fixed drums associated with fixed
commands (I've done that). The next step would be to display menus (with
very large font...) that show commands and the associated drums. The menu
structure should be derived from the commands active in each context. Up to
this point, I implemented this already in Java. But now after some
successful attempts in Haskell, I plan for more features: the user should
ultimately be able to record his own triggers, i.e. short drum rhythms,
and associate them with actions. Since I'm still a beginner with only some
basic experience in Monads, Arrows and their transformers, there is
infinite knowledge to be gained by working on this problem (both library
and concrete apps).

Currently I'm using a monad that combines Parsec (with MIDI event stream)
and a Writer (that writes commands that should result in IO). It's done in
a way that during running the monad, many parses can be done and failing
parses roll back the parser state so that a new parse can be tried.

Now my questions:
I have read about Yampa, but I have not mastered it yet. E.g. I don't
understand switches. Could my triggers be realized with Yampa's events
and switches?
Would you recommend any other approach?
Is there something similar somewhere?

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


Re: [Haskell-cafe] Interpreter with Cont

2011-11-21 Thread Tim Baumgartner
Free Monads. It's amazing to be confronted again with notions I learned
more than ten years ago for groups. I have to admit that I'm probably not
yet prepared for a deeper understanding of this, but hopefully I will
return to it later ;-)
Is Cont free as well? I guess so because I heard it's sometimes called the
mother of all monads.

Regards
Tim

2011/11/21 David Menendez d...@zednenem.com

 On Sat, Nov 19, 2011 at 3:29 PM, Felipe Almeida Lessa
 felipe.le...@gmail.com wrote:
  On Sat, Nov 19, 2011 at 6:08 PM, Tim Baumgartner
  baumgartner@googlemail.com wrote:
  I have not yet gained a good understanding of the continuation monad,
 but I
  wonder if it could be used here. What would a clean solution look like?
  Perhaps there are other things that need to be changed as well?
 
  Your 'Interaction' data type is actually an instance of the more
  general operational monad (as named by Heinrich Apfelmus) or prompt
  monad (as named by Ryan Ingram).

 Both of which are just disguised free monads. For reference:


 data Free f a = Val a | Wrap (f (Free f a))

 foldFree :: Functor f = (a - b) - (f b - b) - Free f a - b
 foldFree v w (Val a)  = v a
 foldFree v w (Wrap t) = w $ fmap (foldFree v w) t

 instance Functor f = Monad (Free f) where
return  = Val
m = f = foldFree f Wrap m



 To use Free, just find the signature functor for Interaction by
 replacing the recursive instances with a new type variable,

 data InteractionF a b x = ExitF b
| OutputF b x
| InputF (a - x)

 instance Functor (InteractionF a b) where
fmap f (ExitF b) = ExitF b
fmap f (OutputF b x) = OutputF b (f x)
fmap f (InputF g)= InputF (f . g)

 roll :: InteractionF a b (Interaction a b) - Interaction a b
 roll (ExitF b) = Exit b
 roll (OutputF b x) = Output b x
 roll (InputF g)= Input g


 type InteractionM a b = Free (InteractionF a b)

 runM :: InteractionM a b b - Interaction a b
 runM = foldFree Exit roll

 exit :: b - InteractionM a b c
 exit b = Wrap (ExitF b)

 output :: b - InteractionM a b ()
 output b = Wrap (OutputF b (Val ()))

 input :: InteractionM a b a
 input = Wrap (InputF Val)

 --
 Dave Menendez d...@zednenem.com
 http://www.eyrie.org/~zednenem/

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


Re: [Haskell-cafe] Interpreter with Cont

2011-11-21 Thread Tim Baumgartner
Hi Heinrich,

I read your article about the operational monad and found it really very
enlightening. So I'm curious to work through the material you linked below.
Thanks!

Regards
Tim


2011/11/21 Heinrich Apfelmus apfel...@quantentunnel.de

 Tim Baumgartner wrote:

 Thanks a lot! Althaugh I have some understanding of the Haskell basics and
 the most important monads, I feel that I have to see more well designed
 code in order to become a good Haskeller. Can somebody make suggestions
 what materials are best to work through in order to achieve this? Are
 there
 easy research papers about Haskell programming? Or should I try the
 Monad.Reader? I'm looking for topics that either can be used directly in
 many situations or that show some functional principles that boost my
 creativity and functional thinking.


 You may want to start with the Functional Pearls

  
 http://www.haskell.org/**haskellwiki/Research_papers/**Functional_pearlshttp://www.haskell.org/haskellwiki/Research_papers/Functional_pearls

 In particular, I recommend

  * Richard Bird. A program to solve Sudoku.
  * Graham Hutton. The countdown problem.
  * Martin Erwig and Steve Kollmansberger.
Probabilistic functional programming in Haskell.
  * Conor McBride and Ross Paterson.
Applicative Programming with Effects.


 Best regards,
 Heinrich Apfelmus

 --
 http://apfelmus.nfshost.com


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Interpreter with Cont

2011-11-21 Thread Tim Baumgartner
2011/11/21 David Menendez d...@zednenem.com


 Here's how you might implement your monad using Cont,

 type InteractionM a b = Cont (Interaction a b)

 exit b   = Cont $ \k - Exit b
 output b = Cont $ \k - Output b (k ())
 input= Cont $ \k - Input k
 runM m   = runCont m Exit


That's what I originally wanted to know. I guess I struggled with the
definition of output.
Oh, there's so much more to learn...

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


Re: [Haskell-cafe] Interpreter with Cont

2011-11-19 Thread Tim Baumgartner
Thanks a lot! Althaugh I have some understanding of the Haskell basics and
the most important monads, I feel that I have to see more well designed
code in order to become a good Haskeller. Can somebody make suggestions
what materials are best to work through in order to achieve this? Are there
easy research papers about Haskell programming? Or should I try the
Monad.Reader? I'm looking for topics that either can be used directly in
many situations or that show some functional principles that boost my
creativity and functional thinking.

Regards,
Tim

2011/11/19 Felipe Almeida Lessa felipe.le...@gmail.com

 On Sat, Nov 19, 2011 at 6:08 PM, Tim Baumgartner
 baumgartner@googlemail.com wrote:
  I have not yet gained a good understanding of the continuation monad,
 but I
  wonder if it could be used here. What would a clean solution look like?
  Perhaps there are other things that need to be changed as well?

 Your 'Interaction' data type is actually an instance of the more
 general operational monad (as named by Heinrich Apfelmus) or prompt
 monad (as named by Ryan Ingram).  You will ready-to-use
 implementations on the packages MonadPrompt [1] and operational [2,3].
  Reading their documentation you'll find some links about the
 development of these concepts.  MonadPrompt uses a Cont-style
 implementation, while operational uses a simple abstract data type
 together with a viewing function that avoids O(n²) behavior.

 If you find it hard to describe your 'Interaction' using operational
 (easiest to use package, IMO), please send us another e-mail.

 Cheers!

 [1] http://hackage.haskell.org/package/MonadPrompt
 [2] http://hackage.haskell.org/package/operational
 [3] http://heinrichapfelmus.github.com/operational/Documentation.html

 --
 Felipe.

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


Re: [Haskell-cafe] MonadRandom-computation that does not terminate

2011-01-12 Thread Tim Baumgartner
2011/1/12 Neil Brown nc...@kent.ac.uk

 On 11/01/11 23:19, Tim Baumgartner wrote:

 Hi,

 I'm having difficulties with this function I wrote:

 iterateR :: (MonadRandom m) = (a - m a) - a - m [a]
 iterateR g s = do
  s' - g s
  return (s:) `ap` iterateR g s'

 I'm running the computation with evalRandIO and surprisingly the first
 call of main in ghci succeeds, but the second does not terminate.
 Reproducible.
 Any clues what I'm doing wrong here?


 If we unfold ap we get:


 iterateR g s = do
  s' - g s
  f - return (s:)
  x - iterateR g s'
  return (f x)

 What happens here depends on exactly how the monad is defined, but for many
 monads that will form an infinite loop that prevents a value being returned.
  In the case of RandT from MonadRandom, it is not possible to execute the
 action after the iterateR call finishes without knowing the final state from
 the call, which requires evaluating the infinite loop of monadic actions.
  Does that help?


Yes, this helps definitely. So if I understand you right, the infinite loop
was not entered immediately because of lazyness? That's funny somehow.

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


[Haskell-cafe] MonadRandom-computation that does not terminate

2011-01-11 Thread Tim Baumgartner
Hi,

I'm having difficulties with this function I wrote:

iterateR :: (MonadRandom m) = (a - m a) - a - m [a]
iterateR g s = do
  s' - g s
  return (s:) `ap` iterateR g s'

I'm running the computation with evalRandIO and surprisingly the first call
of main in ghci succeeds, but the second does not terminate. Reproducible.
Any clues what I'm doing wrong here?

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