fc81f00066df62e264502c24fbd59f3cb4e6fe10
[ghc-hetmet.git] / ghc / tests / programs / ipoole_spec_class / Lib.lhs
1 %\documentstyle[a4wIde,11pt]{report}
2 %\begin{document}
3 %\section{Lib.lgs --- Some miscellaneous functions}
4
5 %\begin{verbatim}
6
7 > module Lib where
8 > import Char(isDigit) -- 1.3
9 > import GoferPreludeBits
10
11
12 %               Copyright (C) 1993  Medical Research Council
13 %
14 % SCCS: %W% %G%
15 %
16 %  MODIFICATIONS
17 %  ----------
18 % 18-01-94       ipoole  added toDouble
19 % 08-11-93       ipoole  added toFloat
20 % 08-11-93       derekc  added Coord2
21 % 04-08-93       ipoole  now compiles with hbc and ghc-0.16.  added seq etc
22 % 18-08-93       ipoole  appended mrclib.lgs
23 % 09-06-93       ipoole  fixed strToFloat "0.0" bug
24 % 11-03-93       derekc  added position, occurences, strToFloat, isDecimalFracn
25 % 11-03-93       derekc  strToInt, isNat, isInt <- IOapp.lgs,
26 %                        trace -> IOapp.lgs
27 % 02-03-93       derekc  newStyleIdentifiersUsed, put under sccs
28 % 23-02-03       ipoole  deleted strToInt
29 % 14-02-93       ipoole  now no need for sqrt or truncate (use iSqrt)
30 % 08-11-92       ipoole  type coord moved in from mrclib, and added to
31 % 07-11-92       ipoole  added map2, numVal
32
33 %\end{verbatim}
34
35
36 \subsection{Miranda equivalents}
37 %------------------------------------------------------------------------------
38
39 \begin{Def}{hd, tail, map2, numVal}
40 These definitions are included to make the conversion of Miranda programs
41 into Gofer just a little easier. In general, prefer the Gofer forms.
42 \begin{vb}
43
44 > hd = head
45 > tl = tail
46 > map2 = zipWith
47 > numVal = strToInt    -- NB capitalised to meet SADLI coding standard
48
49 \end{verbatim}\end{vb}\end{Def}
50
51
52 \subsection{Standard Numerical Functions}
53 %------------------------------------------------------------------------------
54
55 \begin{Def}{absolute}~~\begin{vb}
56
57 > absolute :: Float -> Float
58 > absolute f | f < 0.0   = (-f)
59 >            | otherwise = f
60
61 \end{verbatim}\end{vb}\end{Def}
62
63 \begin{Def}{strToFloat} 
64 A first attempt at converting strings to Floats. This cannot cope with
65 scientific notation, more than 10 significant digits or more than 9 decimal
66 places.  
67 \begin{vb}
68
69 > strToFloat :: String -> Float
70 > strToFloat "" = error "strToFloat (Null)"
71 > strToFloat str
72 >    | isDecimalFraction str = valAsInt / fromInt (10 ^ decimalPlaces str)
73 >    | otherwise             = error ("strToFloat: " ++ str)
74 >      where
75 >         valAsInt
76 >            | sigDigits str' >10 = error "strToFloat: >10 significant digits!"
77 >            | otherwise          = fromInt (strToInt str') :: Float
78 >         str'            =  filter (/='.') str
79 >         sigDigits "0" = 1
80 >         sigDigits (ch:chs) | elem ch ['1'..'9'] =  1 + length chs
81 >                            | otherwise          =  sigDigits chs
82 >         decimalPlaces str 
83 >            | pos  < 0   =  0
84 >            | decs > 9   =  error "strToFloat: >9 decimal places!"
85 >            | otherwise  =  decs
86 >         decs            =  length str - pos - 1
87 >         pos             =  position '.' str
88
89 \end{verbatim}\end{vb}\end{Def}
90
91 \begin{Def}{strToInt}
92 Turn a string containing only digits plus (optionally) leading spaces and 
93 minuses into an integer.
94 \begin{vb}
95
96 > strToInt :: String -> Int
97 > strToInt "" = error "strToInt (Null)"
98 > strToInt (' ':xs) = strToInt xs
99 > strToInt ('-':xs) = (negate . strToInt) xs
100 > strToInt xs
101 >               = loop 0 xs where
102 >           loop n [] = n
103 >           loop n (' ':xs) = n
104 >           loop n (x:xs) | isDigit x = loop (10*n+(fromEnum x - fromEnum '0')) xs
105 >                         | otherwise = error ("strToInt: " ++ xs)
106
107 > toFloat :: Real a => a -> Float
108 > toFloat = fromRational . toRational
109
110 > toDouble :: Real a => a -> Double
111 > toDouble = fromRational . toRational
112
113 \end{verbatim}\end{vb}\end{Def}
114
115 \begin{Def}{isInt}~~\begin{vb}
116
117 > isInt :: String -> Bool
118 > isInt [] = False
119 > isInt ('-':l) = isNat l
120 > isInt l = isNat l
121
122 \end{verbatim}\end{vb}\end{Def}
123
124 \begin{Def}{isNat}~~\begin{vb}
125
126 > isNat :: String -> Bool
127 > isNat [] = False
128 > isNat l = all isDigit l
129
130 \end{verbatim}\end{vb}\end{Def}
131
132 \begin{Def}{isDecimalFraction}~~\begin{vb}
133
134 > isDecimalFraction :: String -> Bool
135 > isDecimalFraction [] = False
136 > isDecimalFraction str = isInt str' && ((occurences '.' str) <= 1)
137 >   where str' = filter (/='.') str
138
139 \end{verbatim}\end{vb}\end{Def}
140
141 \begin{Def}{iSqrt}~~\begin{vb}
142
143 > iSqrt :: Int -> Int
144 > iSqrt = truncate . (+ 0.5) . sqrt . fromInt
145
146 \end{verbatim}\end{vb}\end{Def}
147
148 \begin{Def}{hugenum}~~\begin{vb}
149
150 > hugenum = 2147483647::Int  -- largest integer
151
152 \end{verbatim}\end{vb}\end{Def}
153
154
155 \subsection{Other general functions}
156 %------------------------------------------------------------------------------
157
158 \begin{Def}{tupled}~~\begin{vb}
159
160 > tupled :: (a -> b) -> (a, a) -> (b, b)
161 > tupled f (x, y) = (f x, f y)
162
163 \end{verbatim}\end{vb}\end{Def}
164
165 \begin{Def}{occurences}~~\begin{vb}
166
167 > occurences :: Eq a => a -> [a] -> Int
168 > occurences a [] = 0
169 > occurences a (a':as) 
170 >            | a == a'   =  1 + occurences a as
171 >            | otherwise =      occurences a as
172
173 \end{verbatim}\end{vb}\end{Def}
174
175 \begin{Def}{position} 
176 Return the index of the given element in the list, or (-1)
177 if it is not present.
178 \begin{vb}
179
180 > position :: Eq a => a -> [a] -> Int
181 > position a as = posit 0 a as
182 >    where
183 >       posit n a [] = -1
184 >       posit n a (a':as)  | a==a'     =  n
185 >                          | otherwise =  posit (n+1) a as
186
187 \end{verbatim}\end{vb}\end{Def}
188
189 \subsection{Type Coord}
190 %------------------------------------------------------------------------------
191
192 \begin{Def}{Coord}~~\begin{vb}
193
194 > type Coord  = (Int,Int)
195 > type Coord2 = Coord
196
197 \end{verbatim}\end{vb}\end{Def}
198
199 \begin{Def}{sqDistance}~~\begin{vb}
200
201 > sqDistance (x1,y1) (x2,y2) = (x1-x2)^2 + (y1-y2)^2
202
203 \end{verbatim}\end{vb}\end{Def}
204
205 \begin{Def}{scaleCoord}~~\begin{vb}
206
207 > scaleCoord :: Float -> Coord -> Coord
208 > scaleCoord s (x,y) = (round ((fromInt x) * s),
209 >                        round ((fromInt y) * s))
210
211 \end{verbatim}\end{vb}\end{Def}
212
213 \begin{Def}{addCoord}~~\begin{vb}
214
215 > addCoord (x1,y1) (x2, y2) = (x1+x2, y1+y2)
216
217 \end{verbatim}\end{vb}\end{Def}
218
219 \begin{Def}{subCoord}~~\begin{vb}
220
221 > subCoord (x1,y1) (x2, y2) = (x1-x2, y1-y2)
222
223 \end{verbatim}\end{vb}\end{Def}
224
225 \begin{Def}{relativeTo}~~\begin{vb}
226
227 > relativeTo (x',y') (x,y) = (x - x', y - y')
228
229 \end{verbatim}\end{vb}\end{Def}
230
231 \begin{Def}{inside}
232 Is a point inside the rectangle with the given boxCorners?
233 \begin{vb}
234
235 > inside :: Coord -> (Coord,Coord) -> Bool        
236 > (x,y) `inside` ((blx,bly),(trx,try)) =
237 >           (blx <= x) && (x <= trx)  &&  (bly <= y) && (y <= try)
238
239 \end{verbatim}\end{vb}\end{Def}
240
241 #ifndef __GLASGOW_HASKELL__
242
243 \begin{Dec}{Coords are Nums}
244 Tuples are already members of Text, so nothing is needed to implement
245 Coord as a member of text (I think). But
246 let's make Coord an instance of class Num, in part at least:
247 \begin{vb}
248
249 > instance (Num a, Num b) => Num (a,b) where
250 >       (+) = addCoord
251 >       (-) = subCoord
252 >       negate (x,y) = (-x,-y)
253 > --    abs (x,y) = (abs x, abs y)            
254 > --    signum (x,y) = (signum x, signum y)
255
256 \end{verbatim}\end{vb}\end{Dec}
257
258 \begin{Def}{Coord3}
259 Coord3 will similarly come in handy:
260 \begin{vb}
261
262 > type Coord3 = (Int, Int, Int)
263
264 > instance (Num a, Num b, Num c) => Num (a,b,c) where
265 >       (x1,y1,z1) + (x2,y2,z2) = (x1+x2, y1+y2, z1+z2)
266 >       (x1,y1,z1) - (x2,y2,z2) = (x1-x2, y1-y2, z1-z2)
267 >       negate (x,y,z) = (-x,-y,-z)
268 > --    abs (x,y,z) = (abs x, abs y, abs z)            
269 > --    signum (x,y,z) = (signum x, signum y, signum z)
270
271 \end{verbatim}\end{vb}\end{Def}
272
273 #endif __GLASGOW_HASKELL__
274
275 % Here to end was mrclib.lgs
276
277
278 \begin{Def}{sortBy} accepts a function and a list, and returns the list
279 ordered (ascending) according to the given function.  It can thus be used
280 on lists of structured types for which the \verb@'<'@ operator is not
281 valid, e.g. 
282 \begin{vb}
283
284                sortBy fst [(4,"Fred"), (2,"Bert"), (6,"Gill")]
285                       --> [(2,"Bert"), (4,"Fred"), (6,"Gill")]
286
287 > sortBy :: Ord b => (a->b) -> [a] -> [a]
288 > sortBy v [] = []
289 > sortBy v (a:x) 
290 >       = (sortBy v left) ++ [a] ++ (sortBy v right)
291 >         where
292 >         left  = [b | b <- x, (v b) <= va ]
293 >         right = [b | b <- x, (v b)  > va ]
294 >         va = v a
295
296 \end{verbatim}\end{vb}\end{Def}
297
298 \begin{Def}{maxBy} returns the the element in the given list which yields the 
299 greatest value under the given function.
300 \begin{vb}
301
302 > maxBy :: Ord b => (a->b) -> [a] -> a
303 > maxBy f = foldl1 max2by
304 >               where max2by a b | (f a) >= (f b)  = a
305 >                                | otherwise       = b
306
307 \end{verbatim}\end{vb}\end{Def}
308
309 \begin{Def}{minBy} similar to \verb@maxBy@
310 \begin{vb}
311
312 > minBy :: Ord b => (a->b) -> [a] -> a
313 > minBy f = foldl1 min2By
314 >               where min2By a b | (f a) <= (f b) = a
315 >                                | otherwise      = b
316
317 \begin{Def}{readTable} 
318 converts a text table of numbers (eg from a `feature file').
319 into [[Int]]
320 \begin{vb}
321
322 > readTable:: String -> [[Int]]
323 > readTable = map (map strToInt) . map words . lines
324
325 \end{verbatim}\end{vb}\end{Def}
326
327 \begin{Def}{writeTable} the converse of readTable.
328 \begin{vb}
329
330 > writeTable:: Show{-was:Text-} a => [[a]] -> String
331 > writeTable = unlines . map unwords . (map . map) show
332
333 \end{verbatim}\end{vb}\end{Def}
334
335 \begin{Def}{writeTableN} like readTable, but number each line.
336 \begin{vb}
337
338 > writeTableN:: Show{-was:Text-} a => [[a]] -> String
339 > writeTableN = layn . map unwords . (map . map) show
340
341 \end{verbatim}\end{vb}\end{Def}
342
343 \begin{Def}{plotSurface} 
344 invokes the program ``surface'' to plot a 2--D surface via 
345 stoX. The \verb@switches@ parameter will be passed to ``surface'' 
346 (see "man l surface") and for a first try can be "".
347 \begin{vb}
348
349 > plotSurface :: String -> [[Int]] -> FailCont -> SuccCont -> Dialogue
350 > plotSurface switches table fail succ =
351 >   writeFile "surfacedata" surfData fail
352 >     (writeFile "plotsurf" surfCommand fail succ)
353 >     where
354 >       surfData = "Plotsurface" ++ "\n" ++
355 >                  show yLen ++ " " ++ show xLen ++ "\n" ++
356 >                  writeTable table
357 >       surfCommand = "cat surfacedata | surface " ++ switches ++ " | stoX\n"
358 >       xLen = length (table!!0)
359 >       yLen = length table
360
361 \end{verbatim}\end{vb}\end{Def}
362
363 \begin{Def}{quadSolve} 
364 solve the quadratic equation $a x^2 + b x + c = 0$ for $x$, if
365 possible.  Both solutions are returned, in ascending order.  
366 Deals sensibly with $a=0$.
367 \begin{vb}
368
369 > quadSolve :: Float -> Float -> Float -> (Float, Float)
370 > quadSolve a b c
371 >    | a /= 0.0 && s1 > s2   =  (s1, s2)
372 >    | a /= 0.0 && s1 <= s2  =  (s2, s1) 
373 >    | otherwise           =  (-c/b, -c/b) 
374 >    where
375 >       s1 = (-b + root) / (2.0 * a)
376 >       s2 = (-b - root) / (2.0 * a)
377 >       bs4ac = b*b - 4.0*a*c
378 >       root | bs4ac >= 0.0  =  {-sqrt-} bs4ac 
379 >            | otherwise    
380 >                 = error ("quadSolve " ++ show [a,b,c] ++ " - no solution!") 
381
382 \end{verbatim}\end{vb}\end{Def}
383
384 \begin{Def}{number}
385 Here is a utility to check that a number is a (non negative) number.
386 \begin{vb}
387
388 > number :: String -> Bool
389 > number [] = False
390 > number [a] = isDigit a
391 > number (a:l) = isDigit a && (number l)
392
393 \end{verbatim}\end{vb}\end{Def}
394
395
396
397 \sectionHH{Some strict functions}
398
399 #ifdef Gofer
400
401 \begin{vb}
402
403 > seq :: a -> b -> b
404 > seq a b = strict (const b) a
405
406 > hyperSeq :: [a] -> b -> b
407 > hyperSeq as b = foldr seq b as
408
409 > hyperStrict :: ([a] -> b) -> ([a] -> b)
410 > hyperStrict f x = hyperSeq x (f x)
411
412 \end{verbatim}\end{vb}
413
414 #endif
415
416 %\end{document}