module Lvm.Common.Id
( Id
, stringFromId, idFromString, idFromStringEx, dummyId
, freshIdFromId, getNameSpace, setNameSpace, NameSupply, newNameSupply
, splitNameSupply, splitNameSupplies, freshId, mapWithSupply
, intFromId, idFromInt
) where
import Data.IORef
import Data.Int (Int32)
import Data.List
import System.IO.Unsafe
import Text.PrettyPrint.Leijen
import qualified Data.IntMap as IntMap
newtype Id = Id Int32
intFromId :: Id -> Int
intFromId (Id i) = fromIntegral i
idFromInt :: Int -> Id
idFromInt i = Id (fromIntegral i)
data Names = Names Int (IntMap.IntMap [String])
namesRef :: IORef Names
namesRef = unsafePerformIO (newIORef emptyNames)
emptyNames :: Names
emptyNames = Names 0 IntMap.empty
idFromString :: String -> Id
idFromString = idFromStringEx (0::Int)
idFromStringEx :: Enum a => a -> String -> Id
idFromStringEx ns name
= unsafePerformIO $
do{ names <- readIORef namesRef
; let (x, names') = insertName (fromEnum ns) name names
; writeIORef namesRef names'
; return x
}
stringFromId :: Id -> String
stringFromId x@(Id i)
| isUniq i = '.' : show (extractUniq i)
| otherwise = unsafePerformIO $
do{ names <- readIORef namesRef
; case lookupId x names of
Nothing -> error "Id.nameFromId: unknown id"
Just name -> return name
}
newtype NameSupply = NameSupply (IORef Int32)
newNameSupply :: IO NameSupply
newNameSupply
= do{ ref <- newIORef 0
; return (NameSupply ref)
}
splitNameSupply :: NameSupply -> (NameSupply,NameSupply)
splitNameSupply supply = (supply,supply)
splitNameSupplies :: NameSupply -> [NameSupply]
splitNameSupplies = repeat
freshIdFromId :: Id -> NameSupply -> (Id,NameSupply)
freshIdFromId x supply@(NameSupply ref)
= unsafePerformIO (do{ i <- readIORef ref
; writeIORef ref (i+1)
; let name = stringFromId x ++ "." ++ show i
x1 = idFromString name
x2 = setNameSpace (getNameSpace x :: Int) x1
; seq name $ seq x2 $ return (x2,supply)
})
freshId :: NameSupply -> (Id,NameSupply)
freshId supply@(NameSupply ref)
= unsafePerformIO (do{ i <- readIORef ref
; writeIORef ref (i+1)
; return (Id (initUniq i), supply)
})
mapWithSupply :: (NameSupply -> a -> b) -> NameSupply -> [a] -> [b]
mapWithSupply f = zipWith f . splitNameSupplies
dummyId :: Id
dummyId = Id 0x7FFFFFF1
shiftSort, maxSort :: Int32
shiftSort = 0x00000002
maxSort = 0x7F
maxHash, shiftHash :: Int32
maxHash = 0xFFF
shiftHash = 0x00000100
shiftIdx, maxIdx :: Int32
shiftIdx = 0x00100000
maxIdx = 0x7FF
shiftUniq,maxUniq :: Int32
shiftUniq = 0x00000100
maxUniq = 0x007FFFFF
extractBits, clearBits, initBits :: Int32 -> Int32 -> Int32 -> Int32
extractBits shift maxb i
= (i `div` shift) `mod` (maxb+1)
clearBits shift maxb i
= i (extractBits shift maxb i * shift)
initBits shift v i
= i + (shift * v)
extractSort :: Int32 -> Int32
extractSort = extractBits shiftSort maxSort
clearSort :: Int32 -> Int32
clearSort = clearBits shiftSort maxSort
initSort :: Int32 -> Int32 -> Int32
initSort = initBits shiftSort
extractHash :: Int32 -> Int32
extractHash = extractBits shiftHash maxHash
initHash :: Int32 -> Int32
initHash h = initBits shiftHash h 0
extractIdx :: Int32 -> Int32
extractIdx = extractBits shiftIdx maxIdx
initIdx :: Int32 -> Int32 -> Int32
initIdx = initBits shiftIdx
extractUniq :: Int32 -> Int32
extractUniq = extractBits shiftUniq maxUniq
initUniq :: Int32 -> Int32
initUniq u = initBits shiftUniq u 1
isUniq :: Int32 -> Bool
isUniq = odd
instance Eq Id where
Id i1 == Id i2 = i1 == i2
instance Ord Id where
compare x1@(Id i1) x2@(Id i2) =
case compare (extractHash i1) (extractHash i2) of
LT -> LT
EQ | i1 == i2 -> EQ
| otherwise -> compare (stringFromId x1) (stringFromId x2)
GT -> GT
instance Show Id where
show x = "\"" ++ stringFromId x ++ "\""
instance Pretty Id where
pretty = string . stringFromId
getNameSpace :: Enum a => Id -> a
getNameSpace (Id i)
= toEnum (fromIntegral (extractSort i))
setNameSpace :: Enum a => a -> Id -> Id
setNameSpace srt (Id i)
| s > maxSort = error "Id.setIdSort: sort index out of range"
| otherwise = Id (initSort s (clearSort i))
where
s = fromIntegral (fromEnum srt)
lookupId :: Id -> Names -> Maybe String
lookupId (Id i) (Names _ m)
= let idx = extractIdx i
h = extractHash i
in case IntMap.lookup (fromIntegral h) m of
Nothing -> Nothing
Just xs -> Just (index idx xs)
where
index 0 (x:_) = x
index idx (_:xx) = index (idx1) xx
index _ [] = error "Id.lookupId: corrupted symbol table"
insertName :: Int -> String -> Names -> (Id, Names)
insertName srt name names
= let (x, names') = insertName' name names
in (setNameSpace srt x, names')
insertName' :: String -> Names -> (Id,Names)
insertName' name (Names fresh m)
| idx > maxIdx = error ("Id.insertName: too many names with the same hash value (" ++ show name ++ ")")
| otherwise = (Id (initIdx idx h), Names fresh m1)
where
hname = hash name
h = initHash hname
(old, m1) = IntMap.insertLookupWithKey upd (fromIntegral hname) [name] m
(idx, new) = maybe (0, [name]) (insertIdx name) old
upd _ _ _ = new
insertIdx :: Eq a => a -> [a] -> (Int32,[a])
insertIdx y = walk 0
where
walk idx [] = (idx,[y])
walk idx xs@(x:xx) | x == y = (idx,xs)
| otherwise = let (idx',xx') = walk (idx+1) xx
in (idx',x:xx')
hash :: String -> Int32
hash name
= (hashx name `mod` prime) `mod` maxHash
where
prime = 32537
hashx :: String -> Int32
hashx = foldl' gobble 0
where
gobble n c = n*65599 + fromIntegral (fromEnum c)