module Data.LLVM.BitCode.Parse where
import Text.LLVM.AST
import Text.LLVM.PP
import Control.Applicative (Applicative(..),Alternative(..),(<$>))
import Control.Monad.Fix (MonadFix)
import Data.Maybe (fromMaybe)
import Data.Monoid (Monoid(..))
import Data.Typeable (Typeable)
import Data.Word ( Word32 )
import MonadLib
import qualified Control.Exception as X
import qualified Data.Map as Map
import qualified Data.Sequence as Seq
data Error = Error
{ errContext :: [String]
, errMessage :: String
} deriving (Show)
formatError :: Error -> String
formatError err
| null (errContext err) = errMessage err
| otherwise = unlines
$ errMessage err
: "from:"
: map ('\t' :) (errContext err)
newtype Parse a = Parse
{ unParse :: ReaderT Env (StateT ParseState (ExceptionT Error Lift)) a
} deriving (Functor,Applicative,MonadFix)
instance Monad Parse where
return = Parse . return
Parse m >>= f = Parse (m >>= unParse . f)
fail = failWithContext
instance Alternative Parse where
empty = failWithContext "empty"
a <|> b = Parse (either (const (unParse b)) return =<< try (unParse a))
instance MonadPlus Parse where
mzero = failWithContext "mzero"
mplus = (<|>)
runParse :: Parse a -> Either Error a
runParse (Parse m) = case runM m emptyEnv emptyParseState of
Left err -> Left err
Right (a,_) -> Right a
notImplemented :: Parse a
notImplemented = fail "not implemented"
data ParseState = ParseState
{ psTypeTable :: TypeTable
, psTypeTableSize :: !Int
, psValueTable :: ValueTable
, psMdTable :: ValueTable
, psMdRefs :: MdRefTable
, psFunProtos :: Seq.Seq FunProto
, psNextResultId :: !Int
, psTypeName :: Maybe String
, psNextTypeId :: !Int
, psLastLoc :: Maybe PDebugLoc
, psKinds :: !KindTable
} deriving (Show)
emptyParseState :: ParseState
emptyParseState = ParseState
{ psTypeTable = Map.empty
, psTypeTableSize = 0
, psValueTable = emptyValueTable False
, psMdTable = emptyValueTable False
, psMdRefs = Map.empty
, psFunProtos = Seq.empty
, psNextResultId = 0
, psTypeName = Nothing
, psNextTypeId = 0
, psLastLoc = Nothing
, psKinds = emptyKindTable
}
nextResultId :: Parse Int
nextResultId = Parse $ do
ps <- get
set ps { psNextResultId = psNextResultId ps + 1 }
return (psNextResultId ps)
type PDebugLoc = DebugLoc' Int
setLastLoc :: PDebugLoc -> Parse ()
setLastLoc loc = Parse $ do
ps <- get
set $! ps { psLastLoc = Just loc }
setRelIds :: Bool -> Parse ()
setRelIds b = Parse $ do
ps <- get
set $! ps { psValueTable = (psValueTable ps) { valueRelIds = b }}
getRelIds :: Parse Bool
getRelIds = Parse $ do
ps <- get
return (valueRelIds (psValueTable ps))
getLastLoc :: Parse PDebugLoc
getLastLoc = Parse $ do
ps <- get
case psLastLoc ps of
Just loc -> return loc
Nothing -> fail "No last location available"
enterFunctionDef :: Parse a -> Parse a
enterFunctionDef m = Parse $ do
ps <- get
set ps
{ psNextResultId = 0
}
res <- unParse m
ps' <- get
set ps'
{ psValueTable = psValueTable ps
, psMdTable = psMdTable ps
, psMdRefs = psMdRefs ps
, psLastLoc = Nothing
}
return res
type TypeTable = Map.Map Int Type
mkTypeTable :: [Type] -> TypeTable
mkTypeTable = Map.fromList . zip [0 ..]
data BadForwardRef
= BadTypeRef [String] Int
| BadValueRef [String] Int
deriving (Show,Typeable)
instance X.Exception BadForwardRef
badRefError :: BadForwardRef -> Error
badRefError ref = case ref of
BadTypeRef c i -> Error c ("bad forward reference to type: " ++ show i)
BadValueRef c i -> Error c ("bad forward reference to value: " ++ show i)
lookupTypeRef :: [String] -> Int -> TypeTable -> Type
lookupTypeRef cxt n = fromMaybe (X.throw (BadTypeRef cxt n)) . Map.lookup n
setTypeTable :: TypeTable -> Parse ()
setTypeTable table = Parse $ do
ps <- get
set ps { psTypeTable = table }
getTypeTable :: Parse TypeTable
getTypeTable = Parse (psTypeTable <$> get)
setTypeTableSize :: Int -> Parse ()
setTypeTableSize n = Parse $ do
ps <- get
set ps { psTypeTableSize = n }
getTypeName :: Parse Ident
getTypeName = Parse $ do
ps <- get
str <- case psTypeName ps of
Just tn -> do
set ps { psTypeName = Nothing }
return tn
Nothing -> do
set ps { psNextTypeId = psNextTypeId ps + 1 }
return (show (psNextTypeId ps))
return (Ident str)
setTypeName :: String -> Parse ()
setTypeName name = Parse $ do
ps <- get
set ps { psTypeName = Just name }
getType' :: Int -> Parse Type
getType' ref = do
ps <- Parse get
unless (ref < psTypeTableSize ps)
(fail ("type reference " ++ show ref ++ " is too large"))
cxt <- getContext
return (lookupTypeRef cxt ref (psTypeTable ps))
isTypeTableEmpty :: Parse Bool
isTypeTableEmpty = Parse (Map.null . psTypeTable <$> get)
type PValue = Value' Int
type PInstr = Instr' Int
data ValueTable = ValueTable
{ valueNextId :: !Int
, valueEntries :: Map.Map Int (Typed PValue)
, valueRelIds :: Bool
} deriving (Show)
emptyValueTable :: Bool -> ValueTable
emptyValueTable rel = ValueTable
{ valueNextId = 0
, valueEntries = Map.empty
, valueRelIds = rel
}
addValue :: Typed PValue -> ValueTable -> ValueTable
addValue tv vs = snd (addValue' tv vs)
addValue' :: Typed PValue -> ValueTable -> (Int,ValueTable)
addValue' tv vs = (valueNextId vs,vs')
where
vs' = vs
{ valueNextId = valueNextId vs + 1
, valueEntries = Map.insert (valueNextId vs) tv (valueEntries vs)
}
pushValue :: Typed PValue -> Parse Int
pushValue tv = Parse $ do
ps <- get
let vt = psValueTable ps
set ps { psValueTable = addValue tv vt }
return (valueNextId vt)
nextValueId :: Parse Int
nextValueId = Parse (valueNextId . psValueTable <$> get)
adjustId :: Int -> Parse Int
adjustId n = do
vt <- getValueTable
return (translateValueId vt n)
translateValueId :: ValueTable -> Int -> Int
translateValueId vt n | valueRelIds vt = fromIntegral adjusted
| otherwise = n
where
adjusted :: Word32
adjusted = fromIntegral (valueNextId vt n)
lookupValueTableAbs :: Int -> ValueTable -> Maybe (Typed PValue)
lookupValueTableAbs n values = Map.lookup n (valueEntries values)
lookupValueAbs :: Int -> Parse (Maybe (Typed PValue))
lookupValueAbs n = lookupValueTableAbs n `fmap` getValueTable
lookupValueTable :: Int -> ValueTable -> Maybe (Typed PValue)
lookupValueTable n values =
lookupValueTableAbs (translateValueId values n) values
lookupValue :: Int -> Parse (Maybe (Typed PValue))
lookupValue n = lookupValueTable n `fmap` getValueTable
forwardRef :: [String] -> Int -> ValueTable -> Typed PValue
forwardRef cxt n vt =
fromMaybe (X.throw (BadValueRef cxt n)) (lookupValueTableAbs n vt)
requireValue :: Int -> Parse (Typed PValue)
requireValue n = do
mb <- lookupValue n
case mb of
Just tv -> return tv
Nothing -> fail ("value " ++ show n ++ " is not defined")
getValueTable :: Parse ValueTable
getValueTable = Parse (psValueTable <$> get)
getNextId :: Parse Int
getNextId = valueNextId <$> getValueTable
setValueTable :: ValueTable -> Parse ()
setValueTable vt = Parse $ do
ps <- get
set ps { psValueTable = vt }
fixValueTable :: (ValueTable -> Parse (a,[Typed PValue])) -> Parse a
fixValueTable k = do
vt <- getValueTable
rec let vt' = foldr addValue vt vs
(a,vs) <- k vt'
setValueTable vt'
return a
fixValueTable_ :: (ValueTable -> Parse [Typed PValue]) -> Parse ()
fixValueTable_ k = fixValueTable $ \ vt -> do
vs <- k vt
return ((),vs)
type PValMd = ValMd' Int
type MdTable = ValueTable
getMdTable :: Parse MdTable
getMdTable = Parse (psMdTable <$> get)
setMdTable :: MdTable -> Parse ()
setMdTable md = Parse $ do
ps <- get
set $! ps { psMdTable = md }
getMetadata :: Int -> Parse (Typed PValMd)
getMetadata ix = do
ps <- Parse get
case resolveMd ix ps of
Just tv -> case typedValue tv of
ValMd val -> return tv { typedValue = val }
_ -> fail "unexpected non-metadata value in metadata table"
Nothing -> fail ("metadata index " ++ show ix ++ " is not defined")
resolveMd :: Int -> ParseState -> Maybe (Typed PValue)
resolveMd ix ps = nodeRef `mplus` mdValue
where
reference = Typed (PrimType Metadata) . ValMd . ValMdRef
nodeRef = reference `fmap` Map.lookup ix (psMdRefs ps)
mdValue = Map.lookup ix (valueEntries (psMdTable ps))
type MdRefTable = Map.Map Int Int
setMdRefs :: MdRefTable -> Parse ()
setMdRefs refs = Parse $ do
ps <- get
set $! ps { psMdRefs = refs `Map.union` psMdRefs ps }
data FunProto = FunProto
{ protoType :: Type
, protoLinkage :: Maybe Linkage
, protoGC :: Maybe GC
, protoName :: String
, protoIndex :: Int
, protoSect :: Maybe String
} deriving (Show)
pushFunProto :: FunProto -> Parse ()
pushFunProto p = Parse $ do
ps <- get
set ps { psFunProtos = psFunProtos ps Seq.|> p }
popFunProto :: Parse FunProto
popFunProto = do
ps <- Parse get
case Seq.viewl (psFunProtos ps) of
Seq.EmptyL -> fail "empty function prototype stack"
p Seq.:< ps' -> do
Parse (set ps { psFunProtos = ps' })
return p
data Env = Env
{ envSymtab :: Symtab
, envContext :: [String]
} deriving Show
emptyEnv :: Env
emptyEnv = Env
{ envSymtab = mempty
, envContext = mempty
}
extendSymtab :: Symtab -> Env -> Env
extendSymtab symtab env = env { envSymtab = envSymtab env `mappend` symtab }
addLabel :: String -> Env -> Env
addLabel l env = env { envContext = l : envContext env }
getContext :: Parse [String]
getContext = Parse (envContext `fmap` ask)
data Symtab = Symtab
{ symValueSymtab :: ValueSymtab
, symTypeSymtab :: TypeSymtab
} deriving (Show)
instance Monoid Symtab where
mempty = Symtab
{ symValueSymtab = emptyValueSymtab
, symTypeSymtab = mempty
}
mappend l r = Symtab
{ symValueSymtab = symValueSymtab l `Map.union` symValueSymtab r
, symTypeSymtab = symTypeSymtab l `mappend` symTypeSymtab r
}
withSymtab :: Symtab -> Parse a -> Parse a
withSymtab symtab body = Parse $ do
env <- ask
local (extendSymtab symtab env) (unParse body)
withValueSymtab :: ValueSymtab -> Parse a -> Parse a
withValueSymtab symtab = withSymtab (mempty { symValueSymtab = symtab })
getValueSymtab :: Parse ValueSymtab
getValueSymtab = Parse (symValueSymtab . envSymtab <$> ask)
withTypeSymtab :: TypeSymtab -> Parse a -> Parse a
withTypeSymtab symtab = withSymtab (mempty { symTypeSymtab = symtab })
getTypeSymtab :: Parse TypeSymtab
getTypeSymtab = Parse (symTypeSymtab . envSymtab <$> ask)
label :: String -> Parse a -> Parse a
label l m = Parse $ do
env <- ask
local (addLabel l env) (unParse m)
failWithContext :: String -> Parse a
failWithContext msg = Parse $ do
env <- ask
raise Error
{ errMessage = msg
, errContext = envContext env
}
getType :: Int -> Parse Type
getType ref = do
symtab <- getTypeSymtab
case Map.lookup ref (tsById symtab) of
Just i -> return (Alias i)
Nothing -> getType' ref
getTypeId :: Ident -> Parse Int
getTypeId n = do
symtab <- getTypeSymtab
case Map.lookup n (tsByName symtab) of
Just ix -> return ix
Nothing -> fail ("unknown type alias " ++ show (ppLLVM (ppIdent n)))
type SymName = Either String Int
type ValueSymtab = Map.Map SymTabEntry SymName
data SymTabEntry
= SymTabEntry !Int
| SymTabBBEntry !Int
| SymTabFNEntry !Int
deriving (Eq,Ord,Show)
renderName :: SymName -> String
renderName = either id show
mkBlockLabel :: SymName -> BlockLabel
mkBlockLabel = either (Named . Ident) Anon
emptyValueSymtab :: ValueSymtab
emptyValueSymtab = Map.empty
addEntry :: Int -> String -> ValueSymtab -> ValueSymtab
addEntry i n = Map.insert (SymTabEntry i) (Left n)
addBBEntry :: Int -> String -> ValueSymtab -> ValueSymtab
addBBEntry i n = Map.insert (SymTabBBEntry i) (Left n)
addBBAnon :: Int -> Int -> ValueSymtab -> ValueSymtab
addBBAnon i n = Map.insert (SymTabBBEntry i) (Right n)
addFNEntry :: Int -> Int -> String -> ValueSymtab -> ValueSymtab
addFNEntry i _o n = Map.insert (SymTabFNEntry i) (Left n)
entryName :: Int -> Parse String
entryName n = do
symtab <- getValueSymtab
let mentry = Map.lookup (SymTabEntry n) symtab `mplus`
Map.lookup (SymTabFNEntry n) symtab
case mentry of
Just i -> return (renderName i)
Nothing ->
do isRel <- getRelIds
fail $ unlines
[ "entry " ++ show n ++ (if isRel then " (relative)" else "")
++ " is missing from the symbol table"
, show symtab ]
bbEntryName :: Int -> Parse (Maybe BlockLabel)
bbEntryName n = do
symtab <- getValueSymtab
return (mkBlockLabel <$> Map.lookup (SymTabBBEntry n) symtab)
requireBbEntryName :: Int -> Parse BlockLabel
requireBbEntryName n = do
mb <- bbEntryName n
case mb of
Just l -> return l
Nothing -> fail ("basic block " ++ show n ++ " has no id")
data TypeSymtab = TypeSymtab
{ tsById :: Map.Map Int Ident
, tsByName :: Map.Map Ident Int
} deriving Show
instance Monoid TypeSymtab where
mempty = TypeSymtab
{ tsById = Map.empty
, tsByName = Map.empty
}
mappend l r = TypeSymtab
{ tsById = tsById l `Map.union` tsById r
, tsByName = tsByName l `Map.union` tsByName r
}
addTypeSymbol :: Int -> Ident -> TypeSymtab -> TypeSymtab
addTypeSymbol ix n ts = ts
{ tsById = Map.insert ix n (tsById ts)
, tsByName = Map.insert n ix (tsByName ts)
}
data KindTable = KindTable
{ ktNames :: Map.Map Int String
} deriving (Show)
emptyKindTable :: KindTable
emptyKindTable = KindTable
{ ktNames = Map.fromList
[ (0, "dbg" )
, (1, "tbaa" )
, (2, "prof" )
, (3, "fpmath")
, (4, "range" )
]
}
addKind :: Int -> String -> Parse ()
addKind kind name = Parse $ do
ps <- get
let KindTable { .. } = psKinds ps
set $! ps { psKinds = KindTable { ktNames = Map.insert kind name ktNames } }
getKind :: Int -> Parse String
getKind kind = Parse $ do
ps <- get
let KindTable { .. } = psKinds ps
case Map.lookup kind ktNames of
Just name -> return name
Nothing -> fail ("Unknown kind id: " ++ show kind ++ "\nKind table: " ++ show (psKinds ps))