GHC Error in linker "undeined reference"

Hello, I am using ghc on ubuntu 6.06, and it has worked well for my first few attempts (one example pasted below), but I now have a file that works well in ghci, but not in ghc. When loading the file (pasted below) into ghci, it works fine.and the program runs as expected. Compilation (linking, actually) with ghc gives error messages (pasted below), but when I again start ghci adn load the program, I can see that it now uses the compiled ".o"-file instead of interpreting the program. I assume that some files that should be installed by default are not installed. I apologize if I am violating any policy about pasting in messages. Thanks in advance for any help / johan ---------------------------------------------------- -- Working example: sort [] = [] sort (x:xs) = insert x (sort xs) where insert x [] = [x] insert x (y:ys) | x <= y = (x:y:ys) | otherwise = y : (insert x ys) main = print $ sort [1,4,53,45,1,435,45,45,1,435,45,145,45345,3,345] ---------------------------------------------------------- ------------------------------------------------------ -- Non-linkable example {-# OPTIONS_GHC -fglasgow-exts #-} import Control.Monad.State import Control.Monad.ST import Data.Array.ST import Data.List class Stack s a where emptyStack :: (s a) isEmpty :: State (s a) Bool pop :: State (s a) a push :: a -> State (s a) () nTh :: Int -> State (s a) a depth :: State (s a) Int instance Stack [] a where emptyStack = [] :: [a] isEmpty = get >>= \lst -> return (length lst == 0) pop = get >>= \(x:xs) -> put xs >> return x push x = get >>= \xs -> put (x:xs) >> return () nTh n = get >>= \lst -> return $ lst !! n depth = get >>= (return . length) class Mem m a where emptyMem :: Int -> a -> ST s (m s Int a) fetch :: (m s Int a) -> Int -> ST s a store :: (m s Int a) -> Int -> a -> ST s () instance Mem STArray a where emptyMem n val = newArray (0,n) val :: ST s (STArray s Int a) fetch m ix = readArray m ix store m ix val = writeArray m ix val stackTest = evalState doStackTest (emptyStack :: [Int]) where doStackTest = (push 4 >> push 2 >> pop >>= \a -> pop >>= \b -> return (a,b)) memTest = runST doMemTest where doMemTest :: ST s (Int,Int) doMemTest = ((emptyMem 2 0 :: ST s (STArray s Int Int)) >>= \mem -> store mem 0 2 >> store mem 1 4 >> fetch mem 0 >>= \a -> fetch mem 1 >>= \b -> return (a,b)) main = (print stackTest >> print memTest >> return ()) -------------------------------------------------------------------- Error messages frm ghc: ---------------------------------------------------- ubuntu@ubuntu:~/haskell/Forth$ ghc forth.lhs forth.o: In function `s2Q0_info': undefined reference to `ControlziMonadziState_zdfMonadStates_closure' forth.o: In function `s2Q6_info': undefined reference to `ControlziMonadziState_zdfMonadStates_closure' forth.o: In function `s2Qp_info': undefined reference to `ControlziMonadziState_zdfMonadStates_closure' forth.o: In function `s2QA_info': undefined reference to `ControlziMonadziState_zdfMonadStates_closure' forth.o: In function `s2R5_info': undefined reference to `ControlziMonadziState_zdfMonadStates_closure' forth.o: more undefined references to `ControlziMonadziState_zdfMonadStates_closure' follow forth.o: In function `s2TI_info': undefined reference to `ControlziMonadziState_zdfMonadState_closure' forth.o: In function `s2TL_info': undefined reference to `ControlziMonadziState_zdfMonadState_closure' forth.o: In function `s2Tm_info': undefined reference to `ControlziMonadziState_zdfMonadState_closure' forth.o: In function `s2Tp_info': undefined reference to `ControlziMonadziState_zdfMonadState_closure' forth.o: In function `s2TO_info': undefined reference to `ControlziMonadziState_zdfMonadState_closure' forth.o: In function `r2Pv_info': undefined reference to `ControlziMonadziState_evalState_closure' forth.o: In function `__stginit_Main_': undefined reference to `__stginit_ControlziMonadziState_' forth.o: In function `Main_zdfStackZMZN_srt': undefined reference to `ControlziMonadziState_zdfMonadStates_closure' forth.o: In function `s2TO_srt': undefined reference to `ControlziMonadziState_zdfMonadState_closure' forth.o: In function `r2Pv_srt': undefined reference to `ControlziMonadziState_evalState_closure' collect2: ld returned 1 exit status ---------------------------------------------------

Hi,
On 8/12/06, Johan Grönqvist
import Control.Monad.State import Control.Monad.ST import Data.Array.ST import Data.List
Control.Monad.State is from package mtl, the other modules are part of the base package, I think.
ubuntu@ubuntu:~/haskell/Forth$ ghc forth.lhs
You need to tell ghc that you want to link package mtl. ghc -package mtl forth.lhs or more automatic ghc --make forth.lhs The packages you can import without any additional options are the packages "ghc-pkg list" shows as visible. But without --make, or explicitly telling, ghc doesn't know which packages to link with. HTH, --Esa
participants (2)
-
Esa Ilari Vuokko
-
Johan Grönqvist