| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Crux.LLVM.Config
Synopsis
- data CError
- ppCError :: CError -> String
- throwCError :: MonadIO m => CError -> m b
- abnormalExitBehaviorSpec :: ValueSpec AbnormalExitBehavior
- data SupplyMainArguments
- supplyMainArgumentsSpec :: ValueSpec SupplyMainArguments
- indeterminateLoadBehaviorSpec :: ValueSpec IndeterminateLoadBehavior
- data LLVMOptions = LLVMOptions {
- clangBin :: FilePath
- linkBin :: FilePath
- clangOpts :: [String]
- libDir :: FilePath
- incDirs :: [FilePath]
- targetArch :: Maybe String
- ubSanitizers :: [String]
- intrinsicsOpts :: IntrinsicsOptions
- memOpts :: MemOptions
- transOpts :: TranslationOptions
- entryPoint :: String
- lazyCompile :: Bool
- noCompile :: Bool
- optLevel :: Int
- symFSRoot :: Maybe FilePath
- supplyMainArguments :: SupplyMainArguments
- findDefaultLibDir :: IO FilePath
- llvmCruxConfig :: IO (Config LLVMOptions)
Documentation
Constructors
| ClangError Int String String | |
| LLVMParseError Error | |
| MissingFun String | |
| BadFun String Bool | |
| EnvError String | |
| NoFiles |
Instances
| Exception CError Source # | |
Defined in Crux.LLVM.Config Methods toException :: CError -> SomeException # fromException :: SomeException -> Maybe CError # displayException :: CError -> String # | |
| Show CError Source # | |
throwCError :: MonadIO m => CError -> m b Source #
data SupplyMainArguments Source #
What sort of main functions should crux-llvm support simulating?
Constructors
| NoArguments | Only support simulating |
| EmptyArguments | Support simulating both |
Instances
| Show SupplyMainArguments Source # | |
Defined in Crux.LLVM.Config Methods showsPrec :: Int -> SupplyMainArguments -> ShowS # show :: SupplyMainArguments -> String # showList :: [SupplyMainArguments] -> ShowS # | |
data LLVMOptions Source #
Constructors
| LLVMOptions | |
Fields
| |
findDefaultLibDir :: IO FilePath Source #
The c-src directory, which contains crux-llvm–specific files such as
crucible.h, can live in different locations depending on how crux-llvm
was built. This function looks in a couple of common places:
- A directory relative to the
crux-llvmbinary itself. This is the case when running acrux-llvmbinary distribution. If that can't be found, default to... - The
data-filesdirectory, as reported bycabal'sgetDataDirfunction.
This isn't always guaranteed to work in every situation, but it should cover enough common cases to be useful in practice.
llvmCruxConfig :: IO (Config LLVMOptions) Source #