开发者

Haskell compile time function calculation

I would like to precalculate values for a function at compile-time.

Example (real function is more complex, didn't try compiling):

base = 10
mymodulus n = 开发者_运维知识库n `mod` base -- or substitute with a function that takes
                            -- too much to compute at runtime
printmodules 0 = [mymodulus 0]
printmodules z = (mymodulus z):(printmodules (z-1))

main = printmodules 64

I know that mymodulus n will be called only with n < 64 and I would like to precalculate mymodulus for n values of 0..64 at compile time. The reason is that mymodulus would be really expensive and will be reused multiple times.


You should use Template Haskell. With TH you can generate code programmatically, at compile time. Your mymodulus is effectively a "template" in this case.

For example, we can rewrite your program as follows, to compute your function statically. first, the main code as usual, but instead of calling your modulus function, it calls a function whose body is a splice that will be generated at compile time:

{-# LANGUAGE TemplateHaskell #-}

import Table

mymodulus n = $(genmodulus 64)

main = mapM_ (print . mymodulus) [0..64]

And the code to generate the table statically:

{-# LANGUAGE TemplateHaskell #-}

module Table where

import Language.Haskell.TH
import Language.Haskell.TH.Syntax

genmodulus :: Int -> Q Exp
genmodulus n = return $ CaseE (VarE (mkName "n"))
                              [ Match (LitP (IntegerL i))
                                      (NormalB (LitE (IntegerL (i `mod` base))))
                                      []
                              | i <- [0..fromIntegral n] ]
    where
        base = 10

This describes the abstract syntax of the case expression, which will be generated at compile time. We simply generate a big switch:

    genmodulus 64
  ======>
    case n of {
      0 -> 0
      1 -> 1
      2 -> 2
      3 -> 3
      4 -> 4
      ...
      64 -> 4 }

You can see what code is generated with -ddump-splices. I've written the template code in direct style. Someone more familiar with TH should be able to make the pattern code simpler.

Another option would be to generate a table of values offline, and just import that data structure.

You might also say why you wish to do this. I assume you have a very complex table-driven function?


I don't know any way to precompile it down to a table lookup (though you may have some luck with TH). An alternative is to generate an a lookup table at runtime with something like

mymodulus' x = lt ! x
    where lt = array (0, 64) [(i, mymodulus i) | i <- [0..64]]


As I remember there is some special behaviour attached to top-level definitions. If you'll try simple example:

primes = 2 : 3 : filter isPrime [5, 7 .. 1000000]
isPrime x = walk (tail primes) where
    walk (y:ys) | (y*y > x) = True
                | (x `mod` y) /= 0 = walk ys
    walk _ = False
main = do
    print $ last primes
    print . last $ init primes

You'll see that first call of (last primes) will initiate calculation of primes and second line will reuse those calculations.

0

上一篇:

下一篇:

精彩评论

暂无评论...
验证码 换一张
取 消

最新问答

问答排行榜