<html>
  <head>

    <meta http-equiv="content-type" content="text/html; charset=windows-1251">
  </head>
  <body text="#000000" bgcolor="#FFFFFF">
    <br>
    <div class="moz-forward-container">
      <meta http-equiv="content-type" content="text/html;
        charset=windows-1251">
      Hi all!<br>
      <div class="moz-forward-container"> Not long ago, I faced with
        problem building library with Cabal.<br>
        I'm trying to build simple Haskell project as a shared library
        for use in MS Visual Studio (yes, I use FFI for this).<br>
        <br>
        And I created simple test project:<br>
        <i><small><small><br>
              {-# LANGUAGE ForeignFunctionInterface #-}<br>
              module GrepWrap where<br>
                <br>
              import Foreign<br>
              import Foreign.C.String<br>
              import Data.Char<br>
              <br>
              printCString :: CString -> IO ()<br>
              printCString s = do<br>
                  ss <- peekCString s<br>
                  putStrLn ss<br>
              <br>
              getCStringFromKey :: IO CString<br>
              getCStringFromKey = do<br>
                  guess <- getLine<br>
                  newCString guess<br>
              <br>
              hello :: IO()<br>
              hello = do<br>
                  putStrLn "Hi there!"<br>
              <br>
              foreign export stdcall Â Â Â  Â hello :: IO ()<br>
              foreign export stdcall   printCString :: CString ->
              IO ()<br>
              foreign export stdcall   getCStringFromKey :: IO CString</small></small></i><br>
        <br>
        Also, I created file for safe initialization with wrappers for
        hs_init() and hs_exit() calls:<br>
        <big><i><small><small><small>// StartEnd.c<br>
                  #include <Rts.h><br>
                  extern void __stginit_GrepWrap(void);<br>
                  void HsStart()<br>
                  {<br>
                      int argc = 1;<br>
                      char* argv[] = {"ghcDll", NULL}; // argv must end
                  with NULL<br>
                      // Initialize Haskell runtime<br>
                      char** args = argv;<br>
                      hs_init(&argc, &args);<br>
                  }<br>
                  void HsEnd()<br>
                  {<br>
                      hs_exit();<br>
                  }</small></small></small></i></big><br>
        <br>
        I compile these files with the next commands:<br>
        <i><b>> ghc -c GrepWrap.c</b></i><i><b><br>
          </b></i><i><b>> ghc -c StartEnd.c</b></i><i><b><br>
          </b></i><i><b>> ghc -shared -o grepWrap.dll grepWrap.hs
            StartEnd.o</b></i><br>
        <i>Linking grepWrap.dll ...</i><i><br>
        </i><i> Creating library file: grepWrap.dll.a</i><i><br>
        </i><i> </i><br>
        After it, I've got grepWrap.dll and grepWrap.dll.a files.<br>
        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.<br>
        <br>
        Further, I'd like to use Cabal build system for building the
        same Haskell library filles.<br>
        My cabal file looks like this:<br>
        <small><small><i><b>name:                GrepWrap<br>
                version: 1.0<br>
                synopsis:            example shared library for C use<br>
                build-type:          Simple<br>
                cabal-version:       >=1.10<br>
                <br>
                library<br>
                  default-language:    Haskell2010<br>
                  exposed-modules:     GrepWrap<br>
                  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<br>
                  c-sources: StartEnd.c<br>
                  extensions: ForeignFunctionInterface <br>
                  build-depends:       base >= 4<br>
                  --ghc-options: "-v"</b></i></small></small><br>
        <br>
        After build, in directory dist/build I got a set of files and
        among them there are: <u><i>libHSGrepWrap-1.0-ghc7.6.3.dll</i></u>
        , <u> </u><u><i>libHSGrepWrap-1.0-ghc7.6.3.dll.a</i></u> and <i>
          <u>GrepWrap_stub.h</u></i> .<br>
        I use these files in the same Visual Studio project (of course,
        I changed names of dependent libraries in dependencies
        configuration in Visual Studio).<br>
        Application successfully builds, but after run this app, I've
        got the next exception:<br>
        <br>
        Unhandled exception at 0x6D7905FB (libHSrts-ghc7.6.3.dll) in
        GrepWrapCabalUseDll.exe: 0xC0000005: Access violation reading
        location 0x00000000<br>
        <br>
        It occurs, when I call functions from library (but when
        HsStart() already called).<br>
        <br>
        When I use "-v" flag with compilation (using ghc) I saw such
        linker message log:<br>
        <small><small><i>*** Linker:</i><i><br>
            </i><i> "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"</i><i><br>
            </i><i> Creating library file: grepWrap.dll.a</i><i><br>
            </i><i> link: done</i></small></small><br>
        <br>
        But, when I call cabal build with "-v2" option to get build log,
        I get the following:<br>
        <i><small><small>> cabal build -v2<br>
              I've got the next log:<br>
              creating dist\build<br>
              creating dist\build\autogen<br>
              Building GrepWrap-1.0...<br>
              Preprocessing library GrepWrap-1.0...<br>
              Building library...<br>
              creating dist\build<br>
              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<br>
              [1 of 1] Compiling GrepWrap         ( GrepWrap.hs,
              dist\build\GrepWrap.o )<br>
              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<br>
              [1 of 1] Compiling GrepWrap         ( GrepWrap.hs,
              dist\build\GrepWrap.p_o )<br>
              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<br>
              [1 of 1] Compiling GrepWrap         ( GrepWrap.hs,
              dist\build\GrepWrap.dyn_o )<br>
              Building C Sources...<br>
              creating dist\build<br>
              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<br>
              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<br>
              Linking...<br>
              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<br>
              C:\Program Files (x86)\Haskell
              Platform\2013.2.0.0\mingw\bin\ar.exe: creating
              dist\build\libHSGrepWrap-1.0.a<br>
              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<br>
              C:\Program Files (x86)\Haskell
              Platform\2013.2.0.0\mingw\bin\ar.exe: creating
              dist\build\libHSGrepWrap-1.0_p.a<br>
              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<br>
              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<br>
              Creating library file:
              dist\build\libHSGrepWrap-1.0-ghc7.6.3.dll.a<br>
              In-place registering GrepWrap-1.0...<br>
              C:\Program Files (x86)\Haskell
              Platform\2013.2.0.0\bin\ghc-pkg.exe update - --global
              --user --package-db=dist\package.conf.inplace</small></small></i><br>
        <br>
        I'm confused.. Cabal uses a batch of options, it adds multiple
        options that I can't control.<br>
        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?<br>
        I can call ghc manually, but it will be a hard task, when I'll
        compile library for multiple files.<br>
        <br>
        Best regards,<br>
        Oleg Durandin<br>
      </div>
      <br>
      <br>
    </div>
    <br>
  </body>
</html>