{-# LANGUAGE CPP #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeSynonymInstances #-} {-# OPTIONS_GHC -fwarn-incomplete-patterns #-} {-# OPTIONS_GHC -fwarn-incomplete-uni-patterns #-} module LLVM.Pretty ( ppllvm, ppll, ) where import Prelude hiding ((<$>)) import GHC.Word import LLVM.AST.Typed import LLVM.AST import LLVM.AST.Global import LLVM.AST.Type import LLVM.DataLayout import LLVM.AST.Attribute import LLVM.AST.DataLayout import LLVM.AST.COMDAT import qualified LLVM.AST.Linkage as L import qualified LLVM.AST.Visibility as V import qualified LLVM.AST.CallingConvention as CC import qualified LLVM.AST.Constant as C import qualified LLVM.AST.FloatingPointPredicate as FP import qualified LLVM.AST.IntegerPredicate as IP import qualified LLVM.AST.InlineAssembly as IA import qualified LLVM.AST.AddrSpace as AS import qualified LLVM.AST.Float as F import qualified LLVM.AST.RMWOperation as RMW import LLVM.AST.Operand hiding (DIGLobalVariable(..), GlobalVariable, Module, NoReturn, PointerType) import qualified LLVM.AST.Operand as O import LLVM.AST.ParameterAttribute as PA import LLVM.AST.FunctionAttribute as FA import Data.String import Text.Printf import Data.Text.Lazy.Encoding import Data.Text.Lazy (Text, pack, unpack) import qualified Data.ByteString.Short as SBF import qualified Data.ByteString.Lazy.Char8 as BF import Data.ByteString.Lazy (fromStrict) import Data.ByteString.Internal (w2c) import Data.Text.Prettyprint.Doc import qualified Data.Text.Prettyprint.Doc as P import Data.Text.Prettyprint.Doc.Render.Text import qualified Data.ByteString.Char8 as BL import qualified Data.ByteString.Short as BS import Data.Char (chr, ord, isAscii, isControl, isLetter, isDigit) import Data.Foldable (toList) import Data.Int import Data.List (intersperse) import Data.Maybe (isJust, mapMaybe) -- import Data.Monoid ((<>)) import Numeric (showHex) import Data.Array.Unsafe import Data.Array.MArray import Data.Array.ST import Control.Monad.ST ------------------------------------------------------------------------------- -- Utils ------------------------------------------------------------------------------- parensIf :: Bool -> Doc ann -> Doc ann parensIf True = parens parensIf False = id commas :: [Doc ann] -> Doc ann commas = hsep . punctuate (pretty ',') colons :: [Doc ann] -> Doc ann colons = hcat . intersperse (pretty ':') hlinecat :: [Doc ann] -> Doc ann hlinecat = vcat . intersperse softbreak where softbreak = group hardline wrapbraces :: Doc ann -> Doc ann -> Doc ann wrapbraces leadIn x = (leadIn <> pretty '{') <> line' <> x <> line' <> pretty '}' angleBrackets :: Doc ann -> Doc ann angleBrackets x = pretty '<' <> x <> pretty '>' spacedbraces :: Doc ann -> Doc ann spacedbraces x = pretty '{' <+> x <+> pretty '}' local' :: Doc ann -> Doc ann local' a = "%" <> a global :: Doc ann -> Doc ann global a = "@" <> a label :: Doc ann -> Doc ann label a = "label" <+> "%" <> a cma :: Doc ann -> Doc ann -> Doc ann -- <,> does not work :( a `cma` b = a <> "," <+> b ------------------------------------------------------------------------------- -- Classes ------------------------------------------------------------------------------- -- class Pretty p where -- pretty :: p -> Doc ppMaybe :: Pretty a => Maybe a -> Doc ann ppMaybe (Just x) = pretty x ppMaybe Nothing = mempty ppBool :: Doc ann -> Bool -> Doc ann ppBool x True = x ppBool x False = mempty -- XXX: horrible hack unShort :: BS.ShortByteString -> [Char] unShort xs = fmap (toEnum . fromIntegral) $ BS.unpack xs short :: BS.ShortByteString -> Doc ann short x = pretty (pack (unShort x)) decodeShortUtf8 :: SBF.ShortByteString -> Text decodeShortUtf8 = decodeUtf8 . fromStrict . SBF.fromShort -- instance Pretty Word8 where -- pretty x = int (fromIntegral x) -- instance Pretty Word16 where -- pretty x = int (fromIntegral x) -- instance Pretty Word32 where -- pretty x = int (fromIntegral x) -- instance Pretty Word64 where -- pretty x = int (fromIntegral x) -- instance Pretty Int32 where -- pretty x = int (fromIntegral x) -- instance Pretty Int64 where -- pretty x = int (fromIntegral x) -- instance Pretty Integer where -- pretty = integer instance Pretty BS.ShortByteString where pretty = pretty . unShort -- instance Pretty [Char] where -- pretty = text . pack -- instance Pretty Bool where -- pretty True = "true" -- pretty False = "false" ppBoolean :: Bool -> Doc ann ppBoolean True = "true" ppBoolean False = "false" instance Pretty Name where pretty (Name nm) | BS.null nm = dquotes mempty | isFirst first && all isRest name = pretty (pack name) | otherwise = dquotes . hcat . map escape $ name where name = unShort nm first = head name isFirst c = isLetter c || c == '-' || c == '_' || c == '$' || c == '.' isRest c = isDigit c || isFirst c pretty (UnName x) = pretty ( (fromIntegral x) :: Int) instance Pretty Parameter where pretty (Parameter ty (UnName _) attrs) = pretty ty <+> ppParamAttributes attrs pretty (Parameter ty name attrs) = pretty ty <+> ppParamAttributes attrs <+> local' (pretty name) ppParamAttributes :: [ParameterAttribute] -> Doc ann ppParamAttributes pas = hsep $ fmap pretty pas -- TODO: Auto instance -- instance Pretty [ParameterAttribute] where -- pretty x = hsep $ fmap pretty x -- instance Pretty ([Parameter], Bool) where -- pretty (params, False) = commas (fmap pretty params) -- pretty (params, True) = "TODO" XXX: variadic case -- instance Pretty (Operand, [ParameterAttribute]) where -- pretty (op, attrs) = pretty (typeOf op) <+> pretty attrs <+> pretty op ppArguments :: (Operand, [ParameterAttribute]) -> Doc ann ppArguments (op, attrs) = pretty (typeOf op) <+> ppParamAttributes attrs <+> pretty op instance Pretty UnnamedAddr where pretty LocalAddr = "local_unnamed_addr" pretty GlobalAddr = "unnamed_addr" instance Pretty Type where pretty (IntegerType width) = "i" <> pretty width pretty (FloatingPointType HalfFP) = "half" pretty (FloatingPointType FloatFP ) = "float" pretty (FloatingPointType DoubleFP) = "double" pretty (FloatingPointType FP128FP) = "fp128" pretty (FloatingPointType X86_FP80FP) = "x86_fp80" pretty (FloatingPointType PPC_FP128FP) = "ppc_fp128" pretty VoidType = "void" pretty (PointerType ref (AS.AddrSpace addr)) | addr == 0 = pretty ref <> "*" | otherwise = pretty ref <+> "addrspace" <> parens (pretty addr) <> "*" pretty ft@(FunctionType {..}) = pretty resultType <+> ppFunctionArgumentTypes ft pretty (VectorType {..}) = "<" <> pretty nVectorElements <+> "x" <+> pretty elementType <> ">" pretty (StructureType {..}) = if isPacked then "<{" <> (commas $ fmap pretty elementTypes ) <> "}>" else "{" <> (commas $ fmap pretty elementTypes ) <> "}" pretty (ArrayType {..}) = brackets $ pretty nArrayElements <+> "x" <+> pretty elementType pretty (NamedTypeReference name) = "%" <> pretty name pretty MetadataType = "metadata" pretty TokenType = "token" pretty LabelType = "label" instance Pretty Global where pretty Function {..} = case basicBlocks of [] -> ("declare" <+> pretty linkage <+> pretty callingConvention <+> ppReturnAttributes returnAttributes <+> pretty returnType <+> global (pretty name) <> ppParams (pretty . typeOf) parameters <+> ppFunctionAttributes functionAttributes <+> align <+> gcName <+> pre) -- single unnamed block is special cased, and won't parse otherwise... yeah good times [b@(BasicBlock (UnName _) _ _)] -> ("define" <+> pretty linkage <+> pretty callingConvention <+> ppReturnAttributes returnAttributes <+> pretty returnType <+> global (pretty name) <> ppParams pretty parameters <+> ppFunctionAttributes functionAttributes <+> align <+> gcName <+> pre) `wrapbraces` (indent 2 $ ppSingleBlock b) bs -> ("define" <+> pretty linkage <+> pretty callingConvention <+> ppReturnAttributes returnAttributes <+> pretty returnType <+> global (pretty name) <> ppParams pretty parameters <+> ppFunctionAttributes functionAttributes <+> align <+> gcName <+> pre) `wrapbraces` (vcat $ fmap pretty bs) where pre = case prefix of Nothing -> mempty Just con -> "prefix" <+> ppTyped con align | alignment == 0 = mempty | otherwise = "align" <+> pretty alignment gcName = maybe mempty (\n -> "gc" <+> dquotes (pretty $ pack n)) (fmap unShort garbageCollectorName) pretty GlobalVariable {..} = global (pretty name) <+> "=" <+> ppLinkage hasInitializer linkage <+> ppMaybe unnamedAddr <+> addrSpace' <+> kind <+> pretty type' <+> ppMaybe initializer <> ppAlign alignment where hasInitializer = isJust initializer addrSpace' = case addrSpace of AS.AddrSpace addr | addr == 0 -> mempty | otherwise -> "addrspace" <> parens (pretty addr) kind | isConstant = "constant" | otherwise = "global" pretty GlobalAlias {..} = global (pretty name) <+> "=" <+> pretty linkage <+> ppMaybe unnamedAddr <+> "alias" <+> pretty typ `cma` ppTyped aliasee where typ = getElementType type' ppFunctionAttribute :: Either GroupID FunctionAttribute -> Doc ann ppFunctionAttribute (Left grpId) = pretty grpId ppFunctionAttribute (Right fA) = pretty fA ppFunctionAttributes :: [Either GroupID FunctionAttribute] -> Doc ann ppFunctionAttributes attribs = hsep $ fmap ppFunctionAttribute attribs ppMetadata :: Maybe Metadata -> Doc ann ppMetadata Nothing = "null" ppMetadata (Just m) = pretty m instance Pretty Definition where pretty (GlobalDefinition x) = pretty x pretty (TypeDefinition nm ty) = local' (pretty nm) <+> "=" <+> "type" <+> maybe "opaque" pretty ty pretty (FunctionAttributes gid attrs) = "attributes" <+> pretty gid <+> "=" <+> braces (hsep (fmap ppAttrInGroup attrs)) pretty (NamedMetadataDefinition nm meta) = "!" <> short nm <+> "=" <+> "!" <> braces (commas (fmap pretty meta)) pretty (MetadataNodeDefinition node meta) = pretty node <+> "=" <+> pretty meta pretty (ModuleInlineAssembly asm) = "module asm" <+> dquotes (pretty (pack (BL.unpack asm))) pretty (COMDAT name selKind) = "$" <> short name <+> "=" <+> "comdat" <+> pretty selKind instance Pretty SelectionKind where pretty Any = "any" pretty ExactMatch = "exactmatch" pretty Largest = "largest" pretty NoDuplicates = "noduplicates" pretty SameSize = "samesize" ppAttrInGroup :: FunctionAttribute -> Doc ann ppAttrInGroup = \case StackAlignment n -> "alignstack=" <> pretty n attr -> pretty attr instance Pretty FunctionAttribute where pretty = \case NoReturn -> "noreturn" NoUnwind -> "nounwind" FA.ReadNone -> "readnone" FA.ReadOnly -> "readonly" FA.WriteOnly -> "writeonly" NoInline -> "noinline" AlwaysInline -> "alwaysinline" MinimizeSize -> "minsize" OptimizeForSize -> "optsize" OptimizeNone -> "optnone" SafeStack -> "safestack" StackProtect -> "ssp" StackProtectReq -> "sspreq" StackProtectStrong -> "sspstrong" NoRedZone -> "noredzone" NoImplicitFloat -> "noimplicitfloat" Naked -> "naked" InlineHint -> "inlinehint" StackAlignment n -> "alignstack" <> parens (pretty n) ReturnsTwice -> "returns_twice" UWTable -> "uwtable" NonLazyBind -> "nonlazybind" Builtin -> "builtin" NoBuiltin -> "nobuiltin" Cold -> "cold" JumpTable -> "jumptable" NoDuplicate -> "noduplicate" SanitizeAddress -> "sanitize_address" SanitizeThread -> "sanitize_thread" SanitizeMemory -> "sanitize_memory" SanitizeHWAddress -> "sanitize_hwaddress" NoRecurse -> "norecurse" Convergent -> "convergent" ArgMemOnly -> "argmemonly" InaccessibleMemOnly -> "inaccessiblememonly" AllocSize a Nothing -> "allocsize" <> parens (pretty a) AllocSize a (Just b) -> "allocsize" <> parens (commas [pretty a, pretty b]) InaccessibleMemOrArgMemOnly -> "inaccessiblemem_or_argmemonly" FA.StringAttribute k v -> dquotes (short k) <> "=" <> dquotes (short v) Speculatable -> "speculatable" StrictFP -> "strictfp" instance Pretty ParameterAttribute where pretty = \case ZeroExt -> "zeroext" SignExt -> "signext" InReg -> "inreg" SRet -> "sret" Alignment word -> "align" <+> pretty word NoAlias -> "noalias" ByVal -> "byval" NoCapture -> "nocapture" Nest -> "nest" PA.ReadNone -> "readnone" PA.ReadOnly -> "readonly" PA.WriteOnly -> "writeonly" InAlloca -> "inalloca" NonNull -> "nonnull" Dereferenceable word -> "dereferenceable" <> parens (pretty word) DereferenceableOrNull word -> "dereferenceable_or_null" <> parens (pretty word) Returned -> "returned" SwiftSelf -> "swiftself" SwiftError -> "swifterror" PA.StringAttribute k v -> dquotes (short k) <> "=" <> dquotes (short v) instance Pretty CC.CallingConvention where pretty = \case CC.Numbered word -> "cc" <+> pretty word CC.C -> "ccc" CC.Fast -> "fastcc" CC.Cold -> "coldcc" CC.GHC -> "cc 10" CC.HiPE -> "cc 11" CC.WebKit_JS -> "webkit_jscc" CC.AnyReg -> "anyregcc" CC.PreserveMost -> "preserve_mostcc" CC.PreserveAll -> "preserve_allcc" CC.Swift -> "swiftcc" CC.CXX_FastTLS -> "cxx_fast_tlscc" CC.X86_StdCall -> "cc 64" CC.X86_FastCall -> "cc 65" CC.ARM_APCS -> "cc 66" CC.ARM_AAPCS -> "cc 67" CC.ARM_AAPCS_VFP -> "cc 68" CC.MSP430_INTR -> "cc 69" CC.X86_ThisCall -> "cc 70" CC.PTX_Kernel -> "cc 71" CC.PTX_Device -> "cc 72" CC.SPIR_FUNC -> "cc 75" CC.SPIR_KERNEL -> "cc 76" CC.Intel_OCL_BI -> "cc 77" CC.X86_64_SysV -> "cc 78" CC.Win64 -> "cc 79" CC.X86_Intr -> "x86_intrcc" CC.X86_RegCall -> "x86_regcallcc" CC.X86_VectorCall -> "x86_vectorcallcc" CC.AVR_Intr -> "avr_intrcc" CC.AVR_Signal -> "avr_signalcc" CC.AVR_Builtin -> "cc 86" CC.HHVM -> "hhvmcc" CC.HHVM_C -> "hhvm_ccc" CC.AMDGPU_VS -> "amdgpu_vs" CC.AMDGPU_GS -> "amdgpu_gs" CC.AMDGPU_PS -> "amdgpu_ps" CC.AMDGPU_CS -> "amdgpu_cs" CC.AMDGPU_HS -> "amdgpu_hs" CC.AMDGPU_Kernel -> "amdgpu_kernel" CC.MSP430_Builtin -> "msp430" instance Pretty L.Linkage where pretty = ppLinkage False ppLinkage :: Bool -> L.Linkage -> Doc ann ppLinkage omitExternal = \case L.External | omitExternal -> mempty | otherwise -> "external" L.Private -> "private" L.Internal -> "internal" L.ExternWeak -> "extern_weak" L.AvailableExternally -> "available_externally" L.LinkOnce -> "linkonce" L.Weak -> "weak" L.Common -> "common" L.Appending -> "appending" L.LinkOnceODR -> "linkonce_odr" L.WeakODR -> "weak_odr" ppInstructionMetadata :: InstructionMetadata -> Doc ann ppInstructionMetadata meta = commas ["!" <> short x <+> pretty y | (x,y) <- meta] instance Pretty MetadataNodeID where pretty (MetadataNodeID x) = "!" <> pretty ((fromIntegral x) :: Int) instance Pretty GroupID where pretty (GroupID x) = "#" <> pretty ((fromIntegral x) :: Int) instance Pretty BasicBlock where pretty (BasicBlock nm instrs term) = label <> P.line <> indent 2 (vcat $ (fmap pretty instrs) ++ [pretty term]) where label = case nm of UnName _ -> ";