Moved def. of emptyP
[ghc-base.git] / GHC / PArr.hs
1 {-# OPTIONS_GHC -fparr -funbox-strict-fields #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.PArr
6 -- Copyright   :  (c) 2001-2002 Manuel M T Chakravarty & Gabriele Keller
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  Manuel M. T. Chakravarty <chak@cse.unsw.edu.au>
10 -- Stability   :  internal
11 -- Portability :  non-portable (GHC Extensions)
12 --
13 --  Basic implementation of Parallel Arrays.
14 --
15 --  This module has two functions: (1) It defines the interface to the
16 --  parallel array extension of the Prelude and (2) it provides a vanilla
17 --  implementation of parallel arrays that does not require to flatten the
18 --  array code.  The implementation is not very optimised.
19 --
20 --- DOCU ----------------------------------------------------------------------
21 --
22 --  Language: Haskell 98 plus unboxed values and parallel arrays
23 --
24 --  The semantic difference between standard Haskell arrays (aka "lazy
25 --  arrays") and parallel arrays (aka "strict arrays") is that the evaluation
26 --  of two different elements of a lazy array is independent, whereas in a
27 --  strict array either non or all elements are evaluated.  In other words,
28 --  when a parallel array is evaluated to WHNF, all its elements will be
29 --  evaluated to WHNF.  The name parallel array indicates that all array
30 --  elements may, in general, be evaluated to WHNF in parallel without any
31 --  need to resort to speculative evaluation.  This parallel evaluation
32 --  semantics is also beneficial in the sequential case, as it facilitates
33 --  loop-based array processing as known from classic array-based languages,
34 --  such as Fortran.
35 --
36 --  The interface of this module is essentially a variant of the list
37 --  component of the Prelude, but also includes some functions (such as
38 --  permutations) that are not provided for lists.  The following list
39 --  operations are not supported on parallel arrays, as they would require the
40 --  availability of infinite parallel arrays: `iterate', `repeat', and `cycle'.
41 --
42 --  The current implementation is quite simple and entirely based on boxed
43 --  arrays.  One disadvantage of boxed arrays is that they require to
44 --  immediately initialise all newly allocated arrays with an error thunk to
45 --  keep the garbage collector happy, even if it is guaranteed that the array
46 --  is fully initialised with different values before passing over the
47 --  user-visible interface boundary.  Currently, no effort is made to use
48 --  raw memory copy operations to speed things up.
49 --
50 --- TODO ----------------------------------------------------------------------
51 --
52 --  * We probably want a standard library `PArray' in addition to the prelude
53 --    extension in the same way as the standard library `List' complements the
54 --    list functions from the prelude.
55 --
56 --  * Currently, functions that emphasis the constructor-based definition of
57 --    lists (such as, head, last, tail, and init) are not supported.  
58 --
59 --    Is it worthwhile to support the string processing functions lines,
60 --    words, unlines, and unwords?  (Currently, they are not implemented.)
61 --
62 --    It can, however, be argued that it would be worthwhile to include them
63 --    for completeness' sake; maybe only in the standard library `PArray'.
64 --
65 --  * Prescans are often more useful for array programming than scans.  Shall
66 --    we include them into the Prelude or the library?
67 --
68 --  * Due to the use of the iterator `loop', we could define some fusion rules
69 --    in this module.
70 --
71 --  * We might want to add bounds checks that can be deactivated.
72 --
73
74 module GHC.PArr (
75   -- [::],              -- Built-in syntax
76
77   mapP,                 -- :: (a -> b) -> [:a:] -> [:b:]
78   (+:+),                -- :: [:a:] -> [:a:] -> [:a:]
79   filterP,              -- :: (a -> Bool) -> [:a:] -> [:a:]
80   concatP,              -- :: [:[:a:]:] -> [:a:]
81   concatMapP,           -- :: (a -> [:b:]) -> [:a:] -> [:b:]
82 --  head, last, tail, init,   -- it's not wise to use them on arrays
83   nullP,                -- :: [:a:] -> Bool
84   lengthP,              -- :: [:a:] -> Int
85   (!:),                 -- :: [:a:] -> Int -> a
86   foldlP,               -- :: (a -> b -> a) -> a -> [:b:] -> a
87   foldl1P,              -- :: (a -> a -> a) ->      [:a:] -> a
88   scanlP,               -- :: (a -> b -> a) -> a -> [:b:] -> [:a:]
89   scanl1P,              -- :: (a -> a -> a) ->      [:a:] -> [:a:]
90   foldrP,               -- :: (a -> b -> b) -> b -> [:a:] -> b
91   foldr1P,              -- :: (a -> a -> a) ->      [:a:] -> a
92   scanrP,               -- :: (a -> b -> b) -> b -> [:a:] -> [:b:]
93   scanr1P,              -- :: (a -> a -> a) ->      [:a:] -> [:a:]
94 --  iterate, repeat,          -- parallel arrays must be finite
95   singletonP,           -- :: a -> [:a:]
96   emptyP,               -- :: [:a:]
97   replicateP,           -- :: Int -> a -> [:a:]
98 --  cycle,                    -- parallel arrays must be finite
99   takeP,                -- :: Int -> [:a:] -> [:a:]
100   dropP,                -- :: Int -> [:a:] -> [:a:]
101   splitAtP,             -- :: Int -> [:a:] -> ([:a:],[:a:])
102   takeWhileP,           -- :: (a -> Bool) -> [:a:] -> [:a:]
103   dropWhileP,           -- :: (a -> Bool) -> [:a:] -> [:a:]
104   spanP,                -- :: (a -> Bool) -> [:a:] -> ([:a:], [:a:])
105   breakP,               -- :: (a -> Bool) -> [:a:] -> ([:a:], [:a:])
106 --  lines, words, unlines, unwords,  -- is string processing really needed
107   reverseP,             -- :: [:a:] -> [:a:]
108   andP,                 -- :: [:Bool:] -> Bool
109   orP,                  -- :: [:Bool:] -> Bool
110   anyP,                 -- :: (a -> Bool) -> [:a:] -> Bool
111   allP,                 -- :: (a -> Bool) -> [:a:] -> Bool
112   elemP,                -- :: (Eq a) => a -> [:a:] -> Bool
113   notElemP,             -- :: (Eq a) => a -> [:a:] -> Bool
114   lookupP,              -- :: (Eq a) => a -> [:(a, b):] -> Maybe b
115   sumP,                 -- :: (Num a) => [:a:] -> a
116   productP,             -- :: (Num a) => [:a:] -> a
117   maximumP,             -- :: (Ord a) => [:a:] -> a
118   minimumP,             -- :: (Ord a) => [:a:] -> a
119   zipP,                 -- :: [:a:] -> [:b:]          -> [:(a, b)   :]
120   zip3P,                -- :: [:a:] -> [:b:] -> [:c:] -> [:(a, b, c):]
121   zipWithP,             -- :: (a -> b -> c)      -> [:a:] -> [:b:] -> [:c:]
122   zipWith3P,            -- :: (a -> b -> c -> d) -> [:a:]->[:b:]->[:c:]->[:d:]
123   unzipP,               -- :: [:(a, b)   :] -> ([:a:], [:b:])
124   unzip3P,              -- :: [:(a, b, c):] -> ([:a:], [:b:], [:c:])
125
126   -- overloaded functions
127   --
128   enumFromToP,          -- :: Enum a => a -> a      -> [:a:]
129   enumFromThenToP,      -- :: Enum a => a -> a -> a -> [:a:]
130
131   -- the following functions are not available on lists
132   --
133   toP,                  -- :: [a] -> [:a:]
134   fromP,                -- :: [:a:] -> [a]
135   sliceP,               -- :: Int -> Int -> [:e:] -> [:e:]
136   foldP,                -- :: (e -> e -> e) -> e -> [:e:] -> e
137   fold1P,               -- :: (e -> e -> e) ->      [:e:] -> e
138   permuteP,             -- :: [:Int:] -> [:e:] ->          [:e:]
139   bpermuteP,            -- :: [:Int:] -> [:e:] ->          [:e:]
140   dpermuteP,            -- :: [:Int:] -> [:e:] -> [:e:] -> [:e:]
141   crossP,               -- :: [:a:] -> [:b:] -> [:(a, b):]
142   crossMapP,            -- :: [:a:] -> (a -> [:b:]) -> [:(a, b):]
143   indexOfP              -- :: (a -> Bool) -> [:a:] -> [:Int:]
144 ) where
145
146 #ifndef __HADDOCK__
147
148 import Prelude
149
150 import GHC.ST   ( ST(..), STRep, runST )
151 import GHC.Exts ( Int#, Array#, Int(I#), MutableArray#, newArray#,
152                   unsafeFreezeArray#, indexArray#, writeArray#, (<#), (>=#) )
153
154 infixl 9  !:
155 infixr 5  +:+
156 infix  4  `elemP`, `notElemP`
157
158
159 -- representation of parallel arrays
160 -- ---------------------------------
161
162 -- this rather straight forward implementation maps parallel arrays to the
163 -- internal representation used for standard Haskell arrays in GHC's Prelude
164 -- (EXPORTED ABSTRACTLY)
165 --
166 -- * This definition *must* be kept in sync with `TysWiredIn.parrTyCon'!
167 --
168 data [::] e = PArr Int# (Array# e)
169
170
171 -- exported operations on parallel arrays
172 -- --------------------------------------
173
174 -- operations corresponding to list operations
175 --
176
177 mapP   :: (a -> b) -> [:a:] -> [:b:]
178 mapP f  = fst . loop (mapEFL f) noAL
179
180 (+:+)     :: [:a:] -> [:a:] -> [:a:]
181 a1 +:+ a2  = fst $ loop (mapEFL sel) noAL (enumFromToP 0 (len1 + len2 - 1))
182                        -- we can't use the [:x..y:] form here for tedious
183                        -- reasons to do with the typechecker and the fact that
184                        -- `enumFromToP' is defined in the same module
185              where
186                len1 = lengthP a1
187                len2 = lengthP a2
188                --
189                sel i | i < len1  = a1!:i
190                      | otherwise = a2!:(i - len1)
191
192 filterP   :: (a -> Bool) -> [:a:] -> [:a:]
193 filterP p  = fst . loop (filterEFL p) noAL
194
195 concatP     :: [:[:a:]:] -> [:a:]
196 concatP xss  = foldlP (+:+) [::] xss
197
198 concatMapP   :: (a -> [:b:]) -> [:a:] -> [:b:]
199 concatMapP f  = concatP . mapP f
200
201 --  head, last, tail, init,   -- it's not wise to use them on arrays
202
203 nullP      :: [:a:] -> Bool
204 nullP [::]  = True
205 nullP _     = False
206
207 lengthP             :: [:a:] -> Int
208 lengthP (PArr n# _)  = I# n#
209
210 (!:) :: [:a:] -> Int -> a
211 (!:)  = indexPArr
212
213 foldlP     :: (a -> b -> a) -> a -> [:b:] -> a
214 foldlP f z  = snd . loop (foldEFL (flip f)) z
215
216 foldl1P        :: (a -> a -> a) -> [:a:] -> a
217 foldl1P f [::]  = error "Prelude.foldl1P: empty array"
218 foldl1P f a     = snd $ loopFromTo 1 (lengthP a - 1) (foldEFL f) (a!:0) a
219
220 scanlP     :: (a -> b -> a) -> a -> [:b:] -> [:a:]
221 scanlP f z  = fst . loop (scanEFL (flip f)) z
222
223 scanl1P        :: (a -> a -> a) -> [:a:] -> [:a:]
224 scanl1P f [::]  = error "Prelude.scanl1P: empty array"
225 scanl1P f a     = fst $ loopFromTo 1 (lengthP a - 1) (scanEFL f) (a!:0) a
226
227 foldrP :: (a -> b -> b) -> b -> [:a:] -> b
228 foldrP  = error "Prelude.foldrP: not implemented yet" -- FIXME
229
230 foldr1P :: (a -> a -> a) -> [:a:] -> a
231 foldr1P  = error "Prelude.foldr1P: not implemented yet" -- FIXME
232
233 scanrP :: (a -> b -> b) -> b -> [:a:] -> [:b:]
234 scanrP  = error "Prelude.scanrP: not implemented yet" -- FIXME
235
236 scanr1P :: (a -> a -> a) -> [:a:] -> [:a:]
237 scanr1P  = error "Prelude.scanr1P: not implemented yet" -- FIXME
238
239 --  iterate, repeat           -- parallel arrays must be finite
240
241 singletonP             :: a -> [:a:]
242 {-# INLINE singletonP #-}
243 singletonP e = replicateP 1 e
244   
245 emptyP:: [:a:]
246 {- NOINLINE emptyP #-}
247 emptyP = replicateP 0 undefined
248
249
250 replicateP             :: Int -> a -> [:a:]
251 {-# INLINE replicateP #-}
252 replicateP n e  = runST (do
253   marr# <- newArray n e
254   mkPArr n marr#)
255
256 --  cycle                     -- parallel arrays must be finite
257
258 takeP   :: Int -> [:a:] -> [:a:]
259 takeP n  = sliceP 0 (n - 1)
260
261 dropP     :: Int -> [:a:] -> [:a:]
262 dropP n a  = sliceP n (lengthP a - 1) a
263
264 splitAtP      :: Int -> [:a:] -> ([:a:],[:a:])
265 splitAtP n xs  = (takeP n xs, dropP n xs)
266
267 takeWhileP :: (a -> Bool) -> [:a:] -> [:a:]
268 takeWhileP  = error "Prelude.takeWhileP: not implemented yet" -- FIXME
269
270 dropWhileP :: (a -> Bool) -> [:a:] -> [:a:]
271 dropWhileP  = error "Prelude.dropWhileP: not implemented yet" -- FIXME
272
273 spanP :: (a -> Bool) -> [:a:] -> ([:a:], [:a:])
274 spanP  = error "Prelude.spanP: not implemented yet" -- FIXME
275
276 breakP   :: (a -> Bool) -> [:a:] -> ([:a:], [:a:])
277 breakP p  = spanP (not . p)
278
279 --  lines, words, unlines, unwords,  -- is string processing really needed
280
281 reverseP   :: [:a:] -> [:a:]
282 reverseP a  = permuteP (enumFromThenToP (len - 1) (len - 2) 0) a
283                        -- we can't use the [:x, y..z:] form here for tedious
284                        -- reasons to do with the typechecker and the fact that
285                        -- `enumFromThenToP' is defined in the same module
286               where
287                 len = lengthP a
288
289 andP :: [:Bool:] -> Bool
290 andP  = foldP (&&) True
291
292 orP :: [:Bool:] -> Bool
293 orP  = foldP (||) True
294
295 anyP   :: (a -> Bool) -> [:a:] -> Bool
296 anyP p  = orP . mapP p
297
298 allP :: (a -> Bool) -> [:a:] -> Bool
299 allP p  = andP . mapP p
300
301 elemP   :: (Eq a) => a -> [:a:] -> Bool
302 elemP x  = anyP (== x)
303
304 notElemP   :: (Eq a) => a -> [:a:] -> Bool
305 notElemP x  = allP (/= x)
306
307 lookupP :: (Eq a) => a -> [:(a, b):] -> Maybe b
308 lookupP  = error "Prelude.lookupP: not implemented yet" -- FIXME
309
310 sumP :: (Num a) => [:a:] -> a
311 sumP  = foldP (+) 0
312
313 productP :: (Num a) => [:a:] -> a
314 productP  = foldP (*) 1
315
316 maximumP      :: (Ord a) => [:a:] -> a
317 maximumP [::]  = error "Prelude.maximumP: empty parallel array"
318 maximumP xs    = fold1P max xs
319
320 minimumP :: (Ord a) => [:a:] -> a
321 minimumP [::]  = error "Prelude.minimumP: empty parallel array"
322 minimumP xs    = fold1P min xs
323
324 zipP :: [:a:] -> [:b:] -> [:(a, b):]
325 zipP  = zipWithP (,)
326
327 zip3P :: [:a:] -> [:b:] -> [:c:] -> [:(a, b, c):]
328 zip3P  = zipWith3P (,,)
329
330 zipWithP         :: (a -> b -> c) -> [:a:] -> [:b:] -> [:c:]
331 zipWithP f a1 a2  = let 
332                       len1 = lengthP a1
333                       len2 = lengthP a2
334                       len  = len1 `min` len2
335                     in
336                     fst $ loopFromTo 0 (len - 1) combine 0 a1
337                     where
338                       combine e1 i = (Just $ f e1 (a2!:i), i + 1)
339
340 zipWith3P :: (a -> b -> c -> d) -> [:a:]->[:b:]->[:c:]->[:d:]
341 zipWith3P f a1 a2 a3 = let 
342                         len1 = lengthP a1
343                         len2 = lengthP a2
344                         len3 = lengthP a3
345                         len  = len1 `min` len2 `min` len3
346                       in
347                       fst $ loopFromTo 0 (len - 1) combine 0 a1
348                       where
349                         combine e1 i = (Just $ f e1 (a2!:i) (a3!:i), i + 1)
350
351 unzipP   :: [:(a, b):] -> ([:a:], [:b:])
352 unzipP a  = (fst $ loop (mapEFL fst) noAL a, fst $ loop (mapEFL snd) noAL a)
353 -- FIXME: these two functions should be optimised using a tupled custom loop
354 unzip3P   :: [:(a, b, c):] -> ([:a:], [:b:], [:c:])
355 unzip3P a  = (fst $ loop (mapEFL fst3) noAL a, 
356               fst $ loop (mapEFL snd3) noAL a,
357               fst $ loop (mapEFL trd3) noAL a)
358              where
359                fst3 (a, _, _) = a
360                snd3 (_, b, _) = b
361                trd3 (_, _, c) = c
362
363 -- instances
364 --
365
366 instance Eq a => Eq [:a:] where
367   a1 == a2 | lengthP a1 == lengthP a2 = andP (zipWithP (==) a1 a2)
368            | otherwise                = False
369
370 instance Ord a => Ord [:a:] where
371   compare a1 a2 = case foldlP combineOrdering EQ (zipWithP compare a1 a2) of
372                     EQ | lengthP a1 == lengthP a2 -> EQ
373                        | lengthP a1 <  lengthP a2 -> LT
374                        | otherwise                -> GT
375                   where
376                     combineOrdering EQ    EQ    = EQ
377                     combineOrdering EQ    other = other
378                     combineOrdering other _     = other
379
380 instance Functor [::] where
381   fmap = mapP
382
383 instance Monad [::] where
384   m >>= k  = foldrP ((+:+) . k      ) [::] m
385   m >>  k  = foldrP ((+:+) . const k) [::] m
386   return x = [:x:]
387   fail _   = [::]
388
389 instance Show a => Show [:a:]  where
390   showsPrec _  = showPArr . fromP
391     where
392       showPArr []     s = "[::]" ++ s
393       showPArr (x:xs) s = "[:" ++ shows x (showPArr' xs s)
394
395       showPArr' []     s = ":]" ++ s
396       showPArr' (y:ys) s = ',' : shows y (showPArr' ys s)
397
398 instance Read a => Read [:a:]  where
399   readsPrec _ a = [(toP v, rest) | (v, rest) <- readPArr a]
400     where
401       readPArr = readParen False (\r -> do
402                                           ("[:",s) <- lex r
403                                           readPArr1 s)
404       readPArr1 s = 
405         (do { (":]", t) <- lex s; return ([], t) }) ++
406         (do { (x, t) <- reads s; (xs, u) <- readPArr2 t; return (x:xs, u) })
407
408       readPArr2 s = 
409         (do { (":]", t) <- lex s; return ([], t) }) ++
410         (do { (",", t) <- lex s; (x, u) <- reads t; (xs, v) <- readPArr2 u; 
411               return (x:xs, v) })
412
413 -- overloaded functions
414 -- 
415
416 -- Ideally, we would like `enumFromToP' and `enumFromThenToP' to be members of
417 -- `Enum'.  On the other hand, we really do not want to change `Enum'.  Thus,
418 -- for the moment, we hope that the compiler is sufficiently clever to
419 -- properly fuse the following definitions.
420
421 enumFromToP     :: Enum a => a -> a -> [:a:]
422 enumFromToP x y  = mapP toEnum (eftInt (fromEnum x) (fromEnum y))
423   where
424     eftInt x y = scanlP (+) x $ replicateP (y - x + 1) 1
425
426 enumFromThenToP       :: Enum a => a -> a -> a -> [:a:]
427 enumFromThenToP x y z  = 
428   mapP toEnum (efttInt (fromEnum x) (fromEnum y) (fromEnum z))
429   where
430     efttInt x y z = scanlP (+) x $ 
431                       replicateP (abs (z - x) `div` abs delta + 1) delta
432       where
433        delta = y - x
434
435 -- the following functions are not available on lists
436 --
437
438 -- create an array from a list (EXPORTED)
439 --
440 toP   :: [a] -> [:a:]
441 toP l  = fst $ loop store l (replicateP (length l) ())
442          where
443            store _ (x:xs) = (Just x, xs)
444
445 -- convert an array to a list (EXPORTED)
446 --
447 fromP   :: [:a:] -> [a]
448 fromP a  = [a!:i | i <- [0..lengthP a - 1]]
449
450 -- cut a subarray out of an array (EXPORTED)
451 --
452 sliceP :: Int -> Int -> [:e:] -> [:e:]
453 sliceP from to a = 
454   fst $ loopFromTo (0 `max` from) (to `min` (lengthP a - 1)) (mapEFL id) noAL a
455
456 -- parallel folding (EXPORTED)
457 --
458 -- * the first argument must be associative; otherwise, the result is undefined
459 --
460 foldP :: (e -> e -> e) -> e -> [:e:] -> e
461 foldP  = foldlP
462
463 -- parallel folding without explicit neutral (EXPORTED)
464 --
465 -- * the first argument must be associative; otherwise, the result is undefined
466 --
467 fold1P :: (e -> e -> e) -> [:e:] -> e
468 fold1P  = foldl1P
469
470 -- permute an array according to the permutation vector in the first argument
471 -- (EXPORTED)
472 --
473 permuteP       :: [:Int:] -> [:e:] -> [:e:]
474 permuteP is es 
475   | isLen /= esLen = error "GHC.PArr: arguments must be of the same length"
476   | otherwise      = runST (do
477                        marr <- newArray isLen noElem
478                        permute marr is es
479                        mkPArr isLen marr)
480   where
481     noElem = error "GHC.PArr.permuteP: I do not exist!"
482              -- unlike standard Haskell arrays, this value represents an
483              -- internal error
484     isLen = lengthP is
485     esLen = lengthP es
486
487 -- permute an array according to the back-permutation vector in the first
488 -- argument (EXPORTED)
489 --
490 -- * the permutation vector must represent a surjective function; otherwise,
491 --   the result is undefined
492 --
493 bpermuteP       :: [:Int:] -> [:e:] -> [:e:]
494 bpermuteP is es  = fst $ loop (mapEFL (es!:)) noAL is
495
496 -- permute an array according to the permutation vector in the first
497 -- argument, which need not be surjective (EXPORTED)
498 --
499 -- * any elements in the result that are not covered by the permutation
500 --   vector assume the value of the corresponding position of the third
501 --   argument 
502 --
503 dpermuteP :: [:Int:] -> [:e:] -> [:e:] -> [:e:]
504 dpermuteP is es dft
505   | isLen /= esLen = error "GHC.PArr: arguments must be of the same length"
506   | otherwise      = runST (do
507                        marr <- newArray dftLen noElem
508                        trans 0 (isLen - 1) marr dft copyOne noAL
509                        permute marr is es
510                        mkPArr dftLen marr)
511   where
512     noElem = error "GHC.PArr.permuteP: I do not exist!"
513              -- unlike standard Haskell arrays, this value represents an
514              -- internal error
515     isLen  = lengthP is
516     esLen  = lengthP es
517     dftLen = lengthP dft
518
519     copyOne e _ = (Just e, noAL)
520
521 -- computes the cross combination of two arrays (EXPORTED)
522 --
523 crossP       :: [:a:] -> [:b:] -> [:(a, b):]
524 crossP a1 a2  = fst $ loop combine (0, 0) $ replicateP len ()
525                 where
526                   len1 = lengthP a1
527                   len2 = lengthP a2
528                   len  = len1 * len2
529                   --
530                   combine _ (i, j) = (Just $ (a1!:i, a2!:j), next)
531                                      where
532                                        next | (i + 1) == len1 = (0    , j + 1)
533                                             | otherwise       = (i + 1, j)
534
535 {- An alternative implementation
536    * The one above is certainly better for flattened code, but here where we
537      are handling boxed arrays, the trade off is less clear.  However, I
538      think, the above one is still better.
539
540 crossP a1 a2  = let
541                   len1 = lengthP a1
542                   len2 = lengthP a2
543                   x1   = concatP $ mapP (replicateP len2) a1
544                   x2   = concatP $ replicateP len1 a2
545                 in
546                 zipP x1 x2
547  -}
548
549 -- |Compute a cross of an array and the arrays produced by the given function
550 -- for the elements of the first array.
551 --
552 crossMapP :: [:a:] -> (a -> [:b:]) -> [:(a, b):]
553 crossMapP a f = let
554                   bs   = mapP f a
555                   segd = mapP lengthP bs
556                   as   = zipWithP replicateP segd a
557                 in
558                 zipP (concatP as) (concatP bs)
559
560 {- The following may seem more straight forward, but the above is very cheap
561    with segmented arrays, as `mapP lengthP', `zipP', and `concatP' are
562    constant time, and `map f' uses the lifted version of `f'.
563
564 crossMapP a f = concatP $ mapP (\x -> mapP ((,) x) (f x)) a
565
566  -}
567
568 -- computes an index array for all elements of the second argument for which
569 -- the predicate yields `True' (EXPORTED)
570 --
571 indexOfP     :: (a -> Bool) -> [:a:] -> [:Int:]
572 indexOfP p a  = fst $ loop calcIdx 0 a
573                 where
574                   calcIdx e idx | p e       = (Just idx, idx + 1)
575                                 | otherwise = (Nothing , idx    )
576
577
578 -- auxiliary functions
579 -- -------------------
580
581 -- internally used mutable boxed arrays
582 --
583 data MPArr s e = MPArr Int# (MutableArray# s e)
584
585 -- allocate a new mutable array that is pre-initialised with a given value
586 --
587 newArray             :: Int -> e -> ST s (MPArr s e)
588 {-# INLINE newArray #-}
589 newArray (I# n#) e  = ST $ \s1# ->
590   case newArray# n# e s1# of { (# s2#, marr# #) ->
591   (# s2#, MPArr n# marr# #)}
592
593 -- convert a mutable array into the external parallel array representation
594 --
595 mkPArr                           :: Int -> MPArr s e -> ST s [:e:]
596 {-# INLINE mkPArr #-}
597 mkPArr (I# n#) (MPArr _ marr#)  = ST $ \s1# ->
598   case unsafeFreezeArray# marr# s1#   of { (# s2#, arr# #) ->
599   (# s2#, PArr n# arr# #) }
600
601 -- general array iterator
602 --
603 -- * corresponds to `loopA' from ``Functional Array Fusion'', Chakravarty &
604 --   Keller, ICFP 2001
605 --
606 loop :: (e -> acc -> (Maybe e', acc))    -- mapping & folding, once per element
607      -> acc                              -- initial acc value
608      -> [:e:]                            -- input array
609      -> ([:e':], acc)
610 {-# INLINE loop #-}
611 loop mf acc arr = loopFromTo 0 (lengthP arr - 1) mf acc arr
612
613 -- general array iterator with bounds
614 --
615 loopFromTo :: Int                        -- from index
616            -> Int                        -- to index
617            -> (e -> acc -> (Maybe e', acc))
618            -> acc
619            -> [:e:]
620            -> ([:e':], acc)
621 {-# INLINE loopFromTo #-}
622 loopFromTo from to mf start arr = runST (do
623   marr      <- newArray (to - from + 1) noElem
624   (n', acc) <- trans from to marr arr mf start
625   arr       <- mkPArr n' marr
626   return (arr, acc))
627   where
628     noElem = error "GHC.PArr.loopFromTo: I do not exist!"
629              -- unlike standard Haskell arrays, this value represents an
630              -- internal error
631
632 -- actual loop body of `loop'
633 --
634 -- * for this to be really efficient, it has to be translated with the
635 --   constructor specialisation phase "SpecConstr" switched on; as of GHC 5.03
636 --   this requires an optimisation level of at least -O2
637 --
638 trans :: Int                            -- index of first elem to process
639       -> Int                            -- index of last elem to process
640       -> MPArr s e'                     -- destination array
641       -> [:e:]                          -- source array
642       -> (e -> acc -> (Maybe e', acc))  -- mutator
643       -> acc                            -- initial accumulator
644       -> ST s (Int, acc)                -- final destination length/final acc
645 {-# INLINE trans #-}
646 trans from to marr arr mf start = trans' from 0 start
647   where
648     trans' arrOff marrOff acc 
649       | arrOff > to = return (marrOff, acc)
650       | otherwise   = do
651                         let (oe', acc') = mf (arr `indexPArr` arrOff) acc
652                         marrOff' <- case oe' of
653                                       Nothing -> return marrOff 
654                                       Just e' -> do
655                                         writeMPArr marr marrOff e'
656                                         return $ marrOff + 1
657                         trans' (arrOff + 1) marrOff' acc'
658
659 -- Permute the given elements into the mutable array.
660 --
661 permute :: MPArr s e -> [:Int:] -> [:e:] -> ST s ()
662 permute marr is es = perm 0
663   where
664     perm i
665       | i == n = return ()
666       | otherwise  = writeMPArr marr (is!:i) (es!:i) >> perm (i + 1)
667       where
668         n = lengthP is
669
670
671 -- common patterns for using `loop'
672 --
673
674 -- initial value for the accumulator when the accumulator is not needed
675 --
676 noAL :: ()
677 noAL  = ()
678
679 -- `loop' mutator maps a function over array elements
680 --
681 mapEFL   :: (e -> e') -> (e -> () -> (Maybe e', ()))
682 {-# INLINE mapEFL #-}
683 mapEFL f  = \e a -> (Just $ f e, ())
684
685 -- `loop' mutator that filter elements according to a predicate
686 --
687 filterEFL   :: (e -> Bool) -> (e -> () -> (Maybe e, ()))
688 {-# INLINE filterEFL #-}
689 filterEFL p  = \e a -> if p e then (Just e, ()) else (Nothing, ())
690
691 -- `loop' mutator for array folding
692 --
693 foldEFL   :: (e -> acc -> acc) -> (e -> acc -> (Maybe (), acc))
694 {-# INLINE foldEFL #-}
695 foldEFL f  = \e a -> (Nothing, f e a)
696
697 -- `loop' mutator for array scanning
698 --
699 scanEFL   :: (e -> acc -> acc) -> (e -> acc -> (Maybe acc, acc))
700 {-# INLINE scanEFL #-}
701 scanEFL f  = \e a -> (Just a, f e a)
702
703 -- elementary array operations
704 --
705
706 -- unlifted array indexing 
707 --
708 indexPArr                       :: [:e:] -> Int -> e
709 {-# INLINE indexPArr #-}
710 indexPArr (PArr n# arr#) (I# i#) 
711   | i# >=# 0# && i# <# n# =
712     case indexArray# arr# i# of (# e #) -> e
713   | otherwise = error $ "indexPArr: out of bounds parallel array index; " ++
714                         "idx = " ++ show (I# i#) ++ ", arr len = "
715                         ++ show (I# n#)
716
717 -- encapsulate writing into a mutable array into the `ST' monad
718 --
719 writeMPArr                           :: MPArr s e -> Int -> e -> ST s ()
720 {-# INLINE writeMPArr #-}
721 writeMPArr (MPArr n# marr#) (I# i#) e 
722   | i# >=# 0# && i# <# n# =
723     ST $ \s# ->
724     case writeArray# marr# i# e s# of s'# -> (# s'#, () #)
725   | otherwise = error $ "writeMPArr: out of bounds parallel array index; " ++
726                         "idx = " ++ show (I# i#) ++ ", arr len = "
727                         ++ show (I# n#)
728
729 #endif /* __HADDOCK__ */
730