GHC porting to FreeBSD-amd64 progress report

Wilhelm B. Kloke wb at arb-phys.uni-dortmund.de
Fri Nov 30 07:09:16 EST 2007


Simon Marlow <simonmarhaskell at gmail.com> schrieb:
>
> Perhaps you compiled mkDerivedConstants as a 32-bit executable?

Yes. I was not attentive enough.

But now I have got a working compiler on FreeBSD-amd64-7.0. If anybody is
interested, I shall prepare a package of the installed binaries.

The compiler is good enough to compile itself now. Though there are
problems remaining. One the programs I tested the computation of
Meertens numbers from Bird/Wadler's book. This program segfaults on
amd64, but not on i386.

Here it is:

module Main(main,primes,sieve,meertens) where

-- a Meertens number is one whose decimal representation conincides with
-- its Gödel number
-- The 1st is 81312000 = 2^8*3*5^3*7*11^2

main :: IO()
main = do
        putStr ( show ( meertens 8 ) )
--      putStr ( show ( meertens 9 ) )

primes= sieve [2..]
sieve (p : nos) = p: sieve(remove (multsof p) nos )
                  where multsof p n = n `rem` p == 0
remove p        = filter (not.p)
powers p        = iterate (p*) 1

meertens k = [n| (n,g) <- candidates (0,1),n == g ]
  where
  candidates            = concat . map ( search pps ) . tail . labels ps
  ps : pps              = map powers ( take k primes )
  search [] x           = [x]
  search (ps : pps) x   = concat ( map ( search pps ) (labels ps x ))
  labels ps (n,g)       = zip ( map (m+) ds)(chop(map(g*)ps))
                          where m = 10 * n
  chop                  = takeWhile(< 10000000000)
  ds                    = [0..9]

-- 
Dipl.-Math. Wilhelm Bernhard Kloke
Institut fuer Arbeitsphysiologie an der Universitaet Dortmund
Ardeystrasse 67, D-44139 Dortmund, Tel. 0231-1084-257
PGP: http://vestein.arb-phys.uni-dortmund.de/~wb/mypublic.key



More information about the Glasgow-haskell-users mailing list