Re: [Haskell-cafe] pointers for EDSL design

2010-10-12 Thread Dominique Devriese
2010/10/12  o...@okmij.org:
 An alternative approach to model sharing at the object level is the
 technique I use for modelling context-free grammars in my PADL 2011
 paper Explicitly Recursive Grammar Combinators...  Using ideas from
 the Multirec generic programming library and some recent Haskell type
 system extensions (most importantly GADTs and type families), you can
 do this in a well-typed way for sets of mutually recursive
 object-level expressions.

 I guess you are using what I call `the initial embedding' of an object
 language. Somehow I prefer the final embedding.

No. In the library, I use both embedding styles for different
purposes, but what I was referring to here (the construction of
production rules) is actually implemented using what you call a typed
tagless-final embedding. I see the technique as an encoding of
*recursion* in a typed tagless final object language in such a way
that the recursion is observable in the host language.

Suppose you have the following (logically inconsistent ;)) code (in
Haskell notation):
  term1 :: Int
  term1 = if term2 then 1 else 2
  term2 :: Bool
  term2 = term1 == 2

and you want to model it in the typed tagless final encoding of simply
typed lambda calculus from the examples in your online typed tagless
final lecture notes [1] extended with implicit arbitrary recursion.
Then you could do

  data Term1
  data Term2

  data TermDomain ix where
   Term1 :: TermDomain Term1
   Term2 :: TermDomain Term2

  data family TermVal ix
  newtype instance TermVal Term1 = TV1 {unTV1 :: Int}
  newtype instance TermVal Term2 = TV2 {unTV2 :: Bool}

  class ExtraSymantics repr where
if_ :: repr h Bool - repr h a - repr h a - repr h a
eq_int :: repr h Int - repr h Int - repr h Bool

  class RecSymantics repr phi | repr - phi where
ref :: phi ix - repr h (TermVal ix)

  terms :: (Functor (repr h), Symantics repr, ExtraSymantics repr,
RecSymantics repr TermDomain) = TermDomain ix - repr h
(TermVal ix)
  terms Term1 = fmap TV1 $ if_ (fmap unTV2 (ref Term2)) (int 1) (int 2)
  terms Term2 = fmap TV2 $ eq_int (fmap unTV1 (ref Term1)) (int 2)

In this way, the embedding models the object language recursion in
such a way that the recursion remains observable in the host language
because you can implement it the way you want in your RecSymantics
instance. Possible needs for this observable recursion could be that
you want to do some form of recursion depth-bounded evaluation or some
form of static analysis or whatever... Such modifications are
fundamentally impossible if you model object language recursion
naively using direct host language recursion.

For my parsing library, I need these techniques to get a good view on
the recursion in the grammar. This allows me perform grammar
transformations and analysis.

Dominique

Footnotes:
[1]  http://okmij.org/ftp/tagless-final/course/#infin1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] pointers for EDSL design

2010-10-11 Thread Dominique Devriese
John, Oleg,

2010/10/9  o...@okmij.org:
 So here's a very simple expression:

 t1 = let v = sigGen (cnst 1) in outs v v

 which is what led to my question.  I'm binding the sigGen to 'v' to
 introduce sharing at the meta-level.  Would it be better to introduce
 support for this in the dsl?

 Often this is not a question of preference but that of
 necessity. Sharing at the meta-level may help the generator, but it
 does _not_ translate into the sharing at the object level. In the
 generated code, the code for 'sigGen (cnst 1)' shall be
 duplicated. It could be that two csound blocks must share the same
 signal source, to receive samples in parallel. Meta-level sharing
 (Haskell's let) would not do. We need a construct for an object-level
 let, for example

  t1 = let_ (SigGen (cnst 1)) (\v - outs v v)

An alternative approach to model sharing at the object level is the
technique I use for modelling context-free grammars in my PADL 2011
paper Explicitly Recursive Grammar Combinators [1] (just got
acceptance notification this morning!). The idea is basically that you make the
sharing in the object-level expression explicit by modelling all
your terms as the results of one big recursive function and then
opening up the recursion. Using ideas from the Multirec generic
programming library and some recent Haskell type system extensions
(most importantly GADTs and type families), you can do this in a
well-typed way for sets of mutually recursive object-level
expressions.

In this case, you would get something like the following (written
without any understanding of your problem domain, so sorry if I
interpret stuff wrong here ;) ):

data I1
data T1
data CircuitNode ix where
   I1 :: CircuitNode I1
   T1 :: CircuitNode T1

myCircuit self I1 = sigGen (cnst 1)
myCircuit self T1 = outs (self I1) (self I1)

With a type class such as RecProductionRule in my paper, you can then
even get rid of the self argument and get something like this:

myCircuit I1 = sigGen (cnst 1)
myCircuit T1 = outs (ref I1) (ref I1)

The main advantage is that this approach extends to circuits with
mutually recursive nodes, but contrary to simple meta-level sharing,
allows you to observe and manipulate the recursive structure of the
circuit. Oh, and it stays properly typed. More info in the paper and
the accompanying technical report [2].

cheers
Dominique

Footnotes:
[1]  
http://people.cs.kuleuven.be/~dominique.devriese/permanent/cfgc-submitted-PADL.pdf
[2]  http://www.cs.kuleuven.be/publicaties/rapporten/cw/CW594.abs.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] pointers for EDSL design

2010-10-08 Thread oleg

John Lato wrote:

 So here's a very simple expression:

 t1 = let v = sigGen (cnst 1) in outs v v

 which is what led to my question.  I'm binding the sigGen to 'v' to
 introduce sharing at the meta-level.  Would it be better to introduce
 support for this in the dsl?

Often this is not a question of preference but that of
necessity. Sharing at the meta-level may help the generator, but it
does _not_ translate into the sharing at the object level. In the
generated code, the code for 'sigGen (cnst 1)' shall be
duplicated. It could be that two csound blocks must share the same
signal source, to receive samples in parallel. Meta-level sharing
(Haskell's let) would not do. We need a construct for an object-level
let, for example

  t1 = let_ (SigGen (cnst 1)) (\v - outs v v)

(Template Haskell can improve the syntax.)

The term `off-shoring' was coined by Walid Taha and collaborators, and
first appeared in the paper 
Implicitly Heterogeneous Multi-Stage Programming. GPCE'05
(whose first draft was written in Feb 2004).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] pointers for EDSL design

2010-10-06 Thread John Lato
Hi Stephen,


 From: Stephen Tetley stephen.tet...@gmail.com

 Hi John

 For the user level stuff, I don't think CSound really has functions
 - either for the score or orchestra. The score I think is just a list
 of /notes/ with many, many parameters and the orchestra is a graph
 description saying how the UGens are connected.



This is good news - I believe Pan, Feldspar, Lava etc. generate
 functions or procedures in the output code which means they have to
 involve the complicated techniques for embedding lambdas and functions
 in the EDSL. If they didn't, there would be massive code blow up.
 However because CSound is more or less straight line code - i.e.
 lines are interpreted sequentially, there are no procedures or
 functions to define and call - generating it should be much simpler.


Yes, exactly.  I'm not interested in anything nearly as sophisticated, so
 those aren't great examples for me.


 Andy Gill's Dot package on Hackage has a crafty, but simple technique
 to allow you to reference graph nodes and link them within a monad and
 output as foreign code - here dot files. Something similar might be
 satisfactory for orchestra files.


The orchestra graph is basically the issue I'm looking at (ignoring the
score for now).  My first implementation used an Orch monad very similar to
the one used in Andy Gill's dotgen.  It worked and the implementation was
very straightforward, however I wanted to see if it was possible to create a
non-monadic interface.  That is, change my classes from

class GenM repr a where
  sigGenM :: a - repr (ASig repr)

to

class Gen repr a where
  sigGen :: repr a - repr (ASig repr)

This is in tagless-final style (which really is slick BTW); that's why
everything is represented through type classes.

The second version is really the one I want to use, although it was more
work to implement.  For the Csound interpreter, I needed a naming mechanism
like TH's Q monad, along with some other machinery.

So here's a very simple expression:

t1 = let v = sigGen (cnst 1) in outs v v

which is what led to my question.  I'm binding the sigGen to 'v' to
introduce sharing at the meta-level.  Would it be better to introduce
support for this in the dsl?

Anyway, here are a few simple test expressions to provide the flavor of what
I'm doing:

-- additive synthesis, 20 partials of constant amplitude
t6 = let so = sum . zipWith (oscil (cnst 1000)) [ cnst (110*f) | f - [4..]]
(replicate 20 1)
in outs so so

-- stacked frequency modulation using 4 oscillators
t8 = let stack = foldr ($) (csig 40) (replicate 4 \fq - oscil (cnst 1000)
fq 1) in outs stack stack

The edsl provides the functions oscil, cnst, csig, and outs, but
most of the magic happens in the csound interpreter.

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


Re: [Haskell-cafe] pointers for EDSL design

2010-10-06 Thread Henning Thielemann
John Lato schrieb:
 Thanks for these, and also Stephen's extensive list.  I think it's fair
 to say that I'm just exploring the space and don't know what I'm doing
 yet.  As such, I'm pretty open to exploring ideas.  I'm only familiar
 with a small fraction of these, so I've got some reading to do now! 
 
 For my toy language I've been working on a csound-like DSP language
 which is compiled to Csound code (I am slightly familiar with Atom, and
 moreso with Feldspar, but they're both quite different in usage style
 from what I'm aiming at).  Essentially the Csound module from Haskore,
 but less verbose and typed.  I've implemented it in a final-tagless
 style (at least as far as I understand Kiselyov, Carette, and Shan),
 which has the very nice benefit that even though I'm currently
 targetting csound I could target other languages relatively simply.

Have I already advertised my realtime LLVM sound signal processing package?

http://arxiv.org/abs/1004.4796
http://hackage.haskell.org/package/synthesizer-llvm
http://www.youtube.com/watch?v=GNiAqBTVa6U

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


[Haskell-cafe] pointers for EDSL design

2010-10-05 Thread John Lato
Hello,

I'm working on a prototype edsl (my first one), and I was wondering if there
are any resources that discuss pros and cons of various implementation
issues?  I'm trying to decide what should be included in the edsl vs.
re-using the meta language implementations (e.g. let-binding, lambdas).
 Most of the examples I've found are for full DSL's, not EDSL's, so it's not
clear what the best approach is.  The LLVM interface is sort of close to
what I intend, except it creates a very imperative style whereas I'm aiming
for something more functional.

A little background: I decided on a dsl because I intend to make heavy use
of Haskell functions from Data.List and Control.Monad.  If I made a full DSL
I would need to re-implement much of that functionality, so I thought it
would be more sensible to use an edsl.

Any advice or references would be very much appreciated.

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


Re: [Haskell-cafe] pointers for EDSL design

2010-10-05 Thread C K Kashyap
 Any advice or references would be very much appreciated.
 Best,

Please check out the EDSL around the software build domain -
* slides http://www.galois.com/~dons/talks/hiw-2010/ndm-shake.pdf
* video  http://www.vimeo.com/15465133

This one is around the music composition domain
http://www.haskell.org/haskore/onlinetutorial/index.html

I could not gather the domain you are trying to target.

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


Re: [Haskell-cafe] pointers for EDSL design

2010-10-05 Thread Stephen Tetley
Hello John

If you are wanting variables, lambdas ... it sounds like you might be
off-shoring - i.e. building a little language within Haskell that is
executed on something else GPU (compiled to CUDA), compiled to C,
compiled to VHDL, etc.

Generally this is a deep-embedding as you need to produce output
code for the target system.

There are many papers on this - as for a survey of techniques there is
one by Keon Claessen and Gordon Pace that gives an (albeit brief)
comparison of shallow and deep embedding for Hardware EDSLs -
Embedded Hardware Description Languages: Exploring the Design Space.
Also, the recent Kansas Lava combines a shallow embedding and a deep
embedding so it can run in Haskell but compile to Verilog or
VHDL(?). Andy Gill and colleagues have various papers describing its
design.

Robert Atkey and co-authors had a paper at the 2009 Haskell Symposium
Unembedding domain-specific languages.

Conal Elliott's Pan was one of the first Haskell offshore DSLs (maybe
the first?), there is a paper Compiling Embedded Languages written
with Sigborn Finne and Oege de Moor. The authors acknowledge Samuel
Kamin's previous work in ML. Later Conal Elliott had a paper
describing Vertigo on GPUs.

Quite a few papers have popped up recently about off-shoring subsets
of Haskell to GPUs, see Joel Svensson's Obsidian and GPUgen by Manuel
M. T. Chakravarty and colleagues.

Oleg Kiselyov, Jacques Carette and Chung-chieh Shan have papers
describing embedded DSLs in the tagless style. There are also papers
by Jacques Carette and Oleg Kiselyov describing deep embedding in
Ocaml - I think they coined the term off-shoring, here's one:

http://www.cas.mcmaster.ca/~carette/publications/scp_metamonads.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] pointers for EDSL design

2010-10-05 Thread Sterling Clover
Stephen's list is great! Two more points of reference from the recent ICFP -- 
Geoff Mainland's Nikola [1], and a nice talk on Kansas Lava [2].

[1] http://www.eecs.harvard.edu/~mainland/publications/
[2] http://www.scribd.com/doc/38559736/kansaslava-hiw10 -- hopefully the video 
from the implementor's workshop to appear soon.

I suspect however, that it will prove hard to impossible to reuse Data.List and 
Control.Monad functions directly. You don't want to invoke functions at compile 
time, but represent invocations. 

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


Re: [Haskell-cafe] pointers for EDSL design

2010-10-05 Thread John Lato
Thanks for these, and also Stephen's extensive list.  I think it's fair to
say that I'm just exploring the space and don't know what I'm doing yet.  As
such, I'm pretty open to exploring ideas.  I'm only familiar with a small
fraction of these, so I've got some reading to do now!

For my toy language I've been working on a csound-like DSP language which is
compiled to Csound code (I am slightly familiar with Atom, and moreso with
Feldspar, but they're both quite different in usage style from what I'm
aiming at).  Essentially the Csound module from Haskore, but less verbose
and typed.  I've implemented it in a final-tagless style (at least as far as
I understand Kiselyov, Carette, and Shan), which has the very nice benefit
that even though I'm currently targetting csound I could target other
languages relatively simply.

When I said I wanted to use functions from Data.List and Control.Monad, I
meant that I wanted to use them to manipulate expressions in the edsl, which
has worked very well so far.  In fact everything has worked so well, and has
been so simple to implement, that I figure I must be missing something
important.

John

On Tue, Oct 5, 2010 at 4:29 PM, Sterling Clover s.clo...@gmail.com wrote:

 Stephen's list is great! Two more points of reference from the recent ICFP
 -- Geoff Mainland's Nikola [1], and a nice talk on Kansas Lava [2].

 [1] http://www.eecs.harvard.edu/~mainland/publications/
 [2] http://www.scribd.com/doc/38559736/kansaslava-hiw10 -- hopefully the
 video from the implementor's workshop to appear soon.

 I suspect however, that it will prove hard to impossible to reuse Data.List
 and Control.Monad functions directly. You don't want to invoke functions at
 compile time, but represent invocations.

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


Re: [Haskell-cafe] pointers for EDSL design

2010-10-05 Thread Stephen Tetley
Hi John

For the user level stuff, I don't think CSound really has functions
- either for the score or orchestra. The score I think is just a list
of /notes/ with many, many parameters and the orchestra is a graph
description saying how the UGens are connected.

This is good news - I believe Pan, Feldspar, Lava etc. generate
functions or procedures in the output code which means they have to
involve the complicated techniques for embedding lambdas and functions
in the EDSL. If they didn't, there would be massive code blow up.
However because CSound is more or less straight line code - i.e.
lines are interpreted sequentially, there are no procedures or
functions to define and call - generating it should be much simpler.

Andy Gill's Dot package on Hackage has a crafty, but simple technique
to allow you to reference graph nodes and link them within a monad and
output as foreign code - here dot files. Something similar might be
satisfactory for orchestra files.


Of course if you want to generate UGens in C things get complicated
again, but you still might be able to generate UGens as single
monolithic functions. I think Roger Dannenberg's Nyquist generates
UGens in this way from a Scheme like macro language, but its a long
time since I looked at it.

Best wishes

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