summaryrefslogtreecommitdiff
path: root/compiler/utils
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/utils')
-rw-r--r--compiler/utils/Encoding.hs16
-rw-r--r--compiler/utils/FastMutInt.lhs4
-rw-r--r--compiler/utils/FastString.lhs6
-rw-r--r--compiler/utils/Pretty.lhs8
-rw-r--r--compiler/utils/StringBuffer.lhs2
-rw-r--r--compiler/utils/UniqFM.lhs4
6 files changed, 20 insertions, 20 deletions
diff --git a/compiler/utils/Encoding.hs b/compiler/utils/Encoding.hs
index 35df00478c..e14f1e749a 100644
--- a/compiler/utils/Encoding.hs
+++ b/compiler/utils/Encoding.hs
@@ -50,21 +50,21 @@ import GHC.Base
{-# INLINE utf8DecodeChar# #-}
utf8DecodeChar# :: Addr# -> (# Char#, Addr# #)
utf8DecodeChar# a# =
- let ch0 = word2Int# (indexWord8OffAddr# a# 0#) in
+ let !ch0 = word2Int# (indexWord8OffAddr# a# 0#) in
case () of
_ | ch0 <=# 0x7F# -> (# chr# ch0, a# `plusAddr#` 1# #)
| ch0 >=# 0xC0# && ch0 <=# 0xDF# ->
- let ch1 = word2Int# (indexWord8OffAddr# a# 1#) in
+ let !ch1 = word2Int# (indexWord8OffAddr# a# 1#) in
if ch1 <# 0x80# || ch1 >=# 0xC0# then fail 1# else
(# chr# (((ch0 -# 0xC0#) `uncheckedIShiftL#` 6#) +#
(ch1 -# 0x80#)),
a# `plusAddr#` 2# #)
| ch0 >=# 0xE0# && ch0 <=# 0xEF# ->
- let ch1 = word2Int# (indexWord8OffAddr# a# 1#) in
+ let !ch1 = word2Int# (indexWord8OffAddr# a# 1#) in
if ch1 <# 0x80# || ch1 >=# 0xC0# then fail 1# else
- let ch2 = word2Int# (indexWord8OffAddr# a# 2#) in
+ let !ch2 = word2Int# (indexWord8OffAddr# a# 2#) in
if ch2 <# 0x80# || ch2 >=# 0xC0# then fail 2# else
(# chr# (((ch0 -# 0xE0#) `uncheckedIShiftL#` 12#) +#
((ch1 -# 0x80#) `uncheckedIShiftL#` 6#) +#
@@ -72,11 +72,11 @@ utf8DecodeChar# a# =
a# `plusAddr#` 3# #)
| ch0 >=# 0xF0# && ch0 <=# 0xF8# ->
- let ch1 = word2Int# (indexWord8OffAddr# a# 1#) in
+ let !ch1 = word2Int# (indexWord8OffAddr# a# 1#) in
if ch1 <# 0x80# || ch1 >=# 0xC0# then fail 1# else
- let ch2 = word2Int# (indexWord8OffAddr# a# 2#) in
+ let !ch2 = word2Int# (indexWord8OffAddr# a# 2#) in
if ch2 <# 0x80# || ch2 >=# 0xC0# then fail 2# else
- let ch3 = word2Int# (indexWord8OffAddr# a# 3#) in
+ let !ch3 = word2Int# (indexWord8OffAddr# a# 3#) in
if ch3 <# 0x80# || ch3 >=# 0xC0# then fail 3# else
(# chr# (((ch0 -# 0xF0#) `uncheckedIShiftL#` 18#) +#
((ch1 -# 0x80#) `uncheckedIShiftL#` 12#) +#
@@ -116,7 +116,7 @@ STRICT2(utf8DecodeString)
utf8DecodeString (Ptr a#) (I# len#)
= unpack a#
where
- end# = addr2Int# (a# `plusAddr#` len#)
+ !end# = addr2Int# (a# `plusAddr#` len#)
unpack p#
| addr2Int# p# >=# end# = return []
diff --git a/compiler/utils/FastMutInt.lhs b/compiler/utils/FastMutInt.lhs
index e8ea58c8db..c29b568426 100644
--- a/compiler/utils/FastMutInt.lhs
+++ b/compiler/utils/FastMutInt.lhs
@@ -50,7 +50,7 @@ data FastMutInt = FastMutInt (MutableByteArray# RealWorld)
newFastMutInt = IO $ \s ->
case newByteArray# size s of { (# s, arr #) ->
(# s, FastMutInt arr #) }
- where I# size = SIZEOF_HSINT
+ where !(I# size) = SIZEOF_HSINT
readFastMutInt (FastMutInt arr) = IO $ \s ->
case readIntArray# arr 0# s of { (# s, i #) ->
@@ -65,7 +65,7 @@ data FastMutPtr = FastMutPtr (MutableByteArray# RealWorld)
newFastMutPtr = IO $ \s ->
case newByteArray# size s of { (# s, arr #) ->
(# s, FastMutPtr arr #) }
- where I# size = SIZEOF_VOID_P
+ where !(I# size) = SIZEOF_VOID_P
readFastMutPtr (FastMutPtr arr) = IO $ \s ->
case readAddrArray# arr 0# s of { (# s, i #) ->
diff --git a/compiler/utils/FastString.lhs b/compiler/utils/FastString.lhs
index cf4e37d21d..62bc5d5edf 100644
--- a/compiler/utils/FastString.lhs
+++ b/compiler/utils/FastString.lhs
@@ -380,9 +380,9 @@ hashStr (Ptr a#) (I# len#) = loop 0# 0#
where
loop h n | n GHC.Exts.==# len# = I# h
| otherwise = loop h2 (n GHC.Exts.+# 1#)
- where c = ord# (indexCharOffAddr# a# n)
- h2 = (c GHC.Exts.+# (h GHC.Exts.*# 128#)) `remInt#`
- hASH_TBL_SIZE#
+ where !c = ord# (indexCharOffAddr# a# n)
+ !h2 = (c GHC.Exts.+# (h GHC.Exts.*# 128#)) `remInt#`
+ hASH_TBL_SIZE#
-- -----------------------------------------------------------------------------
-- Operations
diff --git a/compiler/utils/Pretty.lhs b/compiler/utils/Pretty.lhs
index 3e08814ceb..47d4b1e19e 100644
--- a/compiler/utils/Pretty.lhs
+++ b/compiler/utils/Pretty.lhs
@@ -615,7 +615,7 @@ aboveNest (Nest k1 p) g k q = nest_ k1 (aboveNest p g (k -# k1) q)
aboveNest (NilAbove p) g k q = nilAbove_ (aboveNest p g k q)
aboveNest (TextBeside s sl p) g k q = textBeside_ s sl rest
where
- k1 = k -# sl
+ !k1 = k -# sl
rest = case p of
Empty -> nilAboveNest g k1 q
_ -> aboveNest p g k1 q
@@ -775,8 +775,8 @@ fillNB g Empty k (y:ys) = nilBeside g (fill1 g (oneLiner (reduceDoc y)) k1 ys
`mkUnion`
nilAboveNest False k (fill g (y:ys))
where
- k1 | g = k -# _ILIT(1)
- | otherwise = k
+ !k1 | g = k -# _ILIT(1)
+ | otherwise = k
fillNB g p k ys = fill1 g p k ys
\end{code}
@@ -797,7 +797,7 @@ best :: Int -- Line length
best w_ r_ p
= get (iUnbox w_) p
where
- r = iUnbox r_
+ !r = iUnbox r_
get :: FastInt -- (Remaining) width of line
-> Doc -> Doc
get _ Empty = Empty
diff --git a/compiler/utils/StringBuffer.lhs b/compiler/utils/StringBuffer.lhs
index 1aead2d74b..2b3b775791 100644
--- a/compiler/utils/StringBuffer.lhs
+++ b/compiler/utils/StringBuffer.lhs
@@ -224,7 +224,7 @@ parseUnsignedInteger (StringBuffer buf _ cur) len radix char_to_int
--LOL, in implementations where the indexing needs slow unsafePerformIO,
--this is less (not more) efficient than using the IO monad explicitly
--here.
- ptr' = pUnbox ptr
+ !ptr' = pUnbox ptr
byteOff i = cBox (indexWord8OffFastPtrAsFastChar ptr' (iUnbox (cur + i)))
go i x | i == len = x
| otherwise = case byteOff i of
diff --git a/compiler/utils/UniqFM.lhs b/compiler/utils/UniqFM.lhs
index 97f8fb45bc..cc2d066ab7 100644
--- a/compiler/utils/UniqFM.lhs
+++ b/compiler/utils/UniqFM.lhs
@@ -803,8 +803,8 @@ getCommonNodeUFMData (NodeUFMData i p) (NodeUFMData i2 p2)
| p <# p2 = getCommonNodeUFMData_ p2 (j `quotFastInt` (p2 `quotFastInt` p)) j2
| otherwise = getCommonNodeUFMData_ p j (j2 `quotFastInt` (p `quotFastInt` p2))
where
- j = i `quotFastInt` (shiftL1 p)
- j2 = i2 `quotFastInt` (shiftL1 p2)
+ !j = i `quotFastInt` (shiftL1 p)
+ !j2 = i2 `quotFastInt` (shiftL1 p2)
getCommonNodeUFMData_ :: FastInt -> FastInt -> FastInt -> NodeUFMData