Hi all!
Not long ago, I faced with problem building library with Cabal.
I'm trying to build simple Haskell project as a shared library for use in MS Visual Studio (yes, I use FFI for this).

And I created simple test project:
/
{-# LANGUAGE ForeignFunctionInterface #-}
module GrepWrap where

import Foreign
import Foreign.C.String
import Data.Char

printCString :: CString -> IO ()
printCString s = do
    ss <- peekCString s
    putStrLn ss

getCStringFromKey :: IO CString
getCStringFromKey = do
    guess <- getLine
    newCString guess

hello :: IO()
hello = do
    putStrLn "Hi there!"

foreign export stdcall В В В  В hello :: IO ()
foreign export stdcallВ В  printCString :: CString -> IO ()
foreign export stdcallВ В  getCStringFromKey :: IO CString/

Also, I created file for safe initialization with wrappers for hs_init() and hs_exit() calls:
/// StartEnd.c
#include <Rts.h>
extern void __stginit_GrepWrap(void);
void HsStart()
{
    int argc = 1;
    char* argv[] = {"ghcDll", NULL}; // argv must end with NULL
    // Initialize Haskell runtime
    char** args = argv;
    hs_init(&argc, &args);
}
void HsEnd()
{
    hs_exit();
}/

I compile these files with the next commands:
/*> ghc -c GrepWrap.c*//*
*//*> ghc -c StartEnd.c*//*
*//*> ghc -shared -o grepWrap.dll grepWrap.hs StartEnd.o*/
/Linking grepWrap.dll ...//
//Creating library file: grepWrap.dll.a//
///
After it, I've got grepWrap.dll and grepWrap.dll.a files.
I successfully linked that library with my simple C++ test app, that uses these functions. And I was able to use my Haskell functions in my simple C++ app.

Further, I'd like to use Cabal build system for building the same Haskell library filles.
My cabal file looks like this:
/*name:                GrepWrap
version: 1.0
synopsis:            example shared library for C use
build-type:          Simple
cabal-version:       >=1.10

library
  default-language:    Haskell2010
  exposed-modules:     GrepWrap
extra-libraries: HSbase-4.6.0.1, wsock32, user32, shell32, HSinteger-gmp-0.5.0.0, HSghc-prim-0.3.0.0, HSrts, gdi32, winmm
  c-sources: StartEnd.c
  extensions: ForeignFunctionInterface
  build-depends:       base >= 4
  --ghc-options: "-v"*/

After build, in directory dist/build I got a set of files and among them there are: _/libHSGrepWrap-1.0-ghc7.6.3.dll/_ , ___/libHSGrepWrap-1.0-ghc7.6.3.dll.a/_ and /_GrepWrap_stub.h_/ . I use these files in the same Visual Studio project (of course, I changed names of dependent libraries in dependencies configuration in Visual Studio). Application successfully builds, but after run this app, I've got the next exception:

Unhandled exception at 0x6D7905FB (libHSrts-ghc7.6.3.dll) in GrepWrapCabalUseDll.exe: 0xC0000005: Access violation reading location 0x00000000

It occurs, when I call functions from library (but when HsStart() already called).

When I use "-v" flag with compilation (using ghc) I saw such linker message log:
/*** Linker://
//"C:\Program Files (x86)\Haskell Platform\2013.2.0.0\lib/../mingw/bin/gcc.exe" "-fno-stack-protector" "-Wl,--hash-size=31" "-Wl,--reduce-memory-overheads" "-o" "grepWrap.dll" "-shared" "-Wl,--out-implib=grepWrap.dll.a" "grepWrap.o" "-Wl,--enable-auto-import" "StartEnd.o" "-LC:\Program Files (x86)\Haskell Platform\2013.2.0.0\lib\base-4.6.0.1" "-LC:\Program Files (x86)\Haskell Platform\2013.2.0.0\lib\integer-gmp-0.5.0.0" "-LC:\Program Files (x86)\Haskell Platform\2013.2.0.0\lib\ghc-prim-0.3.0.0" "-LC:\Program Files (x86)\Haskell Platform\2013.2.0.0\lib" "-lHSbase-4.6.0.1" "-lwsock32" "-luser32" "-lshell32" "-lHSinteger-gmp-0.5.0.0" "-lHSghc-prim-0.3.0.0" "-lHSrts" "-lm" "-lwsock32" "-lgdi32" "-lwinmm" "-u" "_ghczmprim_GHCziTypes_Izh_static_info" "-u" "_ghczmprim_GHCziTypes_Czh_static_info" "-u" "_ghczmprim_GHCziTypes_Fzh_static_info" "-u" "_ghczmprim_GHCziTypes_Dzh_static_info" "-u" "_base_GHCziPtr_Ptr_static_info" "-u" "_ghczmprim_GHCziTypes_Wzh_static_info" "-u" "_base_GHCziInt_I8zh_static_info" "-u" "_base_GHCziInt_I16zh_static_info" "-u" "_base_GHCziInt_I32zh_static_info" "-u" "_base_GHCziInt_I64zh_static_info" "-u" "_base_GHCziWord_W8zh_static_info" "-u" "_base_GHCziWord_W16zh_static_info" "-u" "_base_GHCziWord_W32zh_static_info" "-u" "_base_GHCziWord_W64zh_static_info" "-u" "_base_GHCziStable_StablePtr_static_info" "-u" "_ghczmprim_GHCziTypes_Izh_con_info" "-u" "_ghczmprim_GHCziTypes_Czh_con_info" "-u" "_ghczmprim_GHCziTypes_Fzh_con_info" "-u" "_ghczmprim_GHCziTypes_Dzh_con_info" "-u" "_base_GHCziPtr_Ptr_con_info" "-u" "_base_GHCziPtr_FunPtr_con_info" "-u" "_base_GHCziStable_StablePtr_con_info" "-u" "_ghczmprim_GHCziTypes_False_closure" "-u" "_ghczmprim_GHCziTypes_True_closure" "-u" "_base_GHCziPack_unpackCString_closure" "-u" "_base_GHCziIOziException_stackOverflow_closure" "-u" "_base_GHCziIOziException_heapOverflow_closure" "-u" "_base_ControlziExceptionziBase_nonTermination_closure" "-u" "_base_GHCziIOziException_blockedIndefinitelyOnMVar_closure" "-u" "_base_GHCziIOziException_blockedIndefinitelyOnSTM_closure" "-u" "_base_ControlziExceptionziBase_nestedAtomically_closure" "-u" "_base_GHCziWeak_runFinalizzerBatch_closure" "-u" "_base_GHCziTopHandler_flushStdHandles_closure" "-u" "_base_GHCziTopHandler_runIO_closure" "-u" "_base_GHCziTopHandler_runNonIO_closure" "-u" "_base_GHCziConcziIO_ensureIOManagerIsRunning_closure" "-u" "_base_GHCziConcziSync_runSparks_closure" "-u" "_base_GHCziConcziSignal_runHandlers_closure"//
//Creating library file: grepWrap.dll.a//
//link: done/

But, when I call cabal build with "-v2" option to get build log, I get the following:
/> cabal build -v2
I've got the next log:
creating dist\build
creating dist\build\autogen
Building GrepWrap-1.0...
Preprocessing library GrepWrap-1.0...
Building library...
creating dist\build
C:\Program Files (x86)\Haskell Platform\2013.2.0.0\bin\ghc.exe --make -fbuilding-cabal-package -O -odir dist\build -hidir dist\build -stubdir dist\build -i -idist\build -i. -idist\build\autogen -Idist\build\autogen -Idist\build -optP-include -optPdist\build\autogen\cabal_macros.h -package-name GrepWrap-1.0 -hide-all-packages -package-db dist\package.conf.inplace -package-id base-4.6.0.1-f0c2cc6dcf0e12bf75312a2e7f354095 -XHaskell2010 -XForeignFunctionInterface GrepWrap
[1 of 1] Compiling GrepWrap         ( GrepWrap.hs, dist\build\GrepWrap.o )
C:\Program Files (x86)\Haskell Platform\2013.2.0.0\bin\ghc.exe --make -fbuilding-cabal-package -O -prof -osuf p_o -hisuf p_hi -odir dist\build -hidir dist\build -stubdir dist\build -i -idist\build -i. -idist\build\autogen -Idist\build\autogen -Idist\build -optP-include -optPdist\build\autogen\cabal_macros.h -package-name GrepWrap-1.0 -hide-all-packages -package-db dist\package.conf.inplace -package-id base-4.6.0.1-f0c2cc6dcf0e12bf75312a2e7f354095 -XHaskell2010 -XForeignFunctionInterface GrepWrap
[1 of 1] Compiling GrepWrap         ( GrepWrap.hs, dist\build\GrepWrap.p_o )
C:\Program Files (x86)\Haskell Platform\2013.2.0.0\bin\ghc.exe --make -fbuilding-cabal-package -O -dynamic -fPIC -osuf dyn_o -hisuf dyn_hi -odir dist\build -hidir dist\build -stubdir dist\build -i -idist\build -i. -idist\build\autogen -Idist\build\autogen -Idist\build -optP-include -optPdist\build\autogen\cabal_macros.h -package-name GrepWrap-1.0 -hide-all-packages -package-db dist\package.conf.inplace -package-id base-4.6.0.1-f0c2cc6dcf0e12bf75312a2e7f354095 -XHaskell2010 -XForeignFunctionInterface GrepWrap [1 of 1] Compiling GrepWrap ( GrepWrap.hs, dist\build\GrepWrap.dyn_o )
Building C Sources...
creating dist\build
C:\Program Files (x86)\Haskell Platform\2013.2.0.0\bin\ghc.exe -c -prof -odir dist\build -Idist\build -optc-O2 -package-db dist\package.conf.inplace -package-id base-4.6.0.1-f0c2cc6dcf0e12bf75312a2e7f354095 StartEnd.c C:\Program Files (x86)\Haskell Platform\2013.2.0.0\bin\ghc.exe -c -prof -dynamic -fPIC -osuf dyn_o -odir dist\build -Idist\build -optc-O2 -package-db dist\package.conf.inplace -package-id base-4.6.0.1-f0c2cc6dcf0e12bf75312a2e7f354095 StartEnd.c
Linking...
C:\Program Files (x86)\Haskell Platform\2013.2.0.0\mingw\bin\ar.exe -r dist\build\libHSGrepWrap-1.0.a dist\build\GrepWrap.o dist\build\StartEnd.o C:\Program Files (x86)\Haskell Platform\2013.2.0.0\mingw\bin\ar.exe: creating dist\build\libHSGrepWrap-1.0.a C:\Program Files (x86)\Haskell Platform\2013.2.0.0\mingw\bin\ar.exe -r dist\build\libHSGrepWrap-1.0_p.a dist\build\GrepWrap.p_o dist\build\StartEnd.o C:\Program Files (x86)\Haskell Platform\2013.2.0.0\mingw\bin\ar.exe: creating dist\build\libHSGrepWrap-1.0_p.a C:\Program Files (x86)\Haskell Platform\2013.2.0.0\mingw\bin\ld.exe -x --hash-size=31 --reduce-memory-overheads -r -o dist\build\HSGrepWrap-1.0.o dist\build\GrepWrap.o dist\build\StartEnd.o C:\Program Files (x86)\Haskell Platform\2013.2.0.0\bin\ghc.exe -shared -dynamic -lHSbase-4.6.0.1 -lwsock32 -luser32 -lshell32 -lHSinteger-gmp-0.5.0.0 -lHSghc-prim-0.3.0.0 -lHSrts -lgdi32 -lwinmm -package-name GrepWrap-1.0 -no-auto-link-packages -package-db dist\package.conf.inplace -package-id base-4.6.0.1-f0c2cc6dcf0e12bf75312a2e7f354095 dist\build\GrepWrap.dyn_o dist\build\StartEnd.dyn_o -o dist\build\libHSGrepWrap-1.0-ghc7.6.3.dll
Creating library file: dist\build\libHSGrepWrap-1.0-ghc7.6.3.dll.a
In-place registering GrepWrap-1.0...
C:\Program Files (x86)\Haskell Platform\2013.2.0.0\bin\ghc-pkg.exe update - --global --user --package-db=dist\package.conf.inplace/

I'm confused.. Cabal uses a batch of options, it adds multiple options that I can't control. I'd like to control this options. How can I build my Haskell library with Cabal build system as same as building it with simple ghc? I can call ghc manually, but it will be a hard task, when I'll compile library for multiple files.

Best regards,
Oleg Durandin



name:                GrepWrap
version: 1.0
synopsis:            example shared library for C use
build-type:          Simple
cabal-version:       >=1.10

library
  default-language:    Haskell2010
  exposed-modules:     GrepWrap
  extra-libraries:     HSbase-4.6.0.1, wsock32, user32, shell32, 
HSinteger-gmp-0.5.0.0, HSghc-prim-0.3.0.0, HSrts, gdi32, winmm
  c-sources: StartEnd.c
  extensions: ForeignFunctionInterface 
  build-depends:       base >= 4
  --ghc-options: "-v"
{-# LANGUAGE ForeignFunctionInterface #-}
  
module GrepWrap where
  
import Foreign
import Foreign.C.String
import Data.Char

printCString :: CString -> IO ()
printCString s = do
        ss <- peekCString s
        putStrLn ss
        
getCStringFromKey :: IO CString
getCStringFromKey = do
        guess <- getLine
        newCString guess


hello :: IO()
hello = do
        putStrLn "Hi there!"

foreign export stdcall   hello :: IO ()
foreign export stdcall   printCString :: CString -> IO ()
foreign export stdcall   getCStringFromKey :: IO CString
// StartEnd.c
#include <Rts.h>

extern void __stginit_GrepWrap(void);


void HsStart()
{
   int argc = 1;
   char* argv[] = {"ghcDll", NULL}; // argv must end with NULL

   // Initialize Haskell runtime
   char** args = argv;
   hs_init(&argc, &args);

   // Tell Haskell about all root modules
   //hs_add_root(__stginit_Adder);
}

void HsEnd()
{
   hs_exit();
}

_______________________________________________
cabal-devel mailing list
cabal-devel@haskell.org
http://www.haskell.org/mailman/listinfo/cabal-devel

Reply via email to