[Haskell-cafe] Installation of hs-plugins
Philipp Volgger
pvolgger at gmail.com
Sat Apr 21 10:31:48 EDT 2007
I now used GHC 6.4 and mingw ( MSYS-1.0.11 ). Now it is possible to
configure, build and install it. But on running the test ( out of a
email from the list, source code see below) it crashes again without any
information.
I compiled the Test1.hs with ghc -c Test1.hs.
Bayley, Alistair wrote:
>> From: haskell-cafe-bounces at haskell.org
>> [mailto:haskell-cafe-bounces at haskell.org] On Behalf Of Philipp Volgger
>>
>> could somebody please tell me how hs-plugins has to be installed. I
>> tried it with hs-plguin 1.0rc1 and I was unable to build it. I did
>> runhaskell Setup.lhs configure
>> runhaskell Setup.lhs build (Crash without any information)
>> I tried it wiht GHC 6.4, 6.4.1 and 6.6.
>>
>> I am using Windows XP with SP2.
>>
>
> I'm pretty sure you need to install under some kind of bash shell. I
> used mingw on WinXP, but I think it can be done with cygwin. I'd
> recommend mingw if you don't have either installed.
>
> Note that hs-plugins doesn't work with ghc-6.6 yet on Windows, so stick
> with 6.4.1 if you can.
>
> Alistair
> *****************************************************************
> Confidentiality Note: The information contained in this message,
> and any attachments, may contain confidential and/or privileged
> material. It is intended solely for the person(s) or entity to
> which it is addressed. Any review, retransmission, dissemination,
> or taking of any action in reliance upon this information by
> persons or entities other than the intended recipient(s) is
> prohibited. If you received this in error, please contact the
> sender and delete the material from any computer.
> *****************************************************************
>
>
Test:
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
More information about the Haskell-Cafe
mailing list