Adjust behaviour of gcd
[ghc-base.git] / GHC / Arr.lhs
index 1b2f0bb..ade0b98 100644 (file)
@@ -1,7 +1,8 @@
 \begin{code}
+{-# LANGUAGE NoImplicitPrelude, NoBangPatterns, MagicHash, UnboxedTuples #-}
 {-# OPTIONS_GHC -funbox-strict-fields #-}
-{-# LANGUAGE NoImplicitPrelude, NoBangPatterns #-}
 {-# OPTIONS_HADDOCK hide #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  GHC.Arr
@@ -49,13 +50,13 @@ default ()
 -- An implementation is entitled to assume the following laws about these
 -- operations:
 --
--- * @'inRange' (l,u) i == 'elem' i ('range' (l,u))@
+-- * @'inRange' (l,u) i == 'elem' i ('range' (l,u))@ @ @
 --
 -- * @'range' (l,u) '!!' 'index' (l,u) i == i@, when @'inRange' (l,u) i@
 --
--- * @'map' ('index' (l,u)) ('range' (l,u))) == [0..'rangeSize' (l,u)-1]@
+-- * @'map' ('index' (l,u)) ('range' (l,u))) == [0..'rangeSize' (l,u)-1]@ @ @
 --
--- * @'rangeSize' (l,u) == 'length' ('range' (l,u))@
+-- * @'rangeSize' (l,u) == 'length' ('range' (l,u))@ @ @
 --
 -- Minimal complete instance: 'range', 'index' and 'inRange'.
 --
@@ -354,13 +355,13 @@ type IPr = (Int, Int)
 
 -- | The type of immutable non-strict (boxed) arrays
 -- with indices in @i@ and elements in @e@.
-data Ix i => Array i e
-                 = Array !i         -- the lower bound, l
-                         !i         -- the upper bound, u
-                         !Int       -- a cache of (rangeSize (l,u))
-                                    -- used to make sure an index is
-                                    -- really in range
-                         (Array# e) -- The actual elements
+data Array i e
+         = Array !i         -- the lower bound, l
+                 !i         -- the upper bound, u
+                 !Int       -- a cache of (rangeSize (l,u))
+                            -- used to make sure an index is
+                            -- really in range
+                 (Array# e) -- The actual elements
 
 -- | Mutable, boxed, non-strict arrays in the 'ST' monad.  The type
 -- arguments are as follows:
@@ -411,7 +412,7 @@ arrEleBottom = error "(Array.!): undefined array element"
 --
 -- Because the indices must be checked for these errors, 'array' is
 -- strict in the bounds argument and in the indices of the association
--- list, but nonstrict in the values.  Thus, recurrences such as the
+-- list, but non-strict in the values.  Thus, recurrences such as the
 -- following are possible:
 --
 -- > a = array (1,100) ((1,1) : [(i, i * a!(i-1)) | i <- [2..100]])
@@ -456,15 +457,18 @@ unsafeArray' (l,u) n@(I# n#) ies = runST (ST $ \s1# ->
 
 {-# INLINE fill #-}
 fill :: MutableArray# s e -> (Int, e) -> STRep s a -> STRep s a
-fill marr# (I# i#, e) next s1# =
-    case writeArray# marr# i# e s1#     of { s2# ->
-    next s2# }
+-- NB: put the \s after the "=" so that 'fill' 
+--     inlines when applied to three args 
+fill marr# (I# i#, e) next 
+ = \s1# -> case writeArray# marr# i# e s1# of 
+             s2# -> next s2# 
 
 {-# INLINE done #-}
 done :: Ix i => i -> i -> Int -> MutableArray# s e -> STRep s (Array i e)
-done l u n marr# s1# =
-    case unsafeFreezeArray# marr# s1# of
-        (# s2#, arr# #) -> (# s2#, Array l u n arr# #)
+-- See NB on 'fill'
+done l u n marr# 
+  = \s1# -> case unsafeFreezeArray# marr# s1# of
+              (# s2#, arr# #) -> (# s2#, Array l u n arr# #)
 
 -- This is inefficient and I'm not sure why:
 -- listArray (l,u) es = unsafeArray (l,u) (zip [0 .. rangeSize (l,u) - 1] es)
@@ -598,11 +602,12 @@ unsafeAccumArray' f initial (l,u) n@(I# n#) ies = runST (ST $ \s1# ->
 
 {-# INLINE adjust #-}
 adjust :: (e -> a -> e) -> MutableArray# s e -> (Int, a) -> STRep s b -> STRep s b
-adjust f marr# (I# i#, new) next s1# =
-    case readArray# marr# i# s1# of
-        (# s2#, old #) ->
-            case writeArray# marr# i# (f old new) s2# of
-                s3# -> next s3#
+-- See NB on 'fill'
+adjust f marr# (I# i#, new) next
+  = \s1# -> case readArray# marr# i# s1# of
+               (# s2#, old #) ->
+                   case writeArray# marr# i# (f old new) s2# of
+                       s3# -> next s3#
 
 -- | Constructs an array identical to the first argument except that it has
 -- been updated by the associations in the right argument.