Next Previous Contents

4. GHC Language Features

As with all known Haskell systems, GHC implements some extensions to the language. To use them, you'll need to give a -fglasgow-exts option.

Virtually all of the Glasgow extensions serve to give you access to the underlying facilities with which we implement Haskell. Thus, you can get at the Raw Iron, if you are willing to write some non-standard code at a more primitive level. You need not be ``stuck'' on performance because of the implementation costs of Haskell's ``high-level'' features---you can always code ``under'' them. In an extreme case, you can write all your time-critical code in C, and then just glue it together with Haskell!

Executive summary of our extensions:

Unboxed types and primitive operations:

You can get right down to the raw machine types and operations; included in this are ``primitive arrays'' (direct access to Big Wads of Bytes). Please see Section Unboxed types and following.

Multi-parameter type classes:

GHC's type system supports extended type classes with multiple parameters. Please see Section Mult-parameter type classes.

Local universal quantification:

GHC's type system supports explicit unversal quantification in constructor fields and function arguments. This is useful for things like defining runST from the state-thread world amongst other things. See Section Local universal quantification.

Calling out to C:

Just what it sounds like. We provide lots of rope that you can dangle around your neck. Please see Section Calling~C directly from Haskell.

Before you get too carried away working at the lowest level (e.g., sloshing MutableByteArray#s around your program), you may wish to check if there are system libraries that provide a ``Haskellised veneer'' over the features you want. See Section GHC Prelude and libraries.

4.1 Unboxed types

These types correspond to the ``raw machine'' types you would use in C: Int# (long int), Double# (double), Addr# (void *), etc. The primitive operations (PrimOps) on these types are what you might expect; e.g., (+#) is addition on Int#s, and is the machine-addition that we all know and love---usually one instruction.

A numerically-intensive program using unboxed types can go a lot faster than its ``standard'' counterpart---we saw a threefold speedup on one example.

Please see Section The module PrelGHC: really primitive stuff for the details of unboxed types and the operations on them.

4.2 Primitive state-transformer monad

This monad underlies our implementation of arrays, mutable and immutable, and our implementation of I/O, including ``C calls''.

The ST library, which provides access to the ST monad, is a GHC/Hugs extension library and is described in the separate GHC/Hugs Extension Libraries document.

4.3 Primitive arrays, mutable and otherwise

GHC knows about quite a few flavours of Large Swathes of Bytes.

First, GHC distinguishes between primitive arrays of (boxed) Haskell objects (type Array# obj) and primitive arrays of bytes (type ByteArray#).

Second, it distinguishes between...

Immutable:

Arrays that do not change (as with ``standard'' Haskell arrays); you can only read from them. Obviously, they do not need the care and attention of the state-transformer monad.

Mutable:

Arrays that may be changed or ``mutated.'' All the operations on them live within the state-transformer monad and the updates happen in-place.

``Static'' (in C land):

A C routine may pass an Addr# pointer back into Haskell land. There are then primitive operations with which you may merrily grab values over in C land, by indexing off the ``static'' pointer.

``Stable'' pointers:

If, for some reason, you wish to hand a Haskell pointer (i.e., not an unboxed value) to a C routine, you first make the pointer ``stable,'' so that the garbage collector won't forget that it exists. That is, GHC provides a safe way to pass Haskell pointers to C.

Please see Section Subverting automatic unboxing with ``stable pointers'' for more details.

``Foreign objects'':

A ``foreign object'' is a safe way to pass an external object (a C allocated pointer, say) to Haskell and have Haskell do the Right Thing when it no longer references the object. So, for example, C could pass a large bitmap over to Haskell and say ``please free this memory when you're done with it.''

Please see Section Pointing outside the Haskell heap for more details.

The libraries section give more details on all these ``primitive array'' types and the operations on them, Section The GHC Prelude and Libraries. Some of these extensions are also supported by Hugs, and the supporting libraries are described in the GHC/Hugs Extension Libraries document.

4.4 Using your own mainIO

Normally, the GHC runtime system begins things by called an internal function

        mainIO :: IO ()

which, in turn, fires up your Main.main. The standard definition of mainIO looks like this:

        mainIO = catch Main.main 
                   (\err -> error ("I/O error: " ++ show err ++ "\n"))

That is, all it does is run Main.main, catching any I/O errors that occur and displaying them on standard error before exiting the program.

To subvert the above process, you need only provide a mainIO of your own (in a module named PrelMain).

Here's a little example, stolen from Alastair Reid:

module GHCmain ( mainIO ) where

import GlaExts

mainIO :: IO ()
mainIO = do
         _ccall_ sleep 5
         _ccall_ printf "%d\n" (14::Int)

4.5 Calling C directly from Haskell

GOOD ADVICE: Because this stuff is not Entirely Stable as far as names and things go, you would be well-advised to keep your C-callery corraled in a few modules, rather than sprinkled all over your code. It will then be quite easy to update later on.

WARNING AS OF 2.03: Yes, the _ccall_ stuff probably will change, to something better, of course! One step in that direction is Green Card, a foreign function interface pre-processor for Haskell (``Glasgow'' Haskell in particular) --- check out

ftp://ftp.dcs.gla.ac.uk/pub/haskell/glasgow/green-card.ANNOUNCE
ftp://ftp.dcs.gla.ac.uk/pub/haskell/glasgow/green-card-src.tar.gz

_ccall_ and _casm_: an introduction

The simplest way to use a simple C function

double fooC( FILE *in, char c, int i, double d, unsigned int u )

is to provide a Haskell wrapper:

fooH :: Char -> Int -> Double -> Word -> IO Double
fooH c i d w = _ccall_ fooC (``stdin''::Addr) c i d w

The function fooH will unbox all of its arguments, call the C function fooC and box the corresponding arguments.

One of the annoyances about _ccall_s is when the C types don't quite match the Haskell compiler's ideas. For this, the _casm_ variant may be just the ticket (NB: no chance of such code going through a native-code generator):

oldGetEnv name
  = _casm_ ``%r = getenv((char *) %0);'' name >>= \ litstring@(A# str#) ->
    return (
        if (litstring == ``NULL'') then
            Left ("Fail:oldGetEnv:"++name)
        else
            Right (unpackCString# str#)
    )

The first literal-literal argument to a _casm_ is like a printf format: %r is replaced with the ``result,'' %0--%n-1 are replaced with the 1st--nth arguments. As you can see above, it is an easy way to do simple C casting. Everything said about _ccall_ goes for _casm_ as well.

Using function headers

When generating C (using the -fvia-C directive), one can assist the C compiler in detecting type errors by using the -#include directive to provide .h files containing function headers.

For example,

typedef unsigned long *StgForeignObj;
typedef long StgInt;

void          initialiseEFS (StgInt size);
StgInt        terminateEFS (void);
StgForeignObj emptyEFS(void);
StgForeignObj updateEFS (StgForeignObj a, StgInt i, StgInt x);
StgInt        lookupEFS (StgForeignObj a, StgInt i);

You can find appropriate definitions for StgInt, StgForeignObj, etc using gcc on your architecture by consulting ghc/includes/StgTypes.lh. The following table summarises the relationship between Haskell types and C types.


C type name Haskell Type StgChar Char# StgInt Int# StgWord Word# StgAddr Addr# StgFloat Float# StgDouble Double# StgArray Array# StgByteArray ByteArray# StgArray MutableArray# StgByteArray MutableByteArray# StgStablePtr StablePtr# StgForeignObj ForeignObj#

Note that this approach is only essential for returning floats (or if sizeof(int) != sizeof(int *) on your architecture) but is a Good Thing for anyone who cares about writing solid code. You're crazy not to do it.

Subverting automatic unboxing with ``stable pointers''

The arguments of a _ccall_ are automatically unboxed before the call. There are two reasons why this is usually the Right Thing to do:

It is possible to subvert the unboxing process by creating a ``stable pointer'' to a value and passing the stable pointer instead. For example, to pass/return an integer lazily to C functions storeC and fetchC, one might write:

storeH :: Int -> IO ()
storeH x = makeStablePtr x              >>= \ stable_x ->
           _ccall_ storeC stable_x

fetchH :: IO Int
fetchH x = _ccall_ fetchC               >>= \ stable_x ->
           deRefStablePtr stable_x      >>= \ x ->
           freeStablePtr stable_x       >>
           return x

The garbage collector will refrain from throwing a stable pointer away until you explicitly call one of the following from C or Haskell.

void freeStablePointer( StgStablePtr stablePtrToToss )
freeStablePtr :: StablePtr a -> IO ()

As with the use of free in C programs, GREAT CARE SHOULD BE EXERCISED to ensure these functions are called at the right time: too early and you get dangling references (and, if you're lucky, an error message from the runtime system); too late and you get space leaks.

And to force evaluation of the argument within fooC, one would call one of the following C functions (according to type of argument).

void     performIO  ( StgStablePtr stableIndex /* StablePtr s (IO ()) */ );
StgInt   enterInt   ( StgStablePtr stableIndex /* StablePtr s Int */ );
StgFloat enterFloat ( StgStablePtr stableIndex /* StablePtr s Float */ );

Note Bene: _ccall_GC_ must be used if any of these functions are used.

Pointing outside the Haskell heap

There are two types that ghc programs can use to reference (heap-allocated) objects outside the Haskell world: Addr and ForeignObj.

If you use Addr, it is up to you to the programmer to arrange allocation and deallocation of the objects.

If you use ForeignObj, ghc's garbage collector will call upon the user-supplied finaliser function to free the object when the Haskell world no longer can access the object. (An object is associated with a finaliser function when the abstract Haskell type ForeignObj is created). The finaliser function is expressed in C, and is passed as argument the object:

void foreignFinaliser ( StgForeignObj fo )

when the Haskell world can no longer access the object. Since ForeignObjs only get released when a garbage collection occurs, we provide ways of triggering a garbage collection from within C and from within Haskell.

void StgPerformGarbageCollection()
performGC :: IO ()

More information on the programmers' interface to ForeignObj can be found in Section Foreign objects.

Avoiding monads

The _ccall_ construct is part of the IO monad because 9 out of 10 uses will be to call imperative functions with side effects such as printf. Use of the monad ensures that these operations happen in a predictable order in spite of laziness and compiler optimisations.

To avoid having to be in the monad to call a C function, it is possible to use unsafePerformIO, which is available from the IOExts module. There are three situations where one might like to call a C function from outside the IO world:

C-calling ``gotchas'' checklist

And some advice, too.

4.6 Multi-parameter type classes

(ToDo)

4.7 Local universal quantification

(ToDo)

4.8 Concurrent and Parallel Haskell

Concurrent and Parallel Haskell are Glasgow extensions to Haskell which let you structure your program as a group of independent `threads'.

Concurrent and Parallel Haskell have very different purposes.

Concurrent Haskell is for applications which have an inherent structure of interacting, concurrent tasks (i.e. `threads'). Threads in such programs may be required. For example, if a concurrent thread has been spawned to handle a mouse click, it isn't optional---the user wants something done!

A Concurrent Haskell program implies multiple `threads' running within a single Unix process on a single processor.

You will find at least one paper about Concurrent Haskell hanging off of Simon Peyton Jones's Web page.

Parallel Haskell is about speed---spawning threads onto multiple processors so that your program will run faster. The `threads' are always advisory---if the runtime system thinks it can get the job done more quickly by sequential execution, then fine.

A Parallel Haskell program implies multiple processes running on multiple processors, under a PVM (Parallel Virtual Machine) framework.

Parallel Haskell is still relatively new; it is more about ``research fun'' than about ``speed.'' That will change.

Again, check Simon's Web page for publications about Parallel Haskell (including ``GUM'', the key bits of the runtime system).

Some details about Concurrent and Parallel Haskell follow.

Language features specific to Concurrent Haskell

The Concurrent interface (recommended)

GHC provides a Concurrent module, a common interface to a collection of useful concurrency abstractions, including those mentioned in the ``concurrent paper''.

Just put import Concurrent into your modules, and away you go. To create a ``required thread'':

forkIO :: IO a -> IO a

The Concurrent interface also provides access to ``I-Vars'' and ``M-Vars'', which are two flavours of synchronising variables.

IVars are write-once variables. They start out empty, and any threads that attempt to read them will block until they are filled. Once they are written, any blocked threads are freed, and additional reads are permitted. Attempting to write a value to a full IVar results in a runtime error. Interface:

newIVar     :: IO (IVar a)
readIVar    :: IVar a -> IO a
writeIVar   :: IVar a -> a -> IO ()

MVars are rendezvous points, mostly for concurrent threads. They begin empty, and any attempt to read an empty MVar blocks. When an MVar is written, a single blocked thread may be freed. Reading an MVar toggles its state from full back to empty. Therefore, any value written to an MVar may only be read once. Multiple reads and writes are allowed, but there must be at least one read between any two writes. Interface:

newEmptyMVar :: IO (MVar a)
newMVar      :: a -> IO (MVar a)
takeMVar     :: MVar a -> IO a
putMVar      :: MVar a -> a -> IO ()
readMVar     :: MVar a -> IO a
swapMVar     :: MVar a -> a -> IO a

A channel variable (CVar) is a one-element channel, as described in the paper:

data CVar a
newCVar :: IO (CVar a)
putCVar :: CVar a -> a -> IO ()
getCVar :: CVar a -> IO a

A Channel is an unbounded channel:

data Chan a 
newChan         :: IO (Chan a)
putChan         :: Chan a -> a -> IO ()
getChan         :: Chan a -> IO a
dupChan         :: Chan a -> IO (Chan a)
unGetChan       :: Chan a -> a -> IO ()
getChanContents :: Chan a -> IO [a]

General and quantity semaphores:

data QSem
newQSem     :: Int   -> IO QSem
waitQSem    :: QSem  -> IO ()
signalQSem  :: QSem  -> IO ()

data QSemN
newQSemN    :: Int   -> IO QSemN
signalQSemN :: QSemN -> Int -> IO ()
waitQSemN   :: QSemN -> Int -> IO ()

Merging streams---binary and n-ary:

mergeIO  :: [a]   -> [a] -> IO [a]
nmergeIO :: [[a]] -> IO [a]

A Sample variable (SampleVar) is slightly different from a normal MVar:

type SampleVar a = MVar (Int, MVar a)

emptySampleVar :: SampleVar a -> IO ()
newSampleVar   :: IO (SampleVar a)
readSample     :: SampleVar a -> IO a
writeSample    :: SampleVar a -> a -> IO ()

Finally, there are operations to delay a concurrent thread, and to make one wait:

threadDelay     :: Int -> IO () -- delay rescheduling for N microseconds
threadWaitRead  :: Int -> IO () -- wait for input on specified file descriptor
threadWaitWrite :: Int -> IO () -- (read and write, respectively).

Features specific to Parallel Haskell

\subsubsubsection{The Parallel interface (recommended)}

GHC provides two functions for controlling parallel execution, through the Parallel interface:

interface Parallel where
infixr 0 `par`
infixr 1 `seq`

par :: a -> b -> b
seq :: a -> b -> b

The expression (x `par` y) sparks the evaluation of x (to weak head normal form) and returns y. Sparks are queued for execution in FIFO order, but are not executed immediately. At the next heap allocation, the currently executing thread will yield control to the scheduler, and the scheduler will start a new thread (until reaching the active thread limit) for each spark which has not already been evaluated to WHNF.

The expression (x `seq` y) evaluates x to weak head normal form and then returns y. The seq primitive can be used to force evaluation of an expression beyond WHNF, or to impose a desired execution sequence for the evaluation of an expression.

For example, consider the following parallel version of our old nemesis, nfib:

import Parallel

nfib :: Int -> Int
nfib n | n <= 1 = 1
       | otherwise = par n1 (seq n2 (n1 + n2 + 1))
                     where n1 = nfib (n-1) 
                           n2 = nfib (n-2)

For values of n greater than 1, we use par to spark a thread to evaluate nfib (n-1), and then we use seq to force the parent thread to evaluate nfib (n-2) before going on to add together these two subexpressions. In this divide-and-conquer approach, we only spark a new thread for one branch of the computation (leaving the parent to evaluate the other branch). Also, we must use seq to ensure that the parent will evaluate n2 before n1 in the expression (n1 + n2 + 1). It is not sufficient to reorder the expression as (n2 + n1 + 1), because the compiler may not generate code to evaluate the addends from left to right.

\subsubsubsection{Underlying functions and primitives}

The functions par and seq are wired into GHC, and unfold into uses of the par# and seq# primitives, respectively. If you'd like to see this with your very own eyes, just run GHC with the -ddump-simpl option. (Anything for a good time...)

You can use par and seq in Concurrent Haskell, though I'm not sure why you would want to.

Features common to Concurrent and Parallel Haskell

Actually, you can use the `par` and `seq` combinators (really for Parallel Haskell) in Concurrent Haskell as well. But doing things like ``par to forkIO many required threads'' counts as ``jumping out the 9th-floor window, just to see what happens.''

\subsubsubsection{Scheduling policy for concurrent/parallel threads}

Runnable threads are scheduled in round-robin fashion. Context switches are signalled by the generation of new sparks or by the expiry of a virtual timer (the timer interval is configurable with the -C[<num>] RTS option). However, a context switch doesn't really happen until the next heap allocation. If you want extremely short time slices, the -C RTS option can be used to force a context switch at each and every heap allocation.

When a context switch occurs, pending sparks which have not already been reduced to weak head normal form are turned into new threads. However, there is a limit to the number of active threads (runnable or blocked) which are allowed at any given time. This limit can be adjusted with the -t<num> RTS option (the default is 32). Once the thread limit is reached, any remaining sparks are deferred until some of the currently active threads are completed.

4.9 Haskell 1.4 vs. Glasgow Haskell 3.00: language non-compliance

This section lists Glasgow Haskell infelicities in its implementation of Haskell 1.4. See also the ``when things go wrong'' section (Section What to do when something goes wrong) for information about crashes, space leaks, and other undesirable phenomena.

The limitations here are listed in Haskell-Report order (roughly).

Expressions and patterns

Very long String constants:

May not go through. If you add a ``string gap'' every few thousand characters, then the strings can be as long as you like.

Bear in mind that string gaps and the -cpp option don't mix very well (see Section The C pre-processor).

Very long literal lists:

These may tickle a ``yacc stack overflow'' error in the parser. (It depends on the Yacc used to build your parser.)

Single quotes in module names:

It might work, but it's just begging for trouble.

Declarations and bindings

Derived instances of Read and Show for infix constructors:

All the carry-on about derived readsPrec and showsPrec for infix constructors---we don't do it (yet). We treat them the same way as all other constructors.

Derived instances for records:

Hmmm.

Module system and interface files

Namespace pollution

Several modules internal to GHC are visible in the standard namespace. All of these modules begin with Prel, so the rule is: don't use any modules beginning with Prel in your programl, or you will be comprehensively screwed.

Can't export primitive types (e.g., Int#):

Don't even try...

Numbers, basic types, and built-in classes

Very large/small fractional constants:

(i.e., with a decimal point somewhere) GHC does not check that these are out of range (e.g., for a Float), and bad things will inevitably follow. (To be corrected?)

This problem does not exist for integral constants.

For very large/small fractional constants near the limits of your floating-point precision, things may go wrong. (It's better than it used to be.) Please report any such bugs.

Unchecked arithmetic:

Arguably not an infelicity, but... Bear in mind that operations on Int, Float, and Double numbers are unchecked for overflow, underflow, and other sad occurrences. (note, however that some architectures trap floating-point overflow and loss-of-precision and report a floating-point exception).

Use Integer, Rational, etc., numeric types if this stuff keeps you awake at night.

Multiply-defined array elements---not checked:

This code fragment should elicit a fatal error, but it does not:

main = print (array (1,1) [ 1:=2, 1:=3 ])

In Prelude support

Arbitrary-sized tuples:

Plain old tuples of arbitrary size do work. Note that lots of overloading can give rise to large tuples ``under the hood'' of your program.

HOWEVER: standard instances for tuples (Eq, Ord, Bounded, Ix Read, and Show) are available only up to 5-tuples.

These limitations are easily subvertible, so please ask if you get stuck on them.

Unicode character set:

Haskell 1.4 embraces the Unicode character set, but GHC 3.00 doesn't handle it. Yet.


Next Previous Contents