Difference between revisions of "CPlusPlus from Haskell"

From HaskellWiki
Jump to navigation Jump to search
(→‎Abstract: Changed Hacanon to hacanon-light)
Line 28: Line 28:
 
The method presented on this page does not use that method -- it just calls the mangled names directly. So far this seems to work OK...
 
The method presented on this page does not use that method -- it just calls the mangled names directly. So far this seems to work OK...
   
==== Finding the mangled named ====
+
==== Finding the mangled name ====
   
 
C++ allows you to have many methods with the same name, but different arguments. However, the underlying linker does not --
 
C++ allows you to have many methods with the same name, but different arguments. However, the underlying linker does not --
so C++ mangles the methods names to ensure that each method name is unique. To import these methods into haskell, we
+
so C++ mangles the methods names to ensure that each method name is unique. To import these methods into Haskell, we
 
need to know the mangled name. Since there is no standard for mangling names, we must figured out how our C++ compiler
 
need to know the mangled name. Since there is no standard for mangling names, we must figured out how our C++ compiler
 
decides to do things.
 
decides to do things.

Revision as of 00:07, 23 May 2017

Calling C++ from Haskell - "The Hard Way"

Abstract

This page describes some of the black magic needed to call C++ from Haskell (on Linux, compiled with g++). I refer to it as the "The Hard Way" because it is a tedious, hand done method of generating C++ bindings. The information on this page is pretty spotty and probably wrong in places. But hopefully it will be of some use. You may also want to look at hacanon-light. It is currently unmaintained, but the idea of using Template Haskell is pretty appealing.

gcc-xml might be a good way to get the information needed to do more automatic C++ binding generation.

(BTW, this was written by JeremyShaw, know as stepcut on irc.freenode.net/#haskell if you have questions).

The basic steps

There are two phases to calling C++ from Haskell

  • making the objects accessible to Haskell programs
  • creating objects at run-time

Making objects accessible to Haskell

According to the Foreign Function Interface section of the Haskell 2010 report -- you import a C++ function by simply specifying the calling convention cplusplus. Unfortunately, no haskell compiler actually supports this calling convention, so we have to use the C calling convention instead.

The standard method for dealing with this is to write C++ code that uses extern "C" to export the methods unmangled. Of course, you still have to uniquify the method names, but *you* get to pick the names instead of letting the compiler do whatever wacky method it wants.

The method presented on this page does not use that method -- it just calls the mangled names directly. So far this seems to work OK...

Finding the mangled name

C++ allows you to have many methods with the same name, but different arguments. However, the underlying linker does not -- so C++ mangles the methods names to ensure that each method name is unique. To import these methods into Haskell, we need to know the mangled name. Since there is no standard for mangling names, we must figured out how our C++ compiler decides to do things.

Let's say I want to import the constructor

KApplication::KApplication (bool allowStyles=true, bool GUIenabled=true)

from /usr/lib/libkdecore.so

First I use nm -C to find the unmangled version of the constructor.

 # nm -D -C /usr/lib/libkdecore.so | grep '::KApplication'
000a9c40 T KApplication::KApplication(bool, bool)
000aa780 T KApplication::KApplication(bool, bool, KInstance*)
000aa000 T KApplication::KApplication(_XDisplay*, unsigned long, unsigned long, bool)
000aa3c0 T KApplication::KApplication(_XDisplay*, unsigned long, unsigned long, bool, KInstance*)
000aab70 T KApplication::KApplication(_XDisplay*, int&, char**, QCString const&, bool, bool)
000a9850 T KApplication::KApplication(int&, char**, QCString const&, bool, bool)
000a9a60 T KApplication::KApplication(bool, bool)
000aa5a0 T KApplication::KApplication(bool, bool, KInstance*)
000a9e20 T KApplication::KApplication(_XDisplay*, unsigned long, unsigned long, bool)
000aa1e0 T KApplication::KApplication(_XDisplay*, unsigned long, unsigned long, bool, KInstance*)
000aa960 T KApplication::KApplication(_XDisplay*, int&, char**, QCString const&, bool, bool)
000a9640 T KApplication::KApplication(int&, char**, QCString const&, bool, bool)
001c7780 W KApplicationPrivate::KApplicationPrivate()
 #

The instance I want is '000a9c40'. So now I grep the mangled symbols for that number:

 # nm -D ./usr/lib/libkdecore.so | grep '000a9c40'
000a9c40 T _ZN12KApplicationC1Ebb
 #

Importing the method into Haskell

I then import that into haskell like this:

data KApplication = KApplication
foreign import ccall "_ZN12KApplicationC1Ebb" kapplication_KApplication :: (Ptr KApplication) -> CInt -> CInt -> IO ()

'kapplication_KApplication' is what I want to call this method in haskell -- I can name it anything I want, as long as it is a valid haskell identifier.

C does not have a bool type, so I guessed (and it seems to work) that a C++ bool is just a CInt.

You will also notice that the first argument to the constructor is a pointer to KApplication, however this argument was not shown in the C++ type signature:

KApplication::KApplication (bool allowStyles=true, bool GUIenabled=true)

All the methods in the KApplication class take a pointer to KApplication as their first argument. Normally C++ manages this for you -- so you never see it. The pointer is, of course, the 'this' pointer.

Calculating the object size

We also need to know how big the object is, so we can allocate space for it with new() later.

Currently I use this little C++ program to figure that out:

#include <qstring.h>
#include <kapplication.h>
#include <klocale.h>
#include <iostream>
using namespace std;


main ()
{
  cout << sizeof(KApplication) << endl;
}
 # g++ size.cpp -I/usr/include/qt3 -I/usr/include/kde -lkdecore -o size && ./size
204

Creating objects at run-time

The steps for creating and destroying an object are:

  • Call new() on the object to allocate space for the object.
  • Call the object constructor
  • do whatever you want with the object
  • Call the object destructor
  • Call delete() on the object

Note that we have to explicitly call the Constructor.

How to link the program

Most programming languages, especially Haskell and C++, link by calling the system linker, passing it appropriate libraries. If you link Haskell and C++ code into the same binary, you cannot have this convenience for both languages. Also, one of both runtime systems may not get initialized correctly.

Currently, I'm using Ghc to do the linking, and instruct it to link the c++ runtime library:

    g++ -c nifty_code.cc -o nifty_code.o
    ghc --make main.hs -o hybrid_program -lstdc++ nifty_code.o

This seems to work (with GHC 6.4.1 and G++ 3.3.5). However, I'm pretty certain, the C++ runtime doesn't get initialized, so as soon as someone touches, say {{{std::cin}}}, all hell breaks lose. I dare not think about what happens, should I ever feel the need to bring a third language into the mix.

AnswerMe: Can anyone confirm that this works, whether it is supposed to work and how to do this correctly? -- UdoStenzel

An example

Here is an example where I create enough bindings to launch a small KDE app. This is actually a bad example because it has a lot of stuff that is unrelated to C++ bindings. Also, it does some things wrong. Things I know of include:

* Should probably use Finalizers and ForeignPtr's
* I read somewhere that you need to call the C++ main() to ensure that some C++ stdlib stuff is properly initialized. 

Also of note is the ->> operator. The entire purpose of the operator is to make things look more C++ like.

instead of writing:

       kapplication_KApplication kapp 1 1

I can use the more C++ like syntax:

       (kapp->> kapplication_KApplication) 1 1

Though, I think I actually prefer the former.

To compile the code on a Debian system you need:

ghc6 and the kdelibs4-dev

My kdelibs is version 3.3.2 and was compiled with the g++ 3.x compiler. I think the name mangling scheme changed with g++ 4.0, so if you are using that version you will have to figure out the new mangled names.

Also, I don't believe the buttons are actually hooked up yet. I think it just sits there looking pretty.

 # ghc --make KApp3.hs -fglasgow-exts -lkdecore -o kapp3
module Main where 

import Word
import Control.Monad
import Control.Monad.State

import Foreign.C
import Foreign.Ptr
import Foreign.Marshal.Array

-- * Heterogeneous lists
data HNil = HNil
data HCons a b = HCons a b

instance (Show a, Show b, HList b) => Show (HCons a b) where
    show (HCons a b) = show a ++ " .:. " ++ show b
{-
instance Show HNil where
    show HNil = "[]"
-}
class HList a
-- instance HList HNil
-- instance (HList b) => HList (HCons a b)

infixr 5 .:.
(.:.) :: a -> b -> HCons a b
a .:. b = HCons a b


{-
instance CreateWidgets HNil where
    createWidgets _ HNil = return ()
-}

data HTrue
data HFalse

class HBool x
instance HBool HTrue
instance HBool HFalse

data Proxy e
proxy :: Proxy e
proxy = undefined;

toProxy :: e -> Proxy e
toProxy _ = undefined

class HBool b => TypeEq x y b | x y -> b
proxyEq :: TypeEq t t' b => Proxy t -> Proxy t' -> b
proxyEq _ _ = undefined

-- * Some Basic Widgets

data QPushButton
    = QPushButton String
      deriving Show

-- * Some Layout Widgets

data (QWidgetList a) => QHBox a 
    = QHBox a
      deriving Show

data (QWidgetList a) => QVBox a 
    = QVBox a
      deriving Show

-- * Add Widgets to Widget Class

class QWidget a
instance QWidget QPushButton
instance QWidget (QHBox a)
instance QWidget (QVBox a)

data NoParent
instance QWidget NoParent

noParent = nullPtr :: Ptr NoParent

-- * Widget List constraint

class QWidgetList a
instance (QWidget a, QWidgetList b) => (QWidgetList (HCons a b))
instance QWidgetList QPushButton
instance (QWidgetList a) => QWidgetList (QHBox a)
instance (QWidgetList a) => QWidgetList (QVBox a)
instance QWidgetList NoParent

-- instance QWidgetList HNil

qwidgets :: (Show a, QWidgetList a) => a -> IO ()
qwidgets a = print $ a


class CreateWidgets a where
    createWidgets :: (QWidget p) => (Ptr p) -> a -> IO ()

instance (CreateWidget a, CreateWidgets b) => CreateWidgets (HCons a b) where
    createWidgets parent (HCons w ws) =
	do createWidget parent w
	   createWidgets parent ws

instance (CreateWidgets QPushButton) where
    createWidgets parent (QPushButton str) =
	do qstr <- qstring str
	   qpb  <- new
	   (qpb->>qpushbutton) qstr (castPtr parent) 0
	   showWidget qpb
	   return ()

instance (QWidgetList a, CreateWidgets a) => (CreateWidgets (QHBox a)) where
    createWidgets parent (QHBox children) =
	do qhbox <- new
	   (qhbox->>qhbox_QHBox) (castPtr parent) 0 0
	   createWidgets qhbox children
	   showWidget qhbox
	   return ()

instance (QWidgetList a, CreateWidgets a) => (CreateWidgets (QVBox a)) where
    createWidgets parent (QVBox children) =
	do qvbox <- new
	   (qvbox->>qvbox_QVBox) (castPtr parent) 0 0
	   createWidgets qvbox children
	   showWidget qvbox
	   return ()


{-
instance (CreateWidget a, QWidget b) => CreateWidgets (HCons a b) where
    createWidgets parent (HCons a b) =
	do createWidget parent a
	   createWidget parent b
-}

{-
createWidgets :: (QWidgetList a, QWidget p) => p -> a -> IO ()
createWidgets _ HNil = return ()
createWidgets parent (HCons a b) =
    do createWidget parent a
       createWidgets parent b
-}

class (QWidget w) => (CreateWidget w) where
    createWidget :: (QWidget p) => (Ptr p) -> w -> IO (Ptr w)

instance (CreateWidget QPushButton) where
    createWidget parent (QPushButton str) =
	do qstr <- qstring str
	   qpb  <- new
	   (qpb->>qpushbutton) qstr (castPtr parent) 0
	   showWidget qpb
	   return qpb

instance (QWidgetList a, CreateWidgets a) => (CreateWidget (QHBox a)) where
    createWidget parent (QHBox children) =
	do qhbox <- new
	   (qhbox->>qhbox_QHBox) (castPtr parent) 0 0
	   createWidgets qhbox children
	   showWidget qhbox
	   return qhbox

instance (QWidgetList a, CreateWidgets a) => (CreateWidget (QVBox a)) where
    createWidget parent (QVBox children) =
	do qvbox <- new
	   (qvbox->>qvbox_QVBox) (castPtr parent) 0 0
	   createWidgets qvbox children
	   showWidget qvbox
	   return qvbox

-- garbage collection ?
qstring :: String -> IO (Ptr QString)
qstring str =
    do cstr <- newCString str
       qstr <- new
       (qstr->>qstring_QString) cstr
       return qstr

-- * Other

data KApplication = KApplication
data KCmdLineArgs = KCmdLineArgs
data QString = QString

class New a where
    new :: IO (Ptr a)

instance New KApplication where
    new = hnew kapplicationSize

instance New QString where
    new = hnew qstringSize

instance New QPushButton where
    new = hnew qpushButtonSize

instance New (QHBox a) where
    new = hnew qhboxsize

instance New (QVBox a) where
    new = hnew qvboxsize

kapplicationSize = 204
qstringSize = 4
qpushButtonSize = 140
qhboxsize = 152
qvboxsize = 152

foreign import ccall "_ZN12KApplicationC1Ebb" kapplication_KApplication :: (Ptr KApplication) -> CInt -> CInt -> IO ()
foreign import ccall "_ZN12QApplication4execEv" qapplication_exec :: (Ptr KApplication) -> IO Int
foreign import ccall "_Znwj" cnew :: Word -> IO (Ptr ())
foreign import ccall "_ZN12KCmdLineArgs4initEiPPcPKcS3_S3_b" kCmdLineArgs_init :: Int -> Ptr CString -> CString -> CString -> CString -> Int -> IO ()
foreign import ccall "_ZN7QStringC1EPKc" qstring_QString :: (Ptr QString) -> CString -> IO ()
foreign import ccall "_ZN11QPushButtonC1ERK7QStringP7QWidgetPKc" qpushbutton :: (Ptr QPushButton) -> (Ptr QString) -> (Ptr ()) -> Int -> IO ()
foreign import ccall "_ZN12QApplication13setMainWidgetEP7QWidget" setMainWidget :: (Ptr KApplication) -> (Ptr ()) -> IO ()
foreign import ccall "_ZN7QWidget4showEv" qshow :: (Ptr ()) -> IO ()
foreign import ccall "_ZN7QObject7connectEPKS_PKcS1_S3_" cconnect :: (Ptr ()) -> CString -> (Ptr ()) -> CString -> IO ()
foreign import ccall "_ZN5QHBoxC1EP7QWidgetPKcj" qhbox_QHBox :: (Ptr (QHBox a)) -> Ptr () -> Int -> Int -> IO ()
foreign import ccall "_ZN5QVBoxC1EP7QWidgetPKcj" qvbox_QVBox :: (Ptr (QVBox a)) -> Ptr () -> Int -> Int -> IO ()

showWidget :: (QWidget w) => (Ptr w) -> IO ()
showWidget w = qshow (castPtr w)

hnew :: (New a) => Word -> IO (Ptr a)
hnew size = 
    do o <- cnew size
       return (castPtr o)

connect :: Ptr a -> String -> Ptr b -> String -> IO ()
connect a signal b slot =
    withCString ('2':signal) $ \sigStr ->
	withCString ('1':slot) $ \slotStr ->
	    cconnect (castPtr a) sigStr (castPtr b) slotStr

infixl 0 ->>
c ->> m = m c

kapplication :: String -> String -> String -> IO (Ptr KApplication)
kapplication name description version = 
    do arg     <- newCString name
       cargv   <- newArray [ arg]
       appname <- newCString "appname"
       desc    <- newCString "desc"
       ver     <- newCString "ver"
       kCmdLineArgs_init 1 cargv appname desc ver 0
       kapp <- new :: IO (Ptr KApplication)
       (kapp->> kapplication_KApplication) 1 1
       return kapp

-- * My Application

layout =
    QVBox (    QHBox ((QPushButton "1") .:. (QPushButton "2") .:. (QPushButton "3"))
	   .:. QHBox ((QPushButton "4") .:. (QPushButton "5") .:. (QPushButton "6"))
	   .:. QHBox ((QPushButton "7") .:. (QPushButton "8") .:. (QPushButton "9"))
	  ) 

main =
    do kapp <- kapplication "Calculator" "A Calculator in Haskell" "1.0"
       mainWidget <- createWidget noParent layout
       (kapp ->> setMainWidget) (castPtr mainWidget)
       (kapp ->> qapplication_exec)