Difference between revisions of "Runtime compilation"

From HaskellWiki
Jump to navigation Jump to search
m (RuntimeCompilation moved to Runtime compilation)
(Haskell-Code markup, Category:Idioms, Links)
Line 1: Line 1:
 
'''Note: This article was written by Andrew Bromage and originally appeared at http://haskell.org/wikisnapshot/RunTimeCompilation.html'''
 
'''Note: This article was written by Andrew Bromage and originally appeared at http://haskell.org/wikisnapshot/RunTimeCompilation.html'''
   
Many algorithms require a pre-processing step which builds some data structure for later use in the algorithm proper. Consider making this pre-processing step build a Haskell function instead. In other words, use FunctionsNotDataStructures.
+
Many algorithms require a pre-processing step which builds some data structure for later use in the algorithm proper. Consider making this pre-processing step build a Haskell function instead. In other words, use [[Functions not data structures]].
   
Consider, for example, KnuthMorrisPratt? substring searching. In a conventional language, the approach would be to compile the string to be searched for into an array of overlaps (this is the pre-processing step) which the search algorithm then uses to actually perform the match. One benefit is that if you need to search for the same substring multiple times, you can share the pre-processing step.
+
Consider, for example, [[Knuth-Morris-Pratt substring search]]ing. In a conventional language, the approach would be to compile the string to be searched for into an array of overlaps (this is the pre-processing step) which the search algorithm then uses to actually perform the match. One benefit is that if you need to search for the same substring multiple times, you can share the pre-processing step.
   
However, consider how you'd implement substring searching if speed were crucial and the string were fixed at compile time. Suppose, for example, you wanted to search for "aab". You might write something like this (note that this uses the NotJustMaybe idiom):
+
However, consider how you'd implement substring searching if speed were crucial and the string were fixed at compile time. Suppose, for example, you wanted to search for "aab". You might write something like this (note that this uses the [[Not just Maybe]] idiom):
   
  +
<haskell>
> search :: (Monad m) => String -> m (String, String)
 
  +
> search cs
 
  +
search :: (Monad m) => String -> m (String, String)
> = search_aab [] cs
 
  +
search cs
> where
 
  +
= search_aab [] cs
> search_fail = fail "can't find aab"
 
  +
where
>
 
  +
search_fail = fail "can't find aab"
> search_aab prev [] = search_fail
 
  +
> search_aab prev (c@'a':cs)
 
  +
search_aab prev [] = search_fail
> = search_ab (c:prev) cs
 
> search_aab prev (c:cs)
+
search_aab prev (c@'a':cs)
> = search_aab (c:prev) cs
+
= search_ab (c:prev) cs
  +
search_aab prev (c:cs)
>
 
  +
= search_aab (c:prev) cs
> search_ab prev [] = search_fail
 
  +
> search_ab prev (c@'a':cs)
 
  +
search_ab prev [] = search_fail
> = search_b (c:prev) cs
 
> search_ab prev (c:cs)
+
search_ab prev (c@'a':cs)
> = search_aab prev (c:cs)
+
= search_b (c:prev) cs
  +
search_ab prev (c:cs)
>
 
  +
= search_aab prev (c:cs)
> search_b prev [] = search_fail
 
  +
> search_b prev (c@'b':cs)
 
  +
search_b prev [] = search_fail
> = return (reverse (c:prev), cs)
 
> search_b prev (c:cs)
+
search_b prev (c@'b':cs)
  +
= return (reverse (c:prev), cs)
> = search_ab prev (c:cs) -- Note special case here
 
  +
search_b prev (c:cs)
  +
= search_ab prev (c:cs) -- Note special case here
  +
  +
</haskell>
   
 
It's not too hard to think of how to write a preprocessor to do this, since the translation is mechanical. However, if you're clever, you can do this compilation at run time.
 
It's not too hard to think of how to write a preprocessor to do this, since the translation is mechanical. However, if you're clever, you can do this compilation at run time.
Line 37: Line 41:
 
[TODO: Clean the code up a bit.]
 
[TODO: Clean the code up a bit.]
   
  +
<haskell>
> overlap :: (Eq a) => [a] -> [Int]
 
> overlap str
 
> = overlap' [0] str
 
> where
 
> overlap' prev []
 
> = reverse prev
 
> overlap' prev (x:xs)
 
> = let get_o o
 
> | o <= 1 || str !! (o-2) == x = o
 
> | otherwise = get_o (1 + prev !! (length prev - o + 1))
 
> in overlap' (get_o (head prev + 1):prev) xs
 
   
  +
overlap :: (Eq a) => [a] -> [Int]
Then using this, we build up a Haskell function using ContinuationPassingStyle to handle the failure states:
 
  +
overlap str
  +
= overlap' [0] str
  +
where
  +
overlap' prev []
  +
= reverse prev
  +
overlap' prev (x:xs)
  +
= let get_o o
  +
| o <= 1 || str !! (o-2) == x = o
  +
| otherwise = get_o (1 + prev !! (length prev - o + 1))
  +
in overlap' (get_o (head prev + 1):prev) xs
   
  +
</haskell>
> matchKMP :: (Monad m, Eq a) => [a] -> ([a] -> m ([a],[a]))
 
  +
> matchKMP []
 
  +
Then using this, we build up a Haskell function using [[Continuation passing style]] to handle the failure states:
> = error "Can't match empty list"
 
  +
> matchKMP xs
 
  +
<haskell>
> = matchfunc []
 
  +
> where
 
  +
matchKMP :: (Monad m, Eq a) => [a] -> ([a] -> m ([a],[a]))
> matchfunc = makeMatchFunc [dofail] (zip xs (overlap xs))
 
  +
matchKMP []
> dofail = \ps xs -> case xs of
 
> [] -> fail "can't match"
+
= error "Can't match empty list"
  +
matchKMP xs
> (y:ys) -> matchfunc (y:ps) ys
 
  +
= matchfunc []
>
 
  +
where
> type PartialMatchFunc? m a = [a] -> [a] -> m ([a], [a])
 
  +
matchfunc = makeMatchFunc [dofail] (zip xs (overlap xs))
>
 
  +
dofail = \ps xs -> case xs of
> makeMatchFunc :: (Monad m, Eq a) => [PartialMatchFunc? m a] -> [(a, Int)]
 
  +
[] -> fail "can't match"
> -> PartialMatchFunc? m a
 
  +
(y:ys) -> matchfunc (y:ps) ys
> makeMatchFunc prev []
 
  +
> = \ps xs -> return (reverse ps, xs)
 
  +
type PartialMatchFunc m a = [a] -> [a] -> m ([a], [a])
> makeMatchFunc prev ((x,failstate):ms)
 
  +
> = thisf
 
  +
makeMatchFunc :: (Monad m, Eq a) => [PartialMatchFunc m a] -> [(a, Int)]
> where
 
  +
-> PartialMatchFunc m a
> mf = makeMatchFunc (thisf:prev) ms
 
  +
makeMatchFunc prev []
> failcont = prev !! (length prev - failstate - 1)
 
> thisf = \ps xs -> case xs of
+
= \ps xs -> return (reverse ps, xs)
  +
makeMatchFunc prev ((x,failstate):ms)
> [] -> fail "can't match"
 
  +
= thisf
> (y:ys) -> if (x == y) then mf (y:ps) ys
 
  +
where
> else failcont ps xs
 
  +
mf = makeMatchFunc (thisf:prev) ms
  +
failcont = prev !! (length prev - failstate - 1)
  +
thisf = \ps xs -> case xs of
  +
[] -> fail "can't match"
  +
(y:ys) -> if (x == y) then mf (y:ps) ys
  +
else failcont ps xs
  +
  +
</haskell>
   
 
We can now either use it as a standard substring match function:
 
We can now either use it as a standard substring match function:
   
  +
<haskell>
> matchKMP "aab" "babaaba"
 
  +
  +
matchKMP "aab" "babaaba"
  +
  +
</haskell>
   
 
or we can use currying to share the compiled function:
 
or we can use currying to share the compiled function:
   
  +
<haskell>
> match_aab :: (Monad m) => String -> m (String, String)
 
> match_aab = matchKMP "aab"
 
   
  +
match_aab :: (Monad m) => String -> m (String, String)
This latter example only compiles the KMP machine once and, thanks to LazyEvaluation?, it's only compiled if it's ever used.
 
  +
match_aab = matchKMP "aab"
   
  +
</haskell>
Getting recursion into your generated code can be hard. The above examplewas relatively simple, but in the general case you may need something more sophisticated. See TyingTheKnot for some ideas.
 
   
  +
This latter example only compiles the KMP machine once and, thanks to [[Lazy evaluation]], it's only compiled if it's ever used.
Caveat: This technique is considered by many to be a hack at best, and a kludge at worst. Things can get very fiddly and extremely hard to debug. RunTimeCompilation can sometimes win you significant efficiency gains, but can often win you almost nothing (at the cost of the your increased stress and reduced productivity). It's almost always worth implementing your algorithm the naive way first and only then if it's found to be the bottleneck, hand-compiling a few examples first to see if that speeds things up sufficiently.
 
  +
  +
Getting recursion into your generated code can be hard.
  +
The above example was relatively simple, but in the general case you may need something more sophisticated.
  +
See [[Tying the knot]] for some ideas.
  +
  +
Caveat: This technique is considered by many to be a hack at best, and a kludge at worst. Things can get very fiddly and extremely hard to debug. [[Runtime compilation]] can sometimes win you significant efficiency gains, but can often win you almost nothing (at the cost of the your increased stress and reduced productivity). It's almost always worth implementing your algorithm the naive way first and only then if it's found to be the bottleneck, hand-compiling a few examples first to see if that speeds things up sufficiently.
   
 
You have been warned.
 
You have been warned.
   
-- AndrewBromage?
+
-- AndrewBromage
  +
  +
[[Category:Idioms]]

Revision as of 15:24, 9 November 2007

Note: This article was written by Andrew Bromage and originally appeared at http://haskell.org/wikisnapshot/RunTimeCompilation.html

Many algorithms require a pre-processing step which builds some data structure for later use in the algorithm proper. Consider making this pre-processing step build a Haskell function instead. In other words, use Functions not data structures.

Consider, for example, Knuth-Morris-Pratt substring searching. In a conventional language, the approach would be to compile the string to be searched for into an array of overlaps (this is the pre-processing step) which the search algorithm then uses to actually perform the match. One benefit is that if you need to search for the same substring multiple times, you can share the pre-processing step.

However, consider how you'd implement substring searching if speed were crucial and the string were fixed at compile time. Suppose, for example, you wanted to search for "aab". You might write something like this (note that this uses the Not just Maybe idiom):

search :: (Monad m) => String -> m (String, String)
search cs
	= search_aab [] cs
	where
	search_fail = fail "can't find aab"

	search_aab prev [] = search_fail
	search_aab prev (c@'a':cs)
	 = search_ab (c:prev) cs
	search_aab prev (c:cs)
	 = search_aab (c:prev) cs

	search_ab prev [] = search_fail
	search_ab prev (c@'a':cs)
	 = search_b (c:prev) cs
	search_ab prev (c:cs)
	 = search_aab prev (c:cs)

	search_b prev [] = search_fail
	search_b prev (c@'b':cs)
	 = return (reverse (c:prev), cs)
	search_b prev (c:cs)
	 = search_ab prev (c:cs)	-- Note special case here

It's not too hard to think of how to write a preprocessor to do this, since the translation is mechanical. However, if you're clever, you can do this compilation at run time.

This Haskell function builds the KMP overlap table:

[TODO: Clean the code up a bit.]

overlap :: (Eq a) => [a] -> [Int]
overlap str
	= overlap' [0] str
	where
	overlap' prev []
	 = reverse prev
	overlap' prev (x:xs)
	 = let get_o o
		 | o <= 1 || str !! (o-2) == x = o
		 | otherwise = get_o (1 + prev !! (length prev - o + 1))
		in overlap' (get_o (head prev + 1):prev) xs

Then using this, we build up a Haskell function using Continuation passing style to handle the failure states:

matchKMP :: (Monad m, Eq a) => [a] -> ([a] -> m ([a],[a]))
matchKMP []
	= error "Can't match empty list"
matchKMP xs
	= matchfunc []
	where
	matchfunc = makeMatchFunc [dofail] (zip xs (overlap xs))
	dofail = \ps xs -> case xs of
				[] -> fail "can't match"
				(y:ys) -> matchfunc (y:ps) ys

type PartialMatchFunc m a = [a] -> [a] -> m ([a], [a])

makeMatchFunc :: (Monad m, Eq a) => [PartialMatchFunc m a] -> [(a, Int)]
		-> PartialMatchFunc m a
makeMatchFunc prev []
	= \ps xs -> return (reverse ps, xs)
makeMatchFunc prev ((x,failstate):ms)
	= thisf
	where
	mf = makeMatchFunc (thisf:prev) ms
	failcont = prev !! (length prev - failstate - 1)
	thisf = \ps xs -> case xs of
				[] -> fail "can't match"
				(y:ys) -> if (x == y) then mf (y:ps) ys
						else failcont ps xs

We can now either use it as a standard substring match function:

matchKMP "aab" "babaaba"

or we can use currying to share the compiled function:

match_aab :: (Monad m) => String -> m (String, String)
match_aab = matchKMP "aab"

This latter example only compiles the KMP machine once and, thanks to Lazy evaluation, it's only compiled if it's ever used.

Getting recursion into your generated code can be hard. The above example was relatively simple, but in the general case you may need something more sophisticated. See Tying the knot for some ideas.

Caveat: This technique is considered by many to be a hack at best, and a kludge at worst. Things can get very fiddly and extremely hard to debug. Runtime compilation can sometimes win you significant efficiency gains, but can often win you almost nothing (at the cost of the your increased stress and reduced productivity). It's almost always worth implementing your algorithm the naive way first and only then if it's found to be the bottleneck, hand-compiling a few examples first to see if that speeds things up sufficiently.

You have been warned.

-- AndrewBromage