You're calling gcc my hand, which means you have to tell it which packages your source need. 

Pass it "-package directory" and it should work. 

Tamar

Sent from my Mobile

On Tue, Jun 11, 2019, 11:57 Kees Bleijenberg <K.Bleijenberg@lijbrandt.nl> wrote:

HI all,

 

I try to create a dll with ghc (ver 8.6.5)  on Windows 7 64 bits. I ‘am using the dll with loadLibrary in a cpp program in Visual Studio. I create the dll with:

ghc Vogels.hs

ghc -c StartEnd.c

ghc --make -static -shared -fPIC Vogels.o StartEnd.o -o Vogels.dll

 

StartEnd.o defines HsStart and HsEnd to initialize and close the Haskell runtime.

 

This works. I can create the dll and use the dll in VS.

But, if I replace in Vogels.hs the line b=True with   b <- doesFileExist vogelsFn, creating the dll fails with error message:

Vogels.o:fake:(.text+0x35c): undefined reference to `directoryzm1zi3zi3zi2zmB9tglvOQ6L9Cf7zzVEJ1S6t_SystemziDirectory_doesFileExist_closure'

Vogels.o:fake:(.text+0x37d): undefined reference to `directoryzm1zi3zi3zi2zmB9tglvOQ6L9Cf7zzVEJ1S6t_SystemziDirectory_doesFileExist_closure'

Vogels.o:fake:(.data+0xd0): undefined reference to `directoryzm1zi3zi3zi2zmB9tglvOQ6L9Cf7zzVEJ1S6t_SystemziDirectory_doesFileExist_closure' 

 

It looks like GHC can’t find the Directory package. I’ve installed this package. What can I do about it and how can I find out  the dependencies in a *.hs or *.o file? Almost all documentation about dll’s is about Linux or about using dll’s in Haskell.

 

Kees 

                                                                                                                                            

{-# LANGUAGE BlockArguments #-}

{-# LANGUAGE ForeignFunctionInterface #-}

module Vogels (  

   loadVogels

) where

   

import System.Directory

import Foreign.Ptr

import Foreign.Storable

import Foreign.C.String

 

loadVogels :: String  -> IO (Either String String)

loadVogels vogelsFn = do

   -- b <- doesFileExist vogelsFn

    let b=True

    if b

    then return $ Left $ "Can\'t find " ++ vogelsFn

    else do

            txt <- readFile vogelsFn

            return $ Right txt

 

loadVogelsFFI :: Ptr Int -> CString -> IO CString

loadVogelsFFI messageKind vogelsFnFFI = do

   vogelsFn  <- peekCString vogelsFnFFI

   eitherRes <- loadVogels vogelsFn

   case eitherRes of

      Left errMsg -> do

            poke messageKind 1

            newCString errMsg

      Right txt ->  do

            poke messageKind 0

            newCString txt

 

foreign export ccall loadVogelsFFI :: Ptr Int -> CString -> IO CString


Virusvrij. www.avast.com
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.