[Haskell-cafe] Problem with plugins

Timo von Holtz timo.v.holtz at googlemail.com
Wed Jun 20 15:54:48 CEST 2012


My example was somewhat wrong, since it only works with runghc >= 7.0
and not <7.
Here a better example which has exactly the same issues as my code.

Main.hs:
module Main where

import Main1

main = main1

Main1.hs:
module Main1 (main1, add) where

import System.Plugins

add = (+1)

main1 :: IO ()
main1 = do
  putStrLn "Loading"
  makeAll "Plug.hs" []
  mv <- load_ "Plug.o" ["."] "thing"
  putStrLn "Loaded"
  case mv of
    LoadFailure msgs -> putStrLn "fail" >> print msgs
    LoadSuccess _ v -> putStrLn "success" >> print (v::Integer)

Plug.hs:
module Plug (thing) where

import Main1

thing :: Integer
thing = add 1234000

- timo

2012/6/20 Timo von Holtz <timo.v.holtz at googlemail.com>:
> I compile the files dynamically, so the compiler version is out of the
> question. I already tested -O0.
> In the modules I dynamically load, I import some of the modules the
> main program also uses. I can reproduce the exact same error with this
> simple example:
>
> Main.hs:
> module Main (main, add) where
>
> import System.Plugins
>
> add = (+1)
>
> main :: IO ()
> main = do
>   putStrLn "Loading"
>   makeAll "Plug.hs" []
>   mv <- load_ "Plug.o" ["."] "thing"
>   putStrLn "Loaded"
>   case mv of
>     LoadFailure msgs -> putStrLn "fail" >> print msgs
>     LoadSuccess _ v -> putStrLn "success" >> print (v::Integer)
>
> Plug.hs:
> module Plug (thing) where
>
> import Main
>
> thing :: Integer
> thing = add 1234000
>
> - timo
> 2012/6/20 Jeremy Shaw <jeremy at n-heptane.com>
>>
>> I really have no idea. I am the new plugins maintainer -- but so far
>> that mostly means I am willing to apply darcs patches and uploading
>> things to hackage. I have not had a chance to really dig into plugins.
>>
>> I will now make some wild guesses.
>>
>>  1. does it matter if you compile with -O2 vs -O0 ?
>>
>>  2. do those .o  files actually exist?
>>
>>  3. Are there perhaps .o and .hi files in your project directory that
>> were compiled with GHC 7.0 but now you are trying to load them with >=
>> 7.0?
>>
>> - jeremy
>>
>> On Tue, Jun 19, 2012 at 10:30 AM, Timo von Holtz
>> <timo.v.holtz at googlemail.com> wrote:
>> > Hi,
>> >
>> > I'm currently working on extending the hascat Server. My problem is, that
>> > for whatever odd reason it will only work on GHC < 7.0 or alternatively if I
>> > execute it with runghc or in ghci.
>> > If I compile it with GHC>=7.0 and execute it, then I get this:
>> >
>> > $ ~/.cabal/bin/hascat config.xml
>> > Installing "Root" at /
>> > hascat: /home/tvh/.cabal/lib/plugins-1.5.2.1/ghc-7.4.1/HSplugins-1.5.2.1.o:
>> > unknown symbol `ghczm7zi4zi1_ErrUtils_zdsinsertzugo3_info'
>> > hascat: unloadObj: can't find
>> > `/usr/lib/ghc/binary-0.5.1.0/HSbinary-0.5.1.0.o' to unload
>> > user error (unloadObj: failed)
>> > Installing "Hascat Server Info" at /ServerInfo/
>> > hascat:
>> > /home/tvh/.cabal/lib/hascat-system-0.2/ghc-7.4.1/HShascat-system-0.2.o:
>> > unknown symbol `base_DataziMaybe_Nothing_closure'
>> > hascat: unloadObj: can't find `/usr/lib/ghc/Cabal-1.14.0/HSCabal-1.14.0.o'
>> > to unload
>> > user error (unloadObj: failed)
>> > Installing "Hascat Application Manager" at /Manager/
>> > hascat:
>> > /home/tvh/.cabal/lib/hascat-system-0.2/ghc-7.4.1/HShascat-system-0.2.o:
>> > unknown symbol `base_DataziMaybe_Nothing_closure'
>> > hascat: unloadObj: can't find `/usr/lib/ghc/Cabal-1.14.0/HSCabal-1.14.0.o'
>> > to unload
>> > user error (unloadObj: failed)
>> > Installing "Hascat Application Deployer" at /Deployer/
>> > hascat:
>> > /usr/lib/haskell-packages/ghc/lib/zlib-0.5.3.3/ghc-7.4.1/HSzlib-0.5.3.3.o:
>> > unknown symbol `base_GHCziForeignPtr_ForeignPtr_con_info'
>> > hascat: unloadObj: can't find `/usr/lib/ghc/Cabal-1.14.0/HSCabal-1.14.0.o'
>> > to unload
>> > user error (unloadObj: failed)
>> > Waiting for connections on port 8012
>> >
>> > Is there a way to make this work?
>> >
>> > Greetings
>> > Timo
>> >
>> > _______________________________________________
>> > Haskell-Cafe mailing list
>> > Haskell-Cafe at haskell.org
>> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>> >



More information about the Haskell-Cafe mailing list