The Dotnet library

The Dotnet library provides you with miscellaneous auxillary functions to help you interoperate with .NET.

Representing object references

At the base, the library defines and exports the Object type which is used to represent .NET object references:

data Object a = ...abstract...

instance Eq (Object a)   where {...}
instance Show (Object a) where {...}
The Object type is parameterised over a type that encodes the .NET class reference it is representing. To illustrate how, the Dotnet.System.Object and Dotnet.System.String modules define the following:
-- module providing the functionality of System.Object
module Dotnet.System.Object 
         ( Dotnet.Object
	 , module Dotnet.System.Object
	 ) where 

import Dotnet ( Object )

getHashCode :: Object a -> IO Int
getHashCode = ...
...

-- module providing the functionality of System.Xml.XmlNode
module Dotnet.System.Xml.XmlNode where

import Dotnet.System.Object
...
data XmlNode_ a
type XmlNode a = Dotnet.System.Object.Object (XmlNode_ a)
...
foreign import dotnet
  "method System.Xml.XmlNode.get_InnerXml"
  get_InnerXml :: XmlNode obj -> IO (String)

...
-- module providing the functionality of System.Xml.XmlDocument
module Dotnet.System.Xml.XmlDocument where

import Dotnet
import Dotnet.System.Xml.XmlNode

data XmlDocument_ a
type XmlDocument a = XmlNode (XmlDocument_ a)

...
foreign import dotnet
  "method System.Xml.XmlDocument.LoadXml"
  loadXml :: String -> XmlDocument obj -> IO (())
...

[The reason why Dotnet. is prefixed to each Haskell module is to avoid naming conflicts with other common Haskell modules. See the tools for more details. ]

Notice the type given to Dotnet.System.Xml.XmlNode.get_InnerXml's argument -- XmlNode obj -- capturing precisely that the method get_InnerXml is supported on any object that is an instance of System.Xml.XmlNode or any of its sub-classes (like XmlDocument.) If we expand a type like XmlDocument (), we get:

XmlDocument () == Dotnet.Object (XmlNode_ (XmlDocument_ ()))

Notice how the type argument to Dotnet.Object encodes the inheritance structure: System.Xml.XmlDocument is a sub-class of System.Xml.XmlNode which again is a sub-class of System.Object. The unit type, (), all the way to the right is used to terminate the chain and state that the type represent just XmlDocument (but none of its sub-classes.)

If instead of () a type variable had been used, like what was done for get_InnerXml's argument type, the type is a subtype. So, if you've got a System.Xml.XmlNode or one of its sub-classes (like XmlDocument), you can safely invoke the method get_InnerXml -- the type variable obj permitting the use of any subtype of System.Xml.XmlNode.

This type trick is a good way to safely represent .NET object references using Haskell's type system. If you're already familiar with the work on integrating COM with Haskell, you'll have already recognised that the type encoding used here mirrors that used for COM interface hierarchies.

OO-style application

To support the syntax for conventional OO-style method invocation, the Dotnet module exports the following two combinators:

infix 8 #
infix 9 ##

( # )  :: a -> (a -> IO b) -> IO b
obj # method = method obj

( ## ) :: IO a -> (a -> IO b) -> IO b
mObj ## method = mObj >>= method
Using these, method invocation can be expressed as follows:
  l <- str # Dotnet.System.String.lengthString 
  putStrLn ("Length of string: " ++ show l)

Supporting marshaling

The main way to bind to the .NET object model is to use FFI declarations, but the Dotnet library provides an alternate way (which used to be the only way prior to the integration of .NET interop into the FFI). This route is mainly provided for backwards compatibility, so unless you have a specific reason not to employ the FFI route, the next couple of sections of this document is of limited interest.

To support the automatic marshaling of values between the .NET and Haskell worlds, Dotnet provides two Haskell type classes:

class NetType a where
   arg    :: a -> InArg
   result :: Object () -> IO a

type InArg = IO (Object ())

class NetArg a where
  marshal :: a -> IO [Object ()]
Both NetType and NetArg work in terms of Dotnet.Object () -- an untyped representation of object references.

The following instances are provided:

instance NetType (Object a)
instance NetType ()
instance NetType Int
instance NetType {Int8, Int16, Int32}
instance NetType {Word8, Word16, Word32}
instance NetType Bool
instance NetType Char
instance NetType String
instance NetType Float
instance NetType Double
In addition to object references, instances also let you convert to/from the 'standard' unboxed types that the .NET framework provides.

The NetType class takes care of marshaling single arguments to/from their .NET representations; the NetArg deals with marshaling a collection of such arguments:

instance NetArg ()  -- no args
instance NetType a => NetArg a  -- one arg
instance (NetArg a1, NetArg a2) => NetArg (a1,a2)     -- 2 args
...
instance (NetArg a1, NetArg a2, NetArg a3,
	  NetArg a4, NetArg a5, NetArg a6,
	  NetArg a7) => NetArg (a1,a2,a3,a4,a5,a6,a7) -- 7 args

The idea is here to use tuples to do uncurried method application; details of which will be introduced in the next section.

Creating .NET objects

To create a new object, use one of the following actions:
type ClassName = String

new    :: ClassName -> IO (Object a)
newObj :: (NetArg a)
       => ClassName
       -> a
       -> IO (Object res)
createObj :: ClassName -> [InArg] -> IO (Object a)
To call the nullary constructor for an object, simply use new:
main = do
   x <- new "System.Object"
   print x -- under-the-hood this calls ToString() on 'x' 

To use a parameterised constructor instead, you can use newObj or createObject:

newXPathDoc :: String
            -> System.Xml.XmlSpace
	    -> IO (System.Xml.XPath.XPathDocument ())
newXPathDoc uri spc = newObj "System.Xml.XPath.XPathDocument" (uri,spc)

newBitmap :: Int -> Int -> IO (System.Drawing.Bitmap ())
newBitmap w h = createObj "System.Drawing.Bitmap" [arg w, arg h]

createObj lets you pass a list of arguments, but you have to explicitly apply arg to each of them. newObj takes care of this automatically provided you 'tuple up' the arguments.

new can clearly be expressed in terms of these more general constructor actions:

-- 
new cls = newObj cls ()
-- or
-- new cls = createObj cls []
Note: the reason why both createObj and newObj, which perform identical functions, are provided, is to gain experience as to what is the preferred invocation style.

Unsurprisingly, these two different forms of marshaling arguments are also used when dealing with method invocation, which we look at next.

Calling .NET methods

To invoke a static method, use invokeStatic or staticMethod:
type MethodName = String

invokeStatic :: (NetArg a, NetType res)
	     => ClassName
	     -> MethodName
             -> a
             -> IO res
staticMethod :: (NetType a)
             => ClassName
	     -> MethodName
             -> [InArg]
             -> IO a
staticMethod_ :: ClassName
	      -> MethodName
              -> [InArg]
              -> IO ()
invokeStatic uses the NetArg type class, so you need to tuple the arguments you pass to the static method:
doFoo :: String -> Int -> IO String
doFoo x y = invokeStatic "System.Bar" "Foo" (x,y)
staticMethod uses a list to pass arguments to the static method, requiring you to apply the (overloaded) marshaling function first:
urlEncode :: String -> IO String
urlEncode url = staticMethod "System.Web.HttpUtility"
                             "UrlEncode"
			     [arg url]
Instance method invocation is similar, but of course requires an extra 'this' argument:
invoke :: (NetArg a, NetType res)
       => MethodName
       -> a
       -> Object b
       -> IO res

method :: (NetType a)
       => MethodName
       -> [InArg]
       -> Object b
       -> IO a

method_ :: MethodName
        -> [InArg]
        -> Object a
        -> IO ()
For example,
main = do
  obj <- new "System.Object"
  x   <- obj # invoke "GetHashCode" ()
  print ("The hash code is: " ++ show (x::Int))

Field access

As with methods, the Dotnet library provides access to both static and instance fields:
type FieldName = String

fieldGet :: (NetType a) => FieldName -> Object b -> IO a
fieldSet :: (NetType a) => FieldName -> Object b -> a -> IO ()

staticFieldGet :: (NetType a) => ClassName -> FieldName -> IO a
staticFieldSet :: (NetType a) => ClassName -> FieldName -> a -> IO ()

Using delegators

To assist in the interoperation with the .NET framework (the UI bits, in particular), the Dotnet library lets you wrap up Haskell function values as .NET delegators:
newDelegator :: (Object a -> Object b -> IO ())
	     -> IO (Object (Dotnet.System.EventHandler ())))
When the System.EventHandler object reference is passed to another .NET method, it can invoke it just like any other EventHandler delegate. When that happens, the Haskell function value you passed to newDelegator is invoked. (The way this is done under the hood is kind of funky, requiring some dynamic code (and class) generation, but I digress.)

To see the delegator support in action, have a look at the UI examples in the distribution.

Creating a Haskell-based .NET class

The Dotnet library provides experimental support for creating new classes that wrap up Haskell IO actions:
defineClass :: Class -> IO (Object b)

data Class 
 = Class String		-- type/class name
 	 (Maybe String) -- Just x => derive from x
 	 [Method]

data Method
 = Method MethodName       -- .NET name (unqualified).
	  Bool             -- True => override.
 	  String           -- Haskell function to call.
	  [BaseType]       -- Argument types
	  (Maybe BaseType) -- result (Nothing => void).
See examples/class/ in the distribution for more.

Tool support for interfacing with .NET Framework classes

One thing that immediately strikes you when looking at the .NET Framework for the first time is its size. Clearly, it wouldn't be practical to manually type out Haskell wrappers for each and every class that it provides.

To assist in the interfacing to .NET classes, a utility HsWrapGen is provided. Given the name of a .NET class, it generates a Haskell module wrapper for the class, containing FFI declarations that lets you access the methods and fields of a particular class. See the dotnet/tools/ directory, if interested.

Note: Hugs98 for .NET makes good use of the hierarchical module extension to Haskell, so if you do write / generate your own class wrappers, you may want to consider putting them inside the library tree that Hugs98 for .NET comes with.

To demonstrate where and how, supposing you had written a Haskell wrapper for System.Xml.Schema.XmlSchema, you need to name the Haskell module just that, i.e.,:

module Dotnet.System.Xml.Schema.XmlSchema where { .... }
and place it in dotnet/lib/Dotnet/System/Xml/Schema/ directory inside the Hugs98 for .NET installation tree. You can then utilise the wrapper module in your own code by importing it as
import Dotnet.System.Xml.Schema.XmlSchema

To avoid naming conflicts with Haskell's hierarchical library tree, we prefix each of the .NET specific modules with Dotnet..


Last modified: Wed Mar 12 19:18:34 Pacific Standard Time 2003