Skip to content

Commit

Permalink
Use Word32 or Word64 in LLVM types instead of Int32. (GaloisInc#74)
Browse files Browse the repository at this point in the history
For integer types, LLVM seems to only support up to 2^24 bits
anyway, but it doesn't make sense to allow them to be negative.
For Array and Vector types, LLVM uses uint_64 to describe
the number of elements, so we use Word64.
  • Loading branch information
robdockins authored Aug 18, 2020
1 parent 0a4a21c commit 52d5d36
Show file tree
Hide file tree
Showing 3 changed files with 18 additions and 14 deletions.
5 changes: 3 additions & 2 deletions src/Text/LLVM.hs
Original file line number Diff line number Diff line change
Expand Up @@ -112,6 +112,7 @@ import Text.LLVM.AST
import Control.Monad.Fix (MonadFix)
import Data.Char (ord)
import Data.Int (Int8,Int16,Int32,Int64)
import Data.Word (Word32, Word64)
import Data.Maybe (maybeToList)
import Data.String (IsString(..))
import MonadLib hiding (jump,Label)
Expand Down Expand Up @@ -413,7 +414,7 @@ terminateBasicBlock = BB $ do

-- Type Helpers ----------------------------------------------------------------

iT :: Int32 -> Type
iT :: Word32 -> Type
iT = PrimType . Integer

ptrT :: Type -> Type
Expand All @@ -422,7 +423,7 @@ ptrT = PtrTo
voidT :: Type
voidT = PrimType Void

arrayT :: Int32 -> Type -> Type
arrayT :: Word64 -> Type -> Type
arrayT = Array


Expand Down
12 changes: 6 additions & 6 deletions src/Text/LLVM/AST.hs
Original file line number Diff line number Diff line change
Expand Up @@ -240,7 +240,7 @@ instance IsString Symbol where
data PrimType
= Label
| Void
| Integer Int32
| Integer Word32
| FloatType FloatType
| X86mmx
| Metadata
Expand All @@ -260,12 +260,12 @@ type Type = Type' Ident
data Type' ident
= PrimType PrimType
| Alias ident
| Array Int32 (Type' ident)
| Array Word64 (Type' ident)
| FunTy (Type' ident) [Type' ident] Bool
| PtrTo (Type' ident)
| Struct [Type' ident]
| PackedStruct [Type' ident]
| Vector Int32 (Type' ident)
| Vector Word64 (Type' ident)
| Opaque
deriving (Data, Eq, Functor, Generic, Generic1, Ord, Show, Typeable)

Expand Down Expand Up @@ -365,11 +365,11 @@ elimPtrTo :: MonadPlus m => Type -> m Type
elimPtrTo (PtrTo ty) = return ty
elimPtrTo _ = mzero

elimVector :: MonadPlus m => Type -> m (Int32,Type)
elimVector :: MonadPlus m => Type -> m (Word64,Type)
elimVector (Vector n pty) = return (n,pty)
elimVector _ = mzero

elimArray :: MonadPlus m => Type -> m (Int32, Type)
elimArray :: MonadPlus m => Type -> m (Word64, Type)
elimArray (Array n ety) = return (n, ety)
elimArray _ = mzero

Expand Down Expand Up @@ -1147,7 +1147,7 @@ data DINameSpace' lab = DINameSpace

-- TODO: Turn these into sum types
-- See https://github.com/llvm-mirror/llvm/blob/release_38/include/llvm/Support/Dwarf.def
type DwarfAttrEncoding = Word8
type DwarfAttrEncoding = Word16
type DwarfLang = Word16
type DwarfTag = Word16
type DwarfVirtuality = Word8
Expand Down
15 changes: 9 additions & 6 deletions src/Text/LLVM/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module Text.LLVM.Parser where
import Text.LLVM.AST

import Data.Char (chr)
import Data.Int (Int32)
import Data.Word (Word32, Word64)
import Text.Parsec
import Text.Parsec.String

Expand Down Expand Up @@ -35,12 +35,15 @@ pSymbol = Symbol <$> (char '@' >> pName)

-- Types -----------------------------------------------------------------------

pInt32 :: Parser Int32
pInt32 = read <$> many1 digit
pWord32 :: Parser Word32
pWord32 = read <$> many1 digit

pWord64 :: Parser Word64
pWord64 = read <$> many1 digit

pPrimType :: Parser PrimType
pPrimType = choice
[ Integer <$> try (char 'i' >> pInt32)
[ Integer <$> try (char 'i' >> pWord32)
, FloatType <$> try pFloatType
, try (string "label") >> return Label
, try (string "void") >> return Void
Expand Down Expand Up @@ -75,9 +78,9 @@ pType = pType0 >>= pFunPtr
pTypeList :: Parser [Type]
pTypeList = sepBy (spaced pType) (char ',')

pNumType :: (Int32 -> Type -> Type) -> Parser Type
pNumType :: (Word64 -> Type -> Type) -> Parser Type
pNumType f =
do n <- pInt32
do n <- pWord64
spaces >> char 'x' >> spaces
t <- pType
return (f n t)
Expand Down

0 comments on commit 52d5d36

Please sign in to comment.