[Haskell-cafe] ANNOUNCE: feldspar-language

Tom Hawkins tomahawkins at gmail.com
Mon Nov 9 12:41:25 EST 2009


On Mon, Nov 9, 2009 at 10:09 AM, Emil Axelsson <emax at 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;
}


More information about the Haskell-Cafe mailing list