X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FbasicTypes%2FUnique.lhs;h=b73b38c4538552facae7369683f723cf457290ae;hb=1f5e55804b97d2b9a77207d568d602ba88d8855d;hp=86e6d600b6e5d4dd7de722ddff868461b0378630;hpb=b4775e5e760111e2d71fba3c44882dce390edfb2;p=ghc-hetmet.git diff --git a/ghc/compiler/basicTypes/Unique.lhs b/ghc/compiler/basicTypes/Unique.lhs index 86e6d60..b73b38c 100644 --- a/ghc/compiler/basicTypes/Unique.lhs +++ b/ghc/compiler/basicTypes/Unique.lhs @@ -17,13 +17,13 @@ Haskell). \begin{code} module Unique ( Unique, Uniquable(..), hasKey, - u2i, -- hack: used in UniqFM pprUnique, pprUnique10, mkUnique, -- Used in UniqSupply mkUniqueGrimily, -- Used in UniqSupply only! - getKey, -- Used in Var only! + getKey, getKey#, -- Used in Var, UniqFM, Name only! + unpkUnique, incrUnique, -- Used for renumbering deriveUnique, -- Ditto @@ -40,8 +40,9 @@ module Unique ( mkTupleTyConUnique, mkTupleDataConUnique, mkPreludeMiscIdUnique, mkPreludeDataConUnique, mkPreludeTyConUnique, mkPreludeClassUnique, + mkPArrDataConUnique, - mkBuiltinUnique, + mkBuiltinUnique, builtinUniques, mkPseudoUnique1, mkPseudoUnique2, mkPseudoUnique3 ) where @@ -49,12 +50,12 @@ module Unique ( import BasicTypes ( Boxity(..) ) import FastString ( FastString, uniqueOfFS ) -import GlaExts -import ST -import PrelBase ( Char(..), chr, ord ) +import Outputable import FastTypes -import Outputable +import GLAEXTS + +import Char ( chr, ord ) \end{code} %************************************************************************ @@ -70,11 +71,6 @@ Fast comparison is everything on @Uniques@: data Unique = MkUnique Int# \end{code} -\begin{code} -u2i :: Unique -> FastInt -u2i (MkUnique i) = i -\end{code} - Now come the functions which construct uniques from their pieces, and vice versa. The stuff about unique *supplies* is handled further down this module. @@ -82,9 +78,9 @@ The stuff about unique *supplies* is handled further down this module. mkUnique :: Char -> Int -> Unique -- Builds a unique from pieces unpkUnique :: Unique -> (Char, Int) -- The reverse -mkUniqueGrimily :: Int# -> Unique -- A trap-door for UniqSupply - -getKey :: Unique -> Int# -- for Var +mkUniqueGrimily :: Int -> Unique -- A trap-door for UniqSupply +getKey :: Unique -> Int -- for Var +getKey# :: Unique -> Int# -- for Var incrUnique :: Unique -> Unique deriveUnique :: Unique -> Int -> Unique @@ -95,10 +91,12 @@ isTupleKey :: Unique -> Bool \begin{code} -mkUniqueGrimily x = MkUnique x +mkUniqueGrimily (I# x) = MkUnique x {-# INLINE getKey #-} -getKey (MkUnique x) = x +getKey (MkUnique x) = I# x +{-# INLINE getKey# #-} +getKey# (MkUnique x) = x incrUnique (MkUnique i) = MkUnique (i +# 1#) @@ -120,7 +118,11 @@ i2w_s x = (x::Int#) mkUnique (C# c) (I# i) = MkUnique (w2i (tag `or#` bits)) where +#if __GLASGOW_HASKELL__ >= 503 + tag = i2w (ord# c) `uncheckedShiftL#` i2w_s 24# +#else tag = i2w (ord# c) `shiftL#` i2w_s 24# +#endif bits = i2w i `and#` (i2w 16777215#){-``0x00ffffff''-} unpkUnique (MkUnique u) @@ -130,7 +132,11 @@ unpkUnique (MkUnique u) in (tag, i) where +#if __GLASGOW_HASKELL__ >= 503 + shiftr x y = uncheckedShiftRL# x y +#else shiftr x y = shiftRL# x y +#endif \end{code} @@ -149,10 +155,10 @@ hasKey :: Uniquable a => a -> Unique -> Bool x `hasKey` k = getUnique x == k instance Uniquable FastString where - getUnique fs = mkUniqueGrimily (uniqueOfFS fs) + getUnique fs = mkUniqueGrimily (I# (uniqueOfFS fs)) instance Uniquable Int where - getUnique (I# i#) = mkUniqueGrimily i# + getUnique i = mkUniqueGrimily i \end{code} @@ -224,48 +230,21 @@ instance Show Unique where A character-stingy way to read/write numbers (notably Uniques). The ``62-its'' are \tr{[0-9a-zA-Z]}. We don't handle negative Ints. Code stolen from Lennart. -\begin{code} -# define BYTE_ARRAY GlaExts.ByteArray -# define RUN_ST ST.runST -# define AND_THEN >>= -# define AND_THEN_ >> -# define RETURN return +\begin{code} iToBase62 :: Int -> SDoc iToBase62 n@(I# n#) = ASSERT(n >= 0) - let -#if __GLASGOW_HASKELL__ < 405 - bytes = case chars62 of { BYTE_ARRAY bounds_who_needs_'em bytes -> bytes } -#else - bytes = case chars62 of { BYTE_ARRAY _ _ bytes -> bytes } -#endif - in if n# <# 62# then - case (indexCharArray# bytes n#) of { c -> + case (indexCharOffAddr# chars62# n#) of { c -> char (C# c) } else case (quotRem n 62) of { (q, I# r#) -> - case (indexCharArray# bytes r#) of { c -> + case (indexCharOffAddr# chars62# r#) of { c -> (<>) (iToBase62 q) (char (C# c)) }} - --- keep this at top level! (bug on 94/10/24 WDP) -chars62 :: BYTE_ARRAY Int -chars62 - = RUN_ST ( - newCharArray (0, 61) AND_THEN \ ch_array -> - fill_in ch_array 0 62 "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ" - AND_THEN_ - unsafeFreezeByteArray ch_array - ) where - fill_in ch_array i lim str - | i == lim - = RETURN () - | otherwise - = writeCharArray ch_array i (str !! i) AND_THEN_ - fill_in ch_array (i+1) lim str + chars62# = "0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ"# \end{code} %************************************************************************ @@ -314,6 +293,10 @@ isTupleKey u = case unpkUnique u of mkPrimOpIdUnique op = mkUnique '9' op mkPreludeMiscIdUnique i = mkUnique '0' i +-- No numbers left anymore, so I pick something different for the character +-- tag +mkPArrDataConUnique a = mkUnique ':' (2*a) + -- The "tyvar uniques" print specially nicely: a, b, c, etc. -- See pprUnique for details @@ -326,6 +309,9 @@ initTidyUniques = (mkUnique 'g' 0, mkUnique 'x' 0) mkPseudoUnique1, mkPseudoUnique2, mkPseudoUnique3, mkBuiltinUnique :: Int -> Unique +builtinUniques :: [Unique] +builtinUniques = map mkBuiltinUnique [1..] + mkBuiltinUnique i = mkUnique 'B' i mkPseudoUnique1 i = mkUnique 'C' i -- used for getUnique on Regs mkPseudoUnique2 i = mkUnique 'D' i -- used in NCG for getUnique on RealRegs