diff options
Diffstat (limited to 'ghc/docs/users_guide')
-rw-r--r-- | ghc/docs/users_guide/Jmakefile | 9 | ||||
-rw-r--r-- | ghc/docs/users_guide/glasgow_exts.lit | 722 | ||||
-rw-r--r-- | ghc/docs/users_guide/gone_wrong.lit | 332 | ||||
-rw-r--r-- | ghc/docs/users_guide/how_to_run.lit | 1139 | ||||
-rw-r--r-- | ghc/docs/users_guide/intro.lit | 69 | ||||
-rw-r--r-- | ghc/docs/users_guide/libraries.lit | 1047 | ||||
-rw-r--r-- | ghc/docs/users_guide/parallel.lit | 662 | ||||
-rw-r--r-- | ghc/docs/users_guide/prof-compiler-options.lit | 84 | ||||
-rw-r--r-- | ghc/docs/users_guide/prof-options.lit | 30 | ||||
-rw-r--r-- | ghc/docs/users_guide/prof-post-processors.lit | 130 | ||||
-rw-r--r-- | ghc/docs/users_guide/prof-reports.lit | 1 | ||||
-rw-r--r-- | ghc/docs/users_guide/prof-rts-options.lit | 120 | ||||
-rw-r--r-- | ghc/docs/users_guide/profiling.lit | 239 | ||||
-rw-r--r-- | ghc/docs/users_guide/runtime_control.lit | 332 | ||||
-rw-r--r-- | ghc/docs/users_guide/sooner.lit | 530 | ||||
-rw-r--r-- | ghc/docs/users_guide/ticky.lit | 26 | ||||
-rw-r--r-- | ghc/docs/users_guide/tutorial.lit | 129 | ||||
-rw-r--r-- | ghc/docs/users_guide/user.lit | 36 | ||||
-rw-r--r-- | ghc/docs/users_guide/utils.lit | 143 | ||||
-rw-r--r-- | ghc/docs/users_guide/vs_haskell.lit | 575 |
20 files changed, 6355 insertions, 0 deletions
diff --git a/ghc/docs/users_guide/Jmakefile b/ghc/docs/users_guide/Jmakefile new file mode 100644 index 0000000000..018e0e1b2d --- /dev/null +++ b/ghc/docs/users_guide/Jmakefile @@ -0,0 +1,9 @@ +LitStuffNeededHere(docs depend) +InfoStuffNeededHere(docs) + +LiterateSuffixRules() +DocProcessingSuffixRules() + +/* no space between the args! */ +/*LitDocRootTarget(profiling,lit)*/ +LitDocRootTarget(user,lit) diff --git a/ghc/docs/users_guide/glasgow_exts.lit b/ghc/docs/users_guide/glasgow_exts.lit new file mode 100644 index 0000000000..e480f8c005 --- /dev/null +++ b/ghc/docs/users_guide/glasgow_exts.lit @@ -0,0 +1,722 @@ +%************************************************************************ +%* * +\section[glasgow-exts]{Glasgow extensions to Haskell} +\index{Haskell, Glasgow extensions} +\index{extensions, Glasgow Haskell} +%* * +%************************************************************************ + +As with all known Haskell systems, GHC implements some extensions to +the language. +To use them, you'll need to give +a \tr{-fglasgow-exts}% +\index{-fglasgow-exts option} 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: +\begin{description} +\item[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 \Sectionref{glasgow-unboxed} and following. + +%\item[Synchronising variables---\tr{_IVar}s, \tr{_MVar}s:] +%These are used when reads and writes need to be coordinated, +%e.g., if the readers and writers are different concurrent threads. +%Please see \Sectionref{ivars-mvars}. + +\item[Calling out to C:] Just what it sounds like. We provide {\em +lots} of rope that you can dangle around your neck. +Please see \Sectionref{glasgow-ccalls}. + +\item[``Monadic I/O:''] This stuff will be coming to you For Real +with Haskell~1.3, whenever that is. +Please see \Sectionref{io-1-3} (the ``1.3 I/O'' section). + +\item[``HBC-ish'' extensions:] Extensions implemented because people said, +``HBC does Y. Could you teach GHC to do the same?'' Please see +\Sectionref{glasgow-hbc-exts} for a quick list. +\end{description} + +Before you get too carried away working at the lowest level (e.g., +sloshing \tr{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 \Sectionref{syslibs}. + +The definitive guide for many of the low-level facilities in GHC is +the ``state interface document'' (distributed in +\tr{ghc/docs/state-interface.dvi}). We do not repeat its details here. + +%Pieter Hartel led an interesting comparison-of-many-compilers (and +%many languages) in which GHC got to show off its extensions. We did +%very well! For the full details, check out +%\tr{pub/computer-systems/functional/packages/pseudoknot.tar.Z} on \tr{ftp.fwi.uva.nl}. +%Good clean fun! + +%************************************************************************ +%* * +\subsection[glasgow-unboxed]{Unboxed types} +\index{Unboxed types (Glasgow extension)} +%* * +%************************************************************************ + +These types correspond to the ``raw machine'' types you would use in +C: \tr{Int#} (long int), \tr{Double#} (double), +\tr{Addr#} (void *), etc. The {\em primitive +operations} (PrimOps) on these types are what you might expect; e.g., +\tr{(+#)} is addition on \tr{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 {\em lot} +faster than its ``standard'' counterpart---we saw a threefold speedup +on one example. + +Please see the very first part of the ``state interface document'' +(distributed in \tr{ghc/docs/state-interface.dvi}) for the details of +unboxed types and the operations on them. + +%************************************************************************ +%* * +\subsection[glasgow-ST-monad]{Primitive state-transformer monad} +\index{state transformers (Glasgow extensions)} +%* * +%************************************************************************ + +This monad underlies our implementation of arrays, mutable and immutable, +and our implementation of I/O, including ``C calls''. + +You probably won't use the monad directly, but you might use all those +other things! + +The ``state interface document'' defines the state-related types in +sections~1.4 and~1.5, and the monad itself in section~2.1. + +%************************************************************************ +%* * +\subsection[glasgow-prim-arrays]{Primitive arrays, mutable and otherwise} +\index{primitive arrays (Glasgow extension)} +\index{arrays, primitive (Glasgow extension)} +%* * +%************************************************************************ + +GHC knows about quite a few flavours of Large Swathes of Bytes. + +First, GHC distinguishes between primitive arrays of (boxed) Haskell +objects (type \tr{Array# obj}) and primitive arrays of bytes (type +\tr{ByteArray#}). + +Second, it distinguishes between... +\begin{description} +\item[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. + +\item[Mutable:] +Arrays that may be changed or ``mutated.'' All the operations on them +live within the state-transformer monad and the updates happen {\em +in-place}. + +\item[``Static'' (in C land):] +A C~routine may pass an \tr{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. + +\item[``Stable'' pointers:] +If, for some reason, you wish to hand a Haskell pointer (i.e., {\em +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 \Sectionref{glasgow-stablePtrs} for more details. + +\item[``Malloc'' pointers:] +A ``malloc'' pointer is a safe way to pass a C~pointer 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 \Sectionref{glasgow-mallocPtrs} for more details. +\end{description} + +See sections~1.4 and~1.6 of the ``state interface document'' for the +details of all these ``primitive array'' types and the operations on +them. + + +%************************************************************************ +%* * +\subsection[glasgow-ccalls]{Calling~C directly from Haskell} +\index{C calls (Glasgow extension)} +\index{_ccall_ (Glasgow extension)} +\index{_casm_ (Glasgow extension)} +%* * +%************************************************************************ + +%Besides using a \tr{-fglasgow-exts} flag, your modules need to include... +%\begin{verbatim} +%import PreludePrimIO +%\end{verbatim} + +SINCE VERSION 0.22: ``Literal-literals'', e.g., \tr{``NULL''}, can now +be any `boxed-primitive' type---they are not automatically taken to be +\tr{_Addr}s. This is cool, except you may sometimes have to put in +a type signature to force the desired type. + +SINCE VERSION 0.19: \tr{ccall} and \tr{casm} have been renamed to +\tr{_ccall_} and \tr{_casm_} and \tr{veryDangerousCcall} and +\tr{veryDangerousCasm} have been removed. It is no longer necessary +(nor legal!) to unbox/rebox the arguments and results to @_ccall_@. +GHC does the unboxing/reboxing for you. + +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 0.26: Yes, the \tr{_ccall_} stuff probably {\em will +change}, to something better, of course! We are only at the +musing-about-it stage, however. + +%************************************************************************ +%* * +\subsubsection[ccall-intro]{\tr{_ccall_} and \tr{_casm_}: an introduction} +%* * +%************************************************************************ + +The simplest way to use a simple C function +\begin{verbatim} +double fooC( FILE *in, char c, int i, double d, unsigned int u ) +\end{verbatim} +is to provide a Haskell wrapper +\begin{verbatim} +fooH :: Char -> Int -> Double -> _Word -> PrimIO Double +fooH c i d w = _ccall_ fooC ``stdin'' c i d w +\end{verbatim} +The function @fooH@ will unbox all of its arguments, call the C +function \tr{fooC} and box the corresponding arguments. + +So, if you want to do C-calling, you have to confront the underlying +Glasgow I/O system. It's just your typical monad whatnot. + +%The code in \tr{ghc/lib/glaExts/*.lhs} is not too obtuse. +%That code, plus \tr{lib/prelude/Builtin.hs}, give examples +%of its use. The latter includes the implementations of \tr{error} and +%\tr{trace}. + +One of the annoyances about \tr{_ccall_}s is when the C types don't quite +match the Haskell compiler's ideas. For this, the \tr{_casm_} variant +may be just the ticket (NB: {\em no chance} of such code going through +a native-code generator): +\begin{verbatim} +oldGetEnv name + = _casm_ ``%r = getenv((char *) %0);'' name `thenPrimIO` \ litstring@(A# str#) -> + returnPrimIO ( + if (litstring == ``NULL'') then + Failure (SearchError ("GetEnv:"++name)) + else + Str (unpackCString# str#) + ) +\end{verbatim} + +The first literal-literal argument to a \tr{_casm_} is like a +\tr{printf} format: \tr{%r} is replaced with the ``result,'' +\tr{%0}--\tr{%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 \tr{_ccall_} goes for \tr{_casm_} as well. + +%************************************************************************ +%* * +\subsubsection[glasgow-foreign-headers]{Using function headers} +\index{C calls---function headers} +%* * +%************************************************************************ + +When generating C (using the \tr{-fvia-C} directive), one can assist +the C compiler in detecting type errors by using the \tr{-#include} +directive to provide \tr{.h} files containing function headers. + +For example, +\begin{verbatim} +typedef unsigned long *StgMallocPtr; +typedef long StgInt; + +extern void initialiseEFS PROTO( (StgInt size) ); +extern StgInt terminateEFS (); +extern StgMallocPtr emptyEFS(); +extern StgMallocPtr updateEFS PROTO( (StgMallocPtr a, StgInt i, StgInt x) ); +extern StgInt lookupEFS PROTO( (StgMallocPtr a, StgInt i) ); +\end{verbatim} + +You can find appropriate definitions for \tr{StgInt}, +\tr{StgMallocPtr}, etc using \tr{gcc} on your architecture by +consulting \tr{ghc/includes/StgTypes.lh}. The following table +summarises the relationship between Haskell types and C types. + +\begin{tabular}{ll} +C type name & Haskell Type \\ \hline +%----- & --------------- +\tr{StgChar} & \tr{Char#}\\ +\tr{StgInt} & \tr{Int#}\\ +\tr{StgWord} & \tr{Word#}\\ +\tr{StgAddr} & \tr{Addr#}\\ +\tr{StgFloat} & \tr{Float#}\\ +\tr{StgDouble} & \tr{Double#}\\ + +\tr{StgArray} & \tr{Array#}\\ +\tr{StgByteArray} & \tr{ByteArray#}\\ +\tr{StgArray} & \tr{MutableArray#}\\ +\tr{StgByteArray} & \tr{MutableByteArray#}\\ + +\tr{StgStablePtr} & \tr{StablePtr#}\\ +\tr{StgMallocPtr} & \tr{MallocPtr#} +\end{tabular} + +Note that this approach is only {\em essential\/} for returning +\tr{float}s (or if \tr{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. + +%************************************************************************ +%* * +\subsubsection[glasgow-stablePtrs]{Subverting automatic unboxing with ``stable pointers''} +\index{stable pointers (Glasgow extension)} +%* * +%************************************************************************ + +The arguments of a \tr{_ccall_} are automatically unboxed before the +call. There are two reasons why this is usually the Right Thing to do: +\begin{itemize} +\item +C is a strict language: it would be excessively tedious to pass +unevaluated arguments and require the C programmer to force their +evaluation before using them. + +\item Boxed values are stored on the Haskell heap and may be moved +within the heap if a garbage collection occurs --- that is, pointers +to boxed objects are not {\em stable\/}. +\end{itemize} + +It is possible to subvert the unboxing process by creating a ``stable +pointer'' to a value and passing the stable pointer instead. (To use +stable pointers, you must \tr{import PreludeGlaMisc}.) For example, to +pass/return an integer lazily to C functions \tr{storeC} and +\tr{fetchC}, one might write: +\begin{verbatim} +storeH :: Int -> PrimIO () +storeH x = makeStablePtr x `thenPrimIO` \ stable_x -> + _ccall_ storeC stable_x + +fetchH :: PrimIO Int +fetchH x = _ccall_ fetchC `thenPrimIO` \ stable_x -> + deRefStablePtr stable_x `thenPrimIO` \ x -> + freeStablePtr stable_x `seqPrimIO` + returnPrimIO x +\end{verbatim} + +The garbage collector will refrain from throwing a stable pointer away +until you explicitly call one of the following from C or Haskell. +\begin{verbatim} +void freeStablePointer( StgStablePtr stablePtrToToss ) +freeStablePtr :: _StablePtr a -> PrimIO () +\end{verbatim} + +As with the use of \tr{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. + +%Doesn't work in ghc-0.23 - best to just keep quiet about them. +% +%And to force evaluation of the argument within \tr{fooC}, one would +%call one of the following C functions (according to type of argument). +% +%\begin{verbatim} +%void performIO ( StgStablePtr stableIndex /* _StablePtr s (PrimIO ()) */ ); +%StgInt enterInt ( StgStablePtr stableIndex /* _StablePtr s Int */ ); +%StgFloat enterFloat ( StgStablePtr stableIndex /* _StablePtr s Float */ ); +%\end{verbatim} +% +%ToDo ADR: test these functions! +% +%Note Bene: \tr{_ccall_GC_} must be used if any of these functions are used. + + +%************************************************************************ +%* * +\subsubsection[glasgow-mallocPtrs]{Pointing outside the Haskell heap} +\index{malloc pointers (Glasgow extension)} +%* * +%************************************************************************ + +There are two types that \tr{ghc} programs can use to reference +(heap-allocated) objects outside the Haskell world: \tr{_Addr} and +\tr{_MallocPtr}. (You must import \tr{PreludeGlaMisc} to use +\tr{_MallocPtr}.) + +If you use \tr{_Addr}, it is up to you to the programmer to arrange +allocation and deallocation of the objects. + +If you use \tr{_MallocPtr}, \tr{ghc}'s garbage collector will +call the user-supplied C function +\begin{verbatim} +void FreeMallocPtr( StgMallocPtr garbageMallocPtr ) +\end{verbatim} +when the Haskell world can no longer access the object. Since +\tr{_MallocPtr}s only get released when a garbage collection occurs, +we provide ways of triggering a garbage collection from within C and +from within Haskell. +\begin{verbatim} +void StgPerformGarbageCollection() +performGC :: PrimIO () +\end{verbatim} + +%************************************************************************ +%* * +\subsubsection[glasgow-avoiding-monads]{Avoiding monads} +\index{C calls to `pure C'} +\index{unsafePerformPrimIO (PreludeGlaST)} +%* * +%************************************************************************ + +The \tr{_ccall_} construct is part of the \tr{PrimIO} monad because 9 +out of 10 uses will be to call imperative functions with side effects +such as \tr{printf}. Use of the monad ensures that these operations +happen in a predictable order in spite of laziness and compiler +optimisations. + +There are three situations where one might like to use +@unsafePerformPrimIO@ to avoid the monad: +\begin{itemize} +\item +Calling a function with no side-effects: +\begin{verbatim} +atan2d :: Double -> Double -> Double +atan2d y x = unsafePerformPrimIO (_ccall_ atan2d y x) + +sincosd :: Double -> (Double, Double) +sincosd x = unsafePerformPrimIO ( + newDoubleArray (0, 1) `thenPrimIO` \ da -> + _casm_ ``sincosd( %0, &((double *)%1[0]), &((double *)%1[1]) );'' x da + `seqPrimIO` + readDoubleArray da 0 `thenPrimIO` \ s -> + readDoubleArray da 1 `thenPrimIO` \ c -> + returnPrimIO (s, c) + ) +\end{verbatim} + +\item Calling a set of functions which have side-effects but which can +be used in a purely functional manner. + +For example, an imperative implementation of a purely functional +lookup-table might be accessed using the following functions. + +\begin{verbatim} +empty :: EFS x +update :: EFS x -> Int -> x -> EFS x +lookup :: EFS a -> Int -> a + +empty = unsafePerformPrimIO (_ccall_ emptyEFS) + +update a i x = unsafePerformPrimIO ( + makeStablePtr x `thenPrimIO` \ stable_x -> + _ccall_ updateEFS a i stable_x + ) + +lookup a i = unsafePerformPrimIO ( + _ccall_ lookupEFS a i `thenPrimIO` \ stable_x -> + deRefStablePtr stable_x + ) +\end{verbatim} + +You will almost always want to use \tr{_MallocPtr}s with this. + +\item Calling a side-effecting function even though the results will +be unpredictable. For example the \tr{trace} function is defined by: + +\begin{verbatim} +trace :: String -> a -> a +trace string expr = unsafePerformPrimIO ( + appendChan# ``stderr'' "Trace On:\n" `seqPrimIO` + appendChan# ``stderr'' string `seqPrimIO` + appendChan# ``stderr'' "\nTrace Off.\n" `seqPrimIO` + returnPrimIO expr ) +\end{verbatim} + +(This kind of use is not highly recommended --- it is only really +useful in debugging code.) + +\end{itemize} + +%************************************************************************ +%* * +\subsubsection[ccall-gotchas]{C-calling ``gotchas'' checklist} +\index{C call dangers} +%* * +%************************************************************************ + +And some advice, too. + +\begin{itemize} +\item +\tr{_ccall_} is part of the \tr{PrimIO} monad --- not the 1.3 \tr{IO} Monad. +Use the function +\begin{verbatim} +primIOToIO :: PrimIO a -> IO a +\end{verbatim} +to promote a \tr{_ccall_} to the \tr{IO} monad. + +\item +For modules that use \tr{_ccall_}s, etc., compile with \tr{-fvia-C}.\index{-fvia-C option} +You don't have to, but you should. + +Also, use the \tr{-#include "prototypes.h"} flag (hack) to inform the +C compiler of the fully-prototyped types of all the C functions you +call. (\Sectionref{glasgow-foreign-headers} says more about this...) + +This scheme is the {\em only} way that you will get {\em any} +typechecking of your \tr{_ccall_}s. (It shouldn't be that way, +but...) + +\item +Try to avoid \tr{_ccall_}s to C~functions that take \tr{float} +arguments or return \tr{float} results. Reason: if you do, you will +become entangled in (ANSI?) C's rules for when arguments/results are +promoted to \tr{doubles}. It's a nightmare and just not worth it. +Use \tr{doubles} if possible. + +If you do use \tr{floats}, check and re-check that the right thing is +happening. Perhaps compile with \tr{-keep-hc-file-too} and look at +the intermediate C (\tr{.hc} file). + +\item +The compiler uses two non-standard type-classes when +type-checking the arguments and results of \tr{_ccall_}: the arguments +(respectively result) of \tr{_ccall_} must be instances of the class +\tr{_CCallable} (respectively \tr{_CReturnable}. (Neither class +defines any methods --- their only function is to keep the +type-checker happy.) + +The type checker must be able to figure out just which of the +C-callable/returnable types is being used. If it can't, you have to +add type signatures. For example, +\begin{verbatim} +f x = _ccall_ foo x +\end{verbatim} +is not good enough, because the compiler can't work out what type @x@ is, nor +what type the @_ccall_@ returns. You have to write, say: +\begin{verbatim} +f :: Int -> PrimIO Double +f x = _ccall_ foo x +\end{verbatim} + +This table summarises the standard instances of these classes. + +% ToDo: check this table against implementation! + +\begin{tabular}{llll} +Type &CCallable&CReturnable & Which is probably... \\ \hline +%------ ---------- ------------ ------------- +\tr{Char} & Yes & Yes & \tr{unsigned char} \\ +\tr{Int} & Yes & Yes & \tr{long int} \\ +\tr{_Word} & Yes & Yes & \tr{unsigned long int} \\ +\tr{_Addr} & Yes & Yes & \tr{char *} \\ +\tr{Float} & Yes & Yes & \tr{float} \\ +\tr{Double} & Yes & Yes & \tr{double} \\ +\tr{()} & No & Yes & \tr{void} \\ +\tr{[Char]} & Yes & No & \tr{char *} (null-terminated) \\ + +\tr{Array} & Yes & No & \tr{unsigned long *}\\ +\tr{_ByteArray} & Yes & No & \tr{unsigned long *}\\ +\tr{_MutableArray} & Yes & No & \tr{unsigned long *}\\ +\tr{_MutableByteArray} & Yes & No & \tr{unsigned long *}\\ + +\tr{_State} & Yes & Yes & nothing!\\ + +\tr{_StablePtr} & Yes & Yes & \tr{unsigned long *}\\ +\tr{_MallocPtr} & Yes & Yes & see later\\ +\end{tabular} + +The brave and careful programmer can add their own instances of these +classes for the following types: +\begin{itemize} +\item +A {\em boxed-primitive} type may be made an instance of both +\tr{_CCallable} and \tr{_CReturnable}. + +A boxed primitive type is any data type with a +single unary constructor with a single primitive argument. For +example, the following are all boxed primitive types: + +\begin{verbatim} +Int +Double +data XDisplay = XDisplay Addr# +data EFS a = EFS# MallocPtr# +\end{verbatim} + +\begin{verbatim} +instance _CCallable (EFS a) +instance _CReturnable (EFS a) +\end{verbatim} + +\item Any datatype with a single nullary constructor may be made an +instance of \tr{_CReturnable}. For example: + +\begin{verbatim} +data MyVoid = MyVoid +instance _CReturnable MyVoid +\end{verbatim} + +\item As at version 0.26, \tr{String} (i.e., \tr{[Char]}) is still +not a \tr{_CReturnable} type. + +Also, the now-builtin type \tr{_PackedString} is neither +\tr{_CCallable} nor \tr{_CReturnable}. (But there are functions in +the PackedString interface to let you get at the necessary bits...) +\end{itemize} + +\item +The code-generator will complain if you attempt to use \tr{%r} +in a \tr{_casm_} whose result type is \tr{PrimIO ()}; or if you don't +use \tr{%r} {\em precisely\/} once for any other result type. These +messages are supposed to be helpful and catch bugs---please tell us +if they wreck your life. + +\item +If you call out to C code which may trigger the Haskell garbage +collector (examples of this later...), then you must use the +\tr{_ccall_GC_} or \tr{_casm_GC_} variant of C-calls. (This does not +work with the native code generator - use \tr{\fvia-C}.) This stuff is +hairy with a capital H! +\end{itemize} + +%************************************************************************ +%* * +%\subsubsection[ccall-good-practice]{C-calling ``good practice'' checklist} +%* * +%************************************************************************ + +%************************************************************************ +%* * +\subsection[glasgow-hbc-exts]{``HBC-ish'' extensions implemented by GHC} +\index{HBC-like Glasgow extensions} +\index{extensions, HBC-like} +%* * +%************************************************************************ + +\begin{description} +%------------------------------------------------------------------- +\item[@fromInt@ method in class @Num@:] +It's there. Converts from an \tr{Int} to the type. + +%------------------------------------------------------------------- +\item[@toInt@ method in class @Integral@:] +Converts from type type to an \tr{Int}. + +%------------------------------------------------------------------- +\item[Overlapping instance declarations:] +\index{overlapping instances} +\index{instances, overlapping} + +In \tr{instance <context> => Class (T x1 ... xn)}, the \tr{xi}s can be +{\em types}, rather than just {\em type variables}. + +Thus, you can have an instance \tr{instance Foo [Char]}, as well as +the more general \tr{instance Foo [a]}; the former will be used in +preference to the latter, where applicable. + +As Lennart says, ``This is a dubious feature and should not be used +carelessly.'' + +See also: \tr{SPECIALIZE instance} pragmas, in \Sectionref{faster}. + +%------------------------------------------------------------------- +\item[Signal-handling I/O request:] +\index{signal handling (extension)} +\index{SigAction I/O request} +The Haskell-1.2 I/O request \tr{SigAction n act} installs a signal handler for signal +\tr{n :: Int}. The number is the usual UNIX signal number. The action +is of this type: +\begin{verbatim} +data SigAct + = SAIgnore + | SADefault + | SACatch Dialogue +\end{verbatim} + +The corresponding continuation-style I/O function is the unsurprising: +\begin{verbatim} +sigAction :: Int -> SigAct -> FailCont -> SuccCont -> Dialogue +\end{verbatim} + +When a signal handler is installed with \tr{SACatch}, receipt of the +signal causes the current top-level computation to be abandoned, and +the specified dialogue to be executed instead. The abandoned +computation may leave some partially evaluated expressions in a +non-resumable state. If you believe that your top-level computation +and your signal handling dialogue may share subexpressions, you should +execute your program with the \tr{-N} RTS option, to prevent +black-holing. + +The \tr{-N} option is not available with concurrent/parallel programs, +so great care should be taken to avoid shared subexpressions between +the top-level computation and any signal handlers when using threads. + +%------------------------------------------------------------------- +%\item[Simple time-out mechanism, in ``monadic I/O'':] +%\index{time-outs (extension)} +% +%This function is available: +%\begin{verbatim} +%timeoutIO :: Int -> IO Void -> IO (IO Void) +%\end{verbatim} +% +%Wait that many seconds, then abandon the current computation and +%perform the given I/O operation (second argument). Uses the +%signal-handling, so it returns the previous signal-handler (in case +%you want to re-install it). As above, you may need to execute your +%program with the RTS flag \tr{-N}, to prevent black-holing. +% +\end{description} + +%************************************************************************ +%* * +%\subsection[glasgow-compiler-namespace]{Fiddlings the compiler's built-in namespaces} +%* * +%************************************************************************ + +%This is really only used for compiling the prelude. It's turgid and +%will probably change. + +% \begin{description} +% \item[\tr{-no-implicit-prelude}:] +% \index{-no-implicit-prelude option} +% +% ???? (Tells the parser not to read \tr{Prelude.hi}). +% +% \item[\tr{-fhide-builtin-names}:] +% \index{-fhide-builtin-names option} +% This hides {\em all} Prelude names built-in to the compiler. +% +% \item[\tr{-fmin-builtin-names}:] +% \index{-fmin-builtin-names option} +% This hides all but a few of the Prelude names that are built-in to the +% compiler. @:@ (cons) is an example of one that would remain visible. +% +% \item[\tr{-fhide-builtin-instances}:] +% \index{-fhide-builtin-instances option} +% This suppresses the compiler's own ideas about what instances already +% exist (e.g., \tr{instance Eq Int}). +% +% This flag is used when actually compiling the various instance +% declarations in the Prelude. +% \end{description} diff --git a/ghc/docs/users_guide/gone_wrong.lit b/ghc/docs/users_guide/gone_wrong.lit new file mode 100644 index 0000000000..4403d203f9 --- /dev/null +++ b/ghc/docs/users_guide/gone_wrong.lit @@ -0,0 +1,332 @@ +%************************************************************************ +%* * +\section[wrong]{What to do when something goes wrong} +\index{problems} +%* * +%************************************************************************ + +If you still have a problem after consulting this section, then you +may have found a {\em bug}---please report it! See +\Sectionref{bug-reports} for a list of things we'd like to know about +your bug. If in doubt, send a report---we love mail from irate users :-! + +(\Sectionref{vs-Haskell-defn}, which describes Glasgow Haskell's +shortcomings vs.~the Haskell language definition, may also be of +interest.) + +%************************************************************************ +%* * +\subsection[wrong-compiler]{When the compiler ``does the wrong thing''} +\index{compiler problems} +\index{problems with the compiler} +%* * +%************************************************************************ + +\begin{description} +%------------------------------------------------------------------- +\item[``Help! The compiler crashed (or `panic'd)!''] +These events are {\em always} bugs in the GHC system---please report +them. + +%Known compiler ``panics'': +%\begin{description} +%\item[From SPARC native-code generator:] These tend to say something +%like ``unknown PrimOp;'' you can avoid it by compiling that module +%with \tr{-fvia-C}.\index{-fvia-C option} +%\end{description} + +%------------------------------------------------------------------- +\item[``The compiler ran out of heap (or stack) when compiling itself!''] +It happens. We try to supply reasonable \tr{-H<n>} flags for +\tr{ghc/compiler/} and \tr{ghc/lib/}, but GHC's memory consumption +can vary by platform (e.g., on a 64-bit machine). + +Just say \tr{make all EXTRA_HC_OPTS=-H<a reasonable number>} and see +how you get along. + +%------------------------------------------------------------------- +\item[``The compiler died with a pattern-matching error.''] +This is a bug just as surely as a ``panic.'' Please report it. + +%------------------------------------------------------------------- +\item[``Some confusion about a value specialised to a type...'' Huh???] +(A deeply obscure and unfriendly error message.) + +This message crops up when the typechecker is sees a reference in an +interface pragma to a specialisation of an overloaded value +(function); for example, \tr{elem} specialised for type \tr{[Char]} +(\tr{String}). The problem is: it doesn't {\em know} that such a +specialisation exists! + +The cause of this problem is (please report any other cases...): The +compiler has imported pragmatic info for the value in question from +more than one interface, and the multiple interfaces did not agree +{\em exactly} about the value's pragmatic info. Since the compiler +doesn't know whom to believe, it believes none of them. + +The cure is to re-compile the modules that {\em re-export} the +offending value (after possibly re-compiling its defining module). +Now the pragmatic info should be exactly the same in every case, and +things should be fine. + +%------------------------------------------------------------------- +\item[``Can't see the data constructors for a ccall/casm'' Huh?] +GHC ``unboxes'' C-call arguments and ``reboxes'' C-call results for you. +To do this, it {\\em has} to be able to see the types fully; +abstract types won't do! + +Thus, if you say \tr{data Foo = Foo Int#} +(a cool ``boxed primitive'' type), but then make it abstract +(only \tr{data Foo} appears in the interface), then GHC can't figure +out what to do with \tr{Foo} arguments/results to C-calls. + +Solutions: either make the type unabstract, or compile with \tr{-O}. +With the latter, the constructor info will be passed along in +the interface pragmas. + +%------------------------------------------------------------------- +\item[``This is a terrible error message.''] +If you think that GHC could have produced a better error message, +please report it as a bug. + +%------------------------------------------------------------------- +\item[``What about these `trace' messages from GHC?''] +Almost surely not a problem. About some specific cases... +\begin{description} +\item[Simplifier still going after N iterations:] +Sad, but harmless. You can change the number with a +\tr{-fmax-simplifier-iterations<N>}\index{-fmax-simplifier-iterations<N> option} option (no space); +and you can see what actions took place in each iteration by +turning on the \tr{-fshow-simplifier-progress} +\index{-fshow-simplifier-progress option} option. + +If the simplifier definitely seems to be ``looping,'' please report +it. +\end{description} + +%------------------------------------------------------------------- +\item[``What about this warning from the C compiler?''] + +For example: ``...warning: `Foo' declared `static' but never defined.'' +Unsightly, but not a problem. + +%------------------------------------------------------------------- +\item[Sensitivity to \tr{.hi} interface files:] + +GHC is very sensitive about interface files. For example, if it picks +up a non-standard \tr{Prelude.hi} file, pretty terrible things will +happen. If you turn on +\tr{-fno-implicit-prelude}\index{-fno-implicit-prelude option}, the +compiler will almost surely die, unless you know what you are doing. + +Furthermore, as sketched below, you may have big problems +running programs compiled using unstable interfaces. + +%------------------------------------------------------------------- +\item[``I think GHC is producing incorrect code'':] + +Unlikely :-) A useful be-more-paranoid option to give to GHC is +\tr{-dcore-lint}\index{-dcore-lint option}; this causes a ``lint'' pass to +check for errors (notably type errors) after each Core-to-Core +transformation pass. We run with \tr{-dcore-lint} on all the time; it +costs about 5\% in compile time. (Or maybe 25\%; who knows?) + +%------------------------------------------------------------------- +%\item[``Can I use HBC-produced \tr{.hi} interface files?''] +%Yes, though you should keep compiling until you have a stable set of +%GHC-produced ones. + +%------------------------------------------------------------------- +\item[``Why did I get a link error?''] + +If the linker complains about not finding \tr{_<something>_fast}, then +your interface files haven't settled---keep on compiling! (In +particular, this error means that arity information, which you can see +in any \tr{.hi} file, has changed.) + +%If the linker complains about not finding \tr{SpA}, \tr{SuA}, and +%other such things, then you've tried to link ``unregisterised'' object +%code (produced with \tr{-O0}) with the normal registerised stuff. + +%If you get undefined symbols that look anything like (for example) +%\tr{J3C_Interact$__writeln}, \tr{C_Prelude$__$2B$2B}, +%\tr{VC_Prelude$__map}, etc., then you are trying to link HBC-produced +%object files with GHC. + +%------------------------------------------------------------------- +\item[``What's a `consistency error'?''] +(These are reported just after linking your program.) + +You tried to link incompatible object files, e.g., normal ones +(registerised, Appel garbage-collector) with profiling ones (two-space +collector). Or those compiled by a previous version of GHC +with an incompatible newer version. + +If you run \tr{nm -o *.o | egrep 't (cc|hsc)\.'} (or, on +unregisterised files: \tr{what *.o}), you'll see all the consistency +tags/strings in your object files. They must all be the same! +(ToDo: tell you what they mean...) + +%------------------------------------------------------------------- +\item[``Is this line number right?''] +On this score, GHC usually does pretty well, especially +if you ``allow'' it to be off by one or two. In the case of an +instance or class declaration, the line number +may only point you to the declaration, not to a specific method. + +Please report line-number errors that you find particularly unhelpful. +\end{description} + +%************************************************************************ +%* * +\subsection[wrong-compilee]{When your program ``does the wrong thing''} +\index{problems running your program} +%* * +%************************************************************************ + +(For advice about overly slow or memory-hungry Haskell programs, +please see \sectionref{sooner-faster-quicker}). + +\begin{description} +%----------------------------------------------------------------------- +\item[``Help! My program crashed!''] +(e.g., a `segmentation fault' or `core dumped') + +If your program has no @_ccall_@s/@_casm_@s in it, then a crash is always +a BUG in the GHC system, except in one case: If your program is made +of several modules, each module must have been compiled with a stable +group of interface (\tr{.hi}) files. + +For example, if an interface is lying about the type of an imported +value then GHC may well generate duff code for the importing module. +{\em This applies to pragmas inside interfaces too!} If the pragma is +lying (e.g., about the ``arity'' of a value), then duff code may result. +Furthermore, arities may change even if types do not. + +In short, if you compile a module and its interface changes, then all +the modules that import that interface {\em must} be re-compiled. + +A useful option to alert you when interfaces change is +\tr{-hi-diffs}\index{-hi-diffs option}. It will run \tr{diff} on the +changed interface file, before and after, when applicable. + +If you are using \tr{make}, a useful tool to make sure that every +module {\em is} up-to-date with respect to its imported interfaces is +\tr{mkdependHS} (which comes with GHC). Please see +\sectionref{mkdependHS}. + +If you are down to your last-compile-before-a-bug-report, we +would recommend that you add a \tr{-dcore-lint} option (for +extra checking) to your compilation options. + +So, before you report a bug because of a core dump, you should probably: +\begin{verbatim} +% rm *.o # scrub your object files +% make my_prog # re-make your program; use -hi-diffs to highlight changes +% ./my_prog ... # retry... +\end{verbatim} + +Of course, if you have @_ccall_@s/@_casm_@s in your program then all bets +are off, because you can trash the heap, the stack, or whatever. + +If you are interested in hard-core debugging of a crashing +GHC-compiled program, please see \sectionref{hard-core-debug}. + +% (If you have an ``unregisterised'' arity-checking +% (\tr{-O0 -darity-checks}) around [as we sometimes do at Glasgow], then you +% might recompile with \tr{-darity-checks}\index{-darity-checks option}, +% which will definitely detect arity-compatibility errors.) + +%------------------------------------------------------------------- +\item[``My program entered an `absent' argument.''] +This is definitely caused by a bug in GHC. Please report it. + +%----------------------------------------------------------------------- +\item[``What's with this `arithmetic (or `floating') exception' ''?] + +@Int@, @Float@, and @Double@ arithmetic is {\em unchecked}. Overflows +and underflows are {\em silent}. Divide-by-zero {\em may} cause an +untrapped exception (please report it if it does). I suppose other +arithmetic uncheckiness might cause an exception, too... +\end{description} + +%************************************************************************ +%* * +\subsection[bug-reports]{How to report a bug in the GHC system} +\index{bug reports} +%* * +%************************************************************************ + +Glasgow Haskell is a changing system so there are sure to be bugs in +it. Please report them to +\tr{glasgow-haskell-bugs@dcs.glasgow.ac.uk}! (However, please check +the earlier part of this section to be sure it's not a known +not-really-a problem.) + +The name of the bug-reporting game is: facts, facts, facts. +Don't omit them because ``Oh, they won't be interested...'' +\begin{enumerate} +\item +What kind of machine are you running on, and exactly what version of the +operating system are you using? (\tr{cat /etc/motd} often shows the desired +information.) + +\item +What version of GCC are you using? \tr{gcc -v} will tell you. + +\item +Run the sequence of compiles/runs that caused the offending behaviour, +capturing all the input/output in a ``script'' (a UNIX command) or in +an Emacs shell window. We'd prefer to see the whole thing. + +\item +Be sure any Haskell compilations are run with a \tr{-v} (verbose) +flag, so we can see exactly what was run, what versions of things you +have, etc. + +\item +What is the program behaviour that is wrong, in your opinion? + +\item +If practical, please send enough source files/interface files for us +to duplicate the problem. + +\item +If you are a Hero and track down the problem in the compilation-system +sources, please send us {\em whole files} (by e-mail or FTP) that we +can compare against some base release. +\end{enumerate} + +%************************************************************************ +%* * +\subsection[hard-core-debug]{Hard-core debugging of GHC-compiled programs} +\index{debugging, hard-core} +%* * +%************************************************************************ + +If your program is crashing, you should almost surely file a bug +report, as outlined in previous sections. + +This section suggests ways to Make Further Progress Anyway. + +The first thing to establish is: Is it a garbage-collection (GC) bug? +Try your program with a very large heap and a \tr{-Sstderr} RTS +flag. +\begin{itemize} +\item +If it crashes {\em without} garbage-collecting, then it is +definitely {\em not} a GC bug. +\item +If you can make it crash with one heap size but not with another, then +it {\em probably is} a GC bug. +\item +If it crashes with the normal +collector, but not when you force two-space collection (\tr{-F2s} +runtime flag), then it {\em probably is} a GC bug. +\end{itemize} + +If it {\em is} a GC bug, you may be able to avoid it by using a +particular heap size or by using a \tr{-F2s} runtime flag. (But don't +forget to report the bug!!!) + +ToDo: more here? diff --git a/ghc/docs/users_guide/how_to_run.lit b/ghc/docs/users_guide/how_to_run.lit new file mode 100644 index 0000000000..79c7ab9fff --- /dev/null +++ b/ghc/docs/users_guide/how_to_run.lit @@ -0,0 +1,1139 @@ +\section[invoking-GHC]{Invoking GHC: Command-line options} +\index{command-line options} +\index{options, GHC command-line} + +Command-line arguments are either options or file names. + +Command-line options begin with \tr{-}. They may {\em not} be +grouped: \tr{-vO} is different from \tr{-v -O}. +Options need not precede filenames: e.g., \tr{ghc *.o -o foo}. +All options are processed +and then apply to all files; you cannot, for example, +invoke \tr{ghc -c -O1 Foo.hs -O2 Bar.hs} to apply different +optimisation levels to the files \tr{Foo.hs} and \tr{Bar.hs}. For +conflicting options, e.g., \tr{-c -S}, we reserve the right to do +anything we want. (Usually, the last one applies.) + +Options related to profiling, Glasgow extensions to Haskell (e.g., +unboxed values), Concurrent and Parallel Haskell are +described in \sectionref{profiling}, \sectionref{glasgow-exts}, and +\sectionref{concurrent-and-parallel}, respectively. + +%************************************************************************ +%* * +\subsection[file-suffixes]{Meaningful file suffixes} +\index{suffixes, file} +\index{file suffixes for GHC} +%* * +%************************************************************************ + +File names with ``meaningful'' suffixes (e.g., \tr{.lhs} or \tr{.o}) +cause the ``right thing'' to happen to those files. + +\begin{description} +\item[\tr{.lhs}:] +\index{lhs suffix@.lhs suffix} +A ``literate Haskell'' module. + +\item[\tr{.hs}:] +A not-so-literate Haskell module. + +\item[\tr{.hi}:] +A Haskell interface file, probably compiler-generated. + +\item[\tr{.hc}:] +Intermediate C file produced by the Haskell compiler. + +\item[\tr{.c}:] +A C~file not produced by the Haskell compiler. + +% \item[\tr{.i}:] +% C code after it has be preprocessed by the C compiler (using the +% \tr{-E} flag). + +\item[\tr{.s}:] +An assembly-language source file, usually +produced by the compiler. + +\item[\tr{.o}:] +An object file, produced by an assembler. +\end{description} + +Files with other suffixes (or without suffixes) are passed straight +to the linker. + +%************************************************************************ +%* * +\subsection[options-help]{Help and verbosity options} +\index{help options (GHC)} +\index{verbose option (GHC)} +%* * +%************************************************************************ + +A good option to start with is the \tr{-help} (or \tr{-?}) option. +\index{-help option} +\index{-? option} +GHC spews a long message to standard output and then exits. + +The \tr{-v}\index{-v option} option makes GHC {\em verbose}: it +reports its version number and shows (on stderr) exactly how it invokes each +phase of the compilation system. Moreover, it passes +the \tr{-v} flag to most phases; each reports +its version number (and possibly some other information). + +Please, oh please, use the \tr{-v} option when reporting bugs! +Knowing that you ran the right bits in the right order is always the +first thing we want to verify. + +%************************************************************************ +%* * +\subsection[options-order]{Running the right phases in the right order} +\index{order of passes in GHC} +\index{pass ordering in GHC} +%* * +%************************************************************************ + +The basic task of the \tr{ghc} driver is to run each input file +through the right phases (parsing, linking, etc.). + +The first phase to run is determined by the input-file suffix, and the +last phase is determined by a flag. If no relevant flag is present, +then go all the way through linking. This table summarises: + +\begin{tabular}{llll} +phase of the & suffix saying & flag saying & (suffix of) \\ +compilation system & ``start here''& ``stop after''& output file \\ \hline + +literate pre-processor & .lhs & - & - \\ +C pre-processor (opt.) & - & - & - \\ +Haskell parser & .hs & - & - \\ +Haskell compiler & - & -C, -S & .hc, .s \\ +C compiler (opt.) & .hc or .c & -S & .s \\ +assembler & .s & -c & .o \\ +linker & other & - & a.out \\ +\end{tabular} +\index{-C option} +\index{-S option} +\index{-c option} + +Thus, a common invocation would be: \tr{ghc -c Foo.hs} + +Note: What the Haskell compiler proper produces depends on whether a +native-code generator is used (producing assembly language) or not +(producing C). + +%The suffix information may be overridden with a \tr{-lang <suf>} +%\index{-lang <suf> option} option. This says: process all inputs +%files as if they had suffix \pl{<suf>}. [NOT IMPLEMENTED YET] + +The option \tr{-cpp}\index{-cpp option} must be given for the C +pre-processor phase to be run. + +The option \tr{-E}\index{-E option} runs just the C-preprocessor part +of the C-compiling phase, sending the result to stdout [I think]. (For +debugging, usually.) + +%************************************************************************ +%* * +\subsection[options-optimise]{Optimisation (code improvement)} +\index{optimisation (GHC)} +\index{improvement, code (GHC)} +%* * +%************************************************************************ + +The \tr{-O*} options specify convenient ``packages'' of optimisation +flags; the \tr{-f*} options described later on specify {\em individual} +optimisations to be turned on/off; the \tr{-m*} options specify {\em +machine-specific} optimisations to be turned on/off. + +%---------------------------------------------------------------------- +\subsubsection[optimise-pkgs]{\tr{-O*}: convenient ``packages'' of optimisation flags.} +\index{-O options (GHC)} + +There are {\em many} options that affect the quality of code produced by +GHC. Most people only have a general goal, something like ``Compile +quickly'' or ``Make my program run like greased lightning.'' The +following ``packages'' of optimisations (or lack thereof) should suffice. + +Once you choose a \tr{-O*} ``package,'' stick with it---don't chop and +change. Modules' interfaces {\em will} change with a shift to a new +\tr{-O*} option, and you will have to recompile all importing modules +before your program can again be run safely. + +\begin{description} +\item[No \tr{-O*}-type option specified:] +\index{-O* not specified} +This is taken to mean: ``Please compile quickly; I'm not over-bothered +about compiled-code quality.'' So, for example: \tr{ghc -c Foo.hs} + +\item[\tr{-O} or \tr{-O1}:] +\index{-O option} +\index{-O1 option} +\index{optimise normally} +Means: ``Generate good-quality code without taking too long about it.'' +Thus, for example: \tr{ghc -c -O Main.lhs} + +\item[\tr{-O2}:] +\index{-O2 option} +\index{optimise aggressively} +Means: ``Apply every non-dangerous optimisation, even if it means +significantly longer compile times.'' + +The avoided ``dangerous'' optimisations are those that can make +runtime or space {\em worse} if you're unlucky. They are +normally turned on or off individually. + +As of version~0.26, \tr{-O2} is {\em unlikely} to produce +better code than \tr{-O}. + +% \item[\tr{-O0}:] +% \index{-O0 option} +% \index{optimise minimally} +% [``Oh zero''] Means: ``Turn {\em off} as many optimisations (e.g., +% simplifications) as possible.'' This is the only optimisation level +% at which the GCC-register-trickery is turned off. {\em You can't use +% it unless you have a suitably-built Prelude to match.} Intended for +% hard-core debugging. + +\item[\tr{-fvia-C}:] +\index{-fvia-C option} +Compile via C, and don't use the native-code generator. +(There are many cases when GHC does this on its own.) You might +pick up a little bit of speed by compiling via C. If you use +\tr{_ccall_}s or \tr{_casm_}s, you probably {\em have to} use +\tr{-fvia-C}. + +\item[\tr{-O2-for-C}:] +\index{-O2-for-C option} +Says to run GCC with \tr{-O2}, which may be worth a few percent in +execution speed. Don't forget \tr{-fvia-C}, lest you use the +native-code generator and bypass GCC altogether! + +\item[\tr{-Onot}:] +\index{-Onot option} +\index{optimising, reset} +This option will make GHC ``forget'' any -Oish options it has seen +so far. Sometimes useful; for example: \tr{make all EXTRA_HC_OPTS=-Onot}. + +\item[\tr{-Ofile <file>}:] +\index{-Ofile <file> option} +\index{optimising, customised} +For those who need {\em absolute} control over {\em exactly} what +options are used (e.g., compiler writers, sometimes :-), a list of +options can be put in a file and then slurped in with \tr{-Ofile}. + +In that file, comments are of the \tr{#}-to-end-of-line variety; blank +lines and most whitespace is ignored. + +Please ask if you are baffled and would like an example of \tr{-Ofile}! +\end{description} + +At Glasgow, we don't use a \tr{-O*} flag for day-to-day work. We use +\tr{-O} to get respectable speed; e.g., when we want to measure +something. When we want to go for broke, we tend to use +\tr{-O -fvia-C -O2-for-C} (and we go for lots of coffee breaks). + +%Here is a table to summarise whether pragmatic interface information +%is used or not, whether the native-code generator is used (if +%available), and whether we use GCC register tricks (for speed!) on the +%generated C code: +% +%\begin{tabular}{lccl} +%\tr{-O*} & Interface & Native code & `Registerised' C \\ +% & pragmas? & (if avail.) & (if avail.) \\ \hline +%% +%\pl{<none>} & no & yes & yes, only if \tr{-fvia-C} \\ +%\tr{-O,-O1} & yes & yes & yes, only if \tr{-fvia-C} \\ +%\tr{-O2} & yes & no & yes \\ +%\tr{-Ofile} & yes & yes & yes, only if \tr{-fvia-C} \\ +%\end{tabular} + +The easiest way to see what \tr{-O} (etc) ``really mean'' is to run +with \tr{-v}, then stand back in amazement. +Alternatively, just look at the +\tr{@HsC_minus<blah>} lists in the \tr{ghc} driver script. + +%---------------------------------------------------------------------- +\subsubsection{\tr{-f*}: platform-independent flags} +\index{-f* options (GHC)} +\index{-fno-* options (GHC)} + +Flags can be turned {\em off} individually. (NB: I hope +you have a good reason for doing this....) To turn off the \tr{-ffoo} +flag, just use the \tr{-fno-foo} flag.\index{-fno-<opt> anti-option} +So, for example, you can say +\tr{-O2 -fno-strictness}, which will then drop out any running of the +strictness analyser. + +The options you are most likely to want to turn off are: +\tr{-fno-update-analysis}\index{-fno-update-analysis option} [because +it is sometimes slow], +\tr{-fno-strictness}\index{-fno-strictness option} (strictness +analyser [because it is sometimes slow]), +\tr{-fno-specialise}\index{-fno-specialise option} (automatic +specialisation of overloaded functions [because it makes your code +bigger]) [US spelling also accepted], +and +\tr{-fno-foldr-build}\index{-fno-foldr-build option} [because no-one +knows what Andy Gill made it do]. + +Should you wish to turn individual flags {\em on}, you are advised to +use the \tr{-Ofile} option, described above. Because the order in +which optimisation passes are run is sometimes crucial, it's quite +hard to do with command-line options. + +Here are some ``dangerous'' optimisations you {\em might} want to try: +\begin{description} +%------------------------------------------------------------------ +\item[\tr{-funfolding-creation-threshold<n>}:] +(Default: 30) By raising or lowering this number, you can raise or lower the +amount of pragmatic junk that gets spewed into interface files. +(An unfolding has a ``size'' that reflects the cost in terms of ``code +bloat'' of expanding that unfolding in another module. A bigger +Core expression would be assigned a bigger cost.) + +\item[\tr{-funfolding-use-threshold<n>}:] +(Default: 3) By raising or lowering this number, you can make the +compiler more or less keen to expand unfoldings. + +OK, folks, these magic numbers `30' and `3' are mildly arbitrary; they +are of the ``seem to be OK'' variety. The `3' is the more critical +one; it's what determines how eager GHC is about expanding unfoldings. + +\item[\tr{-funfolding-override-threshold<n>}:] +(Default: 8) [Pretty obscure] +When deciding what unfoldings from a module should be made available +to the rest of the world (via this module's interface), the compiler +normally likes ``small'' expressions. + +For example, if it sees \tr{foo = bar}, it will decide that the very +small expression \tr{bar} is a great unfolding for \tr{foo}. But if +\tr{bar} turns out to be \tr{(True,False,True)}, we would probably +prefer {\em that} for the unfolding for \tr{foo}. + +Should we ``override'' the initial small unfolding from \tr{foo=bar} +with the bigger-but-better one? Yes, if the bigger one's ``size'' is +still under the ``override threshold.'' You can use this flag to +adjust this threshold (why, I'm not sure). + +\item[\tr{-fliberated-case-threshold<n>}:] +(Default: 12) [Vastly obscure: NOT IMPLEMENTED YET] +``Case liberation'' lifts evaluation out of recursive functions; it +does this by duplicating code. Done without constraint, you can get +serious code bloat; so we only do it if the ``size'' of the duplicated +code is smaller than some ``threshold.'' This flag can fiddle that +threshold. + +\item[\tr{-fsemi-tagging}:] +This option (which {\em does not work} with the native-code generator) +tells the compiler to add extra code to test for already-evaluated +values. You win if you have lots of such values during a run of your +program, you lose otherwise. (And you pay in extra code space.) + +We have not played with \tr{-fsemi-tagging} enough to recommend it. +(For all we know, it doesn't even work in 0.26. Sigh.) +\end{description} + +%---------------------------------------------------------------------- +% \subsubsection[optimise-simplifier]{Controlling ``simplification'' in the Haskell compiler.} +% +%Almost everyone turns program transformation +% (a.k.a. ``simplification'') on/off via one of the ``packages'' above, +%but you can exert absolute control if you want to. Do a \tr{ghc -v -O ...}, +%and you'll see there are plenty of knobs to turn! +% +%The Core-to-Core and STG-to-STG passes can be run multiple times, and +%in varying orders (though you may live to regret it). The on-or-off +%global flags, however, are simply, well, on or off. +% +%The best way to give an exact list of options is the \tr{-Ofile} +%option, described elsewhere. +% +% [Check out \tr{ghc/compiler/simplCore/SimplCore.lhs} and +%\tr{simplStg/SimplStg.lhs} if you {\em really} want to see every +%possible Core-to-Core and STG-to-STG pass, respectively. The +%on-or-off global flags that effect what happens {\em within} one of +%these passes are defined by the \tr{GlobalSwitch} datatype in +%\tr{compiler/main/CmdLineOpts.lhs}.] + +%---------------------------------------------------------------------- +\subsubsection{\tr{-m*}: platform-specific flags} +\index{-m* options (GHC)} +\index{platform-specific options} +\index{machine-specific options} + +Some flags only make sense for particular target platforms. + +\begin{description} +\item[\tr{-mlong-calls}:] +(HPPA machines)\index{-mlong-calls option (HPPA only)} +Means to pass the like-named option to GCC. Required for Very Big +modules, maybe. (Probably means you're in trouble...) + +\item[\tr{-monly-[432]-regs}:] +(iX86 machines)\index{-monly-N-regs option (iX86 only)} +GHC tries to ``steal'' five registers from GCC, for performance +reasons; it almost always works. However, when GCC is compiling some +modules with five stolen registers, it will crash, probably saying: +\begin{verbatim} +Foo.hc:533: fixed or forbidden register was spilled. +This may be due to a compiler bug or to impossible asm +statements or clauses. +\end{verbatim} +Just give some registers back with \tr{-monly-N-regs}. Try `4' first, +then `3', then `2'. If `2' doesn't work, please report the bug to us. +\end{description} + +%---------------------------------------------------------------------- +\subsubsection[optimise-C-compiler]{Code improvement by the C compiler.} +\index{optimisation by GCC} +\index{GCC optimisation} + +The C~compiler, normally GCC, is run with \tr{-O} turned on. (It has +to be, actually.) + +If you want to run GCC with \tr{-O2}---which may be worth a few +percent in execution speed---you can give a +\tr{-O2-for-C}\index{-O2-for-C option} option. + +%If you are brave or foolish, you might want to omit some checking code +% (e.g., for stack-overflow checks), as sketched in +%\sectionref{omit-checking}. + +%************************************************************************ +%* * +\subsection[options-sanity]{Sanity-checking options} +\index{sanity-checking options} +%* * +%************************************************************************ + +If you would like GHC to check that every top-level value has a type +signature, use the \tr{-fsignatures-required} +option.\index{-fsignatures-required option} + +If you would like to disallow ``name shadowing,'' i.e., an inner-scope +value has the same name as an outer-scope value, then use the +\tr{-fname-shadowing-not-ok} +option.\index{-fname-shadowing-not-ok option} +This option catches typographical errors that turn into hard-to-find +bugs, e.g., in the inadvertent cyclic definition \tr{let x = ... x ... in}. + +Consequently, this option does {\em not} allow cyclic recursive +definitions. + +If you're feeling really paranoid, the \tr{-dcore-lint} +option\index{-dcore-lint option} is a good choice. It turns on +heavyweight intra-pass sanity-checking within GHC. (It checks GHC's +sanity, not yours.) + +%************************************************************************ +%* * +\subsection[options-output]{Re-directing the compilation output(s)} +\index{output-directing options} +%* * +%************************************************************************ + +When compiling a Haskell module, GHC may produce several files of +output (usually two). + +One file is usually an {\em interface file}. If compiling +\tr{bar/Foo.hs}, the interface file would normally be \tr{bar/Foo.hi}. +The interface output may be directed to another file +\tr{bar2/Wurble.iface} with the option +\tr{-ohi bar2/Wurble.iface}\index{-ohi <file> option}. + +To avoid generating an interface file at all, use a \tr{-nohi} +option.\index{-nohi option} + +The compiler does not overwrite an existing \tr{.hi} interface file if +the new one is byte-for-byte the same as the old one; this is friendly to +\tr{make}. When an interface does change, it is often enlightening to +be informed. The \tr{-hi-diffs}\index{-hi-diffs option} option will +make \tr{ghc} run \tr{diff} on the old and new \tr{.hi} files. + +GHC's non-interface output normally goes into a \tr{.hc}, \tr{.o}, +etc., file, depending on the last-run compilation phase. The option +\tr{-o foo}\index{-o option} re-directs the output of that last-run +phase to file \tr{foo}. + +Note: this ``feature'' can be counterintuitive: +\tr{ghc -C -o foo.o foo.hs} will put the intermediate C code in the +file \tr{foo.o}, name notwithstanding! + +EXOTICA: But the \tr{-o} option isn't much use if you have {\em +several} input files... Non-interface output files are normally put +in the same directory as their corresponding input file came from. +You may specify that they be put in another directory using the +\tr{-odir <dir>}\index{-odir <dir> option} (the ``Oh, dear'' option). +For example: + +\begin{verbatim} +% ghc -c parse/Foo.hs parse/Bar.hs gurgle/Bumble.hs -odir `arch` +\end{verbatim} + +The output files, \tr{Foo.o}, \tr{Bar.o}, and \tr{Bumble.o} would be +put into a subdirectory named after the architecture of the executing +machine (\tr{sun4}, \tr{mips}, etc). The directory must already +exist; it won't be created. + +Note that the \tr{-odir} option does {\em not} affect where the +interface files are put. In the above example, they would still be +put in \tr{parse/Foo.hi}, \tr{parse/Bar.hi}, and +\tr{gurgle/Bumble.hi}. + +MORE EXOTICA: The \tr{-osuf <suffix>}\index{-osuf <suffix> option} +will change the \tr{.o} file suffix for object files to whatever +you specify. (We use this in compiling the prelude.) + +Similarly, the \tr{-hisuf <suffix>}\index{-hisuf <suffix> option} will +change the \tr{.hi} file suffix for non-system interface files. This +can be useful when you are trying to compile a program several ways, +all in the same directory. The suffix given is used for {\em all} +interfaces files written, {\em and} for all non-system interface files +that your read. + +The \tr{-hisuf}/\tr{-osuf} game is useful if you want to compile a +program with both GHC and HBC (say) in the same directory. Let HBC +use the standard \tr{.hi}/\tr{.o} suffixes; add +\tr{-hisuf _g.hi -osuf _g.o} to your \tr{make} rule for GHC compiling... + +% THIS SHOULD HAPPEN AUTOMAGICALLY: +% If you want to change the suffix looked for on system-supplied +% interface files (notably the \tr{Prelude.hi} file), use the +% \tr{-hisuf-prelude <suffix>}\index{-hisuf-prelude <suffix> option} +% option. (This may be useful if you've built GHC in various funny +% ways, and you are running tests in even more funny ways. It happens.) + +FURTHER EXOTICA: If you are doing a normal \tr{.hs}-to-\tr{.o} compilation +but would like to hang onto the intermediate \tr{.hc} C file, just +throw in a \tr{-keep-hc-file-too} option\index{-keep-hc-file-too option}. +If you would like to look at the assembler output, toss in a +\tr{-keep-s-file-too},\index{-keep-hc-file-too option} too. + +SAVING GHC STDERR OUTPUT: Sometimes, you may cause GHC to be rather +chatty on standard error; with \tr{-fshow-import-specs}, for example. +You can instruct GHC to {\em append} this output to a particular log +file with a \tr{-odump <blah>}\index{-odump <blah> option} option. + +TEMPORARY FILES: If you have trouble because of running out of space +in \tr{/tmp/} (or wherever your installation thinks temporary files +should go), you may use the \tr{-tmpdir <dir>}\index{-tmpdir <dir> option} +option to specify an alternate directory. For example, \tr{-tmpdir .} +says to put temporary files in the current working directory. + +BETTER IDEA FOR TEMPORARY FILES: Use your \tr{TMPDIR} environment +variable.\index{TMPDIR environment variable} Set it to the name of +the directory where temporary files should be put. GCC and other +programs will honour the \tr{TMPDIR} variable as well. + +EVEN BETTER IDEA: Configure GHC with \tr{--with-tmpdir=<mumble>} when +you build it, and never worry about \tr{TMPDIR} again. + +%************************************************************************ +%* * +\subsection[options-finding-imports-etc]{For finding interface files, etc.} +\index{interface files, finding them} +\index{finding interface files} +%* * +%************************************************************************ + +In your program, you import a module \tr{Foo} by saying +\tr{import Foo}. GHC goes looking for an interface file, \tr{Foo.hi}. +It has a builtin list of directories (notably including \tr{.}) where +it looks. + +The \tr{-i<dirs>} option\index{-i<dirs> option} prepends a +colon-separated list of \tr{dirs} to the ``import directories'' list. + +A plain \tr{-i} resets the ``import directories'' list back to nothing. + +GHC normally imports \tr{PreludeCore.hi} and \tr{Prelude.hi} files for +you. If you'd rather it didn't, then give it a +\tr{-fno-implicit-prelude} option\index{-fno-implicit-prelude option}. +(Sadly, it still has to {\em find} a \tr{PreludeNull_.hi} file; it +just won't feed it into the compiler proper.) You are unlikely to get +very far without a Prelude, but, hey, it's a free country. + +If you are using a system-supplied non-Prelude library (e.g., the HBC +library), just use a \tr{-syslib hbc}\index{-syslib <lib> option} +option (for example). The right interface files should then be +available. + +Once a Haskell module has been compiled to C (\tr{.hc} file), you may +wish to specify where GHC tells the C compiler to look for \tr{.h} +files. (Or, if you are using the \tr{-cpp} option\index{-cpp option}, +where it tells the C pre-processor to look...) For this purpose, use +a \tr{-I<dir>}\index{-I<dir> option} in the usual C-ish way. + +Pragmas: Interface files are normally jammed full of +compiler-produced {\em pragmas}, which record arities, strictness +info, etc. If you think these pragmas are messing you up (or you are +doing some kind of weird experiment), you can tell GHC to ignore them +with the \tr{-fignore-interface-pragmas}\index{-fignore-interface-pragmas option} +option. + +See also \sectionref{options-linker}, which describes how the linker +finds standard Haskell libraries. + +%************************************************************************ +%* * +%\subsection[options-names]{Fiddling with namespaces} +%* * +%************************************************************************ + +%-split-objs and -fglobalise-toplev-names. You don't need them and you +%don't want to know; used for the prelude (ToDo). + +%************************************************************************ +%* * +\subsection[options-CPP]{Related to the C pre-processor} +\index{C pre-processor options} +\index{pre-processor (cpp) options} +%* * +%************************************************************************ + +The C pre-processor \tr{cpp} is run over your Haskell code only if the +\tr{-cpp} option \index{-cpp option} is given. Unless you are +building a large system with significant doses of conditional +compilation, you really shouldn't need it. +\begin{description} +\item[\tr{-D<foo>}:] +\index{-D<name> option} +Define macro \tr{<foo>} in the usual way. NB: does {\em not} affect +\tr{-D} macros passed to the C~compiler when compiling via C! For +those, use the \tr{-optc-Dfoo} hack... + +\item[\tr{-U<foo>}:] +\index{-U<name> option} +Undefine macro \tr{<foo>} in the usual way. + +\item[\tr{-I<dir>}:] +\index{-I<dir> option} +Specify a directory in which to look for \tr{#include} files, in +the usual UNIX/C way. +\end{description} + +The \tr{ghc} driver pre-defines several macros: +\begin{description} +\item[\tr{__HASKELL1__}:] +\index{__HASKELL1__ macro} +If defined to $n$, that means GHC supports the +Haskell language defined in the Haskell report version $1.n$. +Currently 2. + +NB: This macro is set both when pre-processing Haskell source and +when pre-processing generated C (\tr{.hc}) files. + +If you give the \tr{-fhaskell-1.3} flag\index{-fhaskell-1.3 option}, +then \tr{__HASKELL1__} is set to 3. Obviously. + +\item[\tr{__GLASGOW_HASKELL__}:] +\index{__GLASGOW_HASKELL__ macro} +For version $n$ of the GHC system, this will be \tr{#define}d to +$100 \times n$. So, for version~0.26, it is 26. + +This macro is {\em only} set when pre-processing Haskell source. +({\em Not} when pre-processing generated C.) + +With any luck, \tr{__GLASGOW_HASKELL__} will be undefined in all other +implementations that support C-style pre-processing. + +(For reference: the comparable symbols for other systems are: +\tr{__YALE_HASKELL__} for Yale Haskell, \tr{__HBC__} for Chalmers +HBC, and \tr{__GOFER__} for Gofer [I think].) + +\item[\tr{__CONCURRENT_HASKELL__}:] +\index{__CONCURRENT_HASKELL__ macro} +Only defined when \tr{-concurrent} is in use! +This symbol is +defined when pre-processing Haskell (input) and pre-processing C (GHC +output). + +\item[\tr{__PARALLEL_HASKELL__}:] +\index{__PARALLEL_HASKELL__ macro} +Only defined when \tr{-parallel} is in use! This symbol is defined when +pre-processing Haskell (input) and pre-processing C (GHC output). +\end{description} + +Options other than the above can be forced through to the C +pre-processor with the \tr{-opt} flags (see +\sectionref{forcing-options-through}). + +A small word of warning: \tr{-cpp} is not friendly to +``string gaps''.\index{-cpp vs string gaps}\index{string gaps vs -cpp} + + +%************************************************************************ +%* * +\subsection[options-C-compiler]{Options affecting the C compiler (if applicable)} +\index{C compiler options} +\index{GCC options} +%* * +%************************************************************************ + +At the moment, quite a few common C-compiler options are passed on +quietly to the C compilation of Haskell-compiler-generated C files. +THIS MAY CHANGE. Meanwhile, options so sent are: + +\begin{tabular}{ll} +\tr{-Wall} & get all warnings from GCC \\ +\tr{-ansi} & do ANSI C (not K\&R) \\ +\tr{-pedantic} & be so\\ +\tr{-dgcc-lint} & (hack) short for ``make GCC very paranoid''\\ +\end{tabular} +\index{-Wall option (for GCC)} +\index{-ansi option (for GCC)} +\index{-pedantic option (for GCC)} +\index{-dgcc-lint option (GCC paranoia)} + +If you are compiling with lots of \tr{ccalls}, etc., you may need to +tell the C~compiler about some \tr{#include} files. There is no +pretty way to do this, but you can use this hack from the +command-line: +\begin{verbatim} +% ghc -c '-#include <X/Xlib.h>' Xstuff.lhs +\end{verbatim} +\index{-#include <file> option} + +%************************************************************************ +%* * +%\subsection[options-native-code]{Options affecting the native-code generator(s)} +%* * +%************************************************************************ + +%The only option is to select the target architecture. Right now, +%you have only at most one choice: \tr{-fasm-sparc}.\index{-fasm-<target> option} +% +%EXPECT this native-code stuff to change in the future. + +%************************************************************************ +%* * +\subsection[options-linker]{Linking and consistency-checking} +\index{linker options} +\index{ld options} +%* * +%************************************************************************ + +GHC has to link your code with various libraries, possibly including: +user-supplied, GHC-supplied, and system-supplied (\tr{-lm} math +library, for example). + +\begin{description} +\item[\tr{-l<FOO>}:] +\index{-l<lib> option} +Link in a library named \tr{lib<FOO>.a} which resides somewhere on the +library directories path. + +Because of the sad state of most UNIX linkers, the order of such +options does matter. Thus: \tr{ghc -lbar *.o} is almost certainly +wrong, because it will search \tr{libbar.a} {\em before} it has +collected unresolved symbols from the \tr{*.o} files. +\tr{ghc *.o -lbar} is probably better. + +The linker will of course be informed about some GHC-supplied +libraries automatically; these are: + +\begin{tabular}{ll} +-l equivalent & description \\ \hline + +-lHSrts,-lHSclib & basic runtime libraries \\ +-lHS & standard Prelude library \\ +-lgmp & GNU multi-precision library (for Integers)\\ +\end{tabular} +\index{-lHS library} +\index{-lHSrts library} +\index{-lgmp library} + +\item[\tr{-syslib <name>}:] +\index{-syslib <name> option} + +If you are using an optional GHC-supplied library (e.g., the HBC +library), just use the \tr{-syslib hbc} option, and the correct code +should be linked in. + +Please see \sectionref{syslibs} for information about optional +GHC-supplied libraries. + +\item[\tr{-L<dir>}:] +\index{-L<dir> option} +Where to find user-supplied libraries... Prepend the directory +\tr{<dir>} to the library directories path. + +\item[\tr{-static}:] +\index{-static option} +Tell the linker to avoid shared libraries. + +\item[\tr{-no-link-chk} and \tr{-link-chk}:] +\index{-no-link-chk option} +\index{-link-chk option} +\index{consistency checking of executables} +By default, immediately after linking an executable, GHC verifies that +the pieces that went into it were compiled with compatible flags; a +``consistency check''. +(This is to avoid mysterious failures caused by non-meshing of +incompatibly-compiled programs; e.g., if one \tr{.o} file was compiled +for a parallel machine and the others weren't.) You may turn off this +check with \tr{-no-link-chk}. You can turn it (back) on with +\tr{-link-chk} (the default). +\end{description} + +%************************************************************************ +%* * +\subsection[options-compiler-RTS]{For the compiler's RTS: heap, stack sizes, etc.} +\index{heap-size options (for GHC)} +\index{stack-size options (for GHC)} +%* * +%************************************************************************ + +The compiler is itself a Haskell program, so it has a tweakable +runtime-system (RTS), just like any other Haskell program. + +\begin{description} +\item[\tr{-H<size>} or \tr{-Rmax-heapsize <size>}:] +\index{-H<size> option} +\index{-Rmax-heapsize <size> option} +Don't use more than \tr{<size>} {\em bytes} for heap space. If more +than one of these arguments is given, the largest will be taken. + +A size of zero can be used to reset the heap size downwards. For +example, to run GHC with a heap of 250KB (the default is 6MB), do +\tr{-H0 -H250k}. + +\item[\tr{-K<size>} or \tr{-Rmax-stksize <size>}:] +\index{-K<size> option} +\index{-Rmax-stksize <size> option} +Set the stack space to \tr{<size>} bytes. If you have to set it very +high [a megabyte or two, say], the compiler is probably looping, which +is a BUG (please report). + +A size of zero can be used to rest the stack size downwards, as above. + +\item[\tr{-Rscale-sizes<factor>}:] +\index{-Rscale-sizes<factor> option} +Multiply the given (or default) heap and stack sizes by \tr{<factor>}. +For example, on a DEC Alpha (a 64-bit machine), you might want to +double those space sizes; just use \tr{-Rscale-sizes2}. + +A non-integral factor is OK, too: \tr{-Rscale-sizes1.2}. + +\item[\tr{-Rghc-timing}:] +\index{-Rghc-timing option} +Reports a one-line useful collection of time- and space- statistics +for a module's compilation. + +\item[\tr{-Rgc-stats}:] +\index{-Rgc-stats option} +Report garbage-collection statistics. It will create a +\tr{<foo>.stat} file, in some obvious place (I hope). + +Alternatively, if you'd rather the GC stats went straight to standard +error, you can ``cheat'' by using, instead: \tr{-optCrts-Sstderr}. + +\item[\tr{-Rhbc}:] +\index{-Rhbc option} +Tell the compiler it has an HBC-style RTS; i.e., it was compiled with +HBC. Not used in Real Life. + +\item[\tr{-Rghc}:] +\index{-Rghc option} +Tell the compiler it has a GHC-style RTS; i.e., it was compiled with +GHC. Not used in Real Life. +\end{description} + +For all \tr{<size>}s: If the last character of \tr{size} is a K, +multiply by 1000; if an M, by 1,000,000; if a G, by 1,000,000,000. +Sizes are always in {\em bytes}, not words. Good luck on the G's (I +think the counter is still only 32-bits [WDP])! + +%************************************************************************ +%* * +%\subsection[options-cross-compiling]{For cross-compiling to another architecture} +%* * +%************************************************************************ +% +% (We do this for GRIP at Glasgow; it's hacked in---not proper +%cross-compiling support. But you could do the same, if required...) +% +%The \tr{-target <arch>} option\index{-target <arch> option} says to +%generate code for the \tr{<arch>} architecture. + +%************************************************************************ +%* * +\subsection[options-parallel]{For Concurrent and Parallel Haskell} +%* * +%************************************************************************ + +For the full story on using GHC for concurrent \& parallel Haskell +programming, please see \Sectionref{concurrent-and-parallel}. + +%The \tr{-fparallel} option\index{-fparallel option} tells the compiler +%to generate code for parallel execution. The \tr{-mgrip} +%option\index{-mgrip option} says that the code should be explicitly +%suitable for the GRIP multiprocessor (the one in our Glasgow basement). + +%************************************************************************ +%* * +\subsection[options-experimental]{For experimental purposes} +\index{experimental options} +%* * +%************************************************************************ + +From time to time, we provide GHC options for ``experimenting.'' Easy +come, easy go. In version~0.26, the ``experimental'' options are: +\begin{description} +\item[\tr{-firrefutable-tuples} option:] +\index{-firrefutable-tuples option (experimental)} +Pretend that every tuple pattern is irrefutable; i.e., has a +``twiddle'' (\tr{~}) in front of it. + +Some parts of the GHC system {\em depend} on strictness properties which +\tr{-firrefutable-tuples} may undo, notably the low-level state-transformer +stuff, which includes I/O (!). You're on your own... + +\item[\tr{-fall-strict} option:] +\index{-fall-strict option (experimental)} +(DOESN'T REALLY WORK, I THINK) Changes the strictness analyser so +that, when it asks the question ``Is this function argument certain to +be evaluated?'', the answer is always ``yes''. + +Compilation is changed in no other way. +\end{description} +% -firrefutable-everything +% -fall-demanded + +%************************************************************************ +%* * +\subsection[options-debugging]{For debugging the compiler} +\index{debugging options (for GHC)} +%* * +%************************************************************************ + +HACKER TERRITORY. HACKER TERRITORY. +(You were warned.) + +%---------------------------------------------------------------------- +\subsubsection[replacing-phases]{Replacing the program for one or more phases.} +\index{GHC phases, changing} +\index{phases, changing GHC} + +You may specify that a different program +be used for one of the phases of the compilation system, in place of +whatever the driver \tr{ghc} has wired into it. For example, you +might want to test a replacement parser. The +\tr{-pgm<phase-code><program-name>}\index{-pgm<phase><stuff> option} option to +\tr{ghc} will cause it to use \pl{<program-name>} for phase +\pl{<phase-code>}, where the codes to indicate the phases are: + +\begin{tabular}{ll} +code & phase \\ \hline +L & literate pre-processor \\ +P & C pre-processor (if -cpp only) \\ +p & parser \\ +C & Haskell compiler \\ +cO & C compiler for `optimised' (normal) compiling \\ +c & C compiler for `unregisterised' compiling \\ +a & assembler \\ +l & linker \\ +\end{tabular} + +If you use the ambiguous \tr{-pgmcOle}, it will take it to mean +``use program \tr{le} for optimised C compiling.'' + +%---------------------------------------------------------------------- +\subsubsection[forcing-options-through]{Forcing options to a particular phase.} +\index{forcing GHC-phase options} + +The preceding sections describe driver options that are mostly +applicable to one particular phase. You may also {\em force} a +specific option \tr{<option>} to be passed to a particular phase +\tr{<phase-code>} by feeding the driver the option +\tr{-opt<phase-code><option>}.\index{-opt<phase><stuff> option} The +codes to indicate the phases are the same as in the previous section. + +So, for example, to force an \tr{-Ewurble} option to the assembler, you +would tell the driver \tr{-opta-Ewurble} (the dash before the E is +required). + +Besides getting options to the Haskell compiler with \tr{-optC<blah>}, +you can get options through to its runtime system with +\tr{-optCrts<blah>}\index{-optCrts<blah> option}. + +So, for example: when I want to use my normal driver but with my +profiled compiler binary, I use this script: +\begin{verbatim} +#! /bin/sh +exec /local/grasp_tmp3/partain/ghc-BUILDS/working-alpha/ghc/driver/ghc \ + -pgmC/local/grasp_tmp3/partain/ghc-BUILDS/working-hsc-prof/hsc \ + -optCrts-i0.5 \ + -optCrts-PT \ + "$@" +\end{verbatim} + +%---------------------------------------------------------------------- +\subsubsection[dumping-output]{Dumping out compiler intermediate structures} +\index{dumping GHC intermediates} +\index{intermediate passes, output} + +\begin{description} +\item[\tr{-noC}:] +\index{-noC option} +Don't bother generating C output {\em or} an interface file. Usually +used in conjunction with one or more of the \tr{-ddump-*} options; for +example: \tr{ghc -noC -ddump-simpl Foo.hs} + +\item[\tr{-hi}:] +\index{-hi option} +{\em Do} generate an interface file. This would normally be used in +conjunction with \tr{-noC}, which turns off interface generation; +thus: \tr{-noC -hi}. + +\item[\tr{-ddump-parser}:] +\index{-ddump-parser option} +This debugging option shows the exact prefix-form Haskell that is fed +into the Haskell compiler proper. + +\item[\tr{-ddump-<pass>}:] +\index{-ddump-<pass> options} +Make a debugging dump after pass \tr{<pass>} (may be common enough to +need a short form...). Some of the most useful ones are: + +\begin{tabular}{ll} +\tr{-ddump-rif2hs} & reader output (earliest stuff in the compiler) \\ +\tr{-ddump-rn4} & renamer output \\ +\tr{-ddump-tc} & typechecker output \\ +\tr{-ddump-deriv} & derived instances \\ +\tr{-ddump-ds} & desugarer output \\ +\tr{-ddump-simpl} & simplifer output (Core-to-Core passes) \\ + & (and don't forget \tr{-O}, too!) \\ +\tr{-ddump-stranal} & strictness analyser output \\ + & (only works in conjunction with -ddump-simpl)\\ +\tr{-ddump-occur-anal} & `occurrence analysis' output \\ + & (only works in conjunction with -ddump-simpl)\\ +\tr{-ddump-spec} & dump specialisation info \\ +\tr{-ddump-stg} & output of STG-to-STG passes \\ +\tr{-ddump-absC} & {\em un}flattened Abstract~C \\ +\tr{-ddump-flatC} & {\em flattened} Abstract~C \\ +\tr{-ddump-realC} & same as what goes to the C compiler \\ +\tr{-ddump-asm} & assembly language from the native-code generator \\ +\end{tabular} +\index{-ddump-rif2hs option}% +\index{-ddump-rn4 option}% +\index{-ddump-tc option}% +\index{-ddump-deriv option}% +\index{-ddump-ds option}% +\index{-ddump-simpl option}% +\index{-ddump-stranal option}% +\index{-ddump-occur-anal option}% +\index{-ddump-spec option}% +\index{-ddump-stg option}% +\index{-ddump-absC option}% +\index{-ddump-flatC option}% +\index{-ddump-realC option}% +\index{-ddump-asm option} + +%For any other \tr{-ddump-*} options: consult the source, notably +%\tr{ghc/compiler/main/CmdLineOpts.lhs}. + +\item[\tr{-dverbose-simpl} and \tr{-dverbose-stg}:] +\index{-dverbose-simpl option} +\index{-dverbose-stg option} +Show the output of the intermediate Core-to-Core and STG-to-STG +passes, respectively. ({\em Lots} of output!) So: when we're +really desperate: +\begin{verbatim} +% ghc -noC -O -ddump-simpl -dverbose-simpl -dcore-lint Foo.hs +\end{verbatim} + +\item[\tr{-dppr-{user,debug,all}}:] +\index{-dppr-user option} +\index{-dppr-debug option} +\index{-dppr-all option} +Debugging output is in one of several ``styles.'' Take the printing +of types, for example. In the ``user'' style, the compiler's internal +ideas about types are presented in Haskell source-level syntax, +insofar as possible. In the ``debug'' style (which is the default for +debugging output), the types are printed in the most-often-desired +form, with explicit foralls, etc. In the ``show all'' style, very +verbose information about the types (e.g., the Uniques on the +individual type variables) is displayed. + +\item[\tr{-ddump-raw-asm}:] +\index{-ddump-raw-asm option} +Dump out the assembly-language stuff, before the ``mangler'' gets it. + +\item[\tr{-dgc-debug}:] +\index{-dgc-debug option} +Enables some debugging code related to the garbage-collector. +\end{description} + +%ToDo: -ddump-asm-insn-counts +%-ddump-asm-globals-info + +%---------------------------------------------------------------------- +\subsubsection[arity-checking]{Options to insert arity-checking code} +\index{arity checking} + +The \tr{-darity-checks}\index{-darity-checks option} option inserts +code to check for arity violations. Unfortunately, it's not that +simple: you have to link with a prelude that was also built with arity +checks. If you have one, then great; otherwise... + +The \tr{-darity-checks-C-only}\index{-darity-checks-C-only option} +option inserts the self-same arity checking code into \tr{.hc} files, +but doesn't compile it into the \tr{.o} files. We use this flag with +the \tr{-keep-hc-file-too}\index{-keep-hc-file-too option}, where we +are keeping \tr{.hc} files around for debugging purposes. + +%---------------------------------------------------------------------- +\subsubsection[omit-checking]{Options to omit checking code} +\index{omitting runtime checks} + +By default, the GHC system emits all possible not-too-expensive +runtime checking code. If you are brave or experimenting, you might +want to turn off some of this (not recommended): + +\begin{tabular}{ll} +-dno-black-holing & won't buy you much (even if it works) \\ +-dno-updates & you're crazy if you do this \\ +-dno-stk-stubbing & omit stack stubbing (NOT DONE YET) \\ +\end{tabular} +\index{-dno-black-holing option}% +\index{-dno-updates option}% +\index{-dno-stk-stubbing option} + +Warning: all very lightly tested, if at all... + +%% %************************************************************************ +%% %* * +%% \subsection[options-GC]{Choosing a garbage collector} +%% %* * +%% %************************************************************************ +%% +%% (Note: you need a Good Reason before launching into this territory.) +%% +%% There are up to four garbage collectors to choose from (it depends how +%% your local system was built); the Appel-style generational collector +%% is the default. +%% +%% If you choose a non-default collector, you must specify it both when +%% compiling the modules and when linking them together into an +%% executable. Also, the native-code generator only works with the +%% default collector (a small point to bear in mind). +%% +%% \begin{description} +%% \item[\tr{-gc-ap} option:] +%% \index{-gc-ap option} +%% Appel-like generational collector (the default). +%% +%% \item[\tr{-gc-2s} option:] +%% \index{-gc-2s option} +%% Two-space copying collector. +%% +%% \item[\tr{-gc-1s} option:] +%% \index{-gc-1s option} +%% One-space compacting collector. +%% +%% \item[\tr{-gc-du} option:] +%% \index{-gc-du option} +%% Dual-mode collector (swaps between copying and compacting). +%% \end{description} diff --git a/ghc/docs/users_guide/intro.lit b/ghc/docs/users_guide/intro.lit new file mode 100644 index 0000000000..4a85d28a9a --- /dev/null +++ b/ghc/docs/users_guide/intro.lit @@ -0,0 +1,69 @@ +% +% $Header: /srv/cvs/cvs.haskell.org/fptools/ghc/docs/users_guide/Attic/intro.lit,v 1.1 1996/01/08 20:25:10 partain Exp $ +% +\section[introduction-GHC]{Introduction to GHC} + +This is a guide to using the Glasgow Haskell compilation (GHC) system. +It is a batch compiler for the Haskell~1.2 language, with support for +various extensions, including the DRAFT 1.3 I/O proposal. + +Many people will use GHC very simply: compile some +modules---\tr{ghc -c -O Foo.hs Bar.hs}; and link them--- +\tr{ghc -o wiggle -O Foo.o Bar.o}. + +But if you need to do something more complicated, GHC can do that, +too: +\begin{verbatim} +ghc -c -O -fno-foldr-build -dcore-lint -fvia-C -ddump-simpl Foo.lhs +\end{verbatim} +Stay tuned---all will be revealed! + +In this document, we assume that GHC has been installed at your +site as \tr{ghc}. +If you are unfamiliar with the conventions of UNIX compilers, the +material in \sectionref{compiler-tutorial} may help. + +%-------------------------------------------------------------------- +\section[mailing-lists-GHC]{Knowing us, knowing you: Web sites, mailing lists, etc.} +\index{mailing lists, Glasgow Haskell} +\index{Glasgow Haskell mailing lists} + +On the World-Wide Web, there are several URLs of likely interest: +\begin{display} +GHC home page -- http://www.dcs.glasgow.ac.uk/fp/software/ghc.html +Glasgow FP group page -- http://www.dcs.glasgow.ac.uk/fp/ +comp.lang.functional FAQ -- http://www.cs.nott.ac.uk/Department/Staff/mpj/faq.html +programming language research page -- + http://www.cs.cmu.edu/afs/cs.cmu.edu/user/mleone/web/language-research.html +\end{display} +We run two mailing lists about Glasgow Haskell. We encourage you to +join, as you feel is appropriate. +\begin{description} +\item[glasgow-haskell-users:] +This list is for GHC users to chat among themselves. Subscribe by +sending mail to \tr{glasgow-haskell-users-request@dcs.glasgow.ac.uk}. +Messages for the list go to \tr{glasgow-haskell-users}. + +\item[glasgow-haskell-bugs:] +Send bug reports for GHC to this address! The sad and lonely people +who subscribe to this list will muse upon what's wrong and what you +might do about it. + +Subscribe via \tr{glasgow-haskell-bugs-request@dcs.glasgow.ac.uk}. +\end{description} + +There is also the general Haskell mailing list. Subscribe by sending +email to \tr{haskell-request@dcs.glasgow.ac.uk} or +\tr{haskell-request@cs.yale.edu}, whichever is geographically closer +to you. + +Some Haskell-related discussion takes place in the Usenet newsgroup +\tr{comp.lang.functional}. (But note: news propagation to Glasgow can +be terrible. That's one reason Glaswegians aren't too active in +c.f.l.) + +The main anonymous-FTP site for Glasgow Haskell is +\tr{ftp.dcs.glasgow.ac.uk}, in \tr{pub/haskell/glasgow/}. +``Important'' bits are mirrored at other Haskell archive sites (and we +have their stuff, too). + diff --git a/ghc/docs/users_guide/libraries.lit b/ghc/docs/users_guide/libraries.lit new file mode 100644 index 0000000000..dbe7b00a1b --- /dev/null +++ b/ghc/docs/users_guide/libraries.lit @@ -0,0 +1,1047 @@ +%************************************************************************ +%* * +\section[syslibs]{System libraries} +\index{system libraries} +\index{libraries, system} +%* * +%************************************************************************ + +We intend to provide more and more ready-to-use Haskell code, so that +every program doesn't have to invent everything from scratch. + +At the moment, we supply a part of the HBC library, as well as the +beginnings of one of our own (``GHC library''). + +If you provide a \tr{-syslib <name>}\index{-syslib <name> option} option, +then the interfaces for that library will come into scope (and may be +\tr{import}ed), and the code will be added in at link time. + +%************************************************************************ +%* * +\subsection[GHC-library]{The GHC system library} +\index{library, GHC} +\index{GHC library} +%* * +%************************************************************************ + +We have started to put together a ``GHC system library.'' + +At the moment, the library is made of generally-useful bits of the +compiler itself. + +To use this library, just give a \tr{-syslib ghc}\index{-syslib ghc option} +option to GHC, both for compiling and linking. + +%************************************************************************ +%* * +\subsubsection[Bag]{The @Bag@ type} +\index{Bag module (GHC syslib)} +%* * +%************************************************************************ + +A {\em bag} is an unordered collection of elements which may contain +duplicates. To use, \tr{import Bag}. + +\begin{verbatim} +emptyBag :: Bag elt +unitBag :: elt -> Bag elt + +unionBags :: Bag elt -> Bag elt -> Bag elt +unionManyBags :: [Bag elt] -> Bag elt +snocBag :: Bag elt -> elt -> Bag elt + +elemBag :: Eq elt => elt -> Bag elt -> Bool +isEmptyBag :: Bag elt -> Bool +filterBag :: (elt -> Bool) -> Bag elt -> Bag elt +partitionBag :: (elt -> Bool) -> Bag elt-> (Bag elt, Bag elt) + -- returns the elements that do/don't satisfy the predicate + +listToBag :: [elt] -> Bag elt +bagToList :: Bag elt -> [elt] +\end{verbatim} + +%************************************************************************ +%* * +\subsubsection[BitSet]{The @BitSet@ type} +\index{BitSet module (GHC syslib)} +%* * +%************************************************************************ + +Bit sets are a fast implementation of sets of integers ranging from 0 +to one less than the number of bits in a machine word (typically 31). +If any element exceeds the maximum value for a particular machine +architecture, the results of these operations are undefined. You have +been warned. [``If you put any safety checks in this code, I will have +to kill you.'' --JSM] + +\begin{verbatim} +mkBS :: [Int] -> BitSet +listBS :: BitSet -> [Int] +emptyBS :: BitSet +singletonBS :: Int -> BitSet + +unionBS :: BitSet -> BitSet -> BitSet +minusBS :: BitSet -> BitSet -> BitSet +elementBS :: Int -> BitSet -> Bool +intersectBS :: BitSet -> BitSet -> BitSet + +isEmptyBS :: BitSet -> Bool +\end{verbatim} + +%************************************************************************ +%* * +\subsubsection[FiniteMap]{The @FiniteMap@ type} +\index{FiniteMap module (GHC syslib)} +%* * +%************************************************************************ + +What functional programmers call a {\em finite map}, everyone else +calls a {\em lookup table}. + +Out code is derived from that in this paper: +\begin{display} +S Adams +"Efficient sets: a balancing act" +Journal of functional programming 3(4) Oct 1993, pages 553-562 +\end{display} +Guess what? The implementation uses balanced trees. + +\begin{verbatim} +-- BUILDING +emptyFM :: FiniteMap key elt +singletonFM :: key -> elt -> FiniteMap key elt +listToFM :: Ord key => [(key,elt)] -> FiniteMap key elt + -- In the case of duplicates, the last is taken + +-- ADDING AND DELETING + -- Throws away any previous binding + -- In the list case, the items are added starting with the + -- first one in the list +addToFM :: Ord key => FiniteMap key elt -> key -> elt -> FiniteMap key elt +addListToFM :: Ord key => FiniteMap key elt -> [(key,elt)] -> FiniteMap key elt + + -- Combines with previous binding +addToFM_C :: Ord key => (elt -> elt -> elt) + -> FiniteMap key elt -> key -> elt + -> FiniteMap key elt +addListToFM_C :: Ord key => (elt -> elt -> elt) + -> FiniteMap key elt -> [(key,elt)] + -> FiniteMap key elt + + -- Deletion doesn't complain if you try to delete something + -- which isn't there +delFromFM :: Ord key => FiniteMap key elt -> key -> FiniteMap key elt +delListFromFM :: Ord key => FiniteMap key elt -> [key] -> FiniteMap key elt + +-- COMBINING + -- Bindings in right argument shadow those in the left +plusFM :: Ord key => FiniteMap key elt -> FiniteMap key elt + -> FiniteMap key elt + + -- Combines bindings for the same thing with the given function +plusFM_C :: Ord key => (elt -> elt -> elt) + -> FiniteMap key elt -> FiniteMap key elt -> FiniteMap key elt + +minusFM :: Ord key => FiniteMap key elt -> FiniteMap key elt -> FiniteMap key elt + -- (minusFM a1 a2) deletes from a1 any bindings which are bound in a2 + +intersectFM :: Ord key => FiniteMap key elt -> FiniteMap key elt -> FiniteMap key elt +intersectFM_C :: Ord key => (elt -> elt -> elt) + -> FiniteMap key elt -> FiniteMap key elt -> FiniteMap key elt + +-- MAPPING, FOLDING, FILTERING +foldFM :: (key -> elt -> a -> a) -> a -> FiniteMap key elt -> a +mapFM :: (key -> elt1 -> elt2) -> FiniteMap key elt1 -> FiniteMap key elt2 +filterFM :: Ord key => (key -> elt -> Bool) + -> FiniteMap key elt -> FiniteMap key elt + +-- INTERROGATING +sizeFM :: FiniteMap key elt -> Int +isEmptyFM :: FiniteMap key elt -> Bool + +elemFM :: Ord key => key -> FiniteMap key elt -> Bool +lookupFM :: Ord key => FiniteMap key elt -> key -> Maybe elt +lookupWithDefaultFM + :: Ord key => FiniteMap key elt -> elt -> key -> elt + -- lookupWithDefaultFM supplies a "default" elt + -- to return for an unmapped key + +-- LISTIFYING +fmToList :: FiniteMap key elt -> [(key,elt)] +keysFM :: FiniteMap key elt -> [key] +eltsFM :: FiniteMap key elt -> [elt] +\end{verbatim} + +%************************************************************************ +%* * +\subsubsection[ListSetOps]{The @ListSetOps@ type} +\index{ListSetOps module (GHC syslib)} +%* * +%************************************************************************ + +Just a few set-sounding operations on lists. If you want sets, use +the \tr{Set} module. + +\begin{verbatim} +unionLists :: Eq a => [a] -> [a] -> [a] +intersectLists :: Eq a => [a] -> [a] -> [a] +minusList :: Eq a => [a] -> [a] -> [a] +disjointLists :: Eq a => [a] -> [a] -> Bool +intersectingLists :: Eq a => [a] -> [a] -> Bool +\end{verbatim} + +%************************************************************************ +%* * +\subsubsection[Maybes]{The @Maybes@ type} +\index{Maybes module (GHC syslib)} +%* * +%************************************************************************ + +Note: a \tr{Maybe} type is nearly inevitable in Haskell~1.3. +You should use this module with \tr{-fhaskell-1.3}. + +Two non-abstract types: +\begin{verbatim} +data Maybe a = Nothing | Just a -- Prelude; re-exported +data MaybeErr val err = Succeeded val | Failed err +\end{verbatim} + +Some operations to do with \tr{Maybe} (some commentary follows): +\begin{verbatim} +maybeToBool :: Maybe a -> Bool -- Nothing => False; Just => True +catMaybes :: [Maybe a] -> [a] +allMaybes :: [Maybe a] -> Maybe [a] +firstJust :: [Maybe a] -> Maybe a +findJust :: (a -> Maybe b) -> [a] -> Maybe b + +assocMaybe :: Eq a => [(a,b)] -> a -> Maybe b +mkLookupFun :: (key -> key -> Bool) -- Equality predicate + -> [(key,val)] -- The assoc list + -> (key -> Maybe val) -- A lookup fun to use + + -- a monad thing +thenMaybe :: Maybe a -> (a -> Maybe b) -> Maybe b +returnMaybe :: a -> Maybe a +failMaybe :: Maybe a +mapMaybe :: (a -> Maybe b) -> [a] -> Maybe [b] +\end{verbatim} + +@catMaybes@ takes a list of @Maybe@s and returns a list of the +contents of all the @Just@s in it. + +@allMaybes@ collects a list of @Justs@ into a single @Just@, returning +@Nothing@ if there are any @Nothings@. + +@firstJust@ takes a list of @Maybes@ and returns the +first @Just@ if there is one, or @Nothing@ otherwise. + +@assocMaybe@ looks up in an association list, returning +@Nothing@ if it fails. + +Now, some operations to do with \tr{MaybeErr} (comments follow): +\begin{verbatim} + -- a monad thing (surprise, surprise) +thenMaB :: MaybeErr a err -> (a -> MaybeErr b err) -> MaybeErr b err +returnMaB :: val -> MaybeErr val err +failMaB :: err -> MaybeErr val err + +listMaybeErrs :: [MaybeErr val err] -> MaybeErr [val] [err] +foldlMaybeErrs :: (acc -> input -> MaybeErr acc err) + -> acc + -> [input] + -> MaybeErr acc [err] +\end{verbatim} + +@listMaybeErrs@ takes a list of @MaybeErrs@ and, if they all succeed, +returns a @Succeeded@ of a list of their values. If any fail, it +returns a @Failed@ of the list of all the errors in the list. + +@foldlMaybeErrs@ works along a list, carrying an accumulator; it +applies the given function to the accumulator and the next list item, +accumulating any errors that occur. + +%************************************************************************ +%* * +\subsubsection[PackedString]{The @_PackedString@ type} +\index{PackedString module (GHC syslib)} +%* * +%************************************************************************ + +The type \tr{_PackedString} is built-in, i.e., no +special action (other than a \tr{-fglasgow-exts} flag) is required to +use it. + +The documentation here describes the {\em built-in} functions. + +You may also access this code as a system library and {\em not} use +the \tr{-fglasgow-exts} flag. Just do \tr{import PackedString}, +heave in your \tr{-syslib ghc}, and drop off the leading underscores +which you see here. + +We still may change this interface (again). + +The basic type and functions which are available are: +\begin{verbatim} +data _PackedString + +_packString :: [Char] -> _PackedString +_packStringST :: [Char] -> _ST s _PackedString +_packCString :: _Addr -> _PackedString +_packCBytes :: Int -> _Addr -> _PackedString +_packCBytesST :: Int -> _Addr -> _ST s _PackedString +_packBytesForC :: [Char] -> _ByteArray Int +_packBytesForCST :: [Char] -> _ST s (_ByteArray Int) +_byteArrayToPS :: _ByteArray Int -> _PackedString +_psToByteArray :: _PackedString -> _ByteArray Int + +_unpackPS :: _PackedString -> [Char] +\end{verbatim} + +We also provide a wad of list-manipulation-like functions: +\begin{verbatim} +_nilPS :: _PackedString +_consPS :: Char -> _PackedString -> _PackedString + +_headPS :: _PackedString -> Char +_tailPS :: _PackedString -> _PackedString +_nullPS :: _PackedString -> Bool +_appendPS :: _PackedString -> _PackedString -> _PackedString +_lengthPS :: _PackedString -> Int +_indexPS :: _PackedString -> Int -> Char + -- 0-origin indexing into the string +_mapPS :: (Char -> Char) -> _PackedString -> _PackedString {-or String?-} +_filterPS :: (Char -> Bool) -> _PackedString -> _PackedString {-or String?-} +_foldlPS :: (a -> Char -> a) -> a -> _PackedString -> a +_foldrPS :: (Char -> a -> a) -> a -> _PackedString -> a +_takePS :: Int -> _PackedString -> _PackedString +_dropPS :: Int -> _PackedString -> _PackedString +_splitAtPS :: Int -> _PackedString -> (_PackedString, _PackedString) +_takeWhilePS:: (Char -> Bool) -> _PackedString -> _PackedString +_dropWhilePS:: (Char -> Bool) -> _PackedString -> _PackedString +_spanPS :: (Char -> Bool) -> _PackedString -> (_PackedString, _PackedString) +_breakPS :: (Char -> Bool) -> _PackedString -> (_PackedString, _PackedString) +_linesPS :: _PackedString -> [_PackedString] +_wordsPS :: _PackedString -> [_PackedString] +_reversePS :: _PackedString -> _PackedString +_concatPS :: [_PackedString] -> _PackedString + +_substrPS :: _PackedString -> Int -> Int -> _PackedString + -- pluck out a piece of a _PS + -- start and end chars you want; both 0-origin-specified +\end{verbatim} + +%************************************************************************ +%* * +\subsubsection[Pretty]{The @Pretty@ type} +\index{Pretty module (GHC syslib)} +%* * +%************************************************************************ + +This is the pretty-printer that we use in GHC. + +\begin{verbatim} +type Pretty + +ppShow :: Int{-width-} -> Pretty -> [Char] + +pp'SP :: Pretty -- "comma space" +ppComma :: Pretty -- , +ppEquals :: Pretty -- = +ppLbrack :: Pretty -- [ +ppLparen :: Pretty -- ( +ppNil :: Pretty -- nothing +ppRparen :: Pretty -- ) +ppRbrack :: Pretty -- ] +ppSP :: Pretty -- space +ppSemi :: Pretty -- ; + +ppChar :: Char -> Pretty +ppDouble :: Double -> Pretty +ppFloat :: Float -> Pretty +ppInt :: Int -> Pretty +ppInteger :: Integer -> Pretty +ppRational :: Rational -> Pretty +ppStr :: [Char] -> Pretty + +ppAbove :: Pretty -> Pretty -> Pretty +ppAboves :: [Pretty] -> Pretty +ppBeside :: Pretty -> Pretty -> Pretty +ppBesides :: [Pretty] -> Pretty +ppCat :: [Pretty] -> Pretty +ppHang :: Pretty -> Int -> Pretty -> Pretty +ppInterleave :: Pretty -> [Pretty] -> Pretty -- spacing between +ppIntersperse :: Pretty -> [Pretty] -> Pretty -- no spacing between +ppNest :: Int -> Pretty -> Pretty +ppSep :: [Pretty] -> Pretty +\end{verbatim} + +%************************************************************************ +%* * +\subsubsection[Set]{The @Set@ type} +\index{Set module (GHC syslib)} +%* * +%************************************************************************ + +Our implementation of {\em sets} (key property: no duplicates) is just +a variant of the \tr{FiniteMap} module. + +\begin{verbatim} +mkSet :: Ord a => [a] -> Set a +setToList :: Set a -> [a] +emptySet :: Set a +singletonSet :: a -> Set a + +union :: Ord a => Set a -> Set a -> Set a +unionManySets :: Ord a => [Set a] -> Set a +intersect :: Ord a => Set a -> Set a -> Set a +minusSet :: Ord a => Set a -> Set a -> Set a +mapSet :: Ord a => (b -> a) -> Set b -> Set a + +elementOf :: Ord a => a -> Set a -> Bool +isEmptySet :: Set a -> Bool +\end{verbatim} + +%************************************************************************ +%* * +\subsubsection[Util]{The @Util@ type} +\index{Util module (GHC syslib)} +%* * +%************************************************************************ + +Stuff that has been useful to use in writing the compiler. Don't be +too surprised if this stuff moves/gets-renamed/etc. + +\begin{verbatim} +-- general list processing +forall :: (a -> Bool) -> [a] -> Bool +exists :: (a -> Bool) -> [a] -> Bool +zipEqual :: [a] -> [b] -> [(a,b)] +nOfThem :: Int -> a -> [a] +lengthExceeds :: [a] -> Int -> Bool +isSingleton :: [a] -> Bool + +-- association lists +assoc :: Eq a => String -> [(a, b)] -> a -> b + +-- duplicate handling +hasNoDups :: Eq a => [a] -> Bool +equivClasses :: (a -> a -> _CMP_TAG) -> [a] -> [[a]] +runs :: (a -> a -> Bool) -> [a] -> [[a]] +removeDups :: (a -> a -> _CMP_TAG) -> [a] -> ([a], [[a]]) + +-- sorting (don't complain of no choice...) +quicksort :: (a -> a -> Bool) -> [a] -> [a] +sortLt :: (a -> a -> Bool) -> [a] -> [a] +stableSortLt :: (a -> a -> Bool) -> [a] -> [a] +mergesort :: (a -> a -> _CMP_TAG) -> [a] -> [a] +mergeSort :: Ord a => [a] -> [a] +naturalMergeSort :: Ord a => [a] -> [a] +mergeSortLe :: Ord a => [a] -> [a] +naturalMergeSortLe :: Ord a => [a] -> [a] + +-- transitive closures +transitiveClosure :: (a -> [a]) -- Successor function + -> (a -> a -> Bool) -- Equality predicate + -> [a] + -> [a] -- The transitive closure + +-- accumulating (Left, Right, Bi-directional) +mapAccumL :: (acc -> x -> (acc, y)) + -- Function of elt of input list and + -- accumulator, returning new accumulator and + -- elt of result list + -> acc -- Initial accumulator + -> [x] -- Input list + -> (acc, [y]) -- Final accumulator and result list + +mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) + +mapAccumB :: (accl -> accr -> x -> (accl, accr,y)) + -> accl -> accr -> [x] + -> (accl, accr, [y]) + +-- comparisons +cmpString :: String -> String -> _CMP_TAG + +-- this type is built-in +data _CMP_TAG = _LT | _EQ | _GT + +-- pairs +applyToPair :: ((a -> c), (b -> d)) -> (a, b) -> (c, d) +applyToFst :: (a -> c) -> (a, b) -> (c, b) +applyToSnd :: (b -> d) -> (a, b) -> (a, d) +foldPair :: (a->a->a, b->b->b) -> (a, b) -> [(a, b)] -> (a, b) +unzipWith :: (a -> b -> c) -> [(a, b)] -> [c] +\end{verbatim} + +%************************************************************************ +%* * +\subsection[C-interfaces]{Interfaces to C libraries} +\index{C library interfaces} +\index{interfaces, C library} +%* * +%************************************************************************ + +The GHC system library (\tr{-syslib ghc}) also provides interfaces to +several useful C libraries, mostly from the GNU project. + +%************************************************************************ +%* * +\subsubsection[Readline]{The @Readline@ interface} +\index{Readline library (GHC syslib)} +\index{command-line editing library} +%* * +%************************************************************************ + +(Darren Moffat supplied the \tr{Readline} interface.) + +The \tr{Readline} module is a straightforward interface to the GNU +Readline library. As such, you will need to look at the GNU +documentation (and have a \tr{libreadline.a} file around somewhere...) + +You'll need to link any Readlining program with \tr{-lreadline -ltermcap}, +besides the usual \tr{-syslib ghc} (and \tr{-fhaskell-1.3}). + +The main function you'll use is: +\begin{verbatim} +readline :: String{-the prompt-} -> IO String +\end{verbatim} + +If you want to mess around with Full Readline G(l)ory, we also +provide: +\begin{verbatim} +rlInitialize, addHistory, + +rlBindKey, rlAddDefun, RlCallbackFunction(..), + +rlGetLineBuffer, rlSetLineBuffer, rlGetPoint, rlSetPoint, rlGetEnd, +rlSetEnd, rlGetMark, rlSetMark, rlSetDone, rlPendingInput, + +rlPrompt, rlTerminalName, rlSetReadlineName, rlGetReadlineName +\end{verbatim} +(All those names are just Haskellised versions of what you +will see in the GNU readline documentation.) + +%************************************************************************ +%* * +\subsubsection[Regexp]{The @Regexp@ and @MatchPS@ interfaces} +\index{Regex library (GHC syslib)} +\index{MatchPS library (GHC syslib)} +\index{regular-expressions library} +%* * +%************************************************************************ + +(Sigbjorn Finne supplied the regular-expressions interface.) + +The \tr{Regex} library provides quite direct interface to the GNU +regular-expression library, for doing manipulation on +\tr{_PackedString}s. You probably need to see the GNU documentation +if you are operating at this level. + +The datatypes and functions that \tr{Regex} provides are: +\begin{verbatim} +data PatBuffer # just a bunch of bytes (mutable) + +data REmatch + = REmatch (Array Int GroupBounds) -- for $1, ... $n + GroupBounds -- for $` (everything before match) + GroupBounds -- for $& (entire matched string) + GroupBounds -- for $' (everything after) + GroupBounds -- for $+ (matched by last bracket) + +-- GroupBounds hold the interval where a group +-- matched inside a string, e.g. +-- +-- matching "reg(exp)" "a regexp" returns the pair (5,7) for the +-- (exp) group. (_PackedString indices start from 0) + +type GroupBounds = (Int, Int) + +re_compile_pattern + :: _PackedString -- pattern to compile + -> Bool -- True <=> assume single-line mode + -> Bool -- True <=> case-insensitive + -> PrimIO PatBuffer + +re_match :: PatBuffer -- compiled regexp + -> _PackedString -- string to match + -> Int -- start position + -> Bool -- True <=> record results in registers + -> PrimIO (Maybe REmatch) + +-- Matching on 2 strings is useful when you're dealing with multiple +-- buffers, which is something that could prove useful for +-- PackedStrings, as we don't want to stuff the contents of a file +-- into one massive heap chunk, but load (smaller chunks) on demand. + +re_match2 :: PatBuffer -- 2-string version + -> _PackedString + -> _PackedString + -> Int + -> Int + -> Bool + -> PrimIO (Maybe REmatch) + +re_search :: PatBuffer -- compiled regexp + -> _PackedString -- string to search + -> Int -- start index + -> Int -- stop index + -> Bool -- True <=> record results in registers + -> PrimIO (Maybe REmatch) + +re_search2 :: PatBuffer -- Double buffer search + -> _PackedString + -> _PackedString + -> Int -- start index + -> Int -- range (?) + -> Int -- stop index + -> Bool -- True <=> results in registers + -> PrimIO (Maybe REmatch) +\end{verbatim} + +The \tr{MatchPS} module provides Perl-like ``higher-level'' facilities +to operate on \tr{_PackedStrings}. The regular expressions in +question are in Perl syntax. The ``flags'' on various functions can +include: \tr{i} for case-insensitive, \tr{s} for single-line mode, and +\tr{g} for global. (It's probably worth your time to peruse the +source code...) + +\begin{verbatim} +matchPS :: _PackedString -- regexp + -> _PackedString -- string to match + -> [Char] -- flags + -> Maybe REmatch -- info about what matched and where + +searchPS :: _PackedString -- regexp + -> _PackedString -- string to match + -> [Char] -- flags + -> Maybe REmatch + +-- Perl-like match-and-substitute: +substPS :: _PackedString -- regexp + -> _PackedString -- replacement + -> [Char] -- flags + -> _PackedString -- string + -> _PackedString + +-- same as substPS, but no prefix and suffix: +replacePS :: _PackedString -- regexp + -> _PackedString -- replacement + -> [Char] -- flags + -> _PackedString -- string + -> _PackedString + +match2PS :: _PackedString -- regexp + -> _PackedString -- string1 to match + -> _PackedString -- string2 to match + -> [Char] -- flags + -> Maybe REmatch + +search2PS :: _PackedString -- regexp + -> _PackedString -- string to match + -> _PackedString -- string to match + -> [Char] -- flags + -> Maybe REmatch + +-- functions to pull the matched pieces out of an REmatch: + +getMatchesNo :: REmatch -> Int +getMatchedGroup :: REmatch -> Int -> _PackedString -> _PackedString +getWholeMatch :: REmatch -> _PackedString -> _PackedString +getLastMatch :: REmatch -> _PackedString -> _PackedString +getAfterMatch :: REmatch -> _PackedString -> _PackedString + +-- (reverse) brute-force string matching; +-- Perl equivalent is index/rindex: +findPS, rfindPS :: _PackedString -> _PackedString -> Maybe Int + +-- Equivalent to Perl "chop" (off the last character, if any): +chopPS :: _PackedString -> _PackedString + +-- matchPrefixPS: tries to match as much as possible of strA starting +-- from the beginning of strB (handy when matching fancy literals in +-- parsers): +matchPrefixPS :: _PackedString -> _PackedString -> Int +\end{verbatim} + +%************************************************************************ +%* * +\subsubsection[Socket]{Network-interface toolkit---@Socket@ and @SocketPrim@} +\index{SocketPrim interface (GHC syslib)} +\index{Socket interface (GHC syslib)} +\index{network-interface library} +\index{sockets library} +\index{BSD sockets library} +%* * +%************************************************************************ + +(Darren Moffat supplied the network-interface toolkit.) + +Your best bet for documentation is to look at the code---really!--- +normally in \tr{ghc/lib/ghc/{BSD,Socket,SocketPrim}.lhs}. + +The \tr{BSD} module provides functions to get at system-database info; +pretty straightforward if you're into this sort of thing: +\begin{verbatim} +getHostName :: IO String + +getServiceByName :: ServiceName -> IO ServiceEntry +getServicePortNumber:: ServiceName -> IO PortNumber +getServiceEntry :: IO ServiceEntry +setServiceEntry :: Bool -> IO () +endServiceEntry :: IO () + +getProtocolByName :: ProtocolName -> IO ProtocolEntry +getProtocolByNumber :: ProtocolNumber -> IO ProtcolEntry +getProtocolNumber :: ProtocolName -> ProtocolNumber +getProtocolEntry :: IO ProtocolEntry +setProtocolEntry :: Bool -> IO () +endProtocolEntry :: IO () + +getHostByName :: HostName -> IO HostEntry +getHostByAddr :: Family -> HostAddress -> IO HostEntry +getHostEntry :: IO HostEntry +setHostEntry :: Bool -> IO () +endHostEntry :: IO () +\end{verbatim} + +The \tr{SocketPrim} interface provides quite direct access to the +socket facilities in a BSD Unix system, including all the +complications. We hope you don't need to use it! See the source if +needed... + +The \tr{Socket} interface is a ``higher-level'' interface to sockets, +and it is what we recommend. Please tell us if the facilities it +offers are inadequate to your task! + +The interface is relatively modest: +\begin{verbatim} +connectTo :: Hostname -> PortID -> IO Handle +listenOn :: PortID -> IO Socket + +accept :: Socket -> IO (Handle, HostName) +sendTo :: Hostname -> PortID -> String -> IO () + +recvFrom :: Hostname -> PortID -> IO String +socketPort :: Socket -> IO PortID + +data PortID -- PortID is a non-abstract type + = Service String -- Service Name eg "ftp" + | PortNumber Int -- User defined Port Number + | UnixSocket String -- Unix family socket in file system + +type Hostname = String +\end{verbatim} + +Various examples of networking Haskell code are provided in +\tr{ghc/misc/examples/}, notably the \tr{net???/Main.hs} programs. + +%************************************************************************ +%* * +\subsection[HBC-library]{The HBC system library} +\index{HBC system library} +\index{system library, HBC} +%* * +%************************************************************************ + +This documentation is stolen directly from the HBC distribution. The +modules that GHC does not support (because they require HBC-specific +extensions) are omitted. + +\begin{description} +\item[\tr{Either}:] +\index{Either module (HBC library)}% +A binary sum data type: +\begin{verbatim} +data Either a b = Left a | Right b +\end{verbatim} +The constructor \tr{Left} is typically used for errors; it can be +renamed to \tr{Wrong} on import. + +\item[\tr{Maybe}:] +\index{Maybe module (HBC library)}% +A type for failure or success: +\begin{verbatim} +data Maybe a = Nothing | Just a +thenM :: Maybe a -> (a -> Maybe b) -> Maybe b + -- apply a function that may fail +\end{verbatim} + +\item[\tr{Option}:] +\index{Option module (HBC library)}% +An alias for \tr{Maybe}: +\begin{verbatim} +data Option a = None | Some a +thenO :: Option a -> (a -> Option b) -> Option b +\end{verbatim} + +\item[\tr{ListUtil}:] +\index{ListUtil module (HBC library)}% +Various useful functions involving lists that are missing from the +\tr{Prelude}: +\begin{verbatim} +assoc :: (Eq c) => (a -> b) -> b -> [(c, a)] -> c -> b + -- assoc f d l k looks for k in the association list l, if it + -- is found f is applied to the value, otherwise d is returned. +concatMap :: (a -> [b]) -> [a] -> [b] + -- flattening map (LML's concmap) +unfoldr :: (a -> (b, a)) -> (a -> Bool) -> a -> [b] + -- unfoldr f p x repeatedly applies f to x until (p x) holds. + -- (f x) should give a list element and a new x. +mapAccuml :: (a -> b -> (a, c)) -> a -> [b] -> (a, [c]) + -- mapAccuml f s l maps f over l, but also threads the state s + -- through (LML's mapstate). +union :: (Eq a) => [a] -> [a] -> [a] + -- union of two lists +intersection :: (Eq a) => [a] -> [a] -> [a] + -- intersection of two lists +chopList :: ([a] -> (b, [a])) -> [a] -> [b] + -- LMLs choplist +assocDef :: (Eq a) => [(a, b)] -> b -> a -> b + -- LMLs assocdef +lookup :: (Eq a) => [(a, b)] -> a -> Option b + -- lookup l k looks for the key k in the association list l + -- and returns an optional value +tails :: [a] -> [[a]] + -- return all the tails of a list +rept :: (Integral a) => a -> b -> [b] + -- repeat a value a number of times +groupEq :: (a->a->Bool) -> [a] -> [[a]] + -- group list elements according to an equality predicate +group :: (Eq a) => [a] -> [[a]] + -- group according to} == +readListLazily :: (Text a) => String -> [a] + -- read a list in a lazy fashion +\end{verbatim} + +\item[\tr{Pretty}:] +\index{Pretty module (HBC library)}% +John Hughes's pretty printing library. +\begin{verbatim} +type Context = (Bool, Int, Int, Int) +type IText = Context -> [String] +text :: String -> IText -- just text +(~.) :: IText -> IText -> IText -- horizontal composition +(^.) :: IText -> IText -> IText -- vertical composition +separate :: [IText] -> IText -- separate by spaces +nest :: Int -> IText -> IText -- indent +pretty :: Int -> Int -> IText -> String -- format it +\end{verbatim} + +\item[\tr{QSort}:] +\index{QSort module (HBC library)}% +A sort function using quicksort. +\begin{verbatim} +sortLe :: (a -> a -> Bool) -> [a] -> [a] + -- sort le l sorts l with le as less than predicate +sort :: (Ord a) => [a] -> [a] + -- sort l sorts l using the Ord class +\end{verbatim} + +\item[\tr{Random}:] +\index{Random module (HBC library)}% +Random numbers. +\begin{verbatim} +randomInts :: Int -> Int -> [Int] + -- given two seeds gives a list of random Int +randomDoubles :: Int -> Int -> [Double] + -- random Double with uniform distribution in (0,1) +normalRandomDoubles :: Int -> Int -> [Double] + -- random Double with normal distribution, mean 0, variance 1 +\end{verbatim} + +\item[\tr{Trace}:] +Simple tracing. (Note: This comes with GHC anyway.) +\begin{verbatim} +trace :: String -> a -> a -- trace x y prints x and returns y +\end{verbatim} + +\item[\tr{Miranda}:] +\index{Miranda module (HBC library)}% +Functions found in the Miranda library. +(Note: Miranda is a registered trade mark of Research Software Ltd.) + +\item[\tr{Word}:] +\index{Word module (HBC library)} +Bit manipulation. (GHC doesn't implement absolutely all of this. +And don't count on @Word@ being 32 bits on a Alpha...) +\begin{verbatim} +class Bits a where + bitAnd :: a -> a -> a -- bitwise and + bitOr :: a -> a -> a -- bitwise or + bitXor :: a -> a -> a -- bitwise xor + bitCompl :: a -> a -- bitwise negation + bitRsh :: a -> Int -> a -- bitwise right shift + bitLsh :: a -> Int -> a -- bitwise left shift + bitSwap :: a -> a -- swap word halves + bit0 :: a -- word with least significant bit set + bitSize :: a -> Int -- number of bits in a word + +data Byte -- 8 bit quantity +data Short -- 16 bit quantity +data Word -- 32 bit quantity + +instance Bits Byte, Bits Short, Bits Word +instance Eq Byte, Eq Short, Eq Word +instance Ord Byte, Ord Short, Ord Word +instance Text Byte, Text Short, Text Word +instance Num Byte, Num Short, Num Word +wordToShorts :: Word -> [Short] -- convert a Word to two Short +wordToBytes :: Word -> [Byte] -- convert a Word to four Byte +bytesToString :: [Byte] -> String -- convert a list of Byte to a String (bit by bit) +wordToInt :: Word -> Int -- convert a Word to Int +shortToInt :: Short -> Int -- convert a Short to Int +byteToInt :: Byte -> Int -- convert a Byte to Int +\end{verbatim} + +\item[\tr{Time}:] +\index{Time module (HBC library)}% +Manipulate time values (a Double with seconds since 1970). +\begin{verbatim} +-- year mon day hour min sec dec-sec weekday +data Time = Time Int Int Int Int Int Int Double Int +dblToTime :: Double -> Time -- convert a Double to a Time +timeToDbl :: Time -> Double -- convert a Time to a Double +timeToString :: Time -> String -- convert a Time to a readable String +\end{verbatim} + +\item[\tr{Hash}:] +\index{Hash module (HBC library)}% +Hashing functions. +\begin{verbatim} +class Hashable a where + hash :: a -> Int -- hash a value, return an Int +-- instances for all Prelude types +hashToMax :: (Hashable a) => Int -> a -> Int -- hash into interval [0..x-1] +\end{verbatim} + +\item[\tr{NameSupply}:] +\index{NameSupply module (HBC library)}% +Functions to generate unique names (Int). +\begin{verbatim} +type Name = Int +initialNameSupply :: NameSupply + -- The initial name supply (may be different every + -- time the program is run. +splitNameSupply :: NameSupply -> (NameSupply,NameSupply) + -- split the namesupply into two +getName :: NameSupply -> Name + -- get the name associated with a name supply +\end{verbatim} + +\item[\tr{Parse}:] +\index{Parse module (HBC library)}% +Higher order functions to build parsers. With a little care these +combinators can be used to build efficient parsers with good error +messages. +\begin{verbatim} +infixr 8 +.+ , ..+ , +.. +infix 6 `act` , >>> , `into` , .> +infixr 4 ||| , ||! , |!! +data ParseResult a b +type Parser a b = a -> Int -> ParseResult a b +(|||) :: Parser a b -> Parser a b -> Parser a b + -- Alternative +(||!) :: Parser a b -> Parser a b -> Parser a b + -- Alternative, but with committed choice +(|!!) :: Parser a b -> Parser a b -> Parser a b + -- Alternative, but with committed choice +(+.+) :: Parser a b -> Parser a c -> Parser a (b,c) + -- Sequence +(..+) :: Parser a b -> Parser a c -> Parser a c + -- Sequence, throw away first part +(+..) :: Parser a b -> Parser a c -> Parser a b + -- Sequence, throw away second part +act :: Parser a b -> (b->c) -> Parser a c + -- Action +(>>>) :: Parser a (b,c) -> (b->c->d) -> Parser a d + -- Action on two items +(.>) :: Parser a b -> c -> Parse a c + -- Action ignoring value +into :: Parser a b -> (b -> Parser a c) -> Parser a c + -- Use a produced value in a parser. +succeed b :: Parser a b + -- Always succeeds without consuming a token +failP :: Parser a b + -- Always fails. +many :: Parser a b -> Parser a [b] + -- Kleene star +many1 :: Parser a b -> Parser a [b] + -- Kleene plus +count :: Parser a b -> Int -> Parser a [b] + -- Parse an exact number of items +sepBy1 :: Parser a b -> Parser a c -> Parser a [b] + -- Non-empty sequence of items separated by something +sepBy :: Parser a b -> Parser a c -> Parser a [b] + -- Sequence of items separated by something +lit :: (Eq a, Text a) => a -> Parser [a] a + -- Recognise a literal token from a list of tokens +litp :: String -> (a->Bool) -> Parser [a] a + -- Recognise a token with a predicate. + -- The string is a description for error messages. +testp :: String -> (a -> Bool) -> (Parser b a) -> Parser b a + -- Test a semantic value. +token :: (a -> Either String (b, a)) -> Parser a b + -- General token recogniser. +parse :: Parser a b -> a -> Either ([String], a) [(b, a)] + -- Do a parse. Return either error (possible tokens and rest + -- of tokens) or all possible parses. +sParse :: (Text a) => (Parser [a] b) -> [a] -> Either String b + -- Simple parse. Return error message or result. +\end{verbatim} + +%%%simpleLex :: String -> [String] -- A simple (but useful) lexical analyzer + +\item[\tr{Native}:] +\index{Native module (HBC library)}% +Functions to convert the primitive types \tr{Int}, \tr{Float}, and \tr{Double} to +their native representation as a list of bytes (\tr{Char}). If such a list +is read/written to a file it will have the same format as when, e.g., +C read/writes the same kind of data. +\begin{verbatim} +type Bytes = [Char] -- A byte stream is just a list of characters + +class Native a where + showBytes :: a -> Bytes -> Bytes + -- prepend the representation of an item the a byte stream + listShowBytes :: [a] -> Bytes -> Bytes + -- prepend the representation of a list of items to a stream + -- (may be more efficient than repeating showBytes). + readBytes :: Bytes -> Maybe (a, Bytes) + -- get an item from the stream and return the rest, + -- or fail if the stream is to short. + listReadBytes :: Int -> Bytes -> Maybe ([a], Bytes) + -- read n items from a stream. + +instance Native Int +instance Native Float +instance Native Double +instance (Native a, Native b) => Native (a,b) + -- juxtaposition of the two items +instance (Native a, Native b, Native c) => Native (a, b, c) + -- juxtaposition of the three items +instance (Native a) => Native [a] + -- an item count in an Int followed by the items + +shortIntToBytes :: Int -> Bytes -> Bytes + -- Convert an Int to what corresponds to a short in C. +bytesToShortInt :: Bytes -> Maybe (Int, Bytes) + -- Get a short from a byte stream and convert to an Int. + +showB :: (Native a) => a -> Bytes -- Simple interface to showBytes. +readB :: (Native a) => Bytes -> a -- Simple interface to readBytes. +\end{verbatim} + +\item[\tr{Number}:] +\index{Number module (HBC library)}% +Simple numbers that belong to all numeric classes and behave like +a naive user would expect (except that printing is still ugly). +(NB: GHC does not provide a magic way to use \tr{Numbers} everywhere, +but you should be able to do it with normal \tr{import}ing and +\tr{default}ing.) +\begin{verbatim} +data Number -- The type itself. +instance ... -- All reasonable instances. +isInteger :: Number -> Bool -- Test if a Number is an integer. +\end{verbatim} +\end{description} diff --git a/ghc/docs/users_guide/parallel.lit b/ghc/docs/users_guide/parallel.lit new file mode 100644 index 0000000000..335e8febcf --- /dev/null +++ b/ghc/docs/users_guide/parallel.lit @@ -0,0 +1,662 @@ +% both concurrent and parallel +%************************************************************************ +%* * +\section[concurrent-and-parallel]{Concurrent and Parallel Haskell} +\index{Concurrent Haskell} +\index{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 {\em 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. + +Simon Peyton Jones and Sigbjorn Finne have a paper available, +``Concurrent Haskell: preliminary version.'' +(draft available via \tr{ftp} +from \tr{ftp.dcs.gla.ac.uk/pub/glasgow-fp/drafts}). + +Parallel Haskell is about {\em speed}---spawning threads onto multiple +processors so that your program will run faster. The `threads' +are always {\em 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 new with GHC 0.26; it is more about ``research +fun'' than about ``speed.'' That will change. There is no paper about +Parallel Haskell. That will change, too. + +Some details about Concurrent and Parallel Haskell follow. + +%************************************************************************ +%* * +\subsection{Concurrent and Parallel Haskell---language features} +\index{Concurrent Haskell---features} +\index{Parallel Haskell---features} +%* * +%************************************************************************ + +%************************************************************************ +%* * +\subsubsection{Features specific to Concurrent Haskell} +%* * +%************************************************************************ + +%************************************************************************ +%* * +\subsubsubsection{The \tr{Concurrent} interface (recommended)} +\index{Concurrent interface} +%* * +%************************************************************************ + +GHC provides a \tr{Concurrent} module, a common interface to a +collection of useful concurrency abstractions, including those +mentioned in the ``concurrent paper''. + +Just put \tr{import Concurrent} into your modules, and away you go. +NB: intended for use with the \tr{-fhaskell-1.3} flag. + +To create a ``required thread'': + +\begin{verbatim} +forkIO :: IO a -> IO a +\end{verbatim} + +The \tr{Concurrent} interface also provides access to ``I-Vars'' +and ``M-Vars'', which are two flavours of {\em synchronising variables}. +\index{synchronising variables (Glasgow extension)} +\index{concurrency -- synchronising variables} + +\tr{_IVars}\index{_IVars (Glasgow extension)} 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 \tr{_IVar} results in a runtime +error. Interface: +\begin{verbatim} +type IVar a = _IVar a -- more convenient name + +newIVar :: IO (_IVar a) +readIVar :: _IVar a -> IO a +writeIVar :: _IVar a -> a -> IO () +\end{verbatim} + +\tr{_MVars}\index{_MVars (Glasgow extension)} are rendezvous points, +mostly for concurrent threads. They begin empty, and any attempt to +read an empty \tr{_MVar} blocks. When an \tr{_MVar} is written, a +single blocked thread may be freed. Reading an \tr{_MVar} toggles its +state from full back to empty. Therefore, any value written to an +\tr{_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: +\begin{verbatim} +type MVar a = _MVar a -- more convenient name + +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 +\end{verbatim} + +A {\em channel variable} (@CVar@) is a one-element channel, as +described in the paper: + +\begin{verbatim} +data CVar a +newCVar :: IO (CVar a) +putCVar :: CVar a -> a -> IO () +getCVar :: CVar a -> IO a +\end{verbatim} + +A @Channel@ is an unbounded channel: + +\begin{verbatim} +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] +\end{verbatim} + +General and quantity semaphores: + +\begin{verbatim} +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 () +\end{verbatim} + +Merging streams---binary and n-ary: + +\begin{verbatim} +mergeIO :: [a] -> [a] -> IO [a] +nmergeIO :: [[a]] -> IO [a] +\end{verbatim} + +A {\em Sample variable} (@SampleVar@) is slightly different from a +normal @_MVar@: +\begin{itemize} +\item Reading an empty @SampleVar@ causes the reader to block + (same as @takeMVar@ on empty @_MVar@). +\item Reading a filled @SampleVar@ empties it and returns value. + (same as @takeMVar@) +\item Writing to an empty @SampleVar@ fills it with a value, and +potentially, wakes up a blocked reader (same as for @putMVar@ on empty @_MVar@). +\item Writing to a filled @SampleVar@ overwrites the current value. + (different from @putMVar@ on full @_MVar@.) +\end{itemize} + +\begin{verbatim} +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 () +\end{verbatim} + +Finally, there are operations to delay a concurrent thread, and to +make one wait:\index{delay a concurrent thread} +\index{wait for a file descriptor} +\begin{verbatim} +threadDelay :: Int -> IO () -- delay rescheduling for N microseconds +threadWait :: Int -> IO () -- wait for input on specified file descriptor +\end{verbatim} + +%************************************************************************ +%* * +\subsubsection{Features specific to Parallel Haskell} +%* * +%************************************************************************ + +%************************************************************************ +%* * +\subsubsubsection{The \tr{Parallel} interface (recommended)} +\index{Parallel interface} +%* * +%************************************************************************ + +GHC provides two functions for controlling parallel execution, through +the \tr{Parallel} interface: +\begin{verbatim} +interface Parallel where +infixr 0 `par` +infixr 1 `seq` + +par :: a -> b -> b +seq :: a -> b -> b +\end{verbatim} + +The expression \tr{(x `par` y)} {\em sparks} the evaluation of \tr{x} +(to weak head normal form) and returns \tr{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 \tr{(x `seq` y)} evaluates \tr{x} to weak head normal +form and then returns \tr{y}. The \tr{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, \tr{nfib}: + +\begin{verbatim} +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) +\end{verbatim} + +For values of \tr{n} greater than 1, we use \tr{par} to spark a thread +to evaluate \tr{nfib (n-1)}, and then we use \tr{seq} to force the +parent thread to evaluate \tr{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 +\tr{seq} to ensure that the parent will evaluate \tr{n2} {\em before} +\tr{n1} in the expression \tr{(n1 + n2 + 1)}. It is not sufficient to +reorder the expression as \tr{(n2 + n1 + 1)}, because the compiler may +not generate code to evaluate the addends from left to right. + +%************************************************************************ +%* * +\subsubsubsection{Underlying functions and primitives} +\index{parallelism primitives} +\index{primitives for parallelism} +%* * +%************************************************************************ + +The functions \tr{par} and \tr{seq} are really just renamings: +\begin{verbatim} +par a b = _par_ a b +seq a b = _seq_ a b +\end{verbatim} + +The functions \tr{_par_} and \tr{_seq_} are built into GHC, and unfold +into uses of the \tr{par#} and \tr{seq#} primitives, respectively. If +you'd like to see this with your very own eyes, just run GHC with the +\tr{-ddump-simpl} option. (Anything for a good time...) + +You can use \tr{_par_} and \tr{_seq_} in Concurrent Haskell, though +I'm not sure why you would want to. + +%************************************************************************ +%* * +\subsubsection{Features common to Concurrent and Parallel Haskell} +%* * +%************************************************************************ + +Actually, you can use the \tr{`par`} and \tr{`seq`} combinators +(really for Parallel Haskell) in Concurrent Haskell as well. +But doing things like ``\tr{par} to \tr{forkIO} many required threads'' +counts as ``jumping out the 9th-floor window, just to see what happens.'' + +%************************************************************************ +%* * +\subsubsubsection{Scheduling policy for concurrent/parallel threads} +\index{Scheduling---concurrent/parallel} +\index{Concurrent/parallel scheduling} +%* * +%************************************************************************ + +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 +\tr{-C[<num>]}\index{-C<num> RTS option (concurrent, parallel)} RTS option). +However, a context switch doesn't really happen until the next heap +allocation. If you want extremely short time slices, the \tr{-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 \tr{-t<num>}\index{-t <num> RTS option (concurrent, parallel)} +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. + +%************************************************************************ +%* * +\subsection{How to use Concurrent and Parallel Haskell} +%* * +%************************************************************************ + +[You won't get far unless your GHC system was configured/built with +concurrency and/or parallelism enabled. (They require separate +library modules.) The relevant section of the installation guide says +how to do this.] + +%************************************************************************ +%* * +\subsubsection{Using Concurrent Haskell} +\index{Concurrent Haskell---use} +%* * +%************************************************************************ + +To compile a program as Concurrent Haskell, use the \tr{-concurrent} +option,\index{-concurrent option} both when compiling {\em and +linking}. You will probably need the \tr{-fglasgow-exts} option, too. + +Three RTS options are provided for modifying the behaviour of the +threaded runtime system. See the descriptions of \tr{-C[<us>]}, \tr{-q}, +and \tr{-t<num>} in \Sectionref{parallel-rts-opts}. + +%************************************************************************ +%* * +\subsubsubsection[concurrent-problems]{Potential problems with Concurrent Haskell} +\index{Concurrent Haskell problems} +\index{problems, Concurrent Haskell} +%* * +%************************************************************************ + +The main thread in a Concurrent Haskell program is given its own +private stack space, but all other threads are given stack space from +the heap. Stack space for the main thread can be +adjusted as usual with the \tr{-K} RTS +option,\index{-K RTS option (concurrent, parallel)} but if this +private stack space is exhausted, the main thread will switch to stack +segments in the heap, just like any other thread. Thus, problems +which would normally result in stack overflow in ``sequential Haskell'' +can be expected to result in heap overflow when using threads. + +The concurrent runtime system uses black holes as synchronisation +points for subexpressions which are shared among multiple threads. In +``sequential Haskell'', a black hole indicates a cyclic data +dependency, which is a fatal error. However, in concurrent execution, a +black hole may simply indicate that the desired expression is being +evaluated by another thread. Therefore, when a thread encounters a +black hole, it simply blocks and waits for the black hole to be +updated. Cyclic data dependencies will result in deadlock, and the +program will fail to terminate. + +Because the concurrent runtime system uses black holes as +synchronisation points, it is not possible to disable black-holing +with the \tr{-N} RTS option.\index{-N RTS option} Therefore, the use +of signal handlers (including timeouts) with the concurrent runtime +system can lead to problems if a thread attempts to enter a black hole +that was created by an abandoned computation. The use of signal +handlers in conjunction with threads is strongly discouraged. + + +%************************************************************************ +%* * +\subsubsection{Using Parallel Haskell} +\index{Parallel Haskell---use} +%* * +%************************************************************************ + +[You won't be able to execute parallel Haskell programs unless PVM3 +(Parallel Virtual Machine, version 3) is installed at your site.] + +To compile a Haskell program for parallel execution under PVM, use the +\tr{-parallel} option,\index{-parallel option} both when compiling +{\em and linking}. You will probably want to \tr{import Parallel} +into your Haskell modules. + +To run your parallel program, once PVM is going, just invoke it ``as +normal''. The main extra RTS option is \tr{-N<n>}, to say how many +PVM ``processors'' your program to run on. (For more details of +all relevant RTS options, please see \sectionref{parallel-rts-opts}.) + +In truth, running Parallel Haskell programs and getting information +out of them (e.g., activity profiles) is a battle with the vagaries of +PVM, detailed in the following sections. + +For example: the stdout and stderr from your parallel program run will +appear in a log file, called something like \tr{/tmp/pvml.NNN}. + +%************************************************************************ +%* * +\subsubsubsection{Dummy's guide to using PVM} +\index{PVM, how to use} +\index{Parallel Haskell---PVM use} +%* * +%************************************************************************ + +Before you can run a parallel program under PVM, you must set the +required environment variables (PVM's idea, not ours); something like, +probably in your \tr{.cshrc} or equivalent: +\begin{verbatim} +setenv PVM_ROOT /wherever/you/put/it +setenv PVM_ARCH `$PVM_ROOT/lib/pvmgetarch` +setenv PVM_DPATH $PVM_ROOT/lib/pvmd +\end{verbatim} + +Creating and/or controlling your ``parallel machine'' is a purely-PVM +business; nothing specific to Parallel Haskell. + +You use the \tr{pvm}\index{pvm command} command to start PVM on your +machine. You can then do various things to control/monitor your +``parallel machine;'' the most useful being: + +\begin{tabular}{ll} +\tr{Control-D} & exit \tr{pvm}, leaving it running \\ +\tr{halt} & kill off this ``parallel machine'' \& exit \\ +\tr{add <host>} & add \tr{<host>} as a processor \\ +\tr{delete <host>} & delete \tr{<host>} \\ +\tr{reset} & kill what's going, but leave PVM up \\ +\tr{conf} & list the current configuration \\ +\tr{ps} & report processes' status \\ +\tr{pstat <pid>} & status of a particular process \\ +\end{tabular} + +The PVM documentation can tell you much, much more about \tr{pvm}! + +%************************************************************************ +%* * +\subsubsection{Parallelism profiles} +\index{parallelism profiles} +\index{profiles, parallelism} +\index{visualisation tools} +%* * +%************************************************************************ + +With Parallel Haskell programs, we usually don't care about the +results---only with ``how parallel'' it was! We want pretty pictures. + +Parallelism profiles (\`a la \tr{hbcpp}) can be generated with the +\tr{-q}\index{-q RTS option (concurrent, parallel)} RTS option. The +per-processor profiling info is dumped into files {\em in your home +directory} named \tr{<program>.gr}. These are then munged into a +PostScript picture, which you can then display. For example, +to run your program \tr{a.out} on 8 processors, then view the +parallelism profile, do: + +\begin{verbatim} +% ./a.out +RTS -N8 -q +% cd # to home directory +% grs2gr *.???.gr # combine the 8 .gr files into one +% gr2ps -O temp.gr # cvt to .ps; output in temp.ps +% ghostview -seascape temp.ps # look at it! +\end{verbatim} + +The scripts for processing the parallelism profiles are distributed +in \tr{ghc/utils/parallel/}. + +%************************************************************************ +%* * +\subsubsection{Activity profiles} +\index{activity profiles} +\index{profiles, activity} +\index{visualisation tools} +%* * +%************************************************************************ + +You can also use the standard GHC ``cost-centre'' profiling to see how +much time each PVM ``processor'' spends + +No special compilation flags beyond \tr{-parallel} are required to get +this basic four-activity profile. Just use the \tr{-P} RTS option, +thusly: +\begin{verbatim} +./a.out +RTS -N7 -P # 7 processors +\end{verbatim} + +The above will create files named \tr{<something>.prof} and/or +\tr{<something>.time} {\em in your home directory}. You can +process the \tr{.time} files into PostScript using \tr{hp2ps}, +\index{hp2ps} +as described elsewhere in this guide. The only thing is: +because of the weird file names, you probably need to use +\tr{hp2ps} as a filter; so: +\begin{verbatim} +% hp2ps < fooo.001.time > temp.ps +\end{verbatim} + +%$$ The first line of the +%$$ \tr{.qp} file contains the name of the program executed, along with +%$$ any program arguments and thread-specific RTS options. The second +%$$ line contains the date and time of program execution. The third +%$$ and subsequent lines contain information about thread state transitions. +%$$ +%$$ The thread state transition lines have the following format: +%$$ \begin{verbatim} +%$$ time transition thread-id thread-name [thread-id thread-name] +%$$ \end{verbatim} +%$$ +%$$ The \tr{time} is the virtual time elapsed since the program started +%$$ execution, in milliseconds. The \tr{transition} is a two-letter code +%$$ indicating the ``from'' queue and the ``to'' queue, where each queue +%$$ is one of: +%$$ \begin{itemize} +%$$ \item[\tr{*}] Void: Thread creation or termination. +%$$ \item[\tr{G}] Green: Runnable (or actively running, with \tr{-qv}) threads. +%$$ \item[\tr{A}] Amber: Runnable threads (\tr{-qv} only). +%$$ \item[\tr{R}] Red: Blocked threads. +%$$ \end{itemize} +%$$ The \tr{thread-id} is a unique integer assigned to each thread. The +%$$ \tr{thread-name} is currently the address of the thread's root closure +%$$ (in hexadecimal). In the future, it will be the name of the function +%$$ associated with the root of the thread. +%$$ +%$$ The first \tr{(thread-id, thread-name)} pair identifies the thread +%$$ involved in the indicated transition. For \tr{RG} and \tr{RA} transitions +%$$ only, there is a second \tr{(thread-id, thread-name)} pair which identifies +%$$ the thread that released the blocked thread. +%$$ +%$$ Provided with the GHC distribution is a perl script, \tr{qp2pp}, which +%$$ will convert \tr{.qp} files to \tr{hbcpp}'s \tr{.pp} format, so that +%$$ you can use the \tr{hbcpp} profiling tools, such as \tr{pp2ps92}. The +%$$ \tr{.pp} format has undergone many changes, so the conversion script +%$$ is not compatible with earlier releases of \tr{hbcpp}. Note that GHC +%$$ and \tr{hbcpp} use different thread scheduling policies (in +%$$ particular, \tr{hbcpp} threads never move from the green queue to the +%$$ amber queue). For compatibility, the \tr{qp2pp} script eliminates the +%$$ GHC amber queue, so there is no point in using the verbose (\tr{-qv}) +%$$ option if you are only interested in using the \tr{hbcpp} profiling +%$$ tools. + +%************************************************************************ +%* * +\subsubsection[parallel-rts-opts]{RTS options for Concurrent/Parallel Haskell} +\index{RTS options, concurrent} +\index{RTS options, parallel} +\index{Concurrent Haskell---RTS options} +\index{Parallel Haskell---RTS options} +%* * +%************************************************************************ + +Besides the usual runtime system (RTS) options +(\sectionref{runtime-control}), there are a few options particularly +for concurrent/parallel execution. + +\begin{description} +\item[\tr{-N<N>}:] +\index{-N<N> RTS option (parallel)} +(PARALLEL ONLY) Use \tr{<N>} PVM processors to run this program; +the default is 2. + +\item[\tr{-C[<us>]}:] +\index{-C<us> RTS option} +Sets the context switch interval to \pl{<us>} microseconds. A context +switch will occur at the next heap allocation after the timer expires. +With \tr{-C0} or \tr{-C}, context switches will occur as often as +possible (at every heap allocation). By default, context switches +occur every 10 milliseconds. Note that many interval timers are only +capable of 10 millisecond granularity, so the default setting may be +the finest granularity possible, short of a context switch at every +heap allocation. + +\item[\tr{-q[v]}:] +\index{-q RTS option} +Produce a quasi-parallel profile of thread activity, in the file +\tr{<program>.qp}. In the style of \tr{hbcpp}, this profile records +the movement of threads between the green (runnable) and red (blocked) +queues. If you specify the verbose suboption (\tr{-qv}), the green +queue is split into green (for the currently running thread only) and +amber (for other runnable threads). We do not recommend that you use +the verbose suboption if you are planning to use the \tr{hbcpp} +profiling tools or if you are context switching at every heap check +(with \tr{-C}). + +\item[\tr{-t<num>}:] +\index{-t<num> RTS option} +Limit the number of concurrent threads per processor to \pl{<num>}. +The default is 32. Each thread requires slightly over 1K {\em words} +in the heap for thread state and stack objects. (For 32-bit machines, +this translates to 4K bytes, and for 64-bit machines, 8K bytes.) + +\item[\tr{-d}:] +\index{-d RTS option (parallel)} +(PARALLEL ONLY) Turn on debugging. It pops up one xterm (or GDB, or +something...) per PVM processor. We use the standard \tr{debugger} +script that comes with PVM3, but we sometimes meddle with the +\tr{debugger2} script. We include ours in the GHC distribution, +in \tr{ghc/utils/pvm/}. +\end{description} + +%************************************************************************ +%* * +\subsubsubsection[parallel-problems]{Potential problems with Parallel Haskell} +\index{Parallel Haskell---problems} +\index{problems, Parallel Haskell} +%* * +%************************************************************************ + +The ``Potential problems'' for Concurrent Haskell also apply for +Parallel Haskell. Please see \Sectionref{concurrent-problems}. + +%$$ \subsubsubsection[par-notes]{notes for 0.26} +%$$ +%$$ \begin{verbatim} +%$$ Install PVM somewhere, as it says. We use 3.3 +%$$ +%$$ pvm.h : can do w/ a link from ghc/includes to its true home (???) +%$$ +%$$ +%$$ ghc -gum ... => a.out +%$$ +%$$ a.out goes to $PVM_ROOT/bin/$PVM_ARCH/$PE +%$$ +%$$ (profiling outputs go to ~/$PE.<process-num>.<suffix>) +%$$ +%$$ trinder scripts in: ~trinder/bin/any/instPHIL +%$$ +%$$ To run: +%$$ +%$$ Then: +%$$ SysMan [-] N (PEs) args-to-program... +%$$ +%$$ - ==> debug mode +%$$ mattson setup: GDB window per task +%$$ /local/grasp_tmp5/mattson/pvm3/lib/debugger{,2} +%$$ +%$$ to set breakpoint, etc, before "run", just modify debugger2 +%$$ +%$$ stderr and stdout are directed to /tmp/pvml.NNN +%$$ +%$$ Visualisation stuff (normal _mp build): +%$$ +%$$ +RTS -q gransim-like profiling +%$$ (should use exactly-gransim RTS options) +%$$ -qb binary dumps : not tried, not recommended: hosed! +%$$ +%$$ ascii dump : same info as gransim, one extra line at top w/ +%$$ start time; all times are ms since then +%$$ +%$$ dumps appear in $HOME/<program>.nnn.gr +%$$ +%$$ ~mattson/grs2gr.pl == combine lots into one (fixing times) +%$$ +%$$ /local/grasp/hwloidl/GrAn/bin/ is where scripts are. +%$$ +%$$ gr2ps == activity profile (bash script) +%$$ +%$$ ~mattson/bin/`arch`/gr2qp must be picked up prior to hwloidl's for +%$$ things to work... +%$$ +%$$ +RTS -[Pp] (parallel) 4-cost-centre "profiling" (gc,MAIN,msg,idle) +%$$ +%$$ ToDos: time-profiles from hp2ps: something about zeroth sample; +%$$ \end{verbatim} diff --git a/ghc/docs/users_guide/prof-compiler-options.lit b/ghc/docs/users_guide/prof-compiler-options.lit new file mode 100644 index 0000000000..21d8ca6965 --- /dev/null +++ b/ghc/docs/users_guide/prof-compiler-options.lit @@ -0,0 +1,84 @@ +% +% Included by prof-options.lit and how_to_run.lit +% + +To make use of the cost centre profiling system {\em all} modules must +be compiled and linked with the \tr{-prof} option.\index{-prof option} +Any \tr{_scc_} constructs you've put in your source will spring to life. + +Without a \tr{-prof} option, your \tr{_scc_}s are ignored; so you can +compiled \tr{_scc_}-laden code without changing it. + +There are a few other profiling-related compilation options. Use them +{\em in addition to} \tr{-prof}. These do not have to be used +consistently for all modules in a program. + +\begin{description} +\item[\tr{-auto}:] +\index{-auto option} +GHC will automatically add \tr{_scc_} constructs for +all top-level, exported functions. + +\item[\tr{-auto-all}:] +\index{-auto-all option} +{\em All} top-level functions, exported or not, will be automatically +\tr{_scc_}'d. + +% secret! +%\item[\tr{-caf-all}:] +%\index{-caf-all option} +%The costs of all CAFs in a module are usually attributed to one +%``big'' CAF cost-centre. With this option, all CAFs get their own cost-centre. + +%\item[\tr{-dict-all}:] +%\index{-dict-all option} +%Similarly, this option means that all ``dictionaries'' (internal +%constructs to support Haskell overloading) should get their own +%cost-centre. (Again, the costs are usually attributed to one ``big'' +%DICT cost-centre.) +% +%Incidentally, something is probably Bad Wrong (i.e., a GHC bug) if you +%see big costs attributed to dictionaries. + +\item[\tr{-ignore-scc}:] +\index{-ignore-scc option} +Ignore any \tr{_scc_} constructs, +so a module which already has \tr{_scc_}s can be +compiled for profiling with the annotations ignored. + +\item[\tr{-G<group>}:] +\index{-G<group> option} +Specifies the \pl{<group>} to be attached to all the cost-centres +declared in the module. If no group is specified it defaults to the +module name. +\end{description} + +%Alternative profiling semantics have also been implemented. To use +%these the runtime system and prelude libraries must have been built +%for the alternative profiling setup. This is done using a particular +%UserWay setup. If your system has this been built for this profiling +%system the alternative profiling system will normally be invoked using +%the options: +%\begin{description} +%\item[\tr{-lex}:] +%\index{-eval option} +%for lexical profiling. +%\item[\tr{-eval}:] +%\index{-eval option} +%for evaluation profiling. +%\end{description} +%All modules must be consistently compiled with the \tr{-lex} or +%\tr{-eval} option instead of the \tr{-prof} option. The other +%profiling options are still applicable. +% +%Finally we note that the options which dump the program source during +%compilation may be useful to determine exactly what code is being +%profiled. Useful options are: +%\begin{description} +%\item[\tr{-ddump-ds}:] dump after desugaring. Any automatic \tr{_scc_} +%annotations will have been added. +%\item[\tr{-ddump-simpl}:] dump after simplification. +%\item[\tr{-ddump-stg}:] dump the STG-code immediately before code +%generation. +%\end{description} + diff --git a/ghc/docs/users_guide/prof-options.lit b/ghc/docs/users_guide/prof-options.lit new file mode 100644 index 0000000000..afee1b901c --- /dev/null +++ b/ghc/docs/users_guide/prof-options.lit @@ -0,0 +1,30 @@ +%************************************************************************ +%* * +\subsection[prof-compiler-options]{Compiling programs for profiling} +\index{profiling options} +\index{options, for profiling} +%* * +%************************************************************************ + +\input{prof-compiler-options.lit} + +%************************************************************************ +%* * +\subsection[prof-rts-options]{Controlling the profiler at runtime} +\index{profiling RTS options} +\index{RTS options, for profiling} +%* * +%************************************************************************ + +\input{prof-rts-options.lit} + +%************************************************************************ +%* * +\subsection[prof-graphs]{Producing graphical heap profiles} +\index{heap profiles, producing} +%* * +%************************************************************************ + +\input{prof-post-processors.lit} + + diff --git a/ghc/docs/users_guide/prof-post-processors.lit b/ghc/docs/users_guide/prof-post-processors.lit new file mode 100644 index 0000000000..c704d2909b --- /dev/null +++ b/ghc/docs/users_guide/prof-post-processors.lit @@ -0,0 +1,130 @@ +% +% Included by prof-options.lit +% + +Utility programs which produce graphical profiles. + +\subsubsection[hp2ps]{\tr{hp2ps}--heap profile to PostScript} +\index{hp2ps (utility)} +\index{heap profiles} +\index{PostScript, from heap profiles} + +%\vspace{2ex} +%\begin{quote} +USAGE: \tr{hp2ps} [flags] [\pl{<file>}[\tr{.stat}]] +%\end{quote} + +The program \tr{hp2ps}\index{hp2ps} converts a heap profile as +produced by the \tr{-h<break-down>}\index{-h<break-down> RTS option} +runtime option into a PostScript graph of the heap profile. By +convention, the file to be processed by \tr{hp2ps} has a \tr{.hp} +extension. The PostScript output is written to \pl{<file>}\tr{.ps}. If +\pl{<file>} is omitted entirely, then the program behaves as a filter. + +\tr{hp2ps} is distributed in \tr{ghc/utils/hp2ps}. It was originally +developed by Dave Wakeling as part of the HBC/LML heap +profiler. + + +The flags are: +\begin{description} +\item[\tr{-d}] +In order to make graphs more readable, \tr{hp2ps} sorts the shaded +bands for each identifier. The default sort ordering is for the bands +with the largest area to be stacked on top of the smaller ones. The +\tr{-d} option causes rougher bands (those representing series of +values with the largest standard deviations) to be stacked on top of +smoother ones. + +\item[\tr{-b}] +Normally, \tr{hp2ps} puts the title of the graph in a small box at the +top of the page. However, if the JOB string is too long to fit in a +small box (more than 35 characters), then +\tr{hp2ps} will choose to use a big box instead. The \tr{-b} +option forces \tr{hp2ps} to use a big box. + +\item[\tr{-e<float>[in|mm|pt]}] +Generate encapsulated PostScript suitable for inclusion in LaTeX +documents. Usually, the PostScript graph is drawn in landscape mode +in an area 9 inches wide by 6 inches high, and \tr{hp2ps} arranges +for this area to be approximately centred on a sheet of a4 paper. +This format is convenient of studying the graph in detail, but it is +unsuitable for inclusion in LaTeX documents. The \tr{-e} option +causes the graph to be drawn in portrait mode, with float specifying +the width in inches, millimetres or points (the default). The +resulting PostScript file conforms to the Encapsulated PostScript +(EPS) convention, and it can be included in a LaTeX document using +Rokicki's dvi-to-PostScript converter \tr{dvips}. + +\item[\tr{-g}] +Create output suitable for the \tr{gs} PostScript previewer (or +similar). In this case the graph is printed in portrait mode without +scaling. The output is unsuitable for a laser printer. + +\item[\tr{-l}] +Normally a profile is limited to 20 bands with additional identifiers +being grouped into an \tr{OTHER} band. The \tr{-l} flag removes this +20 band and limit, producing as many bands as necessary. No key is +produced as it won't fit!. It is useful for creation time profiles +with many bands. + +\item[\tr{-m<int>}] +Normally a profile is limited to 20 bands with additional identifiers +being grouped into an \tr{OTHER} band. The \tr{-m} flag specifies an +alternative band limit (the maximum is 20). + +\tr{-m0} requests the band limit to be removed. As many bands as +necessary are produced. However no key is produced as it won't fit! It +is useful for displaying creation time profiles with many bands. + +\item[\tr{-p}] +Use previous parameters. By default, the PostScript graph is +automatically scaled both horizontally and vertically so that it fills +the page. However, when preparing a series of graphs for use in a +presentation, it is often useful to draw a new graph using the same +scale, shading and ordering as a previous one. The \tr{-p} flag causes +the graph to be drawn using the parameters determined by a previous +run of \tr{hp2ps} on \pl{file}. These are extracted from +\pl{file}\tr{.aux}. + +\item[\tr{-s}] Use a small box for the title. + +\item[\tr{-t<float>}] +Normally trace elements which sum to a total of less than 1\% of the +profile are removed from the profile. The \tr{-t} option allows this +percentage to be modified (maximum 5\%). + +\tr{-t0} requests no trace elements to be removed from the profile, +ensuring that all the data will be displayed. + +\item[\tr{-?}] Print out usage information. +\end{description} + +\subsubsection[stat2resid]{\tr{stat2resid}---residency info from GC stats} +\index{stat2resid (utility)} +\index{GC stats---residency info} +\index{residency, from GC stats} + +%\vspace{2ex} +%\begin{quote} +USAGE: \tr{stat2resid} [\pl{<file>}[\tr{.stat}] [\pl{<outfile>}]] +%\end{quote} + +The program \tr{stat2resid}\index{stat2resid} converts a detailed +garbage collection statistics file produced by the +\tr{-S}\index{-S RTS option} runtime option into a PostScript heap +residency graph. The garbage collection statistics file can be +produced without compiling your program for profiling. + +By convention, the file to be processed by \tr{stat2resid} has a +\tr{.stat} extension. If the \pl{<outfile>} is not specified the +PostScript will be written to \pl{<file>}\tr{.resid.ps}. If +\pl{<file>} is omitted entirely, then the program behaves as a filter. + +The plot can not be produced from the statistics file for a +generational collector, though a suitable stats file can be produced +using the \tr{-F2s}\index{-F2s RTS option} runtime option when the +program has been compiled for generational garbage collection (the +default). + +\tr{stat2resid} is distributed in \tr{ghc/utils/stat2resid}. diff --git a/ghc/docs/users_guide/prof-reports.lit b/ghc/docs/users_guide/prof-reports.lit new file mode 100644 index 0000000000..fd0abfb104 --- /dev/null +++ b/ghc/docs/users_guide/prof-reports.lit @@ -0,0 +1 @@ +What the bits of a profiling report mean. diff --git a/ghc/docs/users_guide/prof-rts-options.lit b/ghc/docs/users_guide/prof-rts-options.lit new file mode 100644 index 0000000000..022d4e3172 --- /dev/null +++ b/ghc/docs/users_guide/prof-rts-options.lit @@ -0,0 +1,120 @@ +% +% Included by prof-options.lit and runtime_control.lit +% + +It isn't enough to compile your program for profiling with \tr{-prof}! + +When you {\em run} your profiled program, you must tell the runtime system (RTS) +what you want to profile (e.g., time and/or space), and how you wish +the collected data to be reported. You also may wish to set the +sampling interval used in time profiling. + +Executive summary: \tr{./a.out +RTS -p} produces a time profile in +\tr{a.out.prof}; \tr{./a.out +RTS -hC} produces space-profiling +info which can be mangled by \tr{hp2ps} and viewed with \tr{ghostview} +(or equivalent). + +Profiling runtime flags are passed to your program between the usual +\tr{+RTS} and \tr{-RTS} options. + +\begin{description} +\item[\tr{-p<sort>} or \tr{-P<sort>}:] +\index{-p<sort> RTS option (profiling)} +\index{-P<sort> RTS option (profiling)} +\index{time profile} +\index{serial time profile} +The \tr{-p} option produces a standard {\em time profile} report. +It is written into the file \pl{<program>}\tr{.prof}. + +The \tr{-P} option produces a more detailed report containing the +actual time and allocation data as well. (Not used much.) + +The \tr{-P} option also produces {\em serial time-profiling} +information, in the file \pl{<program>}\tr{.time}. This can be +converted into a (somewhat unsatisfactory) PostScript graph using +\tr{hp2ps} (see \Sectionref{hp2ps}). + +???? -F2s needed for serial time profile??? ToDo + +The \pl{<sort>} indicates how the cost centres are to be sorted in the +report. Valid \pl{<sort>} options are: +\begin{description} +\item[\tr{T}:] by time, largest first (the default); +\item[\tr{A}:] by bytes allocated, largest first; +\item[\tr{C}:] alphabetically by group, module and cost centre. +\end{description} + +\item[\tr{-i<secs>}:] +\index{-i<secs> RTS option (profiling)} +Set the profiling (sampling) interval to \tr{<secs>} seconds (the +default is 1~second). + +\item[\tr{-h<break-down>}:] +\index{-h<break-down> RTS option (profiling)} +\index{heap profile} +Produce a detailed {\em space profile} of the heap occupied by live +closures. The profile is written to the file \pl{<program>}\tr{.hp} +from which a PostScript graph can be produced using \tr{hp2ps} (see +\Sectionref{hp2ps}). + +The heap space profile may be broken down by different criteria: +\begin{description} +\item[\tr{-hC}:] cost centre which produced the closure (the default). +\item[\tr{-hM}:] cost centre module which produced the closure. +\item[\tr{-hG}:] cost centre group which produced the closure. +\item[\tr{-hD}:] closure description --- a string describing the closure. +\item[\tr{-hY}:] closure type --- a string describing the closure's type. +\item[\tr{-hT<ints>,<start>}:] the time interval the closure was +created. \tr{<ints>} specifies the no. of interval bands plotted +(default 18) and \tr{<start>} the number of seconds after which the +reported intervals start (default 0.0). +\end{description} +By default all live closures in the heap are profiled, but particular +closures of interest can be selected (see below). +\end{description} + + +Heap (space) profiling uses hash tables. If these tables +should fill the run will abort. The +\tr{-z<tbl><size>}\index{-z<tbl><size> RTS option (profiling)} option is used to +increase the size of the relevant hash table (\tr{C}, \tr{M}, +\tr{G}, \tr{D} or \tr{Y}, defined as for \pl{<break-down>} above). The +actual size used is the next largest power of 2. + +The heap profile can be restricted to particular closures of interest. +The closures of interest can selected by the attached cost centre +(module:label, module and group), closure category (description, type, +and kind) and closure age using the following options: +\begin{description} +\item[\tr{-c{<mod>:<lab>,<mod>:<lab>...}}:] +\index{-c{<lab>} RTS option (profiling)} +Selects individual cost centre(s). +\item[\tr{-m{<mod>,<mod>...}}:] +\index{-m{<mod>} RTS option (profiling)} +Selects all cost centres from the module(s) specified. +\item[\tr{-g{<grp>,<grp>...}}:] +\index{-g{<grp>} RTS option (profiling)} +Selects all cost centres from the groups(s) specified. +\item[\tr{-d{<des>,<des>...}}:] +\index{-d{<des>} RTS option (profiling)} +Selects closures which have one of the specified descriptions. +\item[\tr{-y{<typ>,<typ>...}}:] +\index{-y{<typ>} RTS option (profiling)} +Selects closures which have one of the specified type descriptions. +\item[\tr{-k{<knd>,<knd>...}}:] +\index{-k{<knd>} RTS option (profiling)} +Selects closures which are of one of the specified closure kinds. +Valid closure kinds are \tr{CON} (constructor), \tr{FN} (manifest +function), \tr{PAP} (partial application), \tr{BH} (black hole) and +\tr{THK} (thunk). +\item[\tr{-a<age>}:] +\index{-a<age> RTS option (profiling)} +Selects closures which have survived \pl{<age>} complete intervals. +\end{description} +The space occupied by a closure will be reported in the heap profile +if the closure satisfies the following logical expression: +\begin{display} +([-c] or [-m] or [-g]) and ([-d] or [-y] or [-k]) and [-a] +\end{display} +where a particular option is true if the closure (or its attached cost +centre) is selected by the option (or the option is not specified). diff --git a/ghc/docs/users_guide/profiling.lit b/ghc/docs/users_guide/profiling.lit new file mode 100644 index 0000000000..e98cdb5093 --- /dev/null +++ b/ghc/docs/users_guide/profiling.lit @@ -0,0 +1,239 @@ +\begin{onlystandalone} +\documentstyle[11pt,literate]{article} +\begin{document} +\title{The Glorious Haskell Compilation System\\ Profiling Guide} +\author{The AQUA Team (Patrick M. Sansom)\\ +Department of Computing Science\\ +University of Glasgow\\ +Glasgow, Scotland\\ +G12 8QQ\\ +\\ +Email: glasgow-haskell-\{bugs,request\}\@dcs.glasgow.ac.uk} +\maketitle +\begin{rawlatex} +\tableofcontents +\end{rawlatex} +\end{onlystandalone} + +\section[profiling]{Profiling Haskell programs} +\index{profiling, with cost-centres} +\index{cost-centre profiling} + +Glasgow Haskell comes with a time and space profiling system. Its +purpose is to help you improve your understanding of your program's +execution behaviour, so you can improve it. + +%This profiling system is still under development. +%Please e-mail reports of any bugs you discover to +%\tr{glasgow-haskell-bugs@dcs.glasgow.ac.uk}. + +Any comments, suggestions and/or improvements you have to are welcome. +Recommended ``profiling tricks'' would be especially cool! + +\subsection[profiling-intro]{How to profile a Haskell program} + +The GHC approach to profiling is very simple: annotate the expressions +you consider ``interesting'' with {\em cost centre} labels (strings); +so, for example, you might have: + +\begin{verbatim} +f x y + = let + output1 = _scc_ "Pass1" ( pass1 x ) + output2 = _scc_ "Pass2" ( pass2 output1 y ) + output3 = _scc_ "Pass3" ( pass3 (output2 `zip` [1 .. ]) ) + in concat output3 +\end{verbatim} + +The costs of the evaluating the expressions bound to \tr{output1}, +\tr{output2} and \tr{output3} will be attributed to the ``cost +centres'' \tr{Pass1}, \tr{Pass2} and \tr{Pass3}, respectively. + +The costs of evaluating other expressions, e.g., \tr{concat output4}, +will be inherited by the scope which referenced the function \tr{f}. + +You can put in cost-centres via \tr{_scc_} constructs by hand, as in +the example above. Perfectly cool. That's probably what you {\em +would} do if your program divided into obvious ``passes'' or +``phases'', or whatever. + +If your program is large or you have no clue what might be gobbling +all the time, you can get GHC to mark all functions with \tr{_scc_} +constructs, automagically. Add an \tr{-auto} compilation flag to the +usual \tr{-prof} option. + +Once you start homing in on the Guilty Suspects, you may well switch +from automagically-inserted cost-centres to a few well-chosen ones of +your own. + +To use profiling, you must {\em compile} and {\em run} with special +options. (We usually forget the ``run'' magic!---Do as we say, not as +we do...) Details follow. + +If you're serious about this profiling game, you should probably read +one or more of the Sansom/Peyton Jones papers about the GHC profiling +system. Just visit the Glasgow FP Web page... + +%************************************************************************ +%* * +\subsection[prof-compiler-options]{Compiling programs for profiling} +\index{profiling options} +\index{options, for profiling} +%* * +%************************************************************************ + +\input{prof-compiler-options.lit} + +%************************************************************************ +%* * +\subsection[prof-rts-options]{How to control your profiled program at runtime} +\index{profiling RTS options} +\index{RTS options, for profiling} +%* * +%************************************************************************ + +\input{prof-rts-options.lit} + +%************************************************************************ +%* * +\subsection[prof-graphs]{Producing graphical heap profiles} +\index{heap profiles, producing} +%* * +%************************************************************************ + +\input{prof-post-processors.lit} + +% \subsection[cost-centres]{Profiling by Cost Centres} +% +% Problems with lazy evaluation +% +% The central idea is to identify particular source code expressions of +% interest. These expressions are annotated with a {\em cost +% centre}\index{cost centre} label. Execution and allocation costs are +% attributed to the cost centre label which encloses the expression +% incurring the costs. +% +% Simple example +% +% (Note: the paper in \tr{ghc/docs/papers/profiling.ps} may have some +% decent examples...) +% +% Costs are attribution to one cost centre. +% Inheritance of un-profiled costs. +% +% Degree of evaluation +% Unevaluated arguments +% Optimisation and transformation +% Evaluation of instances +% escaping functions: evaluation vs lexical +% +% \subsection[prof-annotations]{Annotating your Haskell source} +% +% Explicit annotations +% Automatic annotation +% +% \subsection[prof-information]{Profiling information} +% +% Cost Centre Label,Module,Group +% Example time/alloc profile +% +% Description of heap profile +% Closure Description, Type and Kind +% \subsection[limitations]{Limitations of the current profiling system} +% +% There are a number of limitations and shortcomings of the current +% profiling system. Any comments on the impact of these and any +% suggested improvements would be greatly appreciated. +% +% \begin{onlylatex} +% \subsubsection*{Explicit \tr{_scc_} annotations} +% \end{onlylatex} +% \begin{onlyinfo} +% Explicit \tr{_scc_} annotations: +% \end{onlyinfo} +% +% The explicit \tr{_scc_} source annotations cannot annotate entire +% function declarations as the clauses, pattern matching are not part of +% the expression syntax --- they are syntactic sugar. It is possible to +% remove the syntactic sugar by hand, translating to a simple +% declaration with case expressions on the rhs, but this is very +% tiresome. +% +% We propose to introduce an additional annotation to enable a \tr{_scc_} +% annotation to be placed around an entire declaration. +% +% To further ease the explicit annotation process we also propose to +% provide annotations which instruct the compiler to annotate all the +% declarations in a particular \tr{let} or \tr{where} clause with the +% name of the declaration. +% +% Other annotation schemes are feasible. Any suggestions / requests? +% +% +% \begin{onlylatex} +% \subsubsection*{Closure descriptions} +% \end{onlylatex} +% \begin{onlyinfo} +% Closure descriptions: +% \end{onlyinfo} +% +% The closure descriptions are by no means perfect ... +% +% The descriptions for expressions are somewhat tedious as they reflect +% some of the structure of the transformed STG code. This is largely to +% provide additional information so use of the STG code can be made if +% required (use the compiler option \tr{-ddump-stg}). This may be +% removed if the name of the \pl{corner} is considered sufficient. +% +% Local bindings introduced by the compiler have a name \tr{?<tag>}. +% Most of these are not related to the source in any meaningful way. For +% example, the \tr{?stg} names are introduced during the CoreToStg pass. +% Some other arbitrary compiler introduced names are: \tr{?ds}, +% \tr{?tpl}, \tr{?si}, \tr{?cs}, \tr{?ll}, and \tr{?sat}. Please let us +% know if any of these turn out to be a problem. We could introduce a +% more meaningful naming scheme into the compiler which assigns names +% that reflect the nearest enclosing source binding. Another possibility +% is to add the unique identifier so they aren't all clumped together as +% one indistinguishable description. +% +% There is only one closure description and type for all black holes, +% ``BH''. It might be useful to record the closure that is currently +% being evaluated as part of the black hole description. +% +% Similarly there is only one partial application description, ``PAP''. +% It might be useful to record the function being applied in the partial +% application as part of the partial application description. +% +% +% \begin{onlylatex} +% \subsubsection*{Garbage collection and paging} +% \end{onlylatex} +% \begin{onlyinfo} +% Garbage collection and paging: +% \end{onlyinfo} +% +% Currently the profiling implementation requires the two-space +% (\tr{-gc-2s}) garbage collector to be used. When using the \tr{-prof} +% options a particular garbage collector should not be specified. This +% imposes particular paging characteristics which may be different from +% the garbage collector your program normally uses. These paging +% characteristics may distort the user time profiling results, though we +% do not believe this is a significant problem. +% +% +% \subsection[references]{Papers describing this work} +% +% A discussion of our initial ideas are described in the paper +% ``Profiling Lazy Functional Languages'' by Patrick Sansom and Simon +% Peyton Jones. +% +% It is in the GHC distribution in \tr{ghc/docs/papers/profiling.ps}, +% or it can be retrieved using ftp from +% \tr{ftp.dcs.glasgow.ac.uk} (\tr{[130.209.240.50]}) +% in the file +% \tr{pub/glasgow-fp/papers/lazy-profiling.ps}. + +\begin{onlystandalone} +\printindex +\end{document} +\end{onlystandalone} diff --git a/ghc/docs/users_guide/runtime_control.lit b/ghc/docs/users_guide/runtime_control.lit new file mode 100644 index 0000000000..db7c4fdc17 --- /dev/null +++ b/ghc/docs/users_guide/runtime_control.lit @@ -0,0 +1,332 @@ +%************************************************************************ +%* * +\section[runtime-control]{Controlling the run-time behaviour of your programs} +\index{runtime control of Haskell programs} +\index{RTS options} +%* * +%************************************************************************ + +To make an executable program, the GHC system compiles your code and +then links it with a non-trivial runtime system (RTS), which handles +storage management, profiling, etc. + +You have some control over the behaviour of the RTS, by giving special +command-line arguments to your program. + +%You have some control over the behavior of the runtime system, either +%by giving special command-line arguments to your program (the usual) or by +%building in your own defaults at compile time (the exotic). + +When your Haskell program starts up, its RTS extracts +command-line arguments bracketed between \tr{+RTS}\index{+RTS option} +and \tr{-RTS}\index{-RTS option} as its own. For example: +\begin{verbatim} +% ./a.out -f +RTS -p -S -RTS -h foo bar +\end{verbatim} +The RTS will snaffle \tr{-p -S} for itself, +and the remaining arguments \tr{-f -h foo bar} will be handed +to your program when it does a @GetArgs@ I/O request. + +No \tr{-RTS} option is required if the runtime-system options extend +to the end of the command line, as in this example: +\begin{verbatim} +% hls -ltr /usr/etc +RTS -H5m +\end{verbatim} +If you absolutely positively want all the rest of the options in a +command line to go to the program (and not the RTS), use a +\tr{--RTS}\index{--RTS option}. + +As always, for RTS options that take \tr{<size>}s: If the last +character of \tr{size} is a K or k, multiply by 1000; if an M or m, by +1,000,000; if a G or G, by 1,000,000,000. (And any wraparound in the +counters is {\em your} fault!) + +Giving a \tr{+RTS -f}\index{-f RTS option} option will print out the +RTS options actually available in your program (which vary, depending +on how you compiled). + +%************************************************************************ +%* * +\subsection{Generally-available RTS options} +\index{RTS options, general} +%* * +%************************************************************************ + +The most important RTS options are: +\begin{description} +\item[\tr{-H<size>}:] +\index{-H<size> RTS option} +Set the heap size to \pl{<size>} bytes +[default: 4M]. + +\item[\tr{-K<size>}:] +\index{-K<size> RTS option} +Set the stack size to \pl{<size>} bytes [default: 64K]. +For concurrent/parallel programs, it is the stack size of the main +thread; generally speaking, c/p stacks are in heap. + +Note: if your program seems to be consuming infinite stack space, it +is probably in a loop :-) Of course, if stacks are in the heap, make +that infinite {\em heap} space... + +\item[\tr{-s<file>} or \tr{-S<file>}:] +\index{-S<file> RTS option} +\index{-s<file> RTS option} +Write modest (\tr{-s}) or verbose (\tr{-S}) garbage-collector +statistics into file \pl{<file>}. The default \pl{<file>} is +\pl{<program>}\tr{.stat}. The \pl{<file>} \tr{stderr} is treated +specially, with the output really being sent to \tr{stderr}. + +%Note that \tr{stdout} is flushed before each garbage collection so the +%interleaving of \tr{stdout} and the garbage collection statistics will +%be accurate. + +%Note that the same program will typically allocate more space with a +%generational collector than with a non-generational collector. +The amount of heap allocation will typically increase as the total heap +size is reduced. The reason for this odd behaviour is that updates of +promoted-to-old-generation objects may require the extra allocation of a new-generation +object to ensure that there are never any pointers from the old +generation to the new generation. + +For some garbage collectors (not including the default one, sadly), +you can convert the \tr{-S} output into a residency graph (in +PostScript), using the \tr{stat2resid}\index{stat2resid} utility in +the GHC distribution (\tr{ghc/utils/stat2resid}). + +\item[\tr{-N}:] +\index{-N RTS option} +Normally, the garbage collector black-holes closures which are being +evaluated, as a space-saving measure. That's exactly what you want +for ordinary Haskell programs. + +When signal handlers are present, however, a computation may be +abandoned prematurely, leaving black holes behind. If the signal +handler shares one of these black-holed closures, disaster can result. +Use the \tr{-N} option to prevent black-holing by the garbage +collector if you suspect that your signal handlers may share {\em any} +subexpressions with the top-level computation. Expect your heap usage +to increase, since the lifetimes of some closures may be extended. +\end{description} + +%************************************************************************ +%* * +\subsection{RTS options to control the garbage-collector} +\index{RTS options, garbage-collection} +%* * +%************************************************************************ + +Besides the \tr{-H} (set heap size) and \tr{-S}/\tr{-s} (GC stats) RTS +options, there are several options to give you precise control over +garbage collection. + +\begin{description} +\item[\tr{-M<n>}:] +\index{-M<n> RTS option} +Minimum \% \pl{<n>} of heap which must be available for allocation. +The default is 3\%. + +\item[\tr{-A<size>}:] +\index{-A<size> RTS option} +Sets a limit on the size of the allocation area for generational +garbage collection to \pl{<size>} bytes (\tr{-A} gives default of 64k). If +a negative size is given the size of the allocation is fixed to +-\pl{<size>}. For non-generational collectors, it fixes the minimum +heap which must be available after a collection, overriding the +\tr{-M<n>} RTS option. + +\item[\tr{-G<size>}:] +\index{-G<size> RTS option} +Sets the percentage of free space to be promoted before a major +collection is invoked to \pl{<size>}\%. The default is 66\%. If a +negative size is given it fixes the size of major generation threshold +to -\pl{<size>} bytes. + +\item[\tr{-F2s}:] +\index{-F2s RTS option} +Forces a program compiled for generational GC to use two-space copying +collection. The two-space collector may outperform the generational +collector for programs which have a very low heap residency. It can +also be used to generate a statistics file from which a basic heap +residency profile can be produced (see Section \ref{stat2resid}). + +There will still be a small execution overhead imposed by the +generational compilation as the test for old generation updates will +still be executed (of course none will actually happen). This +overhead is typically less than 1\%. + +\item[\tr{-j<size>}:] +\index{-j<size> RTS option} +Force a major garbage collection every \pl{<size>} bytes. (Normally +used because you're keen on getting major-GC stats, notably heap residency +info.) +\end{description} + +%************************************************************************ +%* * +\subsection{RTS options for profiling and Concurrent/Parallel Haskell} +%* * +%************************************************************************ + +The RTS options related to profiling are described in +\Sectionref{prof-rts-options}; +and those for concurrent/parallel stuff, in \Sectionref{parallel-rts-opts}. + +%************************************************************************ +%* * +\subsection{RTS options for hackers, debuggers, and over-interested souls} +\index{RTS options, hacking/debugging} +%* * +%************************************************************************ + +These RTS options might be used (a)~to avoid a GHC bug, (b)~to see +``what's really happening'', or (c)~because you feel like it. Not +recommended for everyday use! + +\begin{description} +\item[\tr{-B}:] +\index{-B RTS option} +Sound the bell at the start of each (major) garbage collection. +[Why anyone would do this, I cannot imagine.] + +\item[\tr{-I}:] +Use the ``debugging mini-interpreter'' with sanity-checking; you have +to have an appropriately-compiled version of the prelude, etc. +Goes together nicely with GDB (GNU debugger)... +(OLD, REALLY) + +\item[\tr{-r<file>}:] +\index{-r <file> RTS option} +Produce ``ticky-ticky'' statistics at the end of the program run. +The \tr{<file>} business works just like on the \tr{-S} RTS option (above). + +``Ticky-ticky'' statistics are counts of various program actions +(updates, enters, etc.) +The program must have been compiled using +\tr{-fstg-reduction-counts}\index{-fstg-reduction-counts option} +(a.k.a. ``ticky-ticky profiling''), and, for it to be really useful, +linked with suitable system libraries. Not a trivial undertaking: +consult the installation guide on how to set things up for +easy ``ticky-ticky'' profiling. + +\item[\tr{-T<num>}:] +\index{-T RTS option} +An RTS debugging flag; varying quantities of output depending on which bits +are set in \pl{<num>}. + +\item[\tr{-Z}:] +\index{-Z RTS option} +Turn {\em off} ``update-frame squeezing'' at garbage-collection time. +(There's no particularly good reason to turn it off.) +\end{description} + +%************************************************************************ +%* * +\subsection[rts-hooks]{``Hooks'' to change RTS failure messages} +\index{hooks, RTS} +\index{RTS hooks} +%* * +%************************************************************************ + +GHC lets you exercise rudimentary control over the messages printed +when the runtime system ``blows up,'' e.g., on stack overflow. + +Simply write some of the following procedures in C and then make sure +they get linked in, in preference to those in the RTS library: +\begin{description} +\item[\tr{void ErrorHdrHook (FILE *)}:] +\index{ErrorHdrHook} +What's printed out before the message from \tr{error}. + +\item[\tr{void OutOfHeapHook (unsigned long, unsigned long)}:] +\index{OutOfHeapHook} +The heap-overflow message. + +\item[\tr{void StackOverflowHook (long int)}:] +\index{StackOverflowHook} +The stack-overflow message. + +\item[\tr{void MallocFailHook (long int)}:] +\index{MallocFailHook} +The message printed if \tr{malloc} fails. + +\item[\tr{void PatErrorHdrHook (FILE *)}:] +\index{PatErrorHdrHook} +The message printed if a pattern-match fails (the failures +that were not handled by the Haskell programmer). + +\item[\tr{void PreTraceHook (FILE *)}:] +\index{PreTraceHook} +What's printed out before a \tr{trace} message. + +\item[\tr{void PostTraceHook (FILE *)}:] +\index{PostTraceHook} +What's printed out after a \tr{trace} message. +\end{description} + +For example, here is the ``hooks'' code used by GHC itself: +\begin{verbatim} +#include <stdio.h> +#define W_ unsigned long int +#define I_ long int + +void +ErrorHdrHook (where) + FILE *where; +{ + fprintf(where, "\n"); /* no "Fail: " */ +} + +void +OutOfHeapHook (request_size, heap_size) + W_ request_size; /* in bytes */ + W_ heap_size; /* in bytes */ +{ + fprintf(stderr, "GHC's heap exhausted;\nwhile trying to + allocate %lu bytes in a %lu-byte heap;\nuse the `-H<size>' + option to increase the total heap size.\n", + request_size, + heap_size); +} + +void +StackOverflowHook (stack_size) + I_ stack_size; /* in bytes */ +{ + fprintf(stderr, "GHC stack-space overflow: current size + %ld bytes.\nUse the `-K<size>' option to increase it.\n", + stack_size); +} + +void +PatErrorHdrHook (where) + FILE *where; +{ + fprintf(where, "\n*** Pattern-matching error within GHC!\n\n + This is a compiler bug; please report it to + glasgow-haskell-bugs@dcs.glasgow.ac.uk.\n\nFail: "); +} + +void +PreTraceHook (where) + FILE *where; +{ + fprintf(where, "\n"); /* not "Trace On" */ +} + +void +PostTraceHook (where) + FILE *where; +{ + fprintf(where, "\n"); /* not "Trace Off" */ +} +\end{verbatim} + +%************************************************************************ +%* * +%\subsection[rts-control-shell-scripts]{Hiding the runtime-control mess with a shell script} +%* * +%************************************************************************ + +%NOT DONE YET. + diff --git a/ghc/docs/users_guide/sooner.lit b/ghc/docs/users_guide/sooner.lit new file mode 100644 index 0000000000..a7f535c594 --- /dev/null +++ b/ghc/docs/users_guide/sooner.lit @@ -0,0 +1,530 @@ +%************************************************************************ +%* * +\section[sooner-faster-quicker]{Advice on: sooner, faster, smaller, stingier} +%* * +%************************************************************************ + +Please advise us of other ``helpful hints'' that should go here! + +%************************************************************************ +%* * +\subsection[sooner]{Sooner: producing a program more quickly} +\index{compiling faster} +\index{faster compiling} +%* * +%************************************************************************ + +\begin{description} +%---------------------------------------------------------------- +\item[Don't use \tr{-O} or (especially) \tr{-O2}:] +By using them, you are telling GHC that you are willing to suffer +longer compilation times for better-quality code. + +GHC is surprisingly zippy for normal compilations without \tr{-O}! + +%---------------------------------------------------------------- +\item[Use more memory:] +Within reason, more memory for heap space means less garbage +collection for GHC, which means less compilation time. If you use +the \tr{-Rgc-stats} option, you'll get a garbage-collector report. +(Again, you can use the cheap-and-nasty \tr{-optCrts-Sstderr} option to +send the GC stats straight to standard error.) + +If it says you're using more than 20\% of total time in garbage +collecting, then more memory would help. + +You ask for more heap with the \tr{-H<size>}\index{-H<size> option} +option; e.g.: \tr{ghc -c -O -H16m Foo.hs}. + +If GHC persists in being a bad memory citizen, please report it as a +bug. + +%---------------------------------------------------------------- +\item[Don't use too much memory!] +As soon as GHC plus its ``fellow citizens'' (other processes on your machine) start +using more than the {\em real memory} on your machine, and the machine +starts ``thrashing,'' {\em the party is over}. Compile times will be +worse than terrible! Use something like the csh-builtin \tr{time} +command to get a report on how many page faults you're getting. + +If you don't know what virtual memory, thrashing, and page faults are, +or you don't know the memory configuration of your machine, {\em +don't} try to be clever about memory use: you'll just make your life a +misery (and for other people, too, probably). + +%---------------------------------------------------------------- +\item[Try to use local disks when linking:] +Because Haskell objects and libraries tend to be large, it can take +many real seconds to slurp the bits to/from an NFS filesystem (say). + +It would be quite sensible to {\em compile} on a fast machine using +remotely-mounted disks; then {\em link} on a slow machine that had +your disks directly mounted. + +%---------------------------------------------------------------- +\item[Don't derive \tr{read} for \tr{Text} unnecessarily:] +When doing \tr{deriving Text}, +use \tr{-fomit-derived-read}\index{-fomit-derived-read option} +to derive only the \tr{showsPrec} method. Quicker, smaller code. + +%---------------------------------------------------------------- +\item[Don't re-export instance declarations:] + +(Note: This recommendation totally violates the Haskell language +standard.) + +The Haskell module system dictates that instance declarations are +exported and re-exported into interface files with considerable gusto. +In a large system, especially one with mutually-recursive modules, +this tendency makes your interface files bigger (bad) and decreases +the chances that changes will be propagated incorrectly (bad). + +If you wish, you may use a language-violating option, +\tr{-fomit-reexported-instances}, +\index{-fomit-reexported-instances option} +to get just the effect you might expect. It can't help but +speed things up. + +%---------------------------------------------------------------- +\item[GHC compiles some program constructs slowly:] +Deeply-nested list comprehensions seem to be one such; in the past, +very large constant tables were bad, too. + +We'd rather you reported such behaviour as a bug, so that we can try +to correct it. + +The parts of the compiler that seem most prone to wandering off for a +long time are the abstract interpreters (strictness and update +analysers). You can turn these off individually with +\tr{-fno-strictness}\index{-fno-strictness anti-option} and +\tr{-fno-update-analysis}.\index{-fno-update-analysis anti-option} + +If \tr{-ddump-simpl} produces output after a reasonable time, but +\tr{-ddump-stg} doesn't, then it's probably the update analyser +slowing you down. + +If your module has big wads of constant data, GHC may produce a huge +basic block that will cause the native-code generator's register +allocator to founder. + +If \tr{-ddump-absC} produces output after a reasonable time, but +nothing after that---it's probably the native-code generator. Bring +on \tr{-fvia-C}\index{-fvia-C option} (not that GCC will be that quick about it, either). + +%---------------------------------------------------------------- +\item[Avoid the consistency-check on linking:] +Use \tr{-no-link-chk}\index{-no-link-chk}; saves effort. This is probably +safe in a I-only-compile-things-one-way setup. + +%---------------------------------------------------------------- +\item[Explicit \tr{import} declarations:] +Instead of saying \tr{import Foo}, say +\tr{import Foo (...stuff I want...)}. + +Truthfully, the reduction on compilation time will be very small. +However, judicious use of \tr{import} declarations can make a +program easier to understand, so it may be a good idea anyway. +\end{description} + +%************************************************************************ +%* * +\subsection[faster]{Faster: producing a program that runs quicker} +\index{faster programs, how to produce} +%* * +%************************************************************************ + +The key tool to use in making your Haskell program run faster are +GHC's profiling facilities, described separately in +\sectionref{profiling}. There is {\em no substitute} for finding +where your program's time/space is {\em really} going, as opposed +to where you imagine it is going. + +Another point to bear in mind: By far the best way to improve a +program's performance {\em dramatically} is to use better algorithms. +Once profiling has thrown the spotlight on the guilty +time-consumer(s), it may be better to re-think your program than to +try all the tweaks listed below. + +Another extremely efficient way to make your program snappy is to use +library code that has been Seriously Tuned By Someone Else. You {\em might} be able +to write a better quicksort than the one in the HBC library, but it +will take you much longer than typing \tr{import QSort}. +(Incidentally, it doesn't hurt if the Someone Else is Lennart +Augustsson.) + +Please report any overly-slow GHC-compiled programs. The current +definition of ``overly-slow'' is ``the HBC-compiled version ran +faster''... + +\begin{description} +%---------------------------------------------------------------- +\item[Optimise, using \tr{-O} or \tr{-O2}:] This is the most basic way +to make your program go faster. Compilation time will be slower, +especially with \tr{-O2}. + +At version~0.26, \tr{-O2} is nearly indistinguishable from \tr{-O}. + +%---------------------------------------------------------------- +\item[Compile via C and crank up GCC:] Even with \tr{-O}, GHC tries to +use a native-code generator, if available. But the native +code-generator is designed to be quick, not mind-bogglingly clever. +Better to let GCC have a go, as it tries much harder on register +allocation, etc. + +So, when we want very fast code, we use: \tr{-O -fvia-C -O2-for-C}. + +%---------------------------------------------------------------- +\item[Overloaded functions are not your friend:] +Haskell's overloading (using type classes) is elegant, neat, etc., +etc., but it is death to performance if left to linger in an inner +loop. How can you squash it? + +\begin{description} +\item[Give explicit type signatures:] +Signatures are the basic trick; putting them on exported, top-level +functions is good software-engineering practice, anyway. + +The automatic specialisation of overloaded functions should take care +of overloaded local and/or unexported functions. + +\item[Use \tr{SPECIALIZE} pragmas:] +\index{SPECIALIZE pragma} +\index{overloading, death to} +(UK spelling also accepted.) For key overloaded functions, you can +create extra versions (NB: more code space) specialised to particular +types. Thus, if you have an overloaded function: +\begin{verbatim} +hammeredLookup :: Ord key => [(key, value)] -> key -> value +\end{verbatim} +If it is heavily used on lists with \tr{Widget} keys, you could +specialise it as follows: +\begin{verbatim} +{-# SPECIALIZE hammeredLookup :: [(Widget, value)] -> Widget -> value #-} +\end{verbatim} + +To get very fancy, you can also specify a named function to use for +the specialised value, by adding \tr{= blah}, as in: +\begin{verbatim} +{-# SPECIALIZE hammeredLookup :: ...as before... = blah #-} +\end{verbatim} +It's {\em Your Responsibility} to make sure that \tr{blah} really +behaves as a specialised version of \tr{hammeredLookup}!!! + +An example in which the \tr{= blah} form will Win Big: +\begin{verbatim} +toDouble :: Real a => a -> Double +toDouble = fromRational . toRational + +{-# SPECIALIZE toDouble :: Int -> Double = i2d #-} +i2d (I# i) = D# (int2Double# i) -- uses Glasgow prim-op directly +\end{verbatim} +The \tr{i2d} function is virtually one machine instruction; the +default conversion---via an intermediate \tr{Rational}---is obscenely +expensive by comparison. + +By using the US spelling, your \tr{SPECIALIZE} pragma will work with +HBC, too. Note that HBC doesn't support the \tr{= blah} form. + +A \tr{SPECIALIZE} pragma for a function can be put anywhere its type +signature could be put. + +\item[Use \tr{SPECIALIZE instance} pragmas:] +Same idea, except for instance declarations. For example: +\begin{verbatim} +instance (Eq a) => Eq (Foo a) where { ... usual stuff ... } + +{-# SPECIALIZE instance Eq (Foo [(Int, Bar)] #-} +\end{verbatim} +Compatible with HBC, by the way. + +See also: overlapping instances, in \Sectionref{glasgow-hbc-exts}. +They are to \tr{SPECIALIZE instance} pragmas what \tr{= blah} +hacks are to \tr{SPECIALIZE} (value) pragmas... + +\item[``How do I know what's happening with specialisations?'':] + +The \tr{-fshow-specialisations}\index{-fshow-specialisations option} +will show the specialisations that actually take place. + +The \tr{-fshow-import-specs}\index{-fshow-import-specs option} will +show the specialisations that GHC {\em wished} were available, but +were not. You can add the relevant pragmas to your code if you wish. + +You're a bit stuck if the desired specialisation is of a Prelude +function. If it's Really Important, you can just snap a copy of the +Prelude code, rename it, and then SPECIALIZE that to your heart's +content. + +\item[``But how do I know where overloading is creeping in?'':] + +A low-tech way: grep (search) your interface files for overloaded +type signatures; e.g.,: +\begin{verbatim} +% egrep '^[a-z].*::.*=>' *.hi +\end{verbatim} + +Note: explicit export lists sometimes ``mask'' overloaded top-level +functions; i.e., you won't see anything about them in the interface +file. I sometimes remove my export list temporarily, just to see what +pops out. +\end{description} + +%---------------------------------------------------------------- +\item[Strict functions are your dear friends:] +and, among other things, lazy pattern-matching is your enemy. + +(If you don't know what a ``strict function'' is, please consult a +functional-programming textbook. A sentence or two of +explanation here probably would not do much good.) + +Consider these two code fragments: +\begin{verbatim} +f (Wibble x y) = ... # strict + +f arg = let { (Wibble x y) = arg } in ... # lazy +\end{verbatim} +The former will result in far better code. + +A less contrived example shows the use of \tr{cases} instead +of \tr{lets} to get stricter code (a good thing): +\begin{verbatim} +f (Wibble x y) # beautiful but slow + = let + (a1, b1, c1) = unpackFoo x + (a2, b2, c2) = unpackFoo y + in ... + +f (Wibble x y) # ugly, and proud of it + = case (unpackFoo x) of { (a1, b1, c1) -> + case (unpackFoo y) of { (a2, b2, c2) -> + ... + }} +\end{verbatim} + +%---------------------------------------------------------------- +\item[GHC loves single-constructor data-types:] + +It's all the better if a function is strict in a single-constructor +type (a type with only one data-constructor; for example, tuples are +single-constructor types). + +%---------------------------------------------------------------- +\item[``How do I find out a function's strictness?''] + +Don't guess---look it up. + +Look for your function in the interface file, then for the third field +in the pragma; it should say \tr{_S_ <string>}. The \tr{<string>} +gives the strictness of the function's arguments. \tr{L} is lazy +(bad), \tr{S} and \tr{E} are strict (good), \tr{P} is ``primitive'' (good), +\tr{U(...)} is strict and +``unpackable'' (very good), and \tr{A} is absent (very good). + +If the function isn't exported, just compile with the extra flag \tr{-ddump-simpl}; +next to the signature for any binder, it will print the self-same +pragmatic information as would be put in an interface file. +(Besides, Core syntax is fun to look at!) + +%---------------------------------------------------------------- +\item[Force key functions to be \tr{INLINE}d (esp. monads):] + +GHC (with \tr{-O}, as always) tries to inline (or ``unfold'') +functions/values that are ``small enough,'' thus avoiding the call +overhead and possibly exposing other more-wonderful optimisations. + +You will probably see these unfoldings (in Core syntax) in your +interface files. + +Normally, if GHC decides a function is ``too expensive'' to inline, it +will not do so, nor will it export that unfolding for other modules to +use. + +The sledgehammer you can bring to bear is the +\tr{INLINE}\index{INLINE pragma} pragma, used thusly: +\begin{verbatim} +key_function :: Int -> String -> (Bool, Double) + +#ifdef __GLASGOW_HASKELL__ +{-# INLINE key_function #-} +#endif +\end{verbatim} +(You don't need to do the C pre-processor carry-on unless you're going +to stick the code through HBC---it doesn't like \tr{INLINE} pragmas.) + +The major effect of an \tr{INLINE} pragma is to declare a function's +``cost'' to be very low. The normal unfolding machinery will then be +very keen to inline it. + +An \tr{INLINE} pragma for a function can be put anywhere its type +signature could be put. + +\tr{INLINE} pragmas are a particularly good idea for the +\tr{then}/\tr{return} (or \tr{bind}/\tr{unit}) functions in a monad. +For example, in GHC's own @UniqueSupply@ monad code, we have: +\begin{verbatim} +#ifdef __GLASGOW_HASKELL__ +{-# INLINE thenUs #-} +{-# INLINE returnUs #-} +#endif +\end{verbatim} + +GHC reserves the right to {\em disallow} any unfolding, even if you +explicitly asked for one. That's because a function's body may +become {\em unexportable}, because it mentions a non-exported value, +to which any importing module would have no access. + +If you want to see why candidate unfoldings are rejected, use the +\tr{-freport-disallowed-unfoldings} +\index{-freport-disallowed-unfoldings} +option. + +%---------------------------------------------------------------- +\item[Don't let GHC ignore pragmatic information:] + +Sort-of by definition, GHC is allowed to ignore pragmas in interfaces. +Your program should still work, if not as well. + +Normally, GHC {\em will} ignore an unfolding pragma in an interface if +it cannot figure out all the names mentioned in the unfolding. (A +very much hairier implementation could make sure This Never Happens, +but life is too short to wage constant battle with Haskell's module +system.) + +If you want to prevent such ignorings, give GHC a +\tr{-fshow-pragma-name-errs} +option.\index{-fshow-pragma-name-errs option} +It will then treat any unresolved names in pragmas as {\em +errors}, rather than inconveniences. + +%---------------------------------------------------------------- +\item[Explicit \tr{export} list:] +If you do not have an explicit export list in a module, GHC must +assume that everything in that module will be exported. This has +various pessimising effect. For example, if a bit of code is actually +{\em unused} (perhaps because of unfolding effects), GHC will not be +able to throw it away, because it is exported and some other module +may be relying on its existence. + +GHC can be quite a bit more aggressive with pieces of code if it knows +they are not exported. + +%---------------------------------------------------------------- +\item[Look at the Core syntax!] +(The form in which GHC manipulates your code.) Just run your +compilation with \tr{-ddump-simpl} (don't forget the \tr{-O}). + +If profiling has pointed the finger at particular functions, look at +their Core code. \tr{lets} are bad, \tr{cases} are good, dictionaries +(\tr{d.<Class>.<Unique>}) [or anything overloading-ish] are bad, +nested lambdas are bad, explicit data constructors are good, primitive +operations (e.g., \tr{eqInt#}) are good, ... + +%---------------------------------------------------------------- +\item[Use unboxed types (a GHC extension):] +When you are {\em really} desperate for speed, and you want to +get right down to the ``raw bits.'' +Please see \sectionref{glasgow-unboxed} for some information about +using unboxed types. + +%---------------------------------------------------------------- +\item[Use \tr{_ccall_s} (a GHC extension) to plug into fast libraries:] +This may take real work, but... There exist piles of +massively-tuned library code, and the best thing is not +to compete with it, but link with it. + +\Sectionref{glasgow-ccalls} says a little about how to use C calls. + +%---------------------------------------------------------------- +\item[Don't use \tr{Float}s:] +We don't provide specialisations of Prelude functions for \tr{Float} +(but we do for \tr{Double}). If you end up executing overloaded +code, you will lose on performance, perhaps badly. + +\tr{Floats} (probably 32-bits) are almost always a bad idea, anyway, +unless you Really Know What You Are Doing. Use Doubles. There's +rarely a speed disadvantage---modern machines will use the same +floating-point unit for both. With \tr{Doubles}, you are much less +likely to hang yourself with numerical errors. + +%---------------------------------------------------------------- +\item[Use a bigger heap!] +If your program's GC stats (\tr{-S}\index{-S RTS option} RTS option) +indicate that it's doing lots of garbage-collection (say, more than +20\% of execution time), more memory might help---with the +\tr{-H<size>}\index{-H<size> RTS option} RTS option. + +%---------------------------------------------------------------- +\item[Use a smaller heap!] +Some programs with a very small heap residency (toy programs, usually) +actually benefit from running the heap size way down. The +\tr{-H<size>} RTS option, as above. + +%---------------------------------------------------------------- +\item[Use a smaller ``allocation area'':] +If you can get the garbage-collector's youngest generation to fit +entirely in your machine's cache, it may make quite a difference. +The effect is {\em very machine dependent}. But, for example, +a \tr{+RTS -A128k}\index{-A<size> RTS option} option on one of our +DEC Alphas was worth an immediate 5\% performance boost. +\end{description} + +%************************************************************************ +%* * +\subsection[smaller]{Smaller: producing a program that is smaller} +\index{smaller programs, how to produce} +%* * +%************************************************************************ + +Decrease the ``go-for-it'' threshold for unfolding smallish expressions. +Give a \tr{-funfolding-use-threshold0}\index{-funfolding-use-threshold0 option} +option for the extreme case. (``Only unfoldings with zero cost should proceed.'') + +(Note: I have not been too successful at producing code smaller +than that which comes out with \tr{-O}. WDP 94/12) + +Use \tr{-fomit-derived-read} if you are using a lot of derived +instances of \tr{Text} (and don't need the read methods). + +Use \tr{strip} on your executables. + +%************************************************************************ +%* * +\subsection[stingier]{Stingier: producing a program that gobbles less heap space} +\index{memory, using less heap} +\index{space-leaks, avoiding} +\index{heap space, using less} +%* * +%************************************************************************ + +``I think I have a space leak...'' Re-run your program with +\tr{+RTS -Sstderr},\index{-Sstderr RTS option} and remove all doubt! +(You'll see the heap usage get bigger and bigger...) [Hmmm... this +might be even easier with the \tr{-F2s}\index{-F2s RTS option} RTS +option; so... \tr{./a.out +RTS -Sstderr -F2s}...] + +Once again, the profiling facilities (\sectionref{profiling}) are the +basic tool for demystifying the space behaviour of your program. + +Strict functions are good to space usage, as they are for time, as +discussed in the previous section. Strict functions get right down to +business, rather than filling up the heap with closures (the system's +notes to itself about how to evaluate something, should it eventually +be required). + +If you have a true blue ``space leak'' (your program keeps gobbling up +memory and never ``lets go''), then 7 times out of 10 the problem is +related to a {\em CAF} (constant applicative form). Real people call +them ``top-level values that aren't functions.'' Thus, for example: +\begin{verbatim} +x = (1 :: Int) +f y = x +ones = [ 1, (1 :: Float), .. ] +\end{verbatim} +\tr{x} and \tr{ones} are CAFs; \tr{f} is not. + +The GHC garbage collectors are not clever about CAFs. The part of the +heap reachable from a CAF is never collected. In the case of +\tr{ones} in the example above, it's {\em disastrous}. For this +reason, the GHC ``simplifier'' tries hard to avoid creating CAFs, but +it cannot subvert the will of a determined CAF-writing programmer (as +in the case above). diff --git a/ghc/docs/users_guide/ticky.lit b/ghc/docs/users_guide/ticky.lit new file mode 100644 index 0000000000..478677af51 --- /dev/null +++ b/ghc/docs/users_guide/ticky.lit @@ -0,0 +1,26 @@ +%************************************************************************ +%* * +\section[ticky-ticky]{Using ``ticky-ticky'' profiling (for implementors)} +\index{ticky-ticky profiling (implementors)} +%* * +%************************************************************************ + +(ToDo: document properly.) + +It is possible to compile Glasgow Haskell programs so that they will +count lots and lots of interesting things, e.g., number of updates, +number of data constructors entered, etc., etc. We call this +``ticky-ticky'' profiling,\index{ticky-ticky profiling}% +\index{profiling, ticky-ticky} because that's the sound a Sun4 makes +when it is running up all those counters ({\em slowly}). + +Ticky-ticky profiling is mainly intended for implementors; it is quite +separate from the main ``cost-centre'' profiling system, intended for +all users everywhere. + +To be able to use ticky-ticky profiling, you will need to have built +appropriate libraries and things when you made the system. See +``Customising what libraries to build,'' in the installation guide. + +To get your compiled program to spit out the ticky-ticky numbers, use +a \tr{-r} RTS option\index{-r RTS option}. diff --git a/ghc/docs/users_guide/tutorial.lit b/ghc/docs/users_guide/tutorial.lit new file mode 100644 index 0000000000..89233e6799 --- /dev/null +++ b/ghc/docs/users_guide/tutorial.lit @@ -0,0 +1,129 @@ +% +% $Header: /srv/cvs/cvs.haskell.org/fptools/ghc/docs/users_guide/Attic/tutorial.lit,v 1.1 1996/01/08 20:25:11 partain Exp $ +% +\section[compiler-tutorial]{Tutorial material about this compilation system} + +This guide assumes quite a bit of knowledge about UNIX compilers and +their conventional use. This section has a little extra information +for those who are new at this racket. + +%************************************************************************ +%* * +\subsection[batch-system-parts]{The (batch) compilation system components} +%* * +%************************************************************************ + +The Glorious Haskell Compilation System, as with most UNIX (batch) +compilation systems, has several interacting parts: +\begin{enumerate} +\item +A {\em driver}\index{driver program} \tr{ghc}\index{ghc}---which you +usually think of as ``the compiler''---is a program that merely +invokes/glues-together the other pieces of the system (listed below), +passing the right options to each, slurping in the right libraries, +etc. + +\item +A {\em literate pre-processor} +\index{literate pre-processor} +\index{pre-processor, literate} +\tr{unlit}\index{unlit} that extracts Haskell +code from a literate script; used if you believe in that sort of +thing. + +\item +The {\em Haskellised C pre-processor} +\index{Haskellised C pre-processor} +\index{C pre-processor, Haskellised} +\index{pre-processor, Haskellised C} +\tr{hscpp},\index{hscpp} only needed by people requiring conditional +compilation, probably for large systems. The ``Haskellised'' part +just means that \tr{#line} directives in the output have been +converted into proper Haskell \tr{{-# LINE ... -}} pragmas. + +You must give an explicit \tr{-cpp} option +\index{-cpp option} for the C pre-processor to be invoked. + +\item +The {\em Haskell compiler} +\index{Haskell compiler} +\index{compiler, Haskell} +\tr{hsc},\index{hsc} +which---in normal use---takes its input from the C pre-processor +and produces assembly-language output (sometimes: ANSI C output). + +\item +The {\em ANSI~C Haskell high-level assembler :-)} +\index{ANSI C compiler} +\index{high-level assembler} +\index{assembler, high-level} +compiles \tr{hsc}'s C output into assembly language for a particular +target architecture. (It doesn't have to be an ANSI C compiler, but +that's preferred; to go fastest, you need GNU C, version 2.x.) + +\item +The {\em assembler}\index{assembler}---a standard UNIX one, probably +\tr{as}\index{as}. + +\item +The {\em linker}\index{linker}---a standard UNIX one, probably +\tr{ld}.\index{ld} + +\item +A {\em runtime system},\index{runtime system} including (most notably) +a storage manager; the linker links in the code for this. + +\item +The {\em Haskell standard prelude}\index{standard prelude}, a +large library of standard functions, is linked in as well. + +\item +Parts of other {\em installed libraries} that you have at your site +may be linked in also. +\end{enumerate} + +%************************************************************************ +%* * +\subsection[compile-what-really-happens]{What really happens when I ``compile'' a Haskell program?} +%* * +%************************************************************************ + +You invoke the Glasgow Haskell compilation system through the +driver program \tr{ghc}.\index{ghc} For example, if you had typed a +literate ``Hello, world!'' program into \tr{hello.lhs}, and you then +invoked: +\begin{verbatim} +ghc hello.lhs +\end{verbatim} + +the following would happen: +\begin{enumerate} +\item +The file \tr{hello.lhs} is run through the literate-program +code extractor \tr{unlit}\index{unlit}, feeding its output to + +\item +The Haskell compiler proper \tr{hsc}\index{hsc}, which produces +input for + +\item +The assembler (or that ubiquitous ``high-level assembler,'' a C +compiler), which produces an object file and passes it to + +\item +The linker, which links your code with the appropriate libraries +(including the standard prelude), producing an executable program in +the default output file named \tr{a.out}. +\end{enumerate} + +You have considerable control over the compilation process. You feed +command-line arguments (call them ``options,'' for short) to the +driver, \tr{ghc}; the ``types'' of the input files (as encoded in +their names' suffixes) also matter. + +Here's hoping this is enough background so that you can read the rest +of this guide! + +% The ``style'' of the driver program \tr{ghc} follows that of the GNU C +% compiler driver \tr{gcc}. The use of environment variables to provide +% defaults is more extensive in this compilation system. diff --git a/ghc/docs/users_guide/user.lit b/ghc/docs/users_guide/user.lit new file mode 100644 index 0000000000..51f63e20a5 --- /dev/null +++ b/ghc/docs/users_guide/user.lit @@ -0,0 +1,36 @@ +\begin{onlystandalone} +\documentstyle[11pt,literate]{article} +\begin{document} +\title{The Glorious Glasgow Haskell Compilation System\\ Version~0.26\\ User's Guide} +\author{The AQUA Team\\ +Department of Computing Science\\ +University of Glasgow\\ +Glasgow, Scotland\\ +G12 8QQ\\ +\\ +Email: glasgow-haskell-\{bugs,request\}\@dcs.glasgow.ac.uk} +\maketitle +\begin{rawlatex} +\tableofcontents +\pagebreak +\end{rawlatex} +\end{onlystandalone} + +\input{intro.lit} +\input{how_to_run.lit} +\input{runtime_control.lit} +\input{sooner.lit} +\input{profiling.lit} +\input{glasgow_exts.lit} +\input{libraries.lit} +\input{parallel.lit} +\input{gone_wrong.lit} +\input{vs_haskell.lit} +\input{utils.lit} +\input{ticky.lit} +\input{tutorial.lit} + +\begin{onlystandalone} +\printindex +\end{document} +\end{onlystandalone} diff --git a/ghc/docs/users_guide/utils.lit b/ghc/docs/users_guide/utils.lit new file mode 100644 index 0000000000..d007621521 --- /dev/null +++ b/ghc/docs/users_guide/utils.lit @@ -0,0 +1,143 @@ +%************************************************************************ +%* * +\section[utils]{Other Haskell utility programs} +\index{utilities, Haskell} +%* * +%************************************************************************ + +This section describes other program(s) which we distribute, that help +with the Great Haskell Programming Task. + +%************************************************************************ +%* * +\subsection[mkdependHS]{Makefile dependencies in Haskell: using \tr{mkdependHS}} +\index{mkdependHS} +\index{Makefile dependencies} +\index{dependencies in Makefiles} +%* * +%************************************************************************ + +It is reasonably straightforward to set up a \tr{Makefile} to use with +GHC, assuming you name your source files the same as your modules. +Thus: +\begin{verbatim} +HC = ghc +HCFLAGS = -fhaskell-1.3 -cpp -hi-diffs $(EXTRA_HC_OPTS) + +SRCS = Main.lhs Foo.lhs Bar.lhs +OBJS = Main.o Foo.o Bar.o + +.SUFFIXES : .o .lhs +.lhs.o: + $(RM) $@ + $(HC) -c $< $(HCFLAGS) + +cool_pgm : $(OBJS) + $(RM) $@ + $(HC) -o $@ $(HCFLAGS) $(OBJS) +\end{verbatim} + +The only thing lacking in the above \tr{Makefile} is interface-file +dependencies. If \tr{Foo.lhs} imports module \tr{Bar} and the +\tr{Bar} interface changes, then \tr{Foo.lhs} needs to be recompiled. + +Putting dependencies of the form \tr{Foo.o : Bar.hi} into your +\tr{Makefile} by hand is rather error-prone. Don't worry---never +fear, \tr{mkdependHS} is here! (and is distributed as part of GHC) +Add the following to your \tr{Makefile}: +\begin{verbatim} +depend : + mkdependHS -- $(HCFLAGS) -- $(SRCS) +\end{verbatim} + +Now, before you start compiling, and any time you change the +\tr{imports} in your program, do \tr{make depend} before you do +\tr{make cool_pgm}. \tr{mkdependHS} will append the needed +dependencies to your \tr{Makefile}. + +A few caveats about this simple scheme: (a)~You may need to compile +some modules explicitly to create their interfaces in the first place +(e.g., \tr{make Bar.o} to create \tr{Bar.hi}). (b)~You may have to +type \tr{make} more than once for the dependencies to have full +effect. However, a \tr{make} run that does nothing {\em does} mean +``everything's up-to-date.'' (c) This scheme will work with +mutually-recursive modules but, again, it may take multiple +iterations to ``settle.'' + +%************************************************************************ +%* * +\subsection[hstags]{Emacs `TAGS' for Haskell: \tr{hstags}} +\index{hstags} +\index{TAGS for Haskell} +%* * +%************************************************************************ + +`Tags' is a facility for indexing the definitions of +programming-language things in a multi-file program, and then using +that index to jump around among these definitions. + +Rather than scratch your head, saying ``Now where did we define +`foo'?'', you just do (in Emacs) \tr{M-. foo RET}, and You're There! +Some people go wild over this stuff... + +GHC comes with a program \tr{hstags}, which build Emacs-able TAGS +files. The invocation syntax is: +\begin{verbatim} +hstags [GHC-options] file [files...] +\end{verbatim} + +The best thing is just to feed it your GHC command-line flags. +A good Makefile entry might be: +\begin{verbatim} +tags: + $(RM) TAGS + hstags $(GHC_FLAGS) *.lhs +\end{verbatim} + +The only flags of its own are: \tr{-v} to be verbose; \tr{-a} to +**APPEND** to the TAGS file, rather than write to it. + +Shortcomings: (1)~Instance declarations don't get into the TAGS file +(but the definitions inside them do); as instances aren't named, this +is probably just as well. (2)~Data-constructor definitions don't get +in. Go for the corresponding type constructor instead. + +(Actually, GHC also comes with \tr{etags} [for C], and \tr{perltags} +[for You Know What]. And---I cannot tell a lie---there is Denis +Howe's \tr{fptags} [for Haskell, etc.] in the \tr{ghc/CONTRIB} +section...) + +%************************************************************************ +%* * +\subsection[happy]{``Yacc for Haskell'': \tr{happy}} +\index{happy} +\index{Yacc for Haskell} +\index{parser generator for Haskell} +%* * +%************************************************************************ + +Andy Gill and Simon Marlow have written a parser-generator for +Haskell, called \tr{happy}.\index{happy parser generator} \tr{Happy} +is to Haskell what \tr{Yacc} is to C. + +You can get \tr{happy} by FTP from \tr{ftp.dcs.glasgow.ac.uk} in +\tr{pub/haskell/happy}, the file \tr{happy-0.8.tar.gz}. + +\tr{Happy} is at its shining best when compiled by GHC. + +%************************************************************************ +%* * +\subsection[pphs]{Pretty-printing Haskell: \tr{pphs}} +\index{pphs} +\index{pretty-printing Haskell code} +%* * +%************************************************************************ + +Andrew Preece has written +\tr{pphs},\index{pphs}\index{pretty-printing Haskell} +a utility to pretty-print Haskell code in LaTeX documents. +Keywords in bolds, variables in italics---that sort of thing. It is +good at lining up program clauses and equals signs, things that are +very tiresome to do by hand. + +The code is distributed with GHC in \tr{ghc/CONTRIB/pphs}. diff --git a/ghc/docs/users_guide/vs_haskell.lit b/ghc/docs/users_guide/vs_haskell.lit new file mode 100644 index 0000000000..c4fc5e5b7b --- /dev/null +++ b/ghc/docs/users_guide/vs_haskell.lit @@ -0,0 +1,575 @@ +%************************************************************************ +%* * +\section[vs-Haskell-defn]{Haskell~1.2 vs.~Glasgow Haskell~0.26: language non-compliance} +\index{GHC vs the Haskell 1.2 language} +\index{Haskell 1.2 language vs GHC} +%* * +%************************************************************************ + +This section lists Glasgow Haskell infelicities in its implementation +of Haskell~1.2. See also the ``when things go wrong'' section +(\sectionref{wrong}) for information about crashes, space leaks, and +other undesirable phenomena. + +The limitations here are listed in Haskell-Report order (roughly). +%Limitations related to Glasgow extensions (unboxed numbers, etc.) are +%given thereafter (\sectionref{infelicities-Glasgow-exts}). + +%************************************************************************ +%* * +\subsection[infelicities-exprs-pats]{Expressions and patterns} +%* * +%************************************************************************ + +\begin{description} +%------------------------------------------------------------------- +\item[Some valid irrefutable patterns are rejected:] +As syntax errors; just put parentheses around them. + +%------------------------------------------------------------------- +\item[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 \tr{-cpp}\index{-cpp option} +option don't mix. The C-preprocessor may munch the backslashes. + +%------------------------------------------------------------------- +\item[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.) +\end{description} + +%************************************************************************ +%* * +\subsection[infelicities-decls]{Declarations and bindings} +%* * +%************************************************************************ + +\begin{description} +%------------------------------------------------------------------- +\item[Contexts on @data@ declarations are ignored:] +Not that they do much, anyway... This won't wreck your life. +(We still [vaguely] plan to add them, however.) + +%------------------------------------------------------------------- +\item[Location of instance declarations is unchecked:] +We don't check that instance declarations occur either in the module +where the class is declared or the module where the data type is +declared. This shouldn't hurt you. + +For better or worse, we {\em do} check if you try to declare a Prelude +instance (Prelude class, Prelude type; e.g., \tr{instance Num Bool}) +in one of your own modules. For some reason, people like to do this! +(But it is not legal Haskell.) + +%------------------------------------------------------------------- +\item[Derived instances of @Text@ 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. + +%------------------------------------------------------------------- +\item[Derived instances of @Binary@:] +We don't. (We don't do anything @Binary@ish.) +\end{description} + +%************************************************************************ +%* * +\subsection[infelicities-Modules]{Module system and interface files} +%* * +%************************************************************************ + +\begin{description} +%------------------------------------------------------------------- +\item[Duplicates in a `renaming' list:] +Are not reported. + +%------------------------------------------------------------------- +\item[Duplicates in an `import' declaration:] +These are reported as errors, which some might argue they shouldn't +be. We reckon it's a feature, not a bug. + +%------------------------------------------------------------------- +\item[Export of `renamed' class methods:] +Willnae work. That is: you import a class, renaming one or more +methods; then export that class---the renaming of the methods {\em +will not} propagate. + +(Otherwise, `renaming'---disgusting though it may be---should work.) + +%------------------------------------------------------------------- +\item[Fixities/precedences following `renamed' entities that are exported:] +No chance. + +%------------------------------------------------------------------- +\item[\tr{import Foo ()} vs \tr{import Foo}:] +GHC cannot tell the difference (!). + +Given that the only module on which you might want to do the former is +\tr{import Prelude ()}, there are probably much bigger gremlins that +would jump out and bite you if the import {\em did} work. Besides +which, you can achieve the same result with +\tr{-fno-implicit-prelude}.\index{-fno-implicit-prelude option} + +%------------------------------------------------------------------- +\item[Some selective import/export checking not done:] +On selective import and export of type-constructors/classes in +which the data-constructors/methods are named explicitly: +it'll work; it's just that every conceivable paranoia +check won't be done. + +%------------------------------------------------------------------- +\item[Some Prelude entities cannot be hidden:] +For example, this doesn't work: +\begin{verbatim} +import Prelude hiding (readParen) +\end{verbatim} +That's because there are a few should-be-hideable Prelude entities +which need to appear by magic for derived instances. They are +\tr{(&&)}, \tr{(.)}, \tr{lex}, \tr{map}, \tr{not}, \tr{readParen}, +\tr{showParen}, and \tr{showString}. SIGH. + +%------------------------------------------------------------------- +\item[\tr{M..} exports vs multiply-imported entities:] +If an entity \tr{foo} is imported from several interfaces, as in... +\begin{verbatim} +import A1 (foo); import A2 (foo); import A3 (foo) +\end{verbatim} +... and you then do a ``dot dot'' export of \tr{A1} (for example), it +will be {\em pure luck} if \tr{foo} gets exported. This is very sad. + +Workaround: export \tr{foo} explicitly. + +%------------------------------------------------------------------- +\item[\tr{M..} with Prelude interfaces:] +Doing \tr{Prelude<something>..} in an export list; don't even think +it. + +%------------------------------------------------------------------- +\item[Export of Prelude types/classes must be explicit:] + +If you want to export a data type, type synonym or class from a +Prelude module (its name starts with `Prelude'), then it must be +listed explicitly in the export list. If you say: + +\begin{verbatim} +module PreludeMeGently ( PreludeMeGently.. , other_stuff ) where .. +\end{verbatim} + +then the classes/types in \tr{PreludeMeGently} will {\em not} be +exported; just add them to the export list. (This shortcoming is only +likely to affect people writing their own Prelude modules.) + +%------------------------------------------------------------------- +\item[Can't export primitives types (e.g., \tr{Int#}):] + +Don't even try... + +%------------------------------------------------------------------- +\item[Naming errors with \tr{-O} but not without:] + +Documentation by example---Consider a module with these imports: + +\begin{verbatim} +... various imports ... +import Prettyterm -- desired import + +import Pretty -- sadly-needed import +\end{verbatim} + +The \tr{import Pretty} is required because it defines a type +\tr{Pretty.Doc} which is mentioned in \tr{import Prettyterm}. +(Extremely sad, but them's the rules.) + +But without \tr{-O}, GHC uses its \tr{-fuse-get-mentioned-vars} hack +(for speed), trying to avoid looking at parts of interfaces that have +no relevance to this module. As it happens, the thing in +\tr{Prettyterm} that mentions \tr{Pretty.Doc} is not used here, so +this module will go through without \tr{import Pretty}. Nice, but +wrong. +\end{description} + +%************************************************************************ +%* * +\subsection[infelicities-numbers]{Numbers, basic types, and built-in classes} +%* * +%************************************************************************ + +\begin{description} +%------------------------------------------------------------------- +% now in glasgow_exts +%\item[@fromInt@ method in class @Num@:] +% (Non-standard.) We support it, as does HBC. + +%------------------------------------------------------------------- +\item[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 {\em 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. + +%------------------------------------------------------------------- +\item[Unchecked arithmetic:] +Arguably {\em not} an infelicity, but... Bear in mind that operations +on \tr{Int}, \tr{Float}, and \tr{Double} numbers are {\em unchecked} +for overflow, underflow, and other sad occurrences. + +Use \tr{Integer}, \tr{Rational}, etc., numeric types if this stuff keeps you +awake at night. + +%------------------------------------------------------------------- +\item[Multiply-defined array elements---not checked:] +This code fragment {\em should} elicit a fatal error, but it does not: +\begin{verbatim} +main = print (array (1,1) [ 1:=2, 1:=3 ]) +\end{verbatim} + +%------------------------------------------------------------------- +\item[Support for @Binary@ whatnot:] +We don't. +\end{description} + +%************************************************************************ +%* * +\subsection[infelicities-IO]{Dialogue I/O} +%* * +%************************************************************************ + +Dialogue-style I/O---still the default for GHC---is on its way out +(see the stuff about ``monadic I/O for Haskell~1.3''), so we probably +won't fix these shortcomings. + +\begin{description} +%------------------------------------------------------------------- +\item[Support for @Dialogue@ I/O:] +We do not yet support all @Requests@, notably: +@ReadBinFile@, +@WriteBinFile@, +@AppendBinFile@, +@StatusFile@, +@ReadBinChan@, +@AppendBinChan@, +@StatusChan@, +@SetEnv@. Also, we do not support the optional I/O @Requests@. + +\item[@AppendChan@ and @ReadChan@ requests:] +The former only works for \tr{stdout} and \tr{stderr}; the +latter only for \tr{stdin}. + +\item[@Echo@ request:] +We don't do anything at all. +\end{description} + +%************************************************************************ +%* * +\subsection[infelicities-Prelude]{In Prelude support} +%* * +%************************************************************************ + +\begin{description} +%------------------------------------------------------------------- +\item[Arbitrary-sized tuples:] +Plain old tuples of arbitrary size {\em 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@, @Ix@, and +@Binary@) are available {\em only} up to 5-tuples; except @Binary@, +which we don't do at all. + +These limitations are easily subvertible, so please ask if you get +stuck on them. +\end{description} + +%************************************************************************ +%* * +%\subsection[infelicities-Glasgow-exts]{In Glasgow extensions} +%* * +%************************************************************************ + +%\begin{description} +%------------------------------------------------------------------- +%\item[Glasgow extensions not well ``packaged'':] +%We would rather give you tidy interfaces to the primitive extensions +%that GHC provides. For example, instead of your having to muck around +%with... +%\begin{verbatim} +% ... _ccall_ fflush ``stderr'' `thenIO_Int_#` ... +%\end{verbatim} +%... (all very grimy); you should be able to import a \tr{LibC.hi}, and +%pretend that @fflush@ is really a Haskell function! + +%This problem will be fixed when Haskell~1.3 comes into existence, and +%we implement it. + +%------------------------------------------------------------------- +%\item[@ArrRef@s of @Int#@s, @Float#@s, @Double#@s:] +%Are not in yet, but will be. (Easy to add if you're desperate.) +%\end{description} + +%************************************************************************ +%* * +\section[vs-Haskell-1.3]{Haskell~1.3 DRAFT vs.~Glasgow Haskell~0.26} +\index{GHC vs the DRAFT Haskell 1.3 language} +\index{Haskell 1.3 language DRAFT vs GHC} +%* * +%************************************************************************ + +There is work afoot on ``Haskell~1.3,'' a substantial revision of +the Haskell~1.2 language. + +Haskell 1.3 is NOT a standard; it is NOT even a DRAFT standard. As of +June 1995, there exists a 1.3 PROPOSAL, which will CERTAINLY change. +Therefore, the ``1.3 things'' we ``support'' may change ARBITRARILY +much, and we won't even be mildly apologetic about breaking programs +that use ``1.3'' facilities. + +That said, there are two categories of ``1.3'' things that we commend +to you. +\begin{itemize} +\item +Things virtually certain to end up in any 1.3~standard. An example is +the \tr{Maybe} type. +\item +Wobblier things which are so much better than their 1.2 equivalents +that you will want to use them. We mean: monadic I/O. + +The basic I/O functions are ``unlikely'' to change and so are +reasonably safe to adopt. (But see WARNING above...) +\end{itemize} + +To use our 1.3 code, you should compile {\em and link} using a +\tr{-fhaskell-1.3}\index{-fhaskell-1.3 option} flag. + +%************************************************************************ +%* * +\subsection[duffer-1-3]{Duffer's guide for converting 1.2 I/O to 1.3 I/O} +\index{I/O---converting 1.2 to 1.3} +\index{Dialogue I/O--converting to 1.3} +\index{1.2 I/O---converting to 1.3} +%* * +%************************************************************************ + +Here is our ``crib sheet'' for converting 1.2 I/O to 1.3. In most cases, +it's really easy. +\begin{enumerate} +\item +Change \tr{readChan stdin} to \tr{hGetContents stdin}. +\item +Change \tr{appendChan stdout} to \tr{putStr}, which is equivalent to +\tr{hPutStr stdout}. +Change \tr{appendChan stderr} to \tr{hPutStr stderr}. +\item +You need to \tr{import LibSystem} if you used @getArgs@, @getEnv@, +or @getProgName@. +\item +Assuming continuation-style @Dialogue@ code, change \tr{... exit done $} +to \tr{... >>}. Change \tr{... exit $ \ foo ->} to \tr{... >>= \ foo ->}. +\item +If you had any functions named \tr{(>>)}, \tr{(>>=)}, or \tr{return}, +change them to something else. +\end{enumerate} + +%************************************************************************ +%* * +\subsection[nonio-1-3]{Non-I/O things from the 1.3-DRAFT proposal} +%* * +%************************************************************************ + +Besides the I/O stuff, you also get these things when you use the +\tr{-fhaskell-1.3}\index{-fhaskell-1.3 option} flag. + +Once again: ANY of thing might CHANGE COMPLETELY before we have ``1.3 +for real.'' + +\begin{verbatim} +data Either a b = Left a | Right b deriving (Text, Eq, Ord) + +data Maybe a = Nothing | Just a deriving (Eq, Ord, Text) + +thenMaybe :: Maybe a -> (a -> Maybe b) -> Maybe b +thenMaybe Nothing _ = Nothing +thenMaybe (Just x) f = f x + +curry :: ((a,b) -> c) -> a -> b -> c +curry f x y = f (x,y) + +uncurry :: (a -> b -> c) -> (a,b) -> c +uncurry f (x,y) = f x y +\end{verbatim} +\index{Maybe type (Haskell 1.3)} +\index{Either type (Haskell 1.3)} +\index{curry function (Haskell 1.3)} +\index{uncurry function (Haskell 1.3)} + +%************************************************************************ +%* * +\subsection[io-1-3]{Vs~1.3 monadic I/O} +\index{GHC vs the DRAFT 1.3 I/O proposal} +\index{DRAFT 1.3 I/O proposal vs GHC} +%* * +%************************************************************************ + +The most notable improvement in Haskell~1.3 is its I/O, with a shift to +``monadic-style'' I/O. + +We still offer direct access to the so-called \tr{PrimIO} monad, via +the \tr{PreludeGlaST} interface. This is NON-STANDARD, an extension. +This interface is described in \Sectionref{io-1-3-prim-interface}. + +The old \tr{PreludePrimIO} interface is DEAD. + +The even-older \tr{PreludeGlaIO} interface is DEADER. + +%************************************************************************ +%* * +\subsubsection[io-1-3-shortcomings]{Known shortcomings in monadic I/O} +%* * +%************************************************************************ + +Before you begin with ``1.3-style'' monadic I/O, you might as well +know the known shortcomings of our implementation, as at 0.26. + +The error type is called \tr{IOError13}, rather than \tr{IOError} +\index{IOError13 vs IOError} +(which is still the 1.2 type). (Prelude types cannot be renamed, +so...) You probably shouldn't be messing with \tr{IOError} much, +anyway. + +Some of the 1.3 I/O code, notably the Extremely Cool \tr{LibPosix} +stuff, is relatively untested. Go for it, but be wary... +\index{LibPosix bugs} +\index{bugs, LibPosix} + +%************************************************************************ +%* * +\subsubsection[io-1-3-main-interface]{1.3-style monadic I/O} +%* * +%************************************************************************ + +To use our 1.3 I/O, you should compile {\em and link} using a +\tr{-fhaskell-1.3}\index{-fhaskell-1.3 option} flag. + +You should consult the PROPOSED 1.3-I/O standard. GHC~0.26 implements +the ``December 1994'' draft, which we distribute in +\tr{ghc/docs/io-1.3/}. + +Alternatively, you could grab the ``June 1995'' draft, from +\tr{pub/haskell/report/}, on \tr{ftp.dcs.glasgow.ac.uk}. The main +December--June change that you need to know about is: many of the I/O +functions have been removed from \tr{Prelude*} interfaces (no import +required) and put into \tr{Lib*} interfaces (import required). + +GHC~0.26 still provides the I/O functions via \tr{Prelude.hi} (no +import required). Ignore the ``June draft'' pleadings for +\tr{import LibIO}, and you'll be fine. + +{\em There is no guarantee that the final 1.3 proposal will look +anything like the current DRAFT.} It ain't a standard until the fat +committee sings. + +For interaction with our non-standard \tr{PrimIO}, including +\tr{_ccall_}s. we also provide: +\begin{verbatim} +-- impedance matching stuff +ioToPrimIO :: IO a -> PrimIO a +\end{verbatim} + +%************************************************************************ +%* * +\subsubsection[io-1-3-prim-interface]{Access to the \tr{PrimIO} monad} +\index{PrimIO monad (Glasgow extension)} +\index{I/O, primitive (Glasgow extension)} +%* * +%************************************************************************ + +In what we have implemented, \tr{PrimIO} is the +handle-the-errors-yourself monad (NB: used for C-calls and such); +whereas \tr{IO} is the 1.3-ish we-handle-errors-for-you monad. + +Should you may need to play with the \tr{PrimIO} monad directly, you +can import \tr{PreludeGlaST}. + +NB: You used to get this stuff from the \tr{PreludePrimIO} interface, +which is now deceased. As of 0.26, you get all things +state-transforming from the \tr{PreludeGlaST} interface. + +The usual monadic stuff for \tr{PrimIO}: +\begin{verbatim} +returnPrimIO :: a -> PrimIO a +thenPrimIO :: PrimIO a -> (a -> PrimIO b) -> PrimIO b +seqPrimIO :: PrimIO a -> PrimIO b -> PrimIO b +fixPrimIO :: (a -> PrimIO a) -> PrimIO a +foldrPrimIO :: (a -> b -> PrimIO b) -> PrimIO b -> [a] -> PrimIO b +listPrimIO :: [PrimIO a] -> PrimIO [a] +mapPrimIO :: (a -> PrimIO b) -> [a] -> PrimIO [b] +mapAndUnzipPrimIO :: (a -> PrimIO (b,c)) -> [a] -> PrimIO ([b],[c]) +forkPrimIO :: PrimIO a -> PrimIO a + +unsafePerformPrimIO :: PrimIO a -> a +unsafeInterleavePrimIO :: PrimIO a -> PrimIO a + -- and they are not called "unsafe" for nothing! +\end{verbatim} + +And some other stuff: +\begin{verbatim} +data _FILE -- corresponds to a "FILE *" in C + -- in classes Eq, _CCallable, and _CReturnable + +fclose :: _FILE -> PrimIO Int +fdopen :: Int -> String -> PrimIO _FILE +fflush :: _FILE -> PrimIO Int +fopen :: String -> String -> PrimIO _FILE +fread :: Int -> Int -> _FILE -> PrimIO (Int, _ByteArray Int) +freopen :: String -> String -> _FILE -> PrimIO _FILE +fwrite :: _ByteArray Int -> Int -> Int -> _FILE -> PrimIO Int + +-- please AVOID using these (They will probably die) +appendChanPrimIO :: String -> String -> PrimIO () +appendFilePrimIO :: String -> String -> PrimIO () +getArgsPrimIO :: PrimIO [String] +readChanPrimIO :: String -> PrimIO String +\end{verbatim} + +%************************************************************************ +%* * +\subsubsection[own-mainPrimIO]{Using your own @mainPrimIO@} +\index{mainPrimIO, rolling your own} +%* * +%************************************************************************ + +Normally, the GHC runtime system begins things by called an internal +function @mainPrimIO :: PrimIO ()@ which, in turn, fires up +@dialogueToIO :: Dialogue -> IO ()@, linking in {\em your} @Main.main@ +to provide the @Dialogue@. + +(If you give a \tr{-fhaskell-1.3} flag, then a {\em different} +@mainPrimIO@ will be linked in---that's why it is important to link +with \tr{-fhaskell-1.3}...) + +To subvert the above process, you need only provide +a @mainPrimIO :: PrimIO ()@ of your own +(in a module named \tr{Main}). Do {\em not} use a \tr{-fhaskell-1.3} flag! + +Here's a little example, stolen from Alastair Reid: +\begin{verbatim} +module Main ( mainPrimIO ) where + +import PreludeGlaST + +mainPrimIO :: PrimIO () +mainPrimIO = + sleep 5 `seqPrimIO` + _ccall_ printf "%d\n" (14::Int) + +sleep :: Int -> PrimIO () +sleep t = _ccall_ sleep t +\end{verbatim} |