{-# LANGUAGE DeriveDataTypeable #-} -- | A representation of an LLVM inline assembly module LLVM.General.AST.InlineAssembly where import Data.Data import LLVM.General.AST.Type -- | the dialect of assembly used in an inline assembly string -- data Dialect = ATTDialect | IntelDialect deriving (Eq, Read, Show, Typeable, Data) -- | -- to be used through 'LLVM.General.AST.Operand.CallableOperand' with a -- 'LLVM.General.AST.Instruction.Call' instruction data InlineAssembly = InlineAssembly { type' :: Type, assembly :: String, constraints :: String, hasSideEffects :: Bool, alignStack :: Bool, dialect :: Dialect } deriving (Eq, Read, Show)