Re: [Haskell-cafe] ANNOUNCE: feldspar-language

2009-11-25 Thread Emil Axelsson

(In response to Tom Hawkins' posting of an IIR filter in Atom)

We're still experimenting with how to best describe streaming 
computations with feedback in Feldspar. But for completeness, here one 
possible implementation of an IIR filter:



iir :: forall m n o a . (NaturalT m, NaturalT n, NaturalT o, Num a , Primitive a) 
=
VectorP m a - VectorP n a - VectorP o a - VectorP o a

iir as bs = feedback f
  where
f :: VectorP o a - VectorP o a - Data a
f inPrev outPrev = dotProd as (resize inPrev) - dotProd bs (resize outPrev)



(Please don't mind the type clutter -- we hope to get rid of most of it 
in the future.)


The local function `f` computes a single output, and the `feedback` 
combinator applies `f` across the input stream. You can find the 
resulting C code attached. As you can see, the generated C has lots of 
room for optimization, but the time complexity is right (one top-level 
loop with two inner loops in sequence). We plan to tackle the more 
small-scale optimizations in the future.


The dot product is defined in standard Haskell style:


dotProd :: (Num a, Primitive a) = VectorP n a - VectorP n a - Data a
dotProd as bs = fold (+) 0 (zipWith (*) as bs)


Interestingly, `feedback` is also defined within Feldspar:


feedback :: forall n a . (NaturalT n, Storable a) =
(VectorP n a - VectorP n a - Data a) - VectorP n a - VectorP n a

feedback f inp = unfreezeVector (length inp) outArr'
  where
outArr :: Data (n : a)
outArr = array []

outArr' = for 0 (length inp - 1) outArr $ \i arr -
  let prevInps  = reverse $ take (i+1) inp
  prevOutps = reverse $ take i $ unfreezeVector i arr
  a = f prevInps prevOutps
   in setIx arr i a


This definition uses low-level data structures and loops, and this is 
not something that ordinary Feldspar users should write. It is our hope 
that a few combinators like this one can be defined once and for all, 
and then reused for a wide range of DSP applications.


It turns out that FIR filters are much nicer :)


fir :: (NaturalT m, Num a , Primitive a) =
VectorP m a - VectorP n a - VectorP n a

fir coeffs = map (dotProd coeffs . resize . reverse) . inits


C code attached.

/ Emil


#include feldspar.h

void fir( signed int var0_0_0, signed int var0_0_1[10], signed int var0_1_0, signed int var0_1_1[100], signed int *out_0, signed int out_1[100] )
{
signed int var23[100];

{
int var1;
for( var1 = 0; var1  var0_1_0; var1 += 1)
{
signed int var7;
int var8;
signed int var9;
int var10;
signed int var11;
signed int var12;
signed int var17;
signed int var22_0;

var7 = (var1 + 1);
var8 = (var0_1_0 = var7);
if(var8)
{

var9 = var0_1_0;
}
else
{

var9 = var7;
}
var10 = (var0_0_0 = var9);
if(var10)
{

var11 = var0_0_0;
}
else
{

var11 = var9;
}
var12 = (var11 - 1);
var17 = (var9 - 1);
var22_0 = 0;
var23[var1] = 0;
{
int var13;

var13 = (var22_0 = var12);
while(var13)
{

var23[var1] = (var23[var1] + (var0_0_1[var22_0] * var0_1_1[(var17 - var22_0)]));
var22_0 = (var22_0 + 1);
var13 = (var22_0 = var12);
}
}
}
}
*out_0 = var0_1_0;
copy_arrayOf_signed_int((var23[0]), 100, (out_1[0]));
}

#include feldspar.h

void iir( signed int var0_0_0, signed int var0_0_1[10], signed int var0_1_0, signed int var0_1_1[10], signed int var0_2_0, signed int var0_2_1[100], signed int *out_0, signed int out_1[100] )
{
signed int var3;
signed int var51_0;
signed int var51_1[100];
signed int var53[100];

var3 = (var0_2_0 - 1);
var51_0 = 0;
copy_arrayOf_signed_int(({}[0]), 100, (var51_1[0]));
{
int var4;

var4 = (var51_0 = var3);
while(var4)
{
signed int var12;
int var13;
signed int var14;
int var15;
signed int var16;
signed int var17;
signed int var22;
signed int var27_0;
signed int var27_1;
int var33;
signed int var34;
int var35;
signed int var36;
signed int var37;
signed int var42;
signed int var47_0;
signed int var47_1;
signed int var49[100];

var12 = (var51_0 + 1);
var13 = (var0_2_0 = var12);
if(var13)
{

var14 = var0_2_0;
}
else
{

var14 = var12;
 

Re: [Haskell-cafe] ANNOUNCE: feldspar-language

2009-11-19 Thread Warren Henning
Interesting to see actual generated code.

Is this like code generation systems for database applications where
you stick stuff into string templates (e.g., a generator in Ruby on
Rails), or is it actually compiling an embedded domain specific
language?

On Thu, Nov 19, 2009 at 6:55 PM, Tom Hawkins tomahawk...@gmail.com wrote:
 Yes, but only by creating a custom primitive (see 'action').  But then
 you're writing in C, not Atom.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: feldspar-language

2009-11-19 Thread Tom Hawkins
On Fri, Nov 20, 2009 at 4:14 AM, Warren Henning
warren.henn...@gmail.com wrote:
 Interesting to see actual generated code.

 Is this like code generation systems for database applications where
 you stick stuff into string templates (e.g., a generator in Ruby on
 Rails), or is it actually compiling an embedded domain specific
 language?

Atom is not a macro expansion language by any stretch.  It does let
you write primitive actions as C strings, but the core of the language
is based on GADTs and type classes.  In fact, the example I posted
contained no custom primitive actions; the C code was rendered purely
from the core datatypes.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: feldspar-language

2009-11-09 Thread Emil Axelsson

Tom Hawkins skrev:

On Fri, Nov 6, 2009 at 6:28 AM, Emil Axelsson e...@chalmers.se wrote:


I'm trying to get realtime signal processing with Haskell for long. I make
progress, but slowly. Has Ericsson ever thought about using Haskell itself
for signal processing? (But I think they already have Erlang?)

No, using Haskell directly is not an option (at least with current compiler
technology). Their performance requirements are very high, and the signal
processors have quite limited memory, so putting a Haskell RTS on them
wouldn't work.


Atom may be another option.  Though it is not intended for high
performance DSP, we do use it for basic signal processing.  Here is an
IIR filter that is used is some fault detection logic on our
application:

-- | IIR filter implemented using direct form 2.
iirFilter :: Name - Float - [(Float, Float)] - E Float - Atom (E Float)
iirFilter name b0 coeffs x = do
  -- Create the filter taps.
  vs - mapM (\ i - float (name ++ show i) 0) [1 .. length coeffs]
  -- Cascade the filter taps together.
  mapM_ (\ (vA, vB) - vA == value vB) $ zip (tail vs) vs
  -- Calculate the input to the chain of taps.
  let w0 = sum ( x :  [ (value v) * Const (-a) | (v, (a, _)) - zip vs coeffs ])
  bs = b0 : (snd $ unzip coeffs)
  ws = w0 : map value vs
  us = [ w * Const b | (w, b) - zip ws bs ]
  head vs == w0
  -- Return the output.
  return $ sum us

http://hackage.haskell.org/package/atom


Nice!

One of our project members has been looking at Atom, not for numerical 
computations, but for real-time scheduling (which Feldspar should deal 
with eventually).


What kind of code (in terms of efficiency) does the above description 
compile to?


/ Emil

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


Re: [Haskell-cafe] ANNOUNCE: feldspar-language

2009-11-09 Thread Tom Hawkins
On Mon, Nov 9, 2009 at 10:09 AM, Emil Axelsson e...@chalmers.se wrote:
 Nice!

 One of our project members has been looking at Atom, not for numerical
 computations, but for real-time scheduling (which Feldspar should deal with
 eventually).

 What kind of code (in terms of efficiency) does the above description
 compile to?

Here's and example:

module Main (main) where

import Language.Atom

main :: IO ()
main = do
  compile filter defaults design
  return ()

design :: Atom ()
design = atom filter $ do
  input  - float' input
  output - float' output
  x - iirFilter filter 1 [(2,3), (4,5)] (value input)
  output == x

-- | IIR filter implemented using direct form 2.
iirFilter :: Name - Float - [(Float, Float)] - E Float - Atom (E Float)
iirFilter name b0 coeffs x = do
 -- Create the filter taps.
 vs - mapM (\ i - float (name ++ show i) 0) [1 .. length coeffs]
 -- Cascade the filter taps together.
 mapM_ (\ (vA, vB) - vA == value vB) $ zip (tail vs) vs
 -- Calculate the input to the chain of taps.
 let w0 = sum ( x :  [ (value v) * Const (-a) | (v, (a, _)) - zip vs coeffs ])
 bs = b0 : (snd $ unzip coeffs)
 ws = w0 : map value vs
 us = [ w * Const b | (w, b) - zip ws bs ]
 head vs == w0
 -- Return the output.
 return $ sum us



Here's the generated C.  Note the filter calculation is done entirely
by function __r0:


static unsigned long long __global_clock = 0;
static const unsigned long __coverage_len = 1;
static unsigned long __coverage[1] = {0};
static unsigned long __coverage_index = 0;
static float __v1 = 0;  /* filter.filter.filter2 */
static float __v0 = 0;  /* filter.filter.filter1 */


/* filter.filter */
static void __r0(void) {
  unsigned char __0 = 1;
  float __1 = 0.0;
  float __2 = input;
  float __3 = __1 + __2;
  float __4 = __v0 /* filter.filter.filter1 */ ;
  float __5 = -2.0;
  float __6 = __4 * __5;
  float __7 = __3 + __6;
  float __8 = __v1 /* filter.filter.filter2 */ ;
  float __9 = -4.0;
  float __10 = __8 * __9;
  float __11 = __7 + __10;
  float __12 = 1.0;
  float __13 = __11 * __12;
  float __14 = __1 + __13;
  float __15 = 3.0;
  float __16 = __4 * __15;
  float __17 = __14 + __16;
  float __18 = 5.0;
  float __19 = __8 * __18;
  float __20 = __17 + __19;
  if (__0) {
__coverage[0] = __coverage[0] | (1  0);
  }
  output = __20;
  __v0 /* filter.filter.filter1 */ = __11;
  __v1 /* filter.filter.filter2 */ = __4;
}


void filter(void) {
  {
static unsigned char __scheduling_clock = 0;
if (__scheduling_clock == 0) {
  __r0();  /* filter.filter */
  __scheduling_clock = 0;
}
else {
  __scheduling_clock = __scheduling_clock - 1;
}
  }

  __global_clock = __global_clock + 1;
}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: feldspar-language

2009-11-05 Thread Henning Thielemann


On Tue, 3 Nov 2009, Warren Henning wrote:


I see that section 4.1 of the user guide -
http://feldspar.sourceforge.net/documents/language/FeldsparLanguage.html#htoc23
- includes an example involving autocorrelation.

Does this mean I could use Feldspare to easily build my own Autotune
program? I love T-Pain and Autotune the News!


There are several packages on hackage for performing signal processing: 
like dsp and fftw, that can assist doing autocorrelation.

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


Re: [Haskell-cafe] ANNOUNCE: feldspar-language

2009-11-05 Thread Henning Thielemann


On Wed, 4 Nov 2009, Emil Axelsson wrote:

I'm happy to announce the first release of Feldspar, which is an embedded 
domain-specific language with associated code generator mainly targeting DSP 
algorithms. The language is developed in cooperation by Ericsson, Chalmers 
University and Eötvös Loránd University.


Feldspar stands for *F*unctional *E*mbedded *L*anguage for *DSP* and 
*PAR*allelism.


The language front-end is available on Hackage:

 http://hackage.haskell.org/package/feldspar-language


I'm trying to get realtime signal processing with Haskell for long. I make 
progress, but slowly. Has Ericsson ever thought about using Haskell itself 
for signal processing? (But I think they already have Erlang?)___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: feldspar-language

2009-11-04 Thread Emil Axelsson
One thing I forgot to make clear in the announcement is that the 
language is still highly experimental, and some obvious things, such as 
complex numbers, are currently missing. So this first release should 
probably not be used for real applications.


However, while I don't know how autotuning works, I don't see why you 
shouldn't be able to code it in Feldspar a few releases from now. I 
don't know if it will be easy though :)


/ Emil



Warren Henning skrev:

I see that section 4.1 of the user guide -
http://feldspar.sourceforge.net/documents/language/FeldsparLanguage.html#htoc23
- includes an example involving autocorrelation.

Does this mean I could use Feldspare to easily build my own Autotune
program? I love T-Pain and Autotune the News!

Warren

On Tue, Nov 3, 2009 at 7:39 PM, Emil Axelsson e...@chalmers.se wrote:

I'm happy to announce the first release of Feldspar, which is an embedded
domain-specific language with associated code generator mainly targeting DSP
algorithms. The language is developed in cooperation by Ericsson, Chalmers
University and Eötvös Loránd University.

Feldspar stands for *F*unctional *E*mbedded *L*anguage for *DSP* and
*PAR*allelism.

The language front-end is available on Hackage:

 http://hackage.haskell.org/package/feldspar-language

The back-end C code generator will be uploaded and announced shortly. For
more information, see:

 http://feldspar.sourceforge.net/

/ Emil

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


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

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


Re: [Haskell-cafe] ANNOUNCE: feldspar-language

2009-11-04 Thread Warren Henning
On Wed, Nov 4, 2009 at 12:53 AM, Emil Axelsson e...@chalmers.se wrote:
 I don't see why you shouldn't
 I don't know

I'll take that as an unqualified yes. Shawty snappin'!

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


Re: [Haskell-cafe] ANNOUNCE: feldspar-language

2009-11-03 Thread Warren Henning
I see that section 4.1 of the user guide -
http://feldspar.sourceforge.net/documents/language/FeldsparLanguage.html#htoc23
- includes an example involving autocorrelation.

Does this mean I could use Feldspare to easily build my own Autotune
program? I love T-Pain and Autotune the News!

Warren

On Tue, Nov 3, 2009 at 7:39 PM, Emil Axelsson e...@chalmers.se wrote:
 I'm happy to announce the first release of Feldspar, which is an embedded
 domain-specific language with associated code generator mainly targeting DSP
 algorithms. The language is developed in cooperation by Ericsson, Chalmers
 University and Eötvös Loránd University.

 Feldspar stands for *F*unctional *E*mbedded *L*anguage for *DSP* and
 *PAR*allelism.

 The language front-end is available on Hackage:

  http://hackage.haskell.org/package/feldspar-language

 The back-end C code generator will be uploaded and announced shortly. For
 more information, see:

  http://feldspar.sourceforge.net/

 / Emil

 ___
 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