X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FbasicTypes%2FUnique.lhs;h=41806040d26f36750a8fc9bc1a9ad53745ccd269;hp=aecd37219790545cce74339e7945f9d7f745c40e;hb=5289f5d85610f71625a439747a09384876655eb5;hpb=831a35dd00faff195cf938659c2dd736192b865f diff --git a/compiler/basicTypes/Unique.lhs b/compiler/basicTypes/Unique.lhs index aecd372..4180604 100644 --- a/compiler/basicTypes/Unique.lhs +++ b/compiler/basicTypes/Unique.lhs @@ -16,6 +16,7 @@ Some of the other hair in this code is to be able to use a Haskell). \begin{code} +{-# LANGUAGE BangPatterns #-} module Unique ( -- * Main data types Unique, Uniquable(..), @@ -25,7 +26,6 @@ module Unique ( pprUnique, - mkUnique, -- Used in UniqSupply mkUniqueGrimily, -- Used in UniqSupply only! getKey, getKeyFastInt, -- Used in Var, UniqFM, Name only! @@ -47,6 +47,9 @@ module Unique ( mkPreludeTyConUnique, mkPreludeClassUnique, mkPArrDataConUnique, + mkVarOccUnique, mkDataOccUnique, mkTvOccUnique, mkTcOccUnique, + mkRegSingleUnique, mkRegPairUnique, mkRegClassUnique, mkRegSubUnique, + mkBuiltinUnique, mkPseudoUniqueC, mkPseudoUniqueD, @@ -60,7 +63,7 @@ import BasicTypes import FastTypes import FastString import Outputable -import StaticFlags +-- import StaticFlags #if defined(__GLASGOW_HASKELL__) --just for implementing a fast [0,61) -> Char function @@ -93,7 +96,6 @@ Now come the functions which construct uniques from their pieces, and vice versa The stuff about unique *supplies* is handled further down this module. \begin{code} -mkUnique :: Char -> Int -> Unique -- Builds a unique from pieces unpkUnique :: Unique -> (Char, Int) -- The reverse mkUniqueGrimily :: Int -> Unique -- A trap-door for UniqSupply @@ -131,6 +133,9 @@ newTagUnique u c = mkUnique c i where (_,i) = unpkUnique u -- and as long as the Char fits in 8 bits, which we assume anyway! +mkUnique :: Char -> Int -> Unique -- Builds a unique from pieces +-- NOT EXPORTED, so that we can see all the Chars that +-- are used in this one module mkUnique c i = MkUnique (tag `bitOrFastInt` bits) where @@ -211,9 +216,9 @@ We do sometimes make strings with @Uniques@ in them: \begin{code} pprUnique :: Unique -> SDoc pprUnique uniq - | opt_SuppressUniques - = empty -- Used exclusively to suppress uniques so you - | otherwise -- can compare output easily +-- | opt_SuppressUniques +-- = empty -- Used exclusively to suppress uniques so you +-- | otherwise -- can compare output easily = case unpkUnique uniq of (tag, u) -> finish_ppr tag u (text (iToBase62 u)) @@ -340,8 +345,7 @@ 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 +-- 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. @@ -358,5 +362,18 @@ mkPseudoUniqueC i = mkUnique 'C' i -- used for getUnique on Regs mkPseudoUniqueD i = mkUnique 'D' i -- used in NCG for getUnique on RealRegs mkPseudoUniqueE i = mkUnique 'E' i -- used in NCG spiller to create spill VirtualRegs mkPseudoUniqueH i = mkUnique 'H' i -- used in NCG spiller to create spill VirtualRegs + +mkRegSingleUnique, mkRegPairUnique, mkRegSubUnique, mkRegClassUnique :: Int -> Unique +mkRegSingleUnique = mkUnique 'R' +mkRegSubUnique = mkUnique 'S' +mkRegPairUnique = mkUnique 'P' +mkRegClassUnique = mkUnique 'L' + +mkVarOccUnique, mkDataOccUnique, mkTvOccUnique, mkTcOccUnique :: FastString -> Unique +-- See Note [The Unique of an OccName] in OccName +mkVarOccUnique fs = mkUnique 'i' (iBox (uniqueOfFS fs)) +mkDataOccUnique fs = mkUnique 'd' (iBox (uniqueOfFS fs)) +mkTvOccUnique fs = mkUnique 'v' (iBox (uniqueOfFS fs)) +mkTcOccUnique fs = mkUnique 'c' (iBox (uniqueOfFS fs)) \end{code}