[Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

Anton Kholomiov anton.kholomiov at gmail.com
Tue Feb 19 12:10:43 CET 2013


I'm glad to announce the package for Common subexpression elimination [1].
It's an implementation of the hashconsig algorithm as described in the
paper
'Implementing Explicit and Finding Implicit Sharing in EDSLs' by Oleg
Kiselyov.

Main point of the library is to define this algorithm in the most generic
way.
You can define the AST for your DSL as fixpoint type[2]. And then all you
need
to use the library is to define the instance for type class `Traversable`.
This idea is inspired by `data-reify` [3] package which you can use to
transform
your ASTs to DAGs too. But it relies on inspection of the references for
values
when `data-fix-cse` doesn't sacrifices the purity.

A short example:

Let's define a tiny DSL for signals

import Data.Fix

type Name = String

type E = Fix Exp

data Exp a = Const Double | ReadPort Name | Tfm Name [a] | Mix a a
  deriving (Show, Eq, Ord)

We can make constant signals, read them from some ports and transform them
(apply some named function to the list of signals) and mix two signals.

Let's define an instance of the Traversable (hence for the Functor and
Foldable)

import Control.Applicative

import Data.Monoid
import Data.Traversable
import Data.Foldable

instance Functor Exp where
  fmap f x = case x of
     Const d -> Const d
     ReadPort n -> ReadPort n
     Mix a b -> Mix (f a) (f b)
     Tfm n as -> Tfm n $ fmap f as

instance Foldable Exp where
  foldMap f x = case x of
     Mix a b -> f a <> f b
     Tfm n as -> mconcat $ fmap f as
     _ -> mempty

instance Traversable Exp where
   traverse f x = case x of
      Mix a b -> Mix <$> f a <*> f b
      Tfm n as -> Tfm n <$> traverse f as
      a -> pure a

Now we can use the functio `cse`

cse :: (Eq<http://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Eq.html#t:Eq>(f
Int<http://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Int.html#t:Int>),
Ord<http://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Ord.html#t:Ord>(f
Int<http://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Int.html#t:Int>),
Traversable<http://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Traversable.html#t:Traversable>f)
=>
Fix<http://hackage.haskell.org/packages/archive/data-fix/0.0.1/doc/html/Data-Fix.html#t:Fix>f
->
Dag<http://hackage.haskell.org/packages/archive/data-fix-cse/0.0.1/doc/html/Data-Fix-Cse.html#t:Dag>f

to transform our AST to DAG. DAG is already sorted.

Later we can define a handy wrapper to hide the details from the client

newtype Sig = Sig { unSig :: E }

You can find examples in the package archive

Extra-Source-Files:
    test/Exp.hs
    test/Impl.hs
    test/Expl.hs

If you want to see a real world example of usage you can find it
in the csound-expression[4]. An edsl for the Csound language.

One side-note form my experience: Fixpoint types can be very flexible.
It's easy to compose them. If suddenly we need to add some extra data
to all cases from the example above we can easily do it with just another
Functor:

Imagine that we want to use a SampleRate value with all signals.
Then we can do it like this:

type E = Fix SampledExp

data SampledExp a = SampledExp SampleRate (Exp a)

then we should define an instance of the type class Traversable
for our new type SampleRate. The Exp doesn't change.

[1] http://hackage.haskell.org/package/data-fix-cse-0.0.1
[2] http://hackage.haskell.org/package/data-fix-0.0.1
[3] http://hackage.haskell.org/package/data-reify
[4] http://hackage.haskell.org/package/csound-expression


Anton
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130219/efd6f905/attachment.htm>


More information about the Haskell-Cafe mailing list