[Haskell-cafe] Unfriendly hs-plugins error

Björn Buckwalter bjorn.buckwalter at gmail.com
Mon Oct 1 21:59:21 EDT 2007


Dear all,

I'm getting a rather unfriendly error when trying to load a plugin
with hs-plugins:

    my_program: Ix{Int}.index: Index (65536) out of range ((0,7))

The exact numbers in the message vary depending on what I'm trying to
do. I'm using GHC-6.6.1 on MacOS X. Here are three files that exhibit
the behaviour for me:

API.lhs
=======
> module API where
> data Config = Config { param :: String }

Main.lhs
========
> module Main where
> import System (getArgs)
> import System.Plugins
> import API

> getConfig :: [String] -> IO Config
> getConfig [file] = do
>   status <- make file []
>   obj    <- case status of
>               MakeSuccess _ o -> return o
>               MakeFailure es  -> mapM_ putStrLn es >> error "make failed"
>   putStrLn $ "### loading " ++ file
>   m_v    <- load_ obj ["."] "config"
>   putStrLn $ "### checking " ++ file
>   val    <- case m_v of
>               LoadSuccess _ v -> return v
>               LoadFailure es  -> mapM_ putStrLn es >> error "load failed"
>   return val

> main = getArgs >>= getConfig >>= putStrLn . param

CustomConfig.hs
===============
>module CustomConfig where
> import API
> config = Config { param = "Doomed to fail!" }


I compile the above with "ghc --make -o my_program PluginTest.lhs" and
execute with "./my_program CustomConfig.lhs".

Any hints welcome. Thanks,
Bjorn Buckwalter


More information about the Haskell-Cafe mailing list