Is this using the darcs repository version of hs-plugins? That's the only versions that works with 6.6
alistair: > Does anyone have hs-plugins working on WinXP with ghc-6.6? When I run > the simple test below I get this error: > > Main: > c:/ghc/ghc-6.6/HSbase.o: unknown symbol `_free' > Main: user error (Dynamic loader returned: user error (resolvedObjs > failed.)) > > Am I doing something obviously dumb? > > Alistair > > > module Test1 where > test1 = putStrLn "test1" > > > module Main where > import Prelude hiding (catch) > import Control.Exception > import Data.List > import System.Environment > import System.Plugins > > instance Show (LoadStatus a) where > show (LoadFailure errors) = "LoadFailure - " ++ (concat (intersperse > "\n" errors)) > show (LoadSuccess m p) = "LoadSuccess" > > main = do > a <- getArgs > let > modName = case a of > (n:_) -> n > _ -> "Test1" > let modPath = "./" ++ modName ++ ".o" > let method = "test1" > fc <- catch (load modPath [""] [] method) > (\e -> return (LoadFailure > ["Dynamic loader returned: " ++ show e])) > case fc of > LoadFailure errors -> do > fail (concat (intersperse "\n" errors)) > LoadSuccess modul proc -> do > let p :: IO (); p = proc > proc _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe