[Haskell-cafe] 'Compiling' expression graph into Arrows

Daniel McAllansmith dm.maillists at gmail.com
Tue Aug 29 22:14:40 EDT 2006


Hello,

I have a graph of function applications which I would like to 'compile' into 
an Arrow, specifically the SF Arrow from Yampa.

I'd appreciate any advice on how I might go about this.


The graphs, of which there will be many, will be constructed at runtime and 
will be executed for extended periods of time so execution time will dominate 
compilation time.
The graphs might also need to be passed around and executed 'elsewhere', 
where 'elsewhere' will almost certainly be the same GHC version but maybe on 
different architectures.


The hand-written 'compilation' in the attached file gives a rough idea of 
what I start with and what I need to end up with.


I could just automate the hand-written process by generating the SFs and 
arrow-syntax blocks, write them into a file then call GHC... seems a bit 
cowboyish.

Or, write the graph into a template file that has Template Haskell to generate 
the SFs and arrow-syntax blocks then call GHC... almost as cowboyish?

Or, fold the graph up using loop and arr... probably the simplest, once I get 
rid of my sugar dependency and figure out how to use loop that is ;).

Or, maybe I can actually get the expression graph into a GHC api 
representation somehow and let it work marvels of optimisation on the 
expression before turning it into an arrow.


Any idea on the relative merits of these, or other ideas?

Can GHC optimise arrow code much during compilation, or will code folded up at 
runtime using loop/arr be just as efficient?

Could GHC condense the functions of multiple graph nodes into a single 
function for conversion to an SF arrow?

Will the necessity of introducing delays rule out using GHC to simplify the 
raw expression?



Thanks
Daniel
-------------- next part --------------
{-# OPTIONS -farrows #-}

module ArrowTest where

import Data.Graph.Inductive
--AFRP stuff is from Yampa
import AFRP
import AFRPUtilities

type Delayed = Bool

data MyNode f = MyNode String (Func f)

data Func f
    = Input
    | Func f Delayed

rawNodes = [
    (1, MyNode "A" Input),
    (2, MyNode "B" Input),
    (3, MyNode "C" (Func min True)),
    (4, MyNode "D" (Func (-) False)),
    (5, MyNode "E" (Func (+) True)),
    (6, MyNode "F" (Func max False))
    ]

rawEdges = [
    (1,3,"e1"),
    (1,5,"e2"),
    (2,4,"e3"),
    (3,4,"e4"),
    (4,3,"e5"),
    (4,6,"e6"),
    (5,6,"e7"),
    (6,5,"e8")
    ]

rawGraph :: Gr (MyNode (Int -> Int -> Int)) String
rawGraph = mkGraph rawNodes rawEdges


compiledGraph = proc (a,b) -> do
    d <- scc1 -< (a,b)
    f <- scc2 -< (a,d)
    returnA -< f

scc1 = proc (a,b) -> do
    rec
        c <- sfC -< (a,d)
        d <- sfD -< (b,c)
    returnA -< d

scc2 = proc (a,d) -> do
    rec
        e <- sfE -< (a,f)
        f <- sfF -< (d,e)
    returnA -< f

-- The graphs may be cyclic so delays are introduced such that the resulting
-- function is not infinitely recursive.

-- fby ('followed by'), which comes from Yampa, is used to introduce the delay

sfC = 0 `fby` mkArrow min
sfD = arr mkArrow (-)
sfE = 0 `fby` mkArrow (+)
sfF = arr mkArrow max

mkArrow = arr . uncurry


More information about the Haskell-Cafe mailing list