Weird compilation error while doing Euler problems?

'm trying to compile my file that has my Euler problems in it to output the solution to problem four, but I'm getting a compile error. Here's my .hs file: ------------------------- module Euler1 where import Data.List import Data.Ord main = mapM_ putStrLn problem4 problem1 = foldl1' (+) $ nub $ (takeWhile (< 1000) [3,6..] ++ takeWhile (< 1000) [5,10..]) problem2 = sum $ takeWhile (<= 4000000) [x | x <- fibs, even x] where fibs = unfoldr (\(a,b) -> Just (a,(b,a+b))) (0,1) problem3 z = maximumBy compare (filter (\x -> z `mod` x == 0) (takeWhile (<= ceiling (sqrt (fromIntegral z))) primes)) problem4 = nub [ show $ y * z | y <- [100..999], z <- [100..999], show (y*z) == reverse (show $ y*z)] prime p = p `elem` primes primes = small ++ large where 1:p:candidates = roll $ mkWheel small small = [2,3,5,7] large = p : filter isPrime candidates isPrime n = all (not . divides n) $ takeWhile (\p -> p*p <= n) large divides n p = n `mod` p == 0 mkWheel ds = foldl nextSize w0 ds nextSize (Wheel n rs) p = Wheel (p*n) [r' | k <- [0..(p-1)], r <- rs, let r' = n*k+r, r' `mod` p /= 0] w0 = Wheel 1 [1] roll (Wheel n rs) = [n*k+r | k <- [0..], r <- rs] data Wheel = Wheel Integer [Integer] ------------------------ Here's my output when I try to compile: ian$ ghc ~/Documents/eulerProblem1.hs -o test Undefined symbols: "___stginit_ZCMain", referenced from: ___stginit_ZCMain$non_lazy_ptr in libHSrts.a(Main.o) "_ZCMain_main_closure", referenced from: _ZCMain_main_closure$non_lazy_ptr in libHSrts.a(Main.o) ld: symbol(s) not found collect2: ld returned 1 exit status What's going on? I'm running GHC 6.8.3, if that helps.

On 2008 Oct 20, at 23:36, Ian Duncan wrote:
'm trying to compile my file that has my Euler problems in it to output the solution to problem four, but I'm getting a compile error. Here's my .hs file: ------------------------- module Euler1 where
If you're not using the standard module Main, you need to tell ghc which module you put your main function in: ghc --main-is Euler1 ... -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Am Dienstag, 21. Oktober 2008 05:36 schrieb Ian Duncan:
'm trying to compile my file that has my Euler problems in it to output the solution to problem four, but I'm getting a compile error. Here's my .hs file: ------------------------- module Euler1 where import Data.List import Data.Ord
main = mapM_ putStrLn problem4
problem1 = foldl1' (+) $ nub $ (takeWhile (< 1000) [3,6..] ++ takeWhile (< 1000) [5,10..]) problem2 = sum $ takeWhile (<= 4000000) [x | x <- fibs, even x] where fibs = unfoldr (\(a,b) -> Just (a,(b,a+b))) (0,1)
problem3 z = maximumBy compare (filter (\x -> z `mod` x == 0) (takeWhile (<= ceiling (sqrt (fromIntegral z))) primes))
problem4 = nub [ show $ y * z | y <- [100..999], z <- [100..999], show (y*z) == reverse (show $ y*z)]
prime p = p `elem` primes
primes = small ++ large where 1:p:candidates = roll $ mkWheel small small = [2,3,5,7] large = p : filter isPrime candidates isPrime n = all (not . divides n) $ takeWhile (\p -> p*p <= n) large divides n p = n `mod` p == 0 mkWheel ds = foldl nextSize w0 ds nextSize (Wheel n rs) p = Wheel (p*n) [r' | k <- [0..(p-1)], r <- rs, let r' = n*k+r, r' `mod` p /= 0] w0 = Wheel 1 [1] roll (Wheel n rs) = [n*k+r | k <- [0..], r <- rs] data Wheel = Wheel Integer [Integer] ------------------------
Here's my output when I try to compile:
ian$ ghc ~/Documents/eulerProblem1.hs -o test Undefined symbols: "___stginit_ZCMain", referenced from: ___stginit_ZCMain$non_lazy_ptr in libHSrts.a(Main.o) "_ZCMain_main_closure", referenced from: _ZCMain_main_closure$non_lazy_ptr in libHSrts.a(Main.o) ld: symbol(s) not found collect2: ld returned 1 exit status
What's going on? I'm running GHC 6.8.3, if that helps.
Your module isn't named Main, so to produce an executable you must pass the flag -main-is ModuleName on the command line. Another thing, it is recommendable to develop the habit of passing the --make flag to ghc.
participants (3)
-
Brandon S. Allbery KF8NH
-
Daniel Fischer
-
Ian Duncan