add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / GHC / PArr.hs
1 {-# LANGUAGE CPP, ParallelArrays, MagicHash, UnboxedTuples #-}
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 -- !!!THIS FILE IS ABOUT TO GO AWAY!!!
14
15 module GHC.PArr (
16   -- [::]              -- Built-in syntax
17   emptyPArr, replicatePArr, singletonPArr, indexPArr, lengthPArr
18 ) where
19
20 #ifndef __HADDOCK__
21
22 import Prelude
23
24 import GHC.ST   ( ST(..), runST )
25 import GHC.Base ( Int#, Array#, Int(I#), MutableArray#, newArray#,
26                   unsafeFreezeArray#, indexArray#, {- writeArray#, -} (<#), (>=#) )
27
28
29 -- representation of parallel arrays
30 -- ---------------------------------
31
32 -- this rather straight forward implementation maps parallel arrays to the
33 -- internal representation used for standard Haskell arrays in GHC's Prelude
34 -- (EXPORTED ABSTRACTLY)
35 --
36 -- * This definition *must* be kept in sync with `TysWiredIn.parrTyCon'!
37 --
38 data [::] e = PArr Int# (Array# e)
39
40 emptyPArr :: [:a:]
41 {-# NOINLINE emptyPArr #-}
42 emptyPArr = replicatePArr 0 undefined
43
44 replicatePArr :: Int -> a -> [:a:]
45 {-# NOINLINE replicatePArr #-}
46 replicatePArr n e  = runST (do
47   marr# <- newArray n e
48   mkPArr n marr#)
49
50 singletonPArr :: a -> [:a:]
51 {-# NOINLINE singletonPArr #-}
52 singletonPArr e = replicatePArr 1 e
53
54 indexPArr :: [:e:] -> Int -> e
55 {-# NOINLINE indexPArr #-}
56 indexPArr (PArr n# arr#) (I# i#) 
57   | i# >=# 0# && i# <# n# =
58     case indexArray# arr# i# of (# e #) -> e
59   | otherwise = error $ "indexPArr: out of bounds parallel array index; " ++
60                         "idx = " ++ show (I# i#) ++ ", arr len = "
61                         ++ show (I# n#)
62
63 lengthPArr :: [:a:] -> Int
64 {-# NOINLINE lengthPArr #-}
65 lengthPArr (PArr n# _)  = I# n#
66
67 -- auxiliary functions
68 -- -------------------
69
70 -- internally used mutable boxed arrays
71 --
72 data MPArr s e = MPArr Int# (MutableArray# s e)
73
74 -- allocate a new mutable array that is pre-initialised with a given value
75 --
76 newArray             :: Int -> e -> ST s (MPArr s e)
77 {-# INLINE newArray #-}
78 newArray (I# n#) e  = ST $ \s1# ->
79   case newArray# n# e s1# of { (# s2#, marr# #) ->
80   (# s2#, MPArr n# marr# #)}
81
82 -- convert a mutable array into the external parallel array representation
83 --
84 mkPArr                           :: Int -> MPArr s e -> ST s [:e:]
85 {-# INLINE mkPArr #-}
86 mkPArr (I# n#) (MPArr _ marr#)  = ST $ \s1# ->
87   case unsafeFreezeArray# marr# s1#   of { (# s2#, arr# #) ->
88   (# s2#, PArr n# arr# #) }
89
90 #endif