crucible-llvm-0.8.0.0: Support for translating and executing LLVM code in Crucible
Safe HaskellNone
LanguageHaskell2010

Lang.Crucible.LLVM.MemModel.Strings

Description

Manipulating C-style null-terminated strings

Synopsis

Documentation

loadString Source #

Arguments

:: forall sym bak (wptr :: Natural). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions, HasCallStack) 
=> bak 
-> MemImpl sym

memory to read from

-> LLVMPtr sym wptr

pointer to string value

-> Maybe Int

maximum characters to read

-> IO [Word8] 

Load a null-terminated string from the memory.

The pointer to read from must be concrete and nonnull. Moreover, we require all the characters in the string to be concrete. Otherwise it is very difficult to tell when the string has terminated. If a maximum number of characters is provided, no more than that number of charcters will be read. In either case, loadString will stop reading if it encounters a null-terminator.

loadMaybeString Source #

Arguments

:: forall sym bak (wptr :: Natural). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions, HasCallStack) 
=> bak 
-> MemImpl sym

memory to read from

-> LLVMPtr sym wptr

pointer to string value

-> Maybe Int

maximum characters to read

-> IO (Maybe [Word8]) 

Like loadString, except the pointer to load may be null. If the pointer is null, we return Nothing. Otherwise we load the string as with loadString and return it.

strLen Source #

Arguments

:: forall sym bak (wptr :: Natural). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions) 
=> bak 
-> MemImpl sym

memory to read from

-> LLVMPtr sym wptr

pointer to string value

-> IO (SymBV sym wptr) 

Compute the length of a null-terminated string.

The pointer to read from must be concrete and nonnull. The contents of the string may be symbolic; HOWEVER, this function will not terminate until it eventually reaches a concete null-terminator or a load error.

loadConcretelyNullTerminatedString Source #

Arguments

:: forall sym bak (wptr :: Natural). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions, HasCallStack) 
=> bak 
-> MemImpl sym 
-> LLVMPtr sym wptr 
-> Maybe Int

Maximum number of characters to read

-> IO [SymBV sym 8] 

Load a null-terminated string (with a concrete null terminator) from memory.

The string must contain a concrete null terminator. If a maximum number of characters is provided, no more than that number of characters will be read. In either case, loadConcretelyNullTerminatedString will stop reading if it encounters a (concretely) null terminator.

Note that the loaded string may actually be smaller than the returned list if any of the symbolic bytes are equal to 0.

loadSymbolicString Source #

Arguments

:: forall sym bak scope (st :: Type -> Type) fs solver (wptr :: Natural). (IsSymBackend sym bak, sym ~ ExprBuilder scope st fs, bak ~ OnlineBackend solver scope st fs, OnlineSolver solver, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions, HasCallStack) 
=> bak 
-> MemImpl sym 
-> LLVMPtr sym wptr 
-> Maybe Int

Maximum number of characters to read

-> IO [SymBV sym 8] 

Load a null-terminated string from memory.

Consults an SMT solver to check if any of the loaded bytes are known to be null (0). If a maximum number of characters is provided, no more than that number of charcters will be read. In either case, loadSymbolicString will stop reading if it encounters a null terminator.

Note that the loaded string may actually be smaller than the returned list if any of the symbolic bytes are equal to 0.

storeString Source #

Arguments

:: forall sym bak (w :: Natural). (IsSymBackend sym bak, IsExpr (SymExpr sym), HasPtrWidth w, HasLLVMAnn sym, ?memOpts :: MemOptions) 
=> bak 
-> MemImpl sym 
-> LLVMPtr sym w

Pointer to write string to

-> Vector (SymBV sym 8)

The bytes of the string to write (null terminator not included)

-> IO (MemImpl sym) 

Store a string to memory, adding a null terminator at the end.

Low-level string loading primitives

ByteChecker

data ControlFlow a b Source #

Whether to stop or keep going

Like Rust's std::ops::ControlFlow.

Constructors

Continue a 
Break b 

Instances

Instances details
Bifunctor ControlFlow Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemModel.Strings

Methods

bimap :: (a -> b) -> (c -> d) -> ControlFlow a c -> ControlFlow b d #

first :: (a -> b) -> ControlFlow a c -> ControlFlow b c #

second :: (b -> c) -> ControlFlow a b -> ControlFlow a c #

Functor (ControlFlow a) Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemModel.Strings

Methods

fmap :: (a0 -> b) -> ControlFlow a a0 -> ControlFlow a b #

(<$) :: a0 -> ControlFlow a b -> ControlFlow a a0 #

newtype ByteChecker (m :: Type -> Type) sym bak a b Source #

Compute a result from a symbolic byte, and check if the load should continue to the next byte.

Used to:

Note that it is relatively common for a to be a function [b] -> [b]. This is used to build up a snoc-list.

Constructors

ByteChecker 

Fields

fullyConcreteNullTerminatedString :: forall (m :: Type -> Type) sym bak. (MonadIO m, HasCallStack, IsSymBackend sym bak) => ByteChecker m sym bak ([Word8] -> [Word8]) [Word8] Source #

ByteChecker for loading concrete strings.

Currently unused internally, but analogous with loadString. In fact, it would be good to define that function in terms of this one. However, this is blocked on TODO(#1406).

concretelyNullTerminatedString :: forall (m :: Type -> Type) sym bak. (MonadIO m, HasCallStack, IsSymBackend sym bak) => ByteChecker m sym bak ([SymBV sym 8] -> [SymBV sym 8]) [SymBV sym 8] Source #

ByteChecker for loading symbolic strings with a concrete null terminator.

Used in loadConcretelyNullTerminatedString.

nullTerminatedString :: forall (m :: Type -> Type) sym bak scope (st :: Type -> Type) fs solver. (MonadIO m, HasCallStack, IsSymBackend sym bak, sym ~ ExprBuilder scope st fs, bak ~ OnlineBackend solver scope st fs, OnlineSolver solver) => ByteChecker m sym bak ([SymBV sym 8] -> [SymBV sym 8]) [SymBV sym 8] Source #

ByteChecker for loading symbolic strings with a null terminator.

Used in loadSymbolicString.

withMaxChars Source #

Arguments

:: (HasCallStack, IsSymBackend sym bak, Functor m) 
=> Int

Maximum number of bytes to load

-> (a -> m b)

What to do when the maximum is reached

-> ByteChecker m sym bak a b 
-> ByteChecker m sym bak (a, Int) b 

ByteChecker for adding a maximum character length.

ByteLoader

newtype ByteLoader (m :: Type -> Type) sym bak (wptr :: Nat) Source #

Load a byte from memory.

The only ByteLoader defined here is llvmByteLoader, but Macaw users will most often want one based on doReadMemModel.

Constructors

ByteLoader 

Fields

llvmByteLoader :: forall sym bak (wptr :: Natural) (m :: Type -> Type). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions, HasCallStack, MonadIO m) => MemImpl sym -> ByteLoader m sym bak wptr Source #

A ByteLoader for LLVM memory based on doLoad.

loadBytes

loadBytes Source #

Arguments

:: forall m a b sym bak (wptr :: Natural). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions, HasCallStack, MonadIO m) 
=> bak 
-> MemImpl sym 
-> a

Initial accumulator

-> LLVMPtr sym wptr

Pointer to load from

-> ByteLoader m sym bak wptr

How to load a byte from memory

-> ByteChecker m sym bak a b

How to check if we should continue loading the next byte

-> m b 

Load a sequence of bytes, one at a time.

Used to implement loadConcretelyNullTerminatedString and loadSymbolicString. Highly customizable via ByteLoader and ByteChecker.