Monday, November 23, 2009

Haskell DLL's on Windows

The current section of the GHC manual on creating DLL's on Windows is fairly confusing to read, and has some bugs (i.e. 3605). Since I got tripped up by the current documentation, I offered to rewrite sections 11.6.2 and 11.6.3 (merging them in the process). Creating Windows DLL's with GHC is surprisingly easy, and my revised manual section includes an example which can be called from both Microsoft Word (using VBA) and C++. I've pasted the revised manual section as the rest of this blog post. I'll shortly be submitting it to the GHC team, so any feedback is welcome.




11.6.2. Making DLLs to be called from other languages

This section describes how to create DLLs to be called from other languages, such as Visual Basic or C++. This is a special case of Section 8.2.1.2, "Making a Haskell library that can be called from foreign code"; we'll deal with the DLL-specific issues that arise below. Here's an example:

Use foreign export declarations to export the Haskell functions you want to call from the outside. For example:


-- Adder.hs
{-# LANGUAGE ForeignFunctionInterface #-}
module Adder where

adder :: Int -> Int -> IO Int -- gratuitous use of IO
adder x y = return (x+y)

foreign export stdcall adder :: Int -> Int -> IO Int


Add some helper code that starts up and shuts down the Haskell RTS:


// StartEnd.c
#include <Rts.h>

extern void __stginit_Adder(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();
}


Here, Adder is the name of the root module in the module tree (as mentioned above, there must be a single root module, and hence a single module tree in the DLL). Compile everything up:


$ ghc -c Adder.hs
$ ghc -c StartEnd.c
$ ghc -shared -o Adder.dll Adder.o Adder_stub.o StartEnd.o


Now the file Adder.dll can be used from other programming languages. Before calling any functions in Adder it is necessary to call HsStart, and at the very end call HsEnd.

NOTE: It may appear tempting to use DllMain to call hs_init/hs_exit, but this won’t work (particularly if you compile with -threaded).

11.6.2.1. Using from VBA

An example of using Adder.dll from VBA is:


Private Declare Function Adder Lib "Adder.dll" Alias "adder@8" _
(ByVal x As Long, ByVal y As Long) As Long

Private Declare Sub HsStart Lib "Adder.dll" ()
Private Declare Sub HsEnd Lib "Adder.dll" ()

Private Sub Document_Close()
HsEnd
End Sub

Private Sub Document_Open()
HsStart
End Sub

Public Sub Test()
MsgBox "12 + 5 = " & Adder(12, 5)
End Sub


This example uses the Document_Open/Close functions of Microsoft Word, but provided HsStart is called before the first function, and HsEnd after the last, then it will work fine.

11.6.2.2. Using from C++

An example of using Adder.dll from C++ is:


// Tester.cpp
#include "HsFFI.h"
#include "Adder_stub.h"
#include <stdio.h>

extern "C" {
void HsStart();
void HsEnd();
}

int main()
{
HsStart();
// can now safely call functions from the DLL
printf("12 + 5 = %i\n", adder(12,5)) ;
HsEnd();
return 0;
}


This can be compiled and run with:


$ ghc -o tester Tester.cpp Adder.dll.a
$ tester
12 + 5 = 17


Please give feedback in the comments.

Monday, November 16, 2009

Reviewing View Patterns

View Patterns are an interesting extension to the pattern matching capabilities of Haskell, implemented in GHC 6.10 and above. After using view patterns in real world programs, including HLint, I've come to like them. I use view patterns in 10 of the 27 modules in HLint.

View Pattern Overview

My intuitive understanding of view patterns is given in my Approaches and Applications of Inductive Programming 2009 paper, which describes the view pattern translation as:


f (sort -> min:ascending) = ...
==
f v_1 | min:ascending <- sort v_1 = ...
==
f v_1 | case v_2 of _:_ -> True ; _ -> False = ...
where v_2 = sort v_1 ; min:ascending = v_2


The view pattern on the first line sorts the list elements, then binds the lowest element to min and the remaining elements to ascending. If there are no elements in the list then the pattern will not match. This can be translated to a pattern guard, which can then be translated to a case expression. This translation does not preserve the scoping behaviour of the variables, but is sufficient for all my uses of view patterns. It is important to note that the translation from view patterns to pattern guards is fairly simple, and mainly eliminates one redundant intermediate variable. However, the translation from pattern guards to case expressions and guards is substantially harder.

How I Use View Patterns

My uses of view patterns seem to fall into a few distinct categories. Here are some example code snippets (mainly from HLint), along with explanation.

1) Complex/Nested Matching


uglyEta (fromParen -> App f (fromParen -> App g x)) (fromParen -> App h y) = g == h


Every operation/match pair in a pattern guard requires a separate pattern guard, whereas view patterns can be nested very naturally. Here the abstract syntax tree for expressions has brackets, and the fromParen function unwraps any brackets to find the interesting term inside. View patterns allow us to perform nested matches, which would have required three separate pattern guards.

2) Matching on a Different Structure


isAppend (view -> App2 op _ _) = op ~= "++"


The expression tree I use in HLint has lots of expressions which apply a function to two arguments - for example App (App (Var f) x) y and InfixOp x f y. I have a type class View that maps expressions into the data type data App2 = NoApp2 | App2 String Exp Exp, allowing easy matching on a range of expressions.

3) Safe Normalisation


dismogrify (simplify -> x) = .... x ....


While working with Yhc Core for the Catch and Supero tools I often wanted to process a syntax tree after simplifying it. If you name the original tree x, and the simplified tree y, then it's an easy (and type-safe) mistake to use x instead of y. To avoid this I wrote:


dismogrify bad_x = .... x ....
where x = simplify bad_x


Using bad_x in the expression makes the mistake easy for a human to spot. Using a view pattern makes the mistake impossible.

4) Mapping


classify (Ident (getRank -> x)) = ...


Sometimes I want to take a variable in one domain, and work with it in another. In the above example getRank converts a String to a Rank enumeration. Within the classify function I only wish to work with the rank as an enumeration, so it's convenient to never bind the string. This pattern is similar to safe normalisation, but it's purpose isn't safety - just making things a little neater.

5) Abstraction

The view pattern example in the GHC manual is all about abstraction. I have mainly used HLint in programs which don't use abstract data types, just algebraic data types which are intended to be manipulated directly. I don't think there are many data types which are both abstract and have a structural view, so I suspect this use will be less common (Data.Sequence is the only type that comes to mind).

Improvements I Suggest

I think there are three improvements that should be made to the view patterns in GHC 6.10.4:

1) Warnings

In GHC 6.10 all view patterns are incorrectly considered overlapping (see bug #2395), so all users of view patterns need to supply -fno-warn-overlapping-patterns. This problem has been fixed in GHC 6.12, which is great news.

2) Scoping

The current scoping behaviour seems undesirable:


apply (f -> y) = ...
where f = ...


Here the f in the view pattern isn't the f bound at the where. I suggest that the lhs of the -> can use variables from the where, in a similar manner to pattern guards. (It's possible this suggestion is misguided, as the scoping rules can be quite subtle.)

3) Implicit Patterns

The original view patterns wiki document asks what should become of (-> ...), and proposes it become (view -> ...). I like this idea as HLint already contains 12 instances of (view -> ...). The only question is which view should be used? I think there are two possible answers:

a) The view currently in scope

If the desugaring is simply to view, then people can select their imports appropriately to choose their view function. This proposal is similar to the rebindable syntax already supported, but in this case may be a legitimate default, due to several possible view interpretations. If one day everyone starts using Data.View.view, then the default could be switched. As an example (in combination with proposal 2) we could have:


uglyEta (-> App f (-> App g x)) (-> App h y) = g == h
where view = fromParen


b) Data.View.view

In HLint I have used:


class View a b where
view :: a -> b


I haven't needed any functional dependencies, as the matching always constrains the types sufficiently. I have mapped one source type (i.e. Exp) to several matching types (App2 and App1), but never mapped multiple source types onto one matching type. If I was to add a dependency it should be that b uniquely determines a, as usually b will have a pattern on the RHS which will constrain b already.

I think my preference is for using Data.view.view, primarily because all other Haskell syntax is bound to a fixed name, rather than using the name currently in scope. However, my opinions on functional dependencies should be taken with skepticism - I'm not normally a user of functional dependencies.

4) Rejected Suggestions

I do not support the idea of implicit view patterns without some leading syntax (see bug 3583) - view patterns are nice, but I don't think they are important enough to be first-class, like they are in F# (note that F# interoperates with OO languages, so first-class view patterns are much more reasonable there).

I also do not support the idea of implicit Maybe in view patterns - Maybe should not be special, and this suggestion doesn't seem to fit with the rest of Haskell.

Conclusion

View patterns are a nice enhancement to pattern guards, increasing their compositionality and reducing the need for redundant intermediate variables. I could live without view patterns, but I don't think I should have to - the design is good, and they fit in nicely with the language. As for pattern guards, I consider them an essential part of the Haskell language that really makes a substantially difference to some pieces of code that would otherwise be rather ugly.

Edit: Fix as per Christophe's comment.