[project @ 1996-07-25 20:43:49 by partain]
[ghc-hetmet.git] / ghc / docs / users_guide / libraries.lit
1 %************************************************************************
2 %*                                                                      *
3 \section[syslibs]{System libraries}
4 \index{system libraries}
5 \index{libraries, system}
6 %*                                                                      *
7 %************************************************************************
8
9 We intend to provide more and more ready-to-use Haskell code, so that
10 every program doesn't have to invent everything from scratch.
11
12 If you provide a \tr{-syslib <name>}\index{-syslib <name> option} option,
13 then the interfaces for that library will come into scope (and may be
14 \tr{import}ed), and the code will be added in at link time.
15
16 We supply a part of the HBC library (\tr{-syslib hbc}); as well as one
17 of our own (\tr{-syslib ghc}); one for an interface to POSIX routines
18 (\tr{-syslib posix}); and one of contributed stuff off the net, mostly
19 numerical (\tr{-syslib contrib}).
20
21 If you have Haggis (our GUI X~toolkit for Haskell), it probably works
22 with a \tr{-syslib haggis} flag.
23
24 %************************************************************************
25 %*                                                                      *
26 \subsection[GHC-library]{The GHC system library}
27 \index{library, GHC}
28 \index{GHC library}
29 %*                                                                      *
30 %************************************************************************
31
32 We have started to put together a ``GHC system library.''
33
34 At the moment, the library is made of generally-useful bits of the
35 compiler itself.
36
37 To use this library, just give a \tr{-syslib ghc}\index{-syslib ghc option}
38 option to GHC, both for compiling and linking.
39
40 %************************************************************************
41 %*                                                                      *
42 \subsubsection[Bag]{The @Bag@ type}
43 \index{Bag module (GHC syslib)}
44 %*                                                                      *
45 %************************************************************************
46
47 A {\em bag} is an unordered collection of elements which may contain
48 duplicates.  To use, \tr{import Bag}.
49
50 \begin{verbatim}
51 emptyBag        :: Bag elt
52 unitBag         :: elt -> Bag elt
53
54 unionBags       :: Bag elt   -> Bag elt -> Bag elt
55 unionManyBags   :: [Bag elt] -> Bag elt
56 consBag         :: elt       -> Bag elt -> Bag elt
57 snocBag         :: Bag elt   -> elt     -> Bag elt
58
59 concatBag       :: Bag (Bag a) -> Bag a
60 mapBag          :: (a -> b) -> Bag a -> Bag b
61
62 foldBag :: (r -> r -> r) -- Replace TwoBags with this; should be associative
63         -> (a -> r)      -- Replace UnitBag with this
64         -> r             -- Replace EmptyBag with this
65         -> Bag a
66         -> r
67
68 elemBag         :: Eq elt => elt -> Bag elt -> Bool
69 isEmptyBag      ::                  Bag elt -> Bool
70 filterBag       :: (elt -> Bool) -> Bag elt -> Bag elt
71 partitionBag    :: (elt -> Bool) -> Bag elt-> (Bag elt, Bag elt)
72         -- returns the elements that do/don't satisfy the predicate
73
74 listToBag       :: [elt] -> Bag elt
75 bagToList       :: Bag elt -> [elt]
76 \end{verbatim}
77
78 %************************************************************************
79 %*                                                                      *
80 \subsubsection[BitSet]{The @BitSet@ type}
81 \index{BitSet module (GHC syslib)}
82 %*                                                                      *
83 %************************************************************************
84
85 Bit sets are a fast implementation of sets of integers ranging from 0
86 to one less than the number of bits in a machine word (typically 31).
87 If any element exceeds the maximum value for a particular machine
88 architecture, the results of these operations are undefined.  You have
89 been warned.  [``If you put any safety checks in this code, I will have
90 to kill you.'' --JSM]
91
92 \begin{verbatim}
93 mkBS        :: [Int]  -> BitSet
94 listBS      :: BitSet -> [Int]
95 emptyBS     :: BitSet 
96 unitBS      :: Int    -> BitSet
97
98 unionBS     :: BitSet -> BitSet -> BitSet
99 minusBS     :: BitSet -> BitSet -> BitSet
100 elementBS   :: Int    -> BitSet -> Bool
101 intersectBS :: BitSet -> BitSet -> BitSet
102
103 isEmptyBS   :: BitSet -> Bool
104 \end{verbatim}
105
106 %************************************************************************
107 %*                                                                      *
108 \subsubsection[FiniteMap]{The @FiniteMap@ type}
109 \index{FiniteMap module (GHC syslib)}
110 %*                                                                      *
111 %************************************************************************
112
113 What functional programmers call a {\em finite map}, everyone else
114 calls a {\em lookup table}.
115
116 Out code is derived from that in this paper:
117 \begin{display}
118 S Adams
119 "Efficient sets: a balancing act"
120 Journal of functional programming 3(4) Oct 1993, pages 553-562
121 \end{display}
122 Guess what?  The implementation uses balanced trees.
123
124 \begin{verbatim}
125 --      BUILDING
126 emptyFM         :: FiniteMap key elt
127 unitFM          :: key -> elt -> FiniteMap key elt
128 listToFM        :: Ord key => [(key,elt)] -> FiniteMap key elt
129                         -- In the case of duplicates, the last is taken
130
131 --      ADDING AND DELETING
132                    -- Throws away any previous binding
133                    -- In the list case, the items are added starting with the
134                    -- first one in the list
135 addToFM         :: Ord key => FiniteMap key elt -> key -> elt  -> FiniteMap key elt
136 addListToFM     :: Ord key => FiniteMap key elt -> [(key,elt)] -> FiniteMap key elt
137
138                    -- Combines with previous binding
139 addToFM_C       :: Ord key => (elt -> elt -> elt)
140                            -> FiniteMap key elt -> key -> elt  
141                            -> FiniteMap key elt
142 addListToFM_C   :: Ord key => (elt -> elt -> elt)
143                            -> FiniteMap key elt -> [(key,elt)] 
144                            -> FiniteMap key elt
145
146                    -- Deletion doesn't complain if you try to delete something
147                    -- which isn't there
148 delFromFM       :: Ord key => FiniteMap key elt -> key   -> FiniteMap key elt
149 delListFromFM   :: Ord key => FiniteMap key elt -> [key] -> FiniteMap key elt
150
151 --      COMBINING
152                    -- Bindings in right argument shadow those in the left
153 plusFM          :: Ord key => FiniteMap key elt -> FiniteMap key elt
154                            -> FiniteMap key elt
155
156                    -- Combines bindings for the same thing with the given function
157 plusFM_C        :: Ord key => (elt -> elt -> elt) 
158                            -> FiniteMap key elt -> FiniteMap key elt -> FiniteMap key elt
159
160 minusFM         :: Ord key => FiniteMap key elt -> FiniteMap key elt -> FiniteMap key elt
161                    -- (minusFM a1 a2) deletes from a1 any bindings which are bound in a2
162
163 intersectFM     :: Ord key => FiniteMap key elt -> FiniteMap key elt -> FiniteMap key elt 
164 intersectFM_C   :: Ord key => (elt -> elt -> elt)
165                            -> FiniteMap key elt -> FiniteMap key elt -> FiniteMap key elt 
166
167 --      MAPPING, FOLDING, FILTERING
168 foldFM          :: (key -> elt -> a -> a) -> a -> FiniteMap key elt -> a
169 mapFM           :: (key -> elt1 -> elt2) -> FiniteMap key elt1 -> FiniteMap key elt2
170 filterFM        :: Ord key => (key -> elt -> Bool) 
171                            -> FiniteMap key elt -> FiniteMap key elt
172
173 --      INTERROGATING
174 sizeFM          :: FiniteMap key elt -> Int
175 isEmptyFM       :: FiniteMap key elt -> Bool
176
177 elemFM          :: Ord key => key -> FiniteMap key elt -> Bool
178 lookupFM        :: Ord key => FiniteMap key elt -> key -> Maybe elt
179 lookupWithDefaultFM
180                 :: Ord key => FiniteMap key elt -> elt -> key -> elt
181                 -- lookupWithDefaultFM supplies a "default" elt
182                 -- to return for an unmapped key
183
184 --      LISTIFYING
185 fmToList        :: FiniteMap key elt -> [(key,elt)]
186 keysFM          :: FiniteMap key elt -> [key]
187 eltsFM          :: FiniteMap key elt -> [elt]
188 \end{verbatim}
189
190 %************************************************************************
191 %*                                                                      *
192 \subsubsection[ListSetOps]{The @ListSetOps@ type}
193 \index{ListSetOps module (GHC syslib)}
194 %*                                                                      *
195 %************************************************************************
196
197 Just a few set-sounding operations on lists.  If you want sets, use
198 the \tr{Set} module.
199
200 \begin{verbatim}
201 unionLists          :: Eq a => [a] -> [a] -> [a]
202 intersectLists      :: Eq a => [a] -> [a] -> [a]
203 minusList           :: Eq a => [a] -> [a] -> [a]
204 disjointLists       :: Eq a => [a] -> [a] -> Bool
205 intersectingLists   :: Eq a => [a] -> [a] -> Bool
206 \end{verbatim}
207
208 %************************************************************************
209 %*                                                                      *
210 \subsubsection[Maybes]{The @Maybes@ type}
211 \index{Maybes module (GHC syslib)}
212 %*                                                                      *
213 %************************************************************************
214
215 The \tr{Maybe} type itself is in the Haskell~1.3 prelude.  Moreover,
216 the required \tr{Maybe} library provides many useful functions on
217 \tr{Maybe}s.  This (old) module provides more.
218
219 An \tr{Either}-like type called \tr{MaybeErr}:
220 \begin{verbatim}
221 data MaybeErr val err = Succeeded val | Failed err
222 \end{verbatim}
223
224 Some operations to do with \tr{Maybe} (some commentary follows):
225 \begin{verbatim}
226 maybeToBool :: Maybe a -> Bool      -- Nothing => False; Just => True
227 allMaybes   :: [Maybe a] -> Maybe [a]
228 firstJust   :: [Maybe a] -> Maybe a
229 findJust    :: (a -> Maybe b) -> [a] -> Maybe b
230
231 assocMaybe  :: Eq a => [(a,b)] -> a -> Maybe b
232 mkLookupFun :: (key -> key -> Bool) -- Equality predicate
233             -> [(key,val)]          -- The assoc list
234             -> (key -> Maybe val)   -- A lookup fun to use
235 mkLookupFunDef :: (key -> key -> Bool) -- Ditto, with a default
236             -> [(key,val)]
237             -> val                  -- the default
238             -> (key -> val)         -- NB: not a Maybe anymore
239
240     -- a monad thing
241 thenMaybe   :: Maybe a -> (a -> Maybe b) -> Maybe b
242 returnMaybe :: a -> Maybe a
243 failMaybe   :: Maybe a
244 mapMaybe    :: (a -> Maybe b) -> [a] -> Maybe [b]
245 \end{verbatim}
246
247 NB: @catMaybes@, which used to be here, is in the Haskell~1.3 libraries.
248
249 @allMaybes@ collects a list of @Justs@ into a single @Just@, returning
250 @Nothing@ if there are any @Nothings@.
251
252 @firstJust@ takes a list of @Maybes@ and returns the
253 first @Just@ if there is one, or @Nothing@ otherwise.
254
255 @assocMaybe@ looks up in an association list, returning
256 @Nothing@ if it fails.
257
258 Now, some operations to do with \tr{MaybeErr} (comments follow):
259 \begin{verbatim}
260     -- a monad thing (surprise, surprise)
261 thenMaB   :: MaybeErr a err -> (a -> MaybeErr b err) -> MaybeErr b err
262 returnMaB :: val -> MaybeErr val err
263 failMaB   :: err -> MaybeErr val err
264
265 listMaybeErrs :: [MaybeErr val err] -> MaybeErr [val] [err]
266 foldlMaybeErrs :: (acc -> input -> MaybeErr acc err)
267                -> acc
268                -> [input]
269                -> MaybeErr acc [err]
270 \end{verbatim}
271
272 @listMaybeErrs@ takes a list of @MaybeErrs@ and, if they all succeed,
273 returns a @Succeeded@ of a list of their values.  If any fail, it
274 returns a @Failed@ of the list of all the errors in the list.
275
276 @foldlMaybeErrs@ works along a list, carrying an accumulator; it
277 applies the given function to the accumulator and the next list item,
278 accumulating any errors that occur.
279
280 %************************************************************************
281 %*                                                                      *
282 \subsubsection[PackedString]{The @PackedString@ type}
283 \index{PackedString module (GHC syslib)}
284 %*                                                                      *
285 %************************************************************************
286
287 You need \tr{import PackedString}, and
288 heave in your \tr{-syslib ghc}.
289
290 The basic type and functions which are available are:
291 \begin{verbatim}
292 data PackedString
293
294 packString      :: [Char] -> PackedString
295 packStringST    :: [Char] -> ST s PackedString
296 packCString     :: Addr  -> PackedString
297 packCBytes      :: Int -> Addr -> PackedString
298 packCBytesST    :: Int -> Addr -> ST s PackedString
299 packBytesForC   :: [Char] -> ByteArray Int
300 packBytesForCST :: [Char] -> ST s (ByteArray Int)
301 byteArrayToPS   :: ByteArray Int -> PackedString
302 psToByteArray   :: PackedString -> ByteArray Int
303
304 unpackPS        :: PackedString -> [Char]
305 \end{verbatim}
306
307 We also provide a wad of list-manipulation-like functions:
308 \begin{verbatim}
309 nilPS      :: PackedString
310 consPS     :: Char -> PackedString -> PackedString
311
312 headPS     :: PackedString -> Char
313 tailPS     :: PackedString -> PackedString
314 nullPS     :: PackedString -> Bool
315 appendPS   :: PackedString -> PackedString -> PackedString
316 lengthPS   :: PackedString -> Int
317 indexPS    :: PackedString -> Int -> Char
318            -- 0-origin indexing into the string
319 mapPS      :: (Char -> Char) -> PackedString -> PackedString {-or String?-}
320 filterPS   :: (Char -> Bool) -> PackedString -> PackedString {-or String?-}
321 foldlPS    :: (a -> Char -> a) -> a -> PackedString -> a
322 foldrPS    :: (Char -> a -> a) -> a -> PackedString -> a
323 takePS     :: Int -> PackedString -> PackedString
324 dropPS     :: Int -> PackedString -> PackedString
325 splitAtPS  :: Int -> PackedString -> (PackedString, PackedString)
326 takeWhilePS:: (Char -> Bool) -> PackedString -> PackedString
327 dropWhilePS:: (Char -> Bool) -> PackedString -> PackedString
328 spanPS     :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
329 breakPS    :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
330 linesPS    :: PackedString -> [PackedString]
331 wordsPS    :: PackedString -> [PackedString]
332 reversePS  :: PackedString -> PackedString
333 concatPS   :: [PackedString] -> PackedString
334
335 substrPS   :: PackedString -> Int -> Int -> PackedString
336            -- pluck out a piece of a PS
337            -- start and end chars you want; both 0-origin-specified
338 \end{verbatim}
339
340 %************************************************************************
341 %*                                                                      *
342 \subsubsection[Pretty]{The @Pretty@ type}
343 \index{Pretty module (GHC syslib)}
344 %*                                                                      *
345 %************************************************************************
346
347 This is the pretty-printer that we use in GHC.
348
349 \begin{verbatim}
350 type Pretty
351
352 ppShow          :: Int{-width-} -> Pretty -> [Char]
353
354 pp'SP           :: Pretty -- "comma space"
355 ppComma         :: Pretty -- ,
356 ppEquals        :: Pretty -- =
357 ppLbrack        :: Pretty -- [
358 ppLparen        :: Pretty -- (
359 ppNil           :: Pretty -- nothing
360 ppRparen        :: Pretty -- )
361 ppRbrack        :: Pretty -- ]
362 ppSP            :: Pretty -- space
363 ppSemi          :: Pretty -- ;
364
365 ppChar          :: Char -> Pretty
366 ppDouble        :: Double -> Pretty
367 ppFloat         :: Float -> Pretty
368 ppInt           :: Int -> Pretty
369 ppInteger       :: Integer -> Pretty
370 ppRational      :: Rational -> Pretty
371 ppStr           :: [Char] -> Pretty
372
373 ppAbove         :: Pretty -> Pretty -> Pretty
374 ppAboves        :: [Pretty] -> Pretty
375 ppBeside        :: Pretty -> Pretty -> Pretty
376 ppBesides       :: [Pretty] -> Pretty
377 ppCat           :: [Pretty] -> Pretty
378 ppHang          :: Pretty -> Int -> Pretty -> Pretty
379 ppInterleave    :: Pretty -> [Pretty] -> Pretty -- spacing between
380 ppIntersperse   :: Pretty -> [Pretty] -> Pretty -- no spacing between
381 ppNest          :: Int -> Pretty -> Pretty
382 ppSep           :: [Pretty] -> Pretty
383
384 ppBracket       :: Pretty -> Pretty -- [ ... ] around something
385 ppParens        :: Pretty -> Pretty -- ( ... ) around something
386 ppQuote         :: Pretty -> Pretty -- ` ... ' around something
387 \end{verbatim}
388
389 %************************************************************************
390 %*                                                                      *
391 \subsubsection[Set]{The @Set@ type}
392 \index{Set module (GHC syslib)}
393 %*                                                                      *
394 %************************************************************************
395
396 Our implementation of {\em sets} (key property: no duplicates) is just
397 a variant of the \tr{FiniteMap} module.
398
399 \begin{verbatim}
400 mkSet           :: Ord a => [a]  -> Set a
401 setToList       :: Set a -> [a]
402 emptySet        :: Set a
403 singletonSet    :: a -> Set a
404
405 union           :: Ord a => Set a -> Set a -> Set a
406 unionManySets   :: Ord a => [Set a] -> Set a
407 intersect       :: Ord a => Set a -> Set a -> Set a
408 minusSet        :: Ord a => Set a -> Set a -> Set a
409 mapSet          :: Ord a => (b -> a) -> Set b -> Set a
410
411 elementOf       :: Ord a => a -> Set a -> Bool
412 isEmptySet      :: Set a -> Bool
413 \end{verbatim}
414
415 %************************************************************************
416 %*                                                                      *
417 \subsubsection[Util]{The @Util@ type}
418 \index{Util module (GHC syslib)}
419 %*                                                                      *
420 %************************************************************************
421
422 Stuff that has been useful to use in writing the compiler.  Don't be
423 too surprised if this stuff moves/gets-renamed/etc.
424
425 \begin{verbatim}
426 -- general list processing
427 exists          :: (a -> Bool) -> [a] -> Bool
428 forall          :: (a -> Bool) -> [a] -> Bool
429 isSingleton     :: [a] -> Bool
430 lengthExceeds   :: [a] -> Int -> Bool
431 mapAndUnzip     :: (a -> (b, c)) -> [a] -> ([b], [c])
432 mapAndUnzip3    :: (a -> (b, c, d)) -> [a] -> ([b], [c], [d])
433 nOfThem         :: Int -> a -> [a]
434 zipEqual        :: [a] -> [b] -> [(a,b)]
435 zipWithEqual    :: String -> (a->b->c) -> [a]->[b]->[c]
436 zipWith3Equal   :: String -> (a->b->c->d) -> [a]->[b]->[c]->[d]
437 zipWith4Equal   :: String -> (a->b->c->d->e) -> [a]->[b]->[c]->[d]->[e]
438 zipLazy         :: [a] -> [b] -> [(a,b)] -- lazy in 2nd arg
439
440 -- association lists
441 assoc       :: Eq a => String -> [(a, b)] -> a -> b
442
443 -- duplicate handling
444 hasNoDups    :: Eq a => [a] -> Bool
445 equivClasses :: (a -> a -> Ordering) -> [a] -> [[a]]
446 runs         :: (a -> a -> Bool)     -> [a] -> [[a]]
447 removeDups   :: (a -> a -> Ordering) -> [a] -> ([a], [[a]])
448
449 -- sorting (don't complain of no choice...)
450 quicksort          :: (a -> a -> Bool)     -> [a] -> [a]
451 sortLt             :: (a -> a -> Bool)     -> [a] -> [a]
452 stableSortLt       :: (a -> a -> Bool)     -> [a] -> [a]
453 mergesort          :: (a -> a -> Ordering) -> [a] -> [a]
454 mergeSort          :: Ord a => [a] -> [a]
455 naturalMergeSort   :: Ord a => [a] -> [a]
456 mergeSortLe        :: Ord a => [a] -> [a]
457 naturalMergeSortLe :: Ord a => [a] -> [a]
458
459 -- transitive closures
460 transitiveClosure :: (a -> [a])         -- Successor function
461                   -> (a -> a -> Bool)   -- Equality predicate
462                   -> [a] 
463                   -> [a]                -- The transitive closure
464
465 -- accumulating (Left, Right, Bi-directional)
466 mapAccumL :: (acc -> x -> (acc, y))
467                         -- Function of elt of input list and
468                         -- accumulator, returning new accumulator and
469                         -- elt of result list
470           -> acc        -- Initial accumulator
471           -> [x]        -- Input list
472           -> (acc, [y]) -- Final accumulator and result list
473
474 mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])
475
476 mapAccumB :: (accl -> accr -> x -> (accl, accr,y))
477           -> accl -> accr -> [x]
478           -> (accl, accr, [y])
479
480 -- comparisons
481 cmpString :: String -> String -> Ordering
482
483 -- pairs
484 applyToPair :: ((a -> c), (b -> d)) -> (a, b) -> (c, d)
485 applyToFst  :: (a -> c) -> (a, b) -> (c, b)
486 applyToSnd  :: (b -> d) -> (a, b) -> (a, d)
487 foldPair    :: (a->a->a, b->b->b) -> (a, b) -> [(a, b)] -> (a, b)
488 unzipWith   :: (a -> b -> c) -> [(a, b)] -> [c]
489 \end{verbatim}
490
491 %************************************************************************
492 %*                                                                      *
493 \subsection[C-interfaces]{Interfaces to C libraries}
494 \index{C library interfaces}
495 \index{interfaces, C library}
496 %*                                                                      *
497 %************************************************************************
498
499 The GHC system library (\tr{-syslib ghc}) also provides interfaces to
500 several useful C libraries, mostly from the GNU project.
501
502 %************************************************************************
503 %*                                                                      *
504 \subsubsection[Readline]{The @Readline@ interface}
505 \index{Readline library (GHC syslib)}
506 \index{command-line editing library}
507 %*                                                                      *
508 %************************************************************************
509
510 (Darren Moffat supplied the \tr{Readline} interface.)
511
512 The \tr{Readline} module is a straightforward interface to the GNU
513 Readline library.  As such, you will need to look at the GNU
514 documentation (and have a \tr{libreadline.a} file around somewhere...)
515
516 You'll need to link any Readlining program with \tr{-lreadline -ltermcap},
517 besides the usual \tr{-syslib ghc}.
518
519 The main function you'll use is:
520 \begin{verbatim}
521 readline :: String{-the prompt-} -> IO String
522 \end{verbatim}
523
524 If you want to mess around with Full Readline G(l)ory, we also
525 provide:
526 \begin{verbatim}
527 rlInitialize, addHistory,
528
529 rlBindKey, rlAddDefun, RlCallbackFunction(..),
530
531 rlGetLineBuffer, rlSetLineBuffer, rlGetPoint, rlSetPoint, rlGetEnd,
532 rlSetEnd, rlGetMark, rlSetMark, rlSetDone, rlPendingInput,
533
534 rlPrompt, rlTerminalName, rlSetReadlineName, rlGetReadlineName
535 \end{verbatim}
536 (All those names are just Haskellised versions of what you
537 will see in the GNU readline documentation.)
538
539 %************************************************************************
540 %*                                                                      *
541 \subsubsection[Regexp]{The @Regexp@ and @MatchPS@ interfaces}
542 \index{Regex library (GHC syslib)}
543 \index{MatchPS library (GHC syslib)}
544 \index{regular-expressions library}
545 %*                                                                      *
546 %************************************************************************
547
548 (Sigbjorn Finne supplied the regular-expressions interface.)
549
550 The \tr{Regex} library provides quite direct interface to the GNU
551 regular-expression library, for doing manipulation on
552 \tr{PackedString}s.  You probably need to see the GNU documentation
553 if you are operating at this level.
554
555 The datatypes and functions that \tr{Regex} provides are:
556 \begin{verbatim}
557 data PatBuffer  # just a bunch of bytes (mutable)
558
559 data REmatch
560  = REmatch (Array Int GroupBounds)  -- for $1, ... $n
561            GroupBounds              -- for $` (everything before match)
562            GroupBounds              -- for $& (entire matched string)
563            GroupBounds              -- for $' (everything after)
564            GroupBounds              -- for $+ (matched by last bracket)
565
566 -- GroupBounds hold the interval where a group
567 -- matched inside a string, e.g.
568 --
569 -- matching "reg(exp)" "a regexp" returns the pair (5,7) for the
570 -- (exp) group. (PackedString indices start from 0)
571
572 type GroupBounds = (Int, Int)
573
574 re_compile_pattern
575         :: PackedString -- pattern to compile
576         -> Bool                 -- True <=> assume single-line mode
577         -> Bool                 -- True <=> case-insensitive
578         -> PrimIO PatBuffer
579
580 re_match :: PatBuffer           -- compiled regexp
581          -> PackedString        -- string to match
582          -> Int                 -- start position
583          -> Bool                -- True <=> record results in registers
584          -> PrimIO (Maybe REmatch)
585
586 -- Matching on 2 strings is useful when you're dealing with multiple
587 -- buffers, which is something that could prove useful for
588 -- PackedStrings, as we don't want to stuff the contents of a file
589 -- into one massive heap chunk, but load (smaller chunks) on demand.
590
591 re_match2 :: PatBuffer          -- 2-string version
592           -> PackedString
593           -> PackedString
594           -> Int
595           -> Int
596           -> Bool
597           -> PrimIO (Maybe REmatch)
598
599 re_search :: PatBuffer          -- compiled regexp
600           -> PackedString       -- string to search
601           -> Int                -- start index
602           -> Int                -- stop index
603           -> Bool               -- True <=> record results in registers
604           -> PrimIO (Maybe REmatch)
605
606 re_search2 :: PatBuffer         -- Double buffer search
607            -> PackedString
608            -> PackedString
609            -> Int               -- start index
610            -> Int               -- range (?)
611            -> Int               -- stop index
612            -> Bool              -- True <=> results in registers
613            -> PrimIO (Maybe REmatch)
614 \end{verbatim}
615
616 The \tr{MatchPS} module provides Perl-like ``higher-level'' facilities
617 to operate on \tr{PackedStrings}.  The regular expressions in
618 question are in Perl syntax.  The ``flags'' on various functions can
619 include: \tr{i} for case-insensitive, \tr{s} for single-line mode, and
620 \tr{g} for global.  (It's probably worth your time to peruse the
621 source code...)
622
623 \begin{verbatim}
624 matchPS :: PackedString    -- regexp
625         -> PackedString    -- string to match
626         -> [Char]           -- flags
627         -> Maybe REmatch    -- info about what matched and where
628
629 searchPS :: PackedString   -- regexp
630          -> PackedString   -- string to match
631          -> [Char]          -- flags
632          -> Maybe REmatch
633
634 -- Perl-like match-and-substitute:
635 substPS :: PackedString    -- regexp
636         -> PackedString    -- replacement
637         -> [Char]           -- flags
638         -> PackedString    -- string
639         -> PackedString
640
641 -- same as substPS, but no prefix and suffix:
642 replacePS :: PackedString  -- regexp
643           -> PackedString  -- replacement
644           -> [Char]         -- flags
645           -> PackedString  -- string
646           -> PackedString
647
648 match2PS :: PackedString   -- regexp
649          -> PackedString   -- string1 to match
650          -> PackedString   -- string2 to match
651          -> [Char]          -- flags
652          -> Maybe REmatch
653
654 search2PS :: PackedString  -- regexp
655           -> PackedString  -- string to match
656           -> PackedString  -- string to match
657           -> [Char]         -- flags
658           -> Maybe REmatch
659
660 -- functions to pull the matched pieces out of an REmatch:
661
662 getMatchesNo    :: REmatch -> Int
663 getMatchedGroup :: REmatch -> Int -> PackedString -> PackedString
664 getWholeMatch   :: REmatch -> PackedString -> PackedString
665 getLastMatch    :: REmatch -> PackedString -> PackedString
666 getAfterMatch   :: REmatch -> PackedString -> PackedString
667
668 -- (reverse) brute-force string matching;
669 -- Perl equivalent is index/rindex:
670 findPS, rfindPS :: PackedString -> PackedString -> Maybe Int
671
672 -- Equivalent to Perl "chop" (off the last character, if any):
673 chopPS :: PackedString -> PackedString
674
675 -- matchPrefixPS: tries to match as much as possible of strA starting
676 -- from the beginning of strB (handy when matching fancy literals in
677 -- parsers):
678 matchPrefixPS :: PackedString -> PackedString -> Int
679 \end{verbatim}
680
681 %************************************************************************
682 %*                                                                      *
683 \subsubsection[Socket]{Network-interface toolkit---@Socket@ and @SocketPrim@}
684 \index{SocketPrim interface (GHC syslib)}
685 \index{Socket interface (GHC syslib)}
686 \index{network-interface library}
687 \index{sockets library}
688 \index{BSD sockets library}
689 %*                                                                      *
690 %************************************************************************
691
692 (Darren Moffat supplied the network-interface toolkit.)
693
694 Your best bet for documentation is to look at the code---really!--- 
695 normally in \tr{hslibs/ghc/src/{BSD,Socket,SocketPrim}.lhs}.
696
697 The \tr{BSD} module provides functions to get at system-database info;
698 pretty straightforward if you're into this sort of thing:
699 \begin{verbatim}
700 getHostName         :: IO String
701
702 getServiceByName    :: ServiceName -> IO ServiceEntry
703 getServicePortNumber:: ServiceName -> IO PortNumber
704 getServiceEntry     :: IO ServiceEntry
705 setServiceEntry     :: Bool -> IO ()
706 endServiceEntry     :: IO ()
707
708 getProtocolByName   :: ProtocolName -> IO ProtocolEntry
709 getProtocolByNumber :: ProtocolNumber -> IO ProtcolEntry
710 getProtocolNumber   :: ProtocolName -> ProtocolNumber
711 getProtocolEntry    :: IO ProtocolEntry
712 setProtocolEntry    :: Bool -> IO ()
713 endProtocolEntry    :: IO ()
714
715 getHostByName       :: HostName -> IO HostEntry
716 getHostByAddr       :: Family -> HostAddress -> IO HostEntry
717 getHostEntry        :: IO HostEntry
718 setHostEntry        :: Bool -> IO ()
719 endHostEntry        :: IO ()
720 \end{verbatim}
721
722 The \tr{SocketPrim} interface provides quite direct access to the
723 socket facilities in a BSD Unix system, including all the
724 complications.  We hope you don't need to use it!  See the source if
725 needed...
726
727 The \tr{Socket} interface is a ``higher-level'' interface to sockets,
728 and it is what we recommend.  Please tell us if the facilities it
729 offers are inadequate to your task!
730
731 The interface is relatively modest:
732 \begin{verbatim}
733 connectTo       :: Hostname -> PortID -> IO Handle
734 listenOn        :: PortID -> IO Socket
735
736 accept          :: Socket -> IO (Handle, HostName)
737 sendTo          :: Hostname -> PortID -> String -> IO ()
738
739 recvFrom        :: Hostname -> PortID -> IO String
740 socketPort      :: Socket -> IO PortID
741
742 data PortID     -- PortID is a non-abstract type
743   = Service String      -- Service Name eg "ftp"
744   | PortNumber Int      -- User defined Port Number
745   | UnixSocket String   -- Unix family socket in file system
746
747 type Hostname = String
748 \end{verbatim}
749
750 Various examples of networking Haskell code are provided in
751 \tr{ghc/misc/examples/}, notably the \tr{net???/Main.hs} programs.
752
753 %************************************************************************
754 %*                                                                      *
755 \subsection[HBC-library]{The HBC system library}
756 \index{HBC system library}
757 \index{system library, HBC}
758 %*                                                                      *
759 %************************************************************************
760
761 This documentation is stolen directly from the HBC distribution.  The
762 modules that GHC does not support (because they require HBC-specific
763 extensions) are omitted.
764
765 \begin{description}
766 \item[\tr{ListUtil}:]
767 \index{ListUtil module (HBC library)}%
768 Various useful functions involving lists that are missing from the
769 \tr{Prelude}:
770 \begin{verbatim}
771 assoc :: (Eq c) => (a -> b) -> b -> [(c, a)] -> c -> b
772         -- assoc f d l k looks for k in the association list l, if it
773         -- is found f is applied to the value, otherwise d is returned.
774 concatMap :: (a -> [b]) -> [a] -> [b]
775         -- flattening map (LML's concmap)
776 unfoldr :: (a -> (b, a)) -> (a -> Bool) -> a -> [b]
777         -- unfoldr f p x repeatedly applies f to x until (p x) holds.
778         -- (f x) should give a list element and a new x.
779 mapAccuml :: (a -> b -> (a, c)) -> a -> [b] -> (a, [c])
780         -- mapAccuml f s l maps f over l, but also threads the state s
781         -- through (LML's mapstate).
782 union :: (Eq a) => [a] -> [a] -> [a]
783         -- union of two lists
784 intersection :: (Eq a) => [a] -> [a] -> [a]
785         -- intersection of two lists
786 chopList :: ([a] -> (b, [a])) -> [a] -> [b]
787         -- LMLs choplist
788 assocDef :: (Eq a) => [(a, b)] -> b -> a -> b
789         -- LMLs assocdef
790 lookup :: (Eq a) => [(a, b)] -> a -> Option b
791         -- lookup l k looks for the key k in the association list l
792         -- and returns an optional value
793 tails :: [a] -> [[a]]
794         -- return all the tails of a list
795 rept :: (Integral a) => a -> b -> [b]
796         -- repeat a value a number of times
797 groupEq :: (a->a->Bool) -> [a] -> [[a]]
798         -- group list elements according to an equality predicate
799 group :: (Eq a) => [a] -> [[a]]
800         -- group according to} ==
801 readListLazily :: (Read a) => String -> [a]
802         -- read a list in a lazy fashion
803 \end{verbatim}
804
805 \item[\tr{Pretty}:]
806 \index{Pretty module (HBC library)}%
807 John Hughes's pretty printing library.  
808 \begin{verbatim}
809 type Context = (Bool, Int, Int, Int)
810 type IText = Context -> [String]
811 text :: String -> IText                 -- just text
812 (~.) :: IText -> IText -> IText         -- horizontal composition
813 (^.) :: IText -> IText -> IText         -- vertical composition
814 separate :: [IText] -> IText            -- separate by spaces
815 nest :: Int -> IText -> IText           -- indent
816 pretty :: Int -> Int -> IText -> String -- format it
817 \end{verbatim}
818
819 \item[\tr{QSort}:]
820 \index{QSort module (HBC library)}%
821 A sort function using quicksort.
822 \begin{verbatim}
823 sortLe :: (a -> a -> Bool) -> [a] -> [a]
824         -- sort le l  sorts l with le as less than predicate
825 sort :: (Ord a) => [a] -> [a]
826         -- sort l  sorts l using the Ord class
827 \end{verbatim}
828
829 \item[\tr{Random}:]
830 \index{Random module (HBC library)}%
831 Random numbers.
832 \begin{verbatim}
833 randomInts :: Int -> Int -> [Int]
834         -- given two seeds gives a list of random Int
835 randomDoubles :: Int -> Int -> [Double]
836         -- random Double with uniform distribution in (0,1)
837 normalRandomDoubles :: Int -> Int -> [Double]
838         -- random Double with normal distribution, mean 0, variance 1
839 \end{verbatim}
840
841 \item[\tr{Trace}:]
842 Simple tracing.  (Note: This comes with GHC anyway.)
843 \begin{verbatim}
844 trace :: String -> a -> a       -- trace x y  prints x and returns y
845 \end{verbatim}
846
847 \item[\tr{Miranda}:]
848 \index{Miranda module (HBC library)}%
849 Functions found in the Miranda library.
850 (Note: Miranda is a registered trade mark of Research Software Ltd.)
851
852 \item[\tr{Word}:]
853 \index{Word module (HBC library)}
854 Bit manipulation.  (GHC doesn't implement absolutely all of this.
855 And don't count on @Word@ being 32 bits on a Alpha...)
856 \begin{verbatim}
857 class Bits a where
858     bitAnd :: a -> a -> a       -- bitwise and
859     bitOr :: a -> a -> a        -- bitwise or
860     bitXor :: a -> a -> a       -- bitwise xor
861     bitCompl :: a -> a          -- bitwise negation
862     bitRsh :: a -> Int -> a     -- bitwise right shift
863     bitLsh :: a -> Int -> a     -- bitwise left shift
864     bitSwap :: a -> a           -- swap word halves
865     bit0 :: a                   -- word with least significant bit set
866     bitSize :: a -> Int         -- number of bits in a word
867
868 data Byte                       -- 8  bit quantity
869 data Short                      -- 16 bit quantity
870 data Word                       -- 32 bit quantity
871
872 instance Bits Byte, Bits Short, Bits Word
873 instance Eq Byte, Eq Short, Eq Word
874 instance Ord Byte, Ord Short, Ord Word
875 instance Show Byte, Show Short, Show Word
876 instance Num Byte, Num Short, Num Word
877 wordToShorts :: Word -> [Short]   -- convert a Word to two Short
878 wordToBytes :: Word -> [Byte]     -- convert a Word to four Byte
879 bytesToString :: [Byte] -> String -- convert a list of Byte to a String (bit by bit)
880 wordToInt :: Word -> Int          -- convert a Word to Int
881 shortToInt :: Short -> Int        -- convert a Short to Int
882 byteToInt :: Byte -> Int          -- convert a Byte to Int
883 \end{verbatim}
884
885 \item[\tr{Time}:]
886 \index{Time module (HBC library)}%
887 Manipulate time values (a Double with seconds since 1970).
888 \begin{verbatim}
889 --               year mon  day  hour min  sec  dec-sec  weekday
890 data Time = Time Int  Int  Int  Int  Int  Int  Double  Int
891 dblToTime :: Double -> Time     -- convert a Double to a Time
892 timeToDbl :: Time -> Double     -- convert a Time to a Double
893 timeToString :: Time -> String  -- convert a Time to a readable String
894 \end{verbatim}
895
896 \item[\tr{Hash}:]
897 \index{Hash module (HBC library)}%
898 Hashing functions.
899 \begin{verbatim}
900 class Hashable a where
901     hash :: a -> Int                            -- hash a value, return an Int
902 -- instances for all Prelude types
903 hashToMax :: (Hashable a) => Int -> a -> Int    -- hash into interval [0..x-1]
904 \end{verbatim}
905
906 \item[\tr{NameSupply}:]
907 \index{NameSupply module (HBC library)}%
908 Functions to generate unique names (Int).
909 \begin{verbatim}
910 type Name = Int
911 initialNameSupply :: NameSupply
912         -- The initial name supply (may be different every
913         -- time the program is run.
914 splitNameSupply :: NameSupply -> (NameSupply,NameSupply)
915         -- split the namesupply into two
916 getName :: NameSupply -> Name
917         -- get the name associated with a name supply
918 \end{verbatim}
919
920 \item[\tr{Parse}:]
921 \index{Parse module (HBC library)}%
922 Higher order functions to build parsers.  With a little care these
923 combinators can be used to build efficient parsers with good error
924 messages.
925 \begin{verbatim}
926 infixr 8 +.+ , ..+ , +.. 
927 infix  6 `act` , >>> , `into` , .> 
928 infixr 4 ||| , ||! , |!! 
929 data ParseResult a b 
930 type Parser a b = a -> Int -> ParseResult a b 
931 (|||) :: Parser a b -> Parser a b -> Parser a b
932         -- Alternative
933 (||!) :: Parser a b -> Parser a b -> Parser a b
934         -- Alternative, but with committed choice
935 (|!!) :: Parser a b -> Parser a b -> Parser a b
936         -- Alternative, but with committed choice
937 (+.+) :: Parser a b -> Parser a c -> Parser a (b,c)
938         -- Sequence
939 (..+) :: Parser a b -> Parser a c -> Parser a c
940         -- Sequence, throw away first part
941 (+..) :: Parser a b -> Parser a c -> Parser a b
942         -- Sequence, throw away second part
943 act   :: Parser a b -> (b->c) -> Parser a c
944         -- Action
945 (>>>) :: Parser a (b,c) -> (b->c->d) -> Parser a d
946         -- Action on two items
947 (.>) :: Parser a b -> c -> Parse a c
948         -- Action ignoring value
949 into :: Parser a b -> (b -> Parser a c) -> Parser a c
950         -- Use a produced value in a parser.
951 succeed b :: Parser a b
952         -- Always succeeds without consuming a token
953 failP :: Parser a b
954         -- Always fails.
955 many :: Parser a b -> Parser a [b]
956         -- Kleene star
957 many1 :: Parser a b -> Parser a [b]
958         -- Kleene plus
959 count :: Parser a b -> Int -> Parser a [b]
960         -- Parse an exact number of items
961 sepBy1 :: Parser a b -> Parser a c -> Parser a [b]
962         -- Non-empty sequence of items separated by something
963 sepBy :: Parser a b -> Parser a c -> Parser a [b]
964         -- Sequence of items separated by something
965 lit :: (Eq a, Show a) => a -> Parser [a] a
966         -- Recognise a literal token from a list of tokens
967 litp :: String -> (a->Bool) -> Parser [a] a
968         -- Recognise a token with a predicate.
969         -- The string is a description for error messages.
970 testp :: String -> (a -> Bool) -> (Parser b a) -> Parser b a
971         -- Test a semantic value. 
972 token :: (a -> Either String (b, a)) -> Parser a b
973         -- General token recogniser.
974 parse :: Parser a b -> a -> Either ([String], a) [(b, a)]
975         -- Do a parse.  Return either error (possible tokens and rest
976         -- of tokens) or all possible parses.
977 sParse :: (Show a) => (Parser [a] b) -> [a] -> Either String b
978         -- Simple parse.  Return error message or result.
979 \end{verbatim}
980
981 %%%simpleLex :: String -> [String]              -- A simple (but useful) lexical analyzer
982
983 \item[\tr{Native}:]
984 \index{Native module (HBC library)}%
985 Functions to convert the primitive types \tr{Int}, \tr{Float}, and \tr{Double} to
986 their native representation as a list of bytes (\tr{Char}).  If such a list
987 is read/written to a file it will have the same format as when, e.g.,
988 C read/writes the same kind of data.
989 \begin{verbatim}
990 type Bytes = [Char] -- A byte stream is just a list of characters
991
992 class Native a where 
993     showBytes     :: a -> Bytes -> Bytes
994         -- prepend the representation of an item the a byte stream
995     listShowBytes :: [a] -> Bytes -> Bytes
996         -- prepend the representation of a list of items to a stream
997         -- (may be more efficient than repeating showBytes).
998     readBytes     :: Bytes -> Maybe (a, Bytes)
999         -- get an item from the stream and return the rest,
1000         -- or fail if the stream is to short.
1001     listReadBytes :: Int -> Bytes -> Maybe ([a], Bytes)
1002         -- read n items from a stream.
1003
1004 instance Native Int 
1005 instance Native Float 
1006 instance Native Double 
1007 instance (Native a, Native b) => Native (a,b)
1008         -- juxtaposition of the two items
1009 instance (Native a, Native b, Native c) => Native (a, b, c)
1010         -- juxtaposition of the three items
1011 instance (Native a) => Native [a]
1012         -- an item count in an Int followed by the items
1013
1014 shortIntToBytes :: Int -> Bytes -> Bytes
1015         -- Convert an Int to what corresponds to a short in C.
1016 bytesToShortInt :: Bytes -> Maybe (Int, Bytes)
1017         -- Get a short from a byte stream and convert to an Int.
1018
1019 showB :: (Native a) => a -> Bytes       -- Simple interface to showBytes.
1020 readB :: (Native a) => Bytes -> a       -- Simple interface to readBytes.
1021 \end{verbatim}
1022
1023 \item[\tr{Number}:]
1024 \index{Number module (HBC library)}%
1025 Simple numbers that belong to all numeric classes and behave like
1026 a naive user would expect (except that printing is still ugly).
1027 (NB: GHC does not provide a magic way to use \tr{Numbers} everywhere,
1028 but you should be able to do it with normal \tr{import}ing and
1029 \tr{default}ing.)
1030 \begin{verbatim}
1031 data Number                     -- The type itself.
1032 instance ...                    -- All reasonable instances.
1033 isInteger :: Number -> Bool     -- Test if a Number is an integer.
1034 \end{verbatim}
1035 \end{description}
1036
1037 %************************************************************************
1038 %*                                                                      *
1039 \subsection[contrib-library]{The `contrib' system library}
1040 \index{contrib system library}
1041 \index{system library, contrib}
1042 %*                                                                      *
1043 %************************************************************************
1044
1045 Just for a bit of fun, we took all the old contributed ``Haskell
1046 library'' code---Stephen J.~Bevan the main hero, converted it to
1047 Haskell~1.3 and heaved it into a \tr{contrib} system library.  It is
1048 mostly code for numerical methods (@SetMap@ is an exception); we have
1049 {\em no idea} whether it is any good or not.
1050
1051 The modules provided are:
1052 @Adams_Bashforth_Approx@,
1053 @Adams_Predictor_Corrector_Approx@,
1054 @Choleski_Factorization@,
1055 @Crout_Reduction@,
1056 @Cubic_Spline@,
1057 @Fixed_Point_Approx@,
1058 @Gauss_Seidel_Iteration@,
1059 @Hermite_Interpolation@,
1060 @Horner@,
1061 @Jacobi_Iteration@,
1062 @LLDecompMethod@,
1063 @Least_Squares_Fit@,
1064 @Matrix_Ops@,
1065 @Neville_Iterated_Interpolation@,
1066 @Newton_Cotes@,
1067 @Newton_Interpolatory_Divided_Difference@,
1068 @Newton_Raphson_Approx@,
1069 @Runge_Kutta_Approx@,
1070 @SOR_Iteration@,
1071 @Secant_Approx@,
1072 @SetMap@,
1073 @Steffensen_Approx@,
1074 @Taylor_Approx@, and
1075 @Vector_Ops@.